
Hello everyone, I'm a new haskeller, and (like many others, I assume) I thought I'd try my hand at Conway's "Game of Life". So here is my code that seems to work (up to this point). I am looking for feedback in order to improve my Haskell code on all levels. Especially (In no particular order): 0- Find and fix bugs 1- Write more performance optimal code. 2- Good use of polymorphic types. 3- Good use of higher-order functions. 4- Good use of Haskell's common (and uncommon) abstractions. 5- Coding style (I'm finding it hard to let go of the function types :p) 6- Good code structuring allowing for reuse and updates. 7- Best options to give to the compiler. 8- Anything else that comes to your mind! So I'd really appreciate your feedback :) This is the wikipedia reference for the game of life: https://en.wikipedia.org/wiki/Conway%27s_Game_of_Life And this is the code: START OF CODE -- Game of life Haskell Implementation import Data.List import Control.Monad.State import qualified Data.Map as M -- The cell state is isomorphic to Bool. type CellState = Bool -- The coordinates of a cell type Coord = (Int, Int) -- The board size is (length, width) type Size = (Int, Int) -- The state of the board is simply the coordinates of its live cells type Board = [Coord] -- The state carried in the State Monad, used to count tags for cells type TallyState = State (M.Map Coord (CellState, Int)) () -- The type of the game rules type Rules = (Coord, CellState, Int) -> CellState -- The type for the neighbor functions type Neighbors = Coord -> [Coord] -- Tally the live neighbors of live cells and relevant dead cells tallyBoard :: Neighbors -> Board -> TallyState tallyBoard nb = mapM_ $ tallyCoord nb -- Tally a live cell: Set its state to True (alive) and tag its neighbors -- This function takes the neighbors function as its first argument. We can use -- different neighbor functions to change the zone of influence of a cell tallyCoord :: Neighbors -> Coord -> TallyState tallyCoord nb c = do let merge (a1,b1) (a2,b2) = (a1 || a2, b1 + b2) s <- get let s' = M.insertWith merge c (True, 0) s let neighbors = nb c put $ foldl' (\acc x -> M.insertWith merge x (False, 1) acc) s' neighbors -- Extract the results from a TallyState toResults :: TallyState -> [(Coord, CellState, Int)] toResults s = map flatten . M.toList . execState s $ M.empty where flatten (x,(y,z)) = (x,y,z) -- Use A Rules and Neighbors function to advance the board one step in time advance :: Rules -> Neighbors -> Board -> Board advance rules nb = map first . filter rules . toResults . tallyBoard nb where first (x,_,_) = x -- The standard neighbors function stdNeighbors :: Neighbors stdNeighbors (x,y) = [ (a,b) | a <- [x-1, x, x+1] , b <- [y-1, y, y+1] , (a /= x) || (b /= y) ] -- Standard game rules stdRules :: Size -> Rules stdRules (a,b) ((x,y),_,_) | (x < 0) || (y < 0) || (x >= a) || (y >= b) = False stdRules _ (_,True,c) | (c == 2) || (c == 3) = True | otherwise = False stdRules _ (_,False,3) = True stdRules _ _ = False -- Main loop loop :: (Board -> Board) -> Board -> IO () loop f b = do print b unless (null b) $ loop f (f b) -- Main function main :: IO () main = do putStrLn "Choose board size (x,y)" input <- getLine putStrLn "Choose starting points" start <- getLine putStrLn "Game:" let size = read input let rules = stdRules size let initial = map read . words $ start let game = advance rules stdNeighbors loop game initial END OF CODE Thanks :)