Day 12
[advent-of-code-18.git] / src / advent12 / life.hs
1 {-# LANGUAGE DeriveFunctor #-}
2
3 import Control.Applicative
4 import Control.Comonad
5
6 import Control.Monad (forM_)
7
8 -- These two typeclasses probably make some people groan.
9 class LeftRight t where
10 left :: t a -> t a
11 right :: t a -> t a
12
13 class UpDown t where
14 up :: t a -> t a
15 down :: t a -> t a
16
17 -- | An infinite list of values
18 data Stream a = a :> Stream a
19 deriving (Functor)
20
21
22 -- * Stream utilities
23
24 -- | Allows finitary beings to view slices of a 'Stream'
25 takeS :: Int -> Stream a -> [a]
26 takeS 0 _ = []
27 takeS n (x :> xs) = x : (takeS (n-1) xs)
28
29 -- | Build a 'Stream' from a generator function
30 unfoldS :: (b -> (a, b)) -> b -> Stream a
31 unfoldS f c = x :> unfoldS f d
32 where (x, d) = f c
33
34 -- | Build a 'Stream' by mindlessly repeating a value
35 repeatS :: a -> Stream a
36 repeatS x = x :> repeatS x
37
38 -- | Build a 'Stream' from a finite list, filling in the rest with a designated
39 -- default value
40 fromS :: a -> [a] -> Stream a
41 fromS def [] = repeatS def
42 fromS def (x:xs) = x :> (fromS def xs)
43
44 -- | Prepend values from a list to an existing 'Stream'
45 prependList :: [a] -> Stream a -> Stream a
46 prependList [] str = str
47 prependList (x:xs) str = x :> (prependList xs str)
48
49 -- | A 'Stream' is a comonad
50 instance Comonad Stream where
51 extract (a :> _) = a
52 duplicate s@(a :> as) = s :> (duplicate as)
53
54 -- | It is also a 'ComonadApply'
55 instance ComonadApply Stream where
56 (f :> fs) <@> (x :> xs) = (f x) :> (fs <@> xs)
57
58 -- * Tapes, our workhorse
59
60 -- | A 'Tape' is always focused on one value in a 1-dimensional infinite stream
61 data Tape a = Tape (Stream a) a (Stream a)
62 deriving (Functor)
63
64 -- | We can go left and right along a tape!
65 instance LeftRight Tape where
66 left (Tape (l :> ls) c rs) = Tape ls l (c :> rs)
67 right (Tape ls c (r :> rs)) = Tape (c :> ls) r rs
68
69 -- | Build out the left, middle, and right parts of a 'Tape' with generator
70 -- functions.
71 unfoldT
72 :: (c -> (a, c))
73 -> (c -> a)
74 -> (c -> (a, c))
75 -> c
76 -> Tape a
77 unfoldT prev center next =
78 Tape
79 <$> unfoldS prev
80 <*> center
81 <*> unfoldS next
82
83 -- | A simplified unfolding mechanism that will be useful shortly
84 tapeIterate
85 :: (a -> a)
86 -> (a -> a)
87 -> a
88 -> Tape a
89 tapeIterate prev next = unfoldT (dup . prev) id (dup . next)
90 where dup a = (a, a)
91
92 -- | Create a 'Tape' from a list where everything to the left is some default
93 -- value and the list is the focused value and everything to the right.
94 tapeFromList :: a -> [a] -> Tape a
95 tapeFromList def xs = right $ Tape background def $ fromS def xs
96 where background = repeatS def
97
98 tapeToList :: Int -> Tape a -> [a]
99 tapeToList n (Tape ls x rs) =
100 reverse (takeS n ls) ++ [x] ++ (takeS n rs)
101
102 instance Comonad Tape where
103 extract (Tape _ c _) = c
104 duplicate = tapeIterate left right
105
106 instance ComonadApply Tape where
107 (Tape fl fc fr) <@> (Tape xl xc xr) =
108 Tape (fl <@> xl) (fc xc) (fr <@> xr)
109
110 -- * Sheets! We're so close!
111
112 -- | A 2-dimensional 'Tape' of 'Tape's.
113 newtype Sheet a = Sheet (Tape (Tape a))
114 deriving (Functor)
115
116 instance UpDown Sheet where
117 up (Sheet p) = Sheet (left p)
118 down (Sheet p) = Sheet (right p)
119
120 instance LeftRight Sheet where
121 left (Sheet p) = Sheet (fmap left p)
122 right (Sheet p) = Sheet (fmap right p)
123
124 -- Helper functions to take a given 'Sheet' and make an infinite 'Tape' of it.
125 horizontal :: Sheet a -> Tape (Sheet a)
126 horizontal = tapeIterate left right
127
128 vertical :: Sheet a -> Tape (Sheet a)
129 vertical = tapeIterate up down
130
131 instance Comonad Sheet where
132 extract (Sheet p) = extract $ extract p
133 -- | See? Told you 'tapeIterate' would be useful
134 duplicate s = Sheet $ fmap horizontal $ vertical s
135
136 instance ComonadApply Sheet where
137 (Sheet (Tape fu fc fd)) <@> (Sheet (Tape xu xc xd)) =
138 Sheet $ Tape (fu `ap` xu) (fc <@> xc) (fd `ap` xd)
139
140 where ap t1 t2 = (fmap (<@>) t1) <@> t2
141
142 -- | Produce a 'Sheet' from a list of lists, where each inner list is a row.
143 sheet :: a -> [[a]] -> Sheet a
144 sheet def grid = Sheet cols
145 where cols = fmap (tapeFromList def) rows
146 rows = tapeFromList [def] grid
147
148 -- | Slice a sheet for viewing purposes.
149 sheetToList :: Int -> Sheet a -> [[a]]
150 sheetToList n (Sheet zs) = tapeToList n $ fmap (tapeToList n) zs
151
152 -- | Construct an infinite sheet in all directions from a base value.
153 background :: a -> Sheet a
154 background x = Sheet . duplicate $ Tape (repeatS x) x (repeatS x)
155
156 printSheet :: Show a => Int -> Sheet a -> IO ()
157 printSheet n sh = forM_ (sheetToList n sh) $ putStrLn . show
158
159 -- | This just makes some things more readable
160 (&) :: a -> (a -> b) -> b
161 (&) = flip ($)
162
163 -- | A cell can be alive ('O') or dead ('X').
164 data Cell = X | O deriving (Eq)
165
166 instance Show Cell where
167 show X = "\x2591"
168 show O = "\x2593"
169
170 -- | The first list is of numbers of live neighbors to make a dead 'Cell' become
171 -- alive; the second is numbers of live neighbors that keeps a live 'Cell'
172 -- alive.
173 type Ruleset = ([Int], [Int])
174
175 cellToInt :: Cell -> Int
176 cellToInt X = 0
177 cellToInt O = 1
178
179 conwayRules :: Ruleset
180 conwayRules = ([3], [2, 3])
181
182 executeRules :: Ruleset -> Sheet Cell -> Cell
183 executeRules (born, persist) s = go (extract s) where
184
185 -- there is probably a more elegant way of getting all 8 neighbors
186 neighbors = [ s & up & extract
187 , s & down & extract
188 , s & left & extract
189 , s & right & extract
190 , s & up & right & extract
191 , s & up & left & extract
192 , s & down & left & extract
193 , s & down & right & extract ]
194 liveCount = sum $ map cellToInt neighbors
195 go O | liveCount `elem` persist = O
196 | otherwise = X
197 go X | liveCount `elem` born = O
198 | otherwise = X
199
200 -- | A simple glider
201 initialGame :: [[Cell]]
202 initialGame = [ [ X, X, O ]
203 , [ O, X, O ]
204 , [ X, O, O ] ]
205
206 -- | A 'Stream' of Conway games.
207 timeline :: Ruleset -> Sheet Cell -> Stream (Sheet Cell)
208 timeline rules ig = go ig where
209 go ig = ig :> (go (rules' <@> (duplicate ig)))
210 rules' = background $ executeRules rules
211
212 main :: IO ()
213 main = do
214 let ig = sheet X initialGame
215 let tl = timeline conwayRules ig
216 forM_ (takeS 5 tl) $ \s -> do
217 printSheet 3 s
218 putStrLn "---"