Skip to content

Commit

Permalink
Merge github.com:benl23x5/gloss
Browse files Browse the repository at this point in the history
Conflicts:
	gloss/Graphics/Gloss/Internals/Render/Picture.hs
	gloss/gloss.cabal
  • Loading branch information
benl23x5 committed May 4, 2014
2 parents 78cf938 + d3ad96e commit ae4a920
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 8 deletions.
5 changes: 2 additions & 3 deletions gloss/Graphics/Gloss/Geometry/Angle.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@

-- | Geometric functions concerning angles. If not otherwise specified, all angles are in radians.
module Graphics.Gloss.Geometry.Angle
( degToRad
Expand All @@ -21,6 +20,6 @@ radToDeg r = r * 180 / pi
-- | Normalise an angle to be between 0 and 2*pi radians
{-# INLINE normaliseAngle #-}
normaliseAngle :: Float -> Float
normaliseAngle f = f - 2 * pi * (fromIntegral . floor') (f / (2 * pi))
where floor' :: Float -> Int
normaliseAngle f = f - 2 * pi * floor' (f / (2 * pi))
where floor' :: Float -> Float
floor' x = fromIntegral (floor x :: Int)
11 changes: 8 additions & 3 deletions gloss/Graphics/Gloss/Interface/IO/Game.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE ExplicitForAll #-}

-- | This game mode lets you manage your own input. Pressing ESC will still abort the program,
-- but you don't get automatic pan and zoom controls like with `displayInWindow`.
-- | This game mode lets you manage your own input. Pressing ESC will not abort the program.
-- You also don't get automatic pan and zoom controls like with `displayInWindow`.
module Graphics.Gloss.Interface.IO.Game
( module Graphics.Gloss.Data.Display
, module Graphics.Gloss.Data.Picture
Expand All @@ -28,4 +28,9 @@ playIO :: forall world
-- It is passed the period of time (in seconds) needing to be advanced.
-> IO ()

playIO = playWithBackendIO defaultBackendState
playIO display backColor simResolution
worldStart worldToPicture worldHandleEvent worldAdvance
= playWithBackendIO defaultBackendState
display backColor simResolution
worldStart worldToPicture worldHandleEvent worldAdvance
False
1 change: 1 addition & 0 deletions gloss/Graphics/Gloss/Interface/Pure/Game.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,3 +40,4 @@ play display backColor simResolution
(return . worldToPicture)
(\event world -> return $ worldHandleEvent event world)
(\time world -> return $ worldAdvance time world)
True
8 changes: 6 additions & 2 deletions gloss/Graphics/Gloss/Internals/Interface/Game.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ playWithBackendIO
-> (Event -> world -> IO world) -- ^ A function to handle input events.
-> (Float -> world -> IO world) -- ^ A function to step the world one iteration.
-- It is passed the period of time (in seconds) needing to be advanced.
-> Bool -- ^ Whether to use the callback_exit or not.
-> IO ()

playWithBackendIO
Expand All @@ -46,6 +47,7 @@ playWithBackendIO
worldToPicture
worldHandleEvent
worldAdvance
withCallbackExit
= do
let singleStepTime = 1

Expand Down Expand Up @@ -87,12 +89,14 @@ playWithBackendIO
stateSR animateSR (readIORef viewSR)
worldSR worldStart (\_ -> worldAdvance)
singleStepTime)
, callback_exit ()
, callback_keyMouse worldSR viewSR worldHandleEvent
, callback_motion worldSR worldHandleEvent
, callback_reshape worldSR worldHandleEvent]

createWindow backend display backgroundColor callbacks
let exitCallback
= if withCallbackExit then [callback_exit ()] else []

createWindow backend display backgroundColor $ callbacks ++ exitCallback


-- | Callback for KeyMouse events.
Expand Down

0 comments on commit ae4a920

Please sign in to comment.