I code Haskell as a hobbyist. I'm interested in feedback on my naive implementation of Conway's Game of Life. Specifically, as stated in the Quick Tour of the website, I am interested in:
- Best practices and design pattern usage
- Correctness in unanticipated cases
Admitting the naivete of the implementation, I'm not so much interested in security issues or performance, unless my implementation is just a totally unwise implementation. That is, if I might, for example, run three iterations of a 3x3 Blinker and kill the CPU. No matter how pretty I think my code, that's just stupid.
First I list the test specifications. We don't currently use TDD at work, so I'm a bit inexperienced in TDD.
module Life_Spec where
import Test.Hspec
import Life
-- Any live cell with fewer than two live neighbors dies.
-- Any live cell with two or three live neighbors lives.
-- Any live cell with more than three live neighbors dies.
-- Any dead cell with exactly three live neighbors becomes live.
main :: IO ()
main = hspec $ do
describe "Life" $ do
it "Returns a dead cell for a live cell with fewer than two live neighbors." $
generation (Alive, 1) `shouldBe` Dead
it "Returns a live cell for a live cell with two or three live neighbors." $
generation (Alive, 2) `shouldBe` Alive
it "Returns a live cell for a live cell with two or three live neighbors." $
generation (Alive, 3) `shouldBe` Alive
it "Returns a dead cell for a live cell with more than three live neighbors." $
generation (Alive, 4) `shouldBe` Dead
it "Returns a live cell for a dead cell with more exactly three live neighbors." $
generation (Dead, 3) `shouldBe` Alive
it "Returns the indices of a cell's neighbors for a 3x3 grid." $
neighbors 0 [] [Dead, Alive, Dead] [Dead, Alive, Dead] `shouldBe` [Alive, Dead, Alive]
it "Returns an empty Grid when given an empty Grid." $
gridGeneration (Grid []) `shouldBe` (Grid [])
it "Successfully processes the 3x3 blinker grid." $
gridGeneration (Grid [[Dead, Alive, Dead],
[Dead, Alive, Dead],
[Dead, Alive, Dead]]) `shouldBe` (Grid [[Dead , Dead , Dead ],
[Alive, Alive, Alive],
[Dead , Dead , Dead ]])
it "Successfully processes the 5x5 blinker grid." $
gridGeneration (Grid [[Dead, Dead, Dead , Dead, Dead],
[Dead, Dead, Alive, Dead, Dead],
[Dead, Dead, Alive, Dead, Dead],
[Dead, Dead, Alive, Dead, Dead],
[Dead, Dead, Dead , Dead, Dead]]) `shouldBe` (Grid [[Dead, Dead , Dead , Dead , Dead],
[Dead, Dead , Dead , Dead , Dead],
[Dead, Alive, Alive, Alive, Dead],
[Dead, Dead , Dead , Dead , Dead],
[Dead, Dead , Dead , Dead , Dead]])
Next I list my implementation:
module Life where
import Data.Maybe (catMaybes)
data State = Dead | Alive deriving (Eq, Show)
newtype Grid = Grid [[State]] deriving (Eq, Show)
generation :: (State, Int) -> State
generation (Alive, 2) = Alive
generation (_ , 3) = Alive
generation (_ , _) = Dead
-- Surely this can be done more cleanly...
neighbors :: Int -> [State] -> [State] -> [State] -> [State]
neighbors x rowAbove rowOfX rowBelow =
let (w,y) = (x-1,x+1)
cs = [w, x, y, w, y, w, x, y]
rs = replicate 3 rowAbove ++ replicate 2 rowOfX ++ replicate 3 rowBelow
in catMaybes . map maybeCell $ zip rs cs
where maybeCell (r,c)
| c < 0 = Nothing
| c >= length r = Nothing
| otherwise = Just (r!!c)
gridGeneration :: Grid -> Grid
gridGeneration (Grid []) = Grid []
gridGeneration (Grid rs@(row0:row1:row2:rows)) = Grid $ g ([]:rs)
where
g (r0:r1:r2:rs) = [processRow r0 r1 r2] ++ g (r1:r2:rs)
g (r0:r1:[]) = [processRow r0 r1 []]
g _ = []
processRow r0 r1 r2 = reverse $ foldl p [] [0..(length r1 - 1)]
where p a n = (generation (r1!!n, live $ neighbors n r0 r1 r2)) : a
live = length . filter (==Alive)
gridGeneration _ = undefined
1 Answer 1
Ideomatic code
HLint gave some hints,
catMaybes . map maybeCell <=> mapMaybe maybeCell
and a few superfluous brackets, but nothing big.
Hlint doesn't catch some other unnecessarily convoluted formulations though:
reverse $ foldl p [] someList
p a n = f n : a
In Haskell, foldl
is usually less efficient than foldr
due to laziness. (In some cases you want to use the strict version foldl'
, but almost never foldl
.)
foldr p [] someList
p n a = f n : a
And this is completely equivalent to:
map p someList
p n = f n
Another example: Using a tuple instead of just two values as arguments to generation
. This is not wrong, just unideomatic and doesn't serve any purpose (as far as I can see).
generation :: (State, Int) -> State
why not use
generation :: State -> Int -> State
Formatting
You can use formatting to emphasize structure:
cols = [w, x, y,
w, y,
w, x, y]
Use clear names
Testing
Your tests looks good, you might want to add cases for smaller grids and non-square ones as well though. You might also consider if QuickCheck could be helpful, but I don't see any obvious properties, apart from that all functions should preserve length, but that is already (mostly) covered by the existing tests.
Thanks for supplying tests, it helped me with verifying that my suggestions didn't break anything. :)
Edit: According to Hspec documentation you are supposed to use one describe
per function, not one per module as you did.
Edge cases
As I said, you crash on grids with one or two rows, but your code actually
supports them already (they are handled by g
). Just remove the arbitrary constraint of needing at least
three rows at the second case of gridGeneration
(and remove the third case).
gridGeneration (Grid rs) = Grid $ g ([]:rs)
where
...
The function g
also handles empty grids correctly, so you can remove the first case as well.
Efficiency
I know you weren't that interested in efficiency, but here it is anyways.
Your code currently traverses the whole row for every single cell. Example:
neighbors 0 [] [] $ repeat [Dead]
Will never terminate, despite not really needing anything other than the first value
A good rule of thumb is that if you are indexing over lists, you're probably doing something wrong. And if you are iterating over all indexes of a list, you're definitely doing something wrong.
Either use a different data structure or a different method. In the latter case, you could probably just use a fold or a map.
In your case it is not as simple as that, but you can reuse (read "factor out as a function") the pattern you used for traversing the neighboring rows, but for the columns.
Misc points
You can loosen up the types of some functions, without changing any other code, like neighbors
:
neighbors :: Int -> [a] -> [a] -> [a] -> [a]
This may or may not be better, but it's good to know, so you can factor out more generic functions and just keep the specific ones with the code.
My version
Without changing anything but formatting, names, adding type signatures and replacing equivalent constructs:
module Life where
import Data.Maybe (mapMaybe)
data State = Dead | Alive deriving (Eq, Show)
newtype Grid = Grid [[State]] deriving (Eq, Show)
gridGeneration :: Grid -> Grid
gridGeneration (Grid rs) = Grid $ g ([]:rs)
where
g (r0:r1:r2:rs) = processRow r0 r1 r2 : g (r1:r2:rs)
g [r0,r1] = [processRow r0 r1 []]
g _ = []
processRow :: [State] -> [State] -> [State] -> [State]
processRow r0 r1 r2 = map updateCell [0..(length r1 - 1)]
where
updateCell n = generation (r1 !! n) (live $ neighbors n r0 r1 r2)
live = length . filter (==Alive)
neighbors :: Int -> [a] -> [a] -> [a] -> [a]
neighbors x rowAbove rowOfX rowBelow = mapMaybe maybeCell $ zip rows cols
where
(w,y) = (x-1,x+1)
cols = [w, x, y, -- Use formatting to indicate structure
w, y,
w, x, y]
rows = replicate 3 rowAbove ++
replicate 2 rowOfX ++
replicate 3 rowBelow
maybeCell :: ([a], Int) -> Maybe a
maybeCell (r, idx)
| idx < 0 = Nothing
| idx >= length r = Nothing
| otherwise = Just (r !! idx)
generation :: State -> Int -> State
generation Alive 2 = Alive
generation _ 3 = Alive
generation _ _ = Dead
Update 1:
With new algorithm
I also remade the code with using the same method for traversing both rows and columns. I factored out the function g
as map3
and added the padding first, to simplify things. Then I used zip3
to encapsulate the three lists, so I could map3
over them again.
module Life where
import Data.List (zip3)
data State = Dead | Alive deriving (Eq, Show)
newtype Grid = Grid [[State]] deriving (Eq, Show)
gridGeneration :: Grid -> Grid
gridGeneration (Grid rs) = Grid $ map3 processRow (withEmptyRows . map withEmptyCols $ rs)
where
emptyRow = repeat Dead
withEmptyCols xs = Dead : xs ++ [Dead]
withEmptyRows xss = emptyRow : xss ++ [emptyRow]
-- Map a function over each triplet of neighbouring values
map3 :: (a -> a -> a -> b) -> [a] -> [b]
map3 f (x0:x1:x2:xs) = f x0 x1 x2 : map3 f (x1:x2:xs)
map3 f _ = []
processRow :: [State] -> [State] -> [State] -> [State]
processRow r0 r1 r2 = map updateCell . map3 neighbors $ rows
where
rows :: [(State,State,State)]
rows = zip3 r0 r1 r2
updateCell (cell, neighs) = generation cell (live neighs)
live = length . filter (==Alive)
neighbors :: (a,a,a) -> (a,a,a) -> (a,a,a) -> (a,[a])
neighbors (x1,x2,x3)
(x4,x5,x6)
(x7,x8,x9) = (x5, [x1,x2,x3,
x4, x6,
x7,x8,x9])
generation :: State -> Int -> State
generation Alive 2 = Alive
generation _ 3 = Alive
generation _ _ = Dead
Update 2:
Here is a Hspec for map3
, using QuickCheck:
describe "Life.map3" $ do
it "Decreases the length of the list by two, but not to a negative length" $
property $ \xs -> length (map3 f xs) === 0 `max` (length xs - 2)
where f () () () = ()
The fact that the type is completely generic (map3 :: (a->a->a->b)->[a]->[b]
) means that it cannot do anything with the values, so we don't have to test for that.
-
\$\begingroup\$ We're not supposed to use comments for thanks, so I'll elaborate on my thanks: this is exactly the kind of feedback I was hoping for! So thank you so much! \$\endgroup\$Jeff Maner– Jeff Maner2015年02月20日 16:55:56 +00:00Commented Feb 20, 2015 at 16:55
cs
stands for columns andrs
stands for rows, I understand that part better. Now I just need another 15 minutes to decipher the rest. ;) \$\endgroup\$