Give more documentation

This commit is contained in:
Kiana Sheibani 2021-12-20 16:20:51 -05:00
parent 19f3edc49e
commit 2b79e79ed7
2 changed files with 25 additions and 7 deletions

View file

@ -9,6 +9,9 @@ import Data.Bool (bool)
import GOL.Rule
import GOL.Space
-- | The comonad stack used in the Game of Life engine.
-- It consists of a store comonad over the space @f@,
-- with an environment containing a rule.
type GOL f = EnvT Rule (Store f)
getNeighbors :: forall f a. Space f => GOL f a -> [a]
@ -16,15 +19,15 @@ getNeighbors = experiment $ neighbors @f
nextState :: Space f => GOL f Bool -> Bool
nextState = do
selfState <- extract
neighborStates <- getNeighbors
let count = sum . fmap (bool 0 1) $ neighborStates
Rule survive birth <- ask
return $ if selfState
then survive count
else birth count
selfState <- extract
Rule survive birth <- ask
return $
if selfState
then survive count
else birth count
tick :: Space f => GOL f Bool -> GOL f Bool
tick = extend nextState

View file

@ -6,8 +6,23 @@ module GOL.Space where
import Data.Functor.Rep
-- | A space in which a Conway's Game of Life simulation
-- takes place, with a notion of "neighbors to a cell" defined.
--
-- More specifically, a space is a representable functor @f@ such
-- that @'Rep' f@ is a graph. 'neighbors' then takes a node of
-- that graph and returns all nodes that are adjacent.
--
-- Instances should satisfy:
--
-- * Symmetry: if @x '`elem`' 'neighbors' y@, then @y '`elem`' 'neighbors' x@.
--
-- * Irreflexivity: @x '`elem`' 'neighbors' x@ is always false.
class Representable f => Space f where
neighbors :: Rep f -> [Rep f]
-- | A space is _displayable_ if it is representable over a 2D
-- grid. The graphical system requires a displayable space.
class (Space f, Rep f ~ (Int, Int)) => DisplayableSpace f where
size :: (Int, Int)
sizex :: Int
sizey :: Int