Add documentation
This commit is contained in:
parent
55e5209d91
commit
3e056bf00c
|
@ -1,10 +1,15 @@
|
||||||
module Graphics.Command where
|
module Graphics.Command where
|
||||||
|
|
||||||
import FRP.Yampa (Time, Event)
|
import FRP.Yampa (Event, Time)
|
||||||
|
|
||||||
|
-- | A datatype representing all possible commands the user
|
||||||
|
-- can give through UI.
|
||||||
data Command
|
data Command
|
||||||
= Resize (Int, Int)
|
= -- | A command to resize the window to the given dimensions.
|
||||||
| ChangeSpeed (Time -> Time)
|
Resize (Int, Int)
|
||||||
|
| -- | A command to change the tick speed of the simulation,
|
||||||
|
-- given by a function on the period between ticks.
|
||||||
|
ChangeSpeed (Time -> Time)
|
||||||
|
|
||||||
getResize :: Command -> Maybe (Int, Int)
|
getResize :: Command -> Maybe (Int, Int)
|
||||||
getResize (Resize size) = Just size
|
getResize (Resize size) = Just size
|
||||||
|
@ -14,4 +19,5 @@ getChangeSpeed :: Command -> Maybe (Time -> Time)
|
||||||
getChangeSpeed (ChangeSpeed f) = Just f
|
getChangeSpeed (ChangeSpeed f) = Just f
|
||||||
getChangeSpeed _ = Nothing
|
getChangeSpeed _ = Nothing
|
||||||
|
|
||||||
|
-- | An event signalling that a command has been given by the user.
|
||||||
type CommandEvent = Event Command
|
type CommandEvent = Event Command
|
|
@ -10,6 +10,7 @@ import Graphics.Gloss
|
||||||
|
|
||||||
-- * Drawing the display grid
|
-- * Drawing the display grid
|
||||||
|
|
||||||
|
-- | Draw a square with the given size and position.
|
||||||
square :: Float -> Point -> Picture
|
square :: Float -> Point -> Picture
|
||||||
square size (x, y) = translate (x + size / 2) y (rectangleUpperSolid size size)
|
square size (x, y) = translate (x + size / 2) y (rectangleUpperSolid size size)
|
||||||
|
|
||||||
|
@ -27,6 +28,7 @@ drawCells xs size =
|
||||||
let poss = (,) <$> [0 .. sizex @f -1] <*> [0 .. sizey @f -1]
|
let poss = (,) <$> [0 .. sizex @f -1] <*> [0 .. sizey @f -1]
|
||||||
in mapMaybe (\pos -> drawCell xs pos size) poss
|
in mapMaybe (\pos -> drawCell xs pos size) poss
|
||||||
|
|
||||||
|
-- | Draw a grid of a displayable space given the window size and cell color.
|
||||||
drawGrid :: forall f. DisplayableSpace f => (Int, Int) -> Color -> f Bool -> Picture
|
drawGrid :: forall f. DisplayableSpace f => (Int, Int) -> Color -> f Bool -> Picture
|
||||||
drawGrid (w, h) c xs =
|
drawGrid (w, h) c xs =
|
||||||
let size = fromIntegral $ if w > h then h `div` sizey @f else w `div` sizex @f
|
let size = fromIntegral $ if w > h then h `div` sizey @f else w `div` sizex @f
|
||||||
|
|
Loading…
Reference in a new issue