life/life.hs
2014-12-19 20:09:30 +01:00

53 lines
1.4 KiB
Haskell

{-#LANGUAGE TypeSynonymInstances, FlexibleInstances#-}
import Data.Maybe (listToMaybe)
import Data.List (intercalate)
import Matrix
type Cell = Int
type Grid = Mat Cell
instance Show Grid where
show (Mat m) = concatMap ((++"\n") . intercalate " " . map replace) m
where
replace 1 = ""
replace 0 = "'"
-- | Get the state of a cell
-- 0 when out of the grid
(!) :: Grid -> Pos -> Cell
(Mat g) ! (x, y) = case g ?? y >>= (?? x) of
Nothing -> 0
Just v -> v
-- | List of neighbours cells
near :: Grid -> Pos -> [Cell]
near g (x, y) = [g ! (x+x', y+y') | x' <- [-1..1],
y' <- [-1..1],
(x',y') /= (0,0)]
-- | Find if a cell will be alive in the next generation
alive :: Grid -> Pos -> Cell
alive g p
| v == 0 && n == 3 = 1
| v == 1 && (n == 2 || n == 3) = 1
| otherwise = 0
where
(n, v) = (sum (near g p), g ! p)
-- | Compute next generation
next :: Grid -> Grid
next g = fmap (alive g) (indeces g)
main :: IO ()
main = mapM_ print (iterate next grid)
grid = Mat [
[0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]
, [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]
]