<div dir="auto"><div>Thanks for the suggestions, I will update the code :)</div><div dir="auto">Is it better to go with parallelizing the code? Or using ST for some mutations?</div><div dir="auto"><br><div class="gmail_quote" dir="auto"><div dir="ltr" class="gmail_attr">On Sun, Feb 24, 2019, 8:59 PM Utku Demir <<a href="mailto:lists@utdemir.com">lists@utdemir.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><u></u><div><div>Looks great to me, I especially liked how you extracted 'stdRules' out :). A few minor suggestions:<br></div><div><br></div><div>* Instead of type aliases, you can try using 'newtype' wrappers or concrete data types. e.g `newtype Size = Size (Int, Int)` or `data Size = Size Int Int`. This way it'll be a compiler error when you accidently pass a Size when actually a Coord is expected etc. You might need to do a bit of wrapping/unwrapping but it's usually worth the type safety they bring.<br></div><div>* This is a bit contraversial, but you can use some light point-free notation in a few places. e.g `tallyBoard = mapM_ . tallyCoord` and `toResults = map flatten . M.toList . flip execState M.empty`<br></div><div>* 'read' is a partial function, an especially when using external inputs it'd be better to use 'readMaybe', or a proper parser like 'trifecta' for more complex inputs.<br></div><div><br></div><div id="m_4491813946558470024sig64983520"><div class="m_4491813946558470024signature">--<br></div><div class="m_4491813946558470024signature">Utku Demir<br></div><div class="m_4491813946558470024signature"><br></div></div><div><br></div><div><br></div><div>On Sun, Feb 24, 2019, at 4:37 AM, Michel Haber wrote:<br></div><blockquote type="cite" id="m_4491813946558470024fastmail-quoted"><div dir="ltr"><div dir="ltr"><div dir="ltr"><div>Hello everyone,<br></div><div>I'm a new haskeller, and (like many others, I assume) I thought  I'd try my hand<br></div><div>at Conway's "Game of Life".<br></div><div><br></div><div>So here is my code that seems to work (up to this point).<br></div><div>I am looking for feedback in order to improve my Haskell code on all levels.<br></div><div>Especially (In no particular order):<br></div><div>0- Find and fix bugs<br></div><div>1- Write more performance optimal code.<br></div><div>2- Good use of polymorphic types.<br></div><div>3- Good use of higher-order functions.<br></div><div>4- Good use of Haskell's common (and uncommon) abstractions.<br></div><div>5- Coding style (I'm finding it hard to let go of the function types :p)<br></div><div>6- Good code structuring allowing for reuse and updates.<br></div><div>7- Best options to give to the compiler.<br></div><div>8- Anything else that comes to your mind!<br></div><div><br></div><div>So I'd really appreciate your feedback :)<br></div><div><br></div><div>This is the wikipedia reference for the game of life: <a href="https://en.wikipedia.org/wiki/Conway%27s_Game_of_Life" target="_blank" rel="noreferrer">https://en.wikipedia.org/wiki/Conway%27s_Game_of_Life</a><br></div><div><br></div><div>And this is the code:<br></div><div><br></div><div>START OF CODE<br></div><div><div>-- Game of life Haskell Implementation<br></div><div><br></div><div>import Data.List<br></div><div>import Control.Monad.State<br></div><div>import qualified Data.Map as M<br></div><div><br></div><div>-- The cell state is isomorphic to Bool.<br></div><div>type CellState = Bool<br></div><div><br></div><div>-- The coordinates of a cell<br></div><div>type Coord = (Int, Int)<br></div><div><br></div><div>-- The board size is (length, width)<br></div><div>type Size = (Int, Int)<br></div><div><br></div><div>-- The state of the board is simply the coordinates of its live cells<br></div><div>type Board = [Coord]<br></div><div><br></div><div>-- The state carried in the State Monad, used to count tags for cells<br></div><div>type TallyState = State (M.Map Coord (CellState, Int)) ()<br></div><div><br></div><div>-- The type of the game rules<br></div><div>type Rules = (Coord, CellState, Int) -> CellState<br></div><div><br></div><div>-- The type for the neighbor functions<br></div><div>type Neighbors = Coord -> [Coord]<br></div><div><br></div><div>-- Tally the live neighbors of live cells and relevant dead cells<br></div><div>tallyBoard :: Neighbors -> Board -> TallyState<br></div><div>tallyBoard nb = mapM_ $ tallyCoord nb<br></div><div><br></div><div>-- Tally a live cell: Set its state to True (alive) and tag its neighbors<br></div><div>-- This function takes the neighbors function as its first argument. We can use<br></div><div>-- different neighbor functions to change the zone of influence of a cell<br></div><div>tallyCoord :: Neighbors -> Coord -> TallyState<br></div><div>tallyCoord nb c = do<br></div><div>    let merge (a1,b1) (a2,b2) = (a1 || a2, b1 + b2)<br></div><div>    s <- get<br></div><div>    let s' = M.insertWith merge c (True, 0) s<br></div><div>    let neighbors = nb c<br></div><div>    put $ foldl' (\acc x -> M.insertWith merge x (False, 1) acc) s' neighbors<br></div><div><br></div><div>-- Extract the results from a TallyState<br></div><div>toResults :: TallyState -> [(Coord, CellState, Int)]<br></div><div>toResults s = map flatten . M.toList . execState s $ M.empty<br></div><div>    where flatten (x,(y,z)) = (x,y,z)<br></div><div><br></div><div>-- Use A Rules and Neighbors function to advance the board one step in time<br></div><div>advance :: Rules -> Neighbors -> Board -> Board<br></div><div>advance rules nb = map first . filter rules . toResults . tallyBoard nb<br></div><div>    where first (x,_,_) = x<br></div><div><br></div><div>-- The standard neighbors function<br></div><div>stdNeighbors :: Neighbors<br></div><div>stdNeighbors (x,y) =<br></div><div>    [ (a,b)<br></div><div>    | a <- [x-1, x, x+1]<br></div><div>    , b <- [y-1, y, y+1]<br></div><div>    , (a /= x) || (b /= y)<br></div><div>    ]<br></div><div><br></div><div>-- Standard game rules<br></div><div>stdRules :: Size -> Rules<br></div><div>stdRules (a,b) ((x,y),_,_)<br></div><div>    | (x < 0) || (y < 0) || (x >= a) || (y >= b) = False<br></div><div>stdRules _ (_,True,c)<br></div><div>    | (c == 2) || (c == 3) = True<br></div><div>    | otherwise = False<br></div><div>stdRules _ (_,False,3) = True<br></div><div>stdRules _ _ = False<br></div><div><br></div><div><br></div><div>-- Main loop<br></div><div>loop :: (Board -> Board) -> Board -> IO ()<br></div><div>loop f b = do<br></div><div>    print b<br></div><div>    unless (null b) $ loop f (f b)<br></div><div><br></div><div>-- Main function<br></div><div>main :: IO ()<br></div><div>main = do<br></div><div>    putStrLn "Choose board size (x,y)"<br></div><div>    input <- getLine<br></div><div>    putStrLn "Choose starting points"<br></div><div>    start <- getLine<br></div><div>    putStrLn "Game:"<br></div><div>    let size = read input<br></div><div>    let rules = stdRules size<br></div><div>    let initial = map read . words $ start<br></div><div>    let game = advance rules stdNeighbors<br></div><div>    loop game initial<br></div></div><div><br></div><div>END OF CODE<br></div><div><br></div><div>Thanks :)<br></div></div></div></div><div>_______________________________________________<br></div><div>Beginners mailing list<br></div><div><a href="mailto:Beginners@haskell.org" target="_blank" rel="noreferrer">Beginners@haskell.org</a><br></div><div><a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" target="_blank" rel="noreferrer">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a><br></div><div><br></div></blockquote><div><br></div></div>_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org" target="_blank" rel="noreferrer">Beginners@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a><br>
</blockquote></div></div></div>