Create Graphics.Display

This commit is contained in:
Kiana Sheibani 2021-12-28 00:46:39 -05:00
parent dd8fd9c6a4
commit b967297642
2 changed files with 30 additions and 1 deletions

28
Graphics/Display.hs Normal file
View file

@ -0,0 +1,28 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Graphics.Display where
import Control.Monad.Representable.Reader
import Data.Maybe (mapMaybe)
import GOL.Space
import Graphics.Gloss
square :: Float -> Point -> Picture
square size (x, y) = translate (x + size / 2) y (rectangleUpperSolid size size)
squareAtIndex :: (Int, Int) -> Float -> Picture
squareAtIndex (x, y) size = square size (fromIntegral x * size, fromIntegral y * size)
-- * Calculating the display grid
drawCell :: DisplayableSpace f => f Bool -> (Int, Int) -> Float -> Maybe Picture
drawCell xs pos size =
if index xs pos
then Just $ squareAtIndex pos size
else Nothing
drawGrid :: forall f. DisplayableSpace f => f Bool -> Float -> [Picture]
drawGrid xs size =
let poss = (,) <$> [0 .. sizex @f -1] <*> [0 .. sizey @f -1]
in mapMaybe (\pos -> drawCell xs pos size) poss

View file

@ -12,7 +12,8 @@ executable main
GOL.Space,
GOL.Engine,
Graphics.GlossUtils,
Graphics.Engine
Graphics.Engine,
Graphics.Display
build-depends: base,
vector,
comonad,