Portability | haskell2011 |
---|---|
Maintainer | Manuel M T Chakravarty <chak@cse.unsw.edu.au> |
Safe Haskell | None |
- module Graphics.Gloss.Data.Color
- module Graphics.Gloss.Data.Display
- module Graphics.Gloss.Data.Picture
- module Graphics.Gloss.Interface.Pure.Game
- type Size = (Float, Float)
- type Rect = (Point, Size)
- bmp :: FilePath -> Picture
- png :: FilePath -> Picture
- jpg :: FilePath -> Picture
- boundingBox :: Picture -> Rect
- play :: Display -> Color -> Int -> world -> (world -> Picture) -> (Event -> world -> world) -> [Float -> world -> world] -> IO ()
- playInScene :: Display -> Color -> Int -> world -> Scene world -> (Float -> Event -> world -> world) -> [Float -> Float -> world -> world] -> IO ()
- data Animation
- animation :: [Picture] -> Float -> Float -> Animation
- noAnimation :: Animation
- data Scene world
- picture :: Picture -> Scene world
- picturing :: (world -> Picture) -> Scene world
- animating :: (world -> Animation) -> Picture -> Scene world
- translating :: (world -> Point) -> Scene world -> Scene world
- rotating :: (world -> Float) -> Scene world -> Scene world
- scaling :: (world -> (Float, Float)) -> Scene world -> Scene world
- scenes :: [Scene world] -> Scene world
- drawScene :: Scene world -> Float -> world -> Picture
Reexport some basic Gloss datatypes
module Graphics.Gloss.Data.Color
module Graphics.Gloss.Data.Display
module Graphics.Gloss.Data.Picture
Geometry
Load sprites into pictures
bmp :: FilePath -> PictureSource
Turn a bitmap file into a picture.
NB: Define loaded pictures on the toplevel to avoid reloading.
png :: FilePath -> PictureSource
Turn a PNG file into a picture.
NB: Define loaded pictures on the toplevel to avoid reloading.
jpg :: FilePath -> PictureSource
Turn a JPEG file into a picture.
NB: Define loaded pictures on the toplevel to avoid reloading.
Query pictures
boundingBox :: Picture -> RectSource
Determine the bounding box of a picture.
FIXME: Current implementation is incomplete!
More convenient game play
:: Display | Display mode |
-> Color | Background color |
-> Int | Number of simulation steps to take for each second of real time |
-> world | The initial world state |
-> (world -> Picture) | A function to convert the world to a picture |
-> (Event -> world -> world) | A function to handle individual input events |
-> [Float -> world -> world] | Set of functions invoked once per iteration — first argument is the period of time (in seconds) needing to be advanced |
-> IO () |
Play a game.
:: Display | Display mode |
-> Color | Background color |
-> Int | Number of simulation steps to take for each second of real time |
-> world | The initial world state |
-> Scene world | A scene parameterised by the world |
-> (Float -> Event -> world -> world) | A function to handle individual input events * first argument is the absolute time (in seconds) |
-> [Float -> Float -> world -> world] | Set of functions invoked once per iteration — * first argument is the absolute time (in seconds) * second argument is the period of time needing to be advanced |
-> IO () |
Play a game in a scene.
Game scenes
animation :: [Picture] -> Float -> Float -> AnimationSource
Construct a new animation with a list of pictures for the animation, the time between animation frames, and a given (absolute) start time.
noAnimation :: AnimationSource
An empty animation.
A scene describes the rendering of a world state — i.e., which picture should be draw depending on the current time and of the state of the world.
animating :: (world -> Animation) -> Picture -> Scene worldSource
Animate a world-dependent animation. The default picture is displayed while no animation is running.
translating :: (world -> Point) -> Scene world -> Scene worldSource
Move a scene in dependences on a world-dependent location.
rotating :: (world -> Float) -> Scene world -> Scene worldSource
Rotate a scene in dependences on a world-dependent angle.