Done day 21
[advent-of-code-17.git] / src / advent21 / advent21.ipynb
1 {
2 "cells": [
3 {
4 "cell_type": "code",
5 "execution_count": 1,
6 "metadata": {},
7 "outputs": [],
8 "source": [
9 "{-# LANGUAGE NegativeLiterals #-}\n",
10 "{-# LANGUAGE FlexibleContexts #-}\n",
11 "{-# LANGUAGE OverloadedStrings #-}\n",
12 "{-# LANGUAGE TypeFamilies #-}\n",
13 "{-# LANGUAGE BangPatterns #-}"
14 ]
15 },
16 {
17 "cell_type": "code",
18 "execution_count": 2,
19 "metadata": {},
20 "outputs": [],
21 "source": [
22 "import Data.Text (Text)\n",
23 "import qualified Data.Text as T\n",
24 "import qualified Data.Text.IO as TIO\n",
25 "\n",
26 "import Text.Megaparsec hiding (State)\n",
27 "import qualified Text.Megaparsec.Lexer as L\n",
28 "import Text.Megaparsec.Text (Parser)\n",
29 "import qualified Control.Applicative as CA\n",
30 "-- import Data.Functor (void)\n",
31 "\n",
32 "import qualified Data.Map.Strict as M\n",
33 "import Data.Map.Strict ((!))\n",
34 "\n",
35 "-- import Data.Vector ((!), (//))\n",
36 "-- import qualified Data.Vector as V\n",
37 "\n",
38 "import Data.List \n",
39 "import qualified Data.Functor as F"
40 ]
41 },
42 {
43 "cell_type": "code",
44 "execution_count": 3,
45 "metadata": {},
46 "outputs": [],
47 "source": [
48 "type Grid = M.Map (Int, Int) Bool\n",
49 "-- type Grid = [[Char]]\n",
50 "-- type Grid = [[Bool]]\n",
51 "\n",
52 "type ExplodedGrid = M.Map (Int, Int) Grid\n",
53 "\n",
54 "data Rule = Rule Grid Grid deriving (Eq, Show)\n",
55 "\n",
56 "rulePre (Rule g _) = g\n",
57 "rulePost (Rule _ g) = g"
58 ]
59 },
60 {
61 "cell_type": "code",
62 "execution_count": 38,
63 "metadata": {},
64 "outputs": [],
65 "source": [
66 "onlySpace = (char ' ') <|> (char '\\t')\n",
67 "\n",
68 "sc :: Parser ()\n",
69 "sc = L.space (skipSome onlySpace) CA.empty CA.empty"
70 ]
71 },
72 {
73 "cell_type": "code",
74 "execution_count": 5,
75 "metadata": {},
76 "outputs": [],
77 "source": [
78 "lexeme = L.lexeme sc\n",
79 "\n",
80 "symbol = L.symbol sc\n",
81 "rowSep = symbol \"/\"\n",
82 "ruleJoin = symbol \"=>\"\n",
83 "\n",
84 "-- present :: Parser Bool\n",
85 "present = id True <$ symbol \"#\"\n",
86 "\n",
87 "-- absent :: Parser Bool\n",
88 "absent = id False <$ symbol \".\"\n",
89 "\n",
90 "rulesP = ruleP `sepBy` space\n",
91 "ruleP = Rule <$> gridP <*> (ruleJoin *> gridP)\n",
92 "\n",
93 "gridP = gridify <$> rowP `sepBy` rowSep\n",
94 " where gridify g = M.fromList $ concat \n",
95 " [map (\\(c, v) -> ((r, c), v)) nr | \n",
96 " (r, nr) <- zip [0..] \n",
97 " [zip [0..] r | r <- g]]\n",
98 "\n",
99 "\n",
100 "rowP = some (present <|> absent)\n",
101 " \n",
102 "successfulParse :: Text -> [Rule]\n",
103 "successfulParse input = \n",
104 " case parse rulesP \"input\" input of\n",
105 " Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err\n",
106 " Right instructions -> instructions"
107 ]
108 },
109 {
110 "cell_type": "code",
111 "execution_count": 6,
112 "metadata": {},
113 "outputs": [
114 {
115 "data": {
116 "text/plain": [
117 "Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)])"
118 ]
119 },
120 "metadata": {},
121 "output_type": "display_data"
122 }
123 ],
124 "source": [
125 "parseTest ruleP \"#./.. => .##/.##/#..\""
126 ]
127 },
128 {
129 "cell_type": "code",
130 "execution_count": 7,
131 "metadata": {},
132 "outputs": [
133 {
134 "data": {
135 "text/plain": [
136 "Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
137 ]
138 },
139 "metadata": {},
140 "output_type": "display_data"
141 }
142 ],
143 "source": [
144 "parseTest ruleP \"##./#.#/... => #.#./.#../.##./...#\""
145 ]
146 },
147 {
148 "cell_type": "code",
149 "execution_count": 8,
150 "metadata": {},
151 "outputs": [],
152 "source": [
153 "testRule = head $ successfulParse \"##./#.#/... => #.#./.#../.##./...#\""
154 ]
155 },
156 {
157 "cell_type": "code",
158 "execution_count": 9,
159 "metadata": {},
160 "outputs": [
161 {
162 "data": {
163 "text/plain": [
164 "Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
165 ]
166 },
167 "metadata": {},
168 "output_type": "display_data"
169 }
170 ],
171 "source": [
172 "testRule"
173 ]
174 },
175 {
176 "cell_type": "code",
177 "execution_count": 10,
178 "metadata": {},
179 "outputs": [
180 {
181 "data": {
182 "text/plain": [
183 "[Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])]"
184 ]
185 },
186 "metadata": {},
187 "output_type": "display_data"
188 }
189 ],
190 "source": [
191 "parseTest rulesP \"#./.. => .##/.##/#..\\n##./#.#/... => #.#./.#../.##./...#\""
192 ]
193 },
194 {
195 "cell_type": "markdown",
196 "metadata": {},
197 "source": [
198 "Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) \n",
199 " (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False),((2,3),True),((2,4),True),((2,5),False),((3,0),True),((3,1),False),((3,2),True),((4,0),False),((4,1),False),((4,2),False)]),\n",
200 " \n",
201 "Rule (fromList []) \n",
202 " (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
203 ]
204 },
205 {
206 "cell_type": "code",
207 "execution_count": 11,
208 "metadata": {},
209 "outputs": [],
210 "source": [
211 "g = [[False,True,True],[False,True,True],[True,False,False]]"
212 ]
213 },
214 {
215 "cell_type": "code",
216 "execution_count": 12,
217 "metadata": {},
218 "outputs": [
219 {
220 "data": {
221 "text/plain": [
222 "[((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]"
223 ]
224 },
225 "metadata": {},
226 "output_type": "display_data"
227 }
228 ],
229 "source": [
230 "concat [map (\\(c, v) -> ((r, c), v)) nr | (r, nr) <- zip [0..] [zip [0..] r | r <- g]]"
231 ]
232 },
233 {
234 "cell_type": "code",
235 "execution_count": 53,
236 "metadata": {},
237 "outputs": [],
238 "source": [
239 "bounds :: M.Map (Int, Int) a -> (Int, Int)\n",
240 "bounds grid = (maximum $ map fst $ M.keys grid, maximum $ map snd $ M.keys grid)"
241 ]
242 },
243 {
244 "cell_type": "code",
245 "execution_count": 54,
246 "metadata": {},
247 "outputs": [
248 {
249 "data": {
250 "text/plain": [
251 "(3,3)"
252 ]
253 },
254 "metadata": {},
255 "output_type": "display_data"
256 }
257 ],
258 "source": [
259 "bounds (rulePost testRule)"
260 ]
261 },
262 {
263 "cell_type": "code",
264 "execution_count": 15,
265 "metadata": {},
266 "outputs": [],
267 "source": [
268 "showGrid g = unlines [[showChar $ M.findWithDefault False (r, c) g | \n",
269 " c <- [0..cm] ] | r <- [0..rm] ]\n",
270 " where (rm, cm) = bounds g\n",
271 " showChar True = '#'\n",
272 " showChar False = '.'"
273 ]
274 },
275 {
276 "cell_type": "code",
277 "execution_count": 16,
278 "metadata": {},
279 "outputs": [
280 {
281 "data": {
282 "text/plain": [
283 "#.#.\n",
284 ".#..\n",
285 ".##.\n",
286 "...#"
287 ]
288 },
289 "metadata": {},
290 "output_type": "display_data"
291 }
292 ],
293 "source": [
294 "putStrLn $ showGrid $ rulePost testRule"
295 ]
296 },
297 {
298 "cell_type": "code",
299 "execution_count": 17,
300 "metadata": {},
301 "outputs": [],
302 "source": [
303 "initialGrid = case parse gridP \"\" \".#./..#/###\" of \n",
304 " Left _ -> M.empty \n",
305 " Right g -> g"
306 ]
307 },
308 {
309 "cell_type": "code",
310 "execution_count": 18,
311 "metadata": {},
312 "outputs": [
313 {
314 "data": {
315 "text/plain": [
316 "fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),False),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),True)]"
317 ]
318 },
319 "metadata": {},
320 "output_type": "display_data"
321 }
322 ],
323 "source": [
324 "initialGrid"
325 ]
326 },
327 {
328 "cell_type": "code",
329 "execution_count": 19,
330 "metadata": {},
331 "outputs": [
332 {
333 "data": {
334 "text/plain": [
335 ".#.\n",
336 "..#\n",
337 "###"
338 ]
339 },
340 "metadata": {},
341 "output_type": "display_data"
342 }
343 ],
344 "source": [
345 "putStrLn $ showGrid initialGrid"
346 ]
347 },
348 {
349 "cell_type": "code",
350 "execution_count": 20,
351 "metadata": {},
352 "outputs": [],
353 "source": [
354 "reflectH g = M.fromList [((r, c) , M.findWithDefault False (rm - r, c) g) | r <- [0..rm], c <- [0..cm] ]\n",
355 " where (rm, cm) = bounds g"
356 ]
357 },
358 {
359 "cell_type": "code",
360 "execution_count": 21,
361 "metadata": {},
362 "outputs": [
363 {
364 "data": {
365 "text/plain": [
366 "###\n",
367 "..#\n",
368 ".#."
369 ]
370 },
371 "metadata": {},
372 "output_type": "display_data"
373 }
374 ],
375 "source": [
376 "putStrLn $ showGrid $ reflectH initialGrid"
377 ]
378 },
379 {
380 "cell_type": "code",
381 "execution_count": 22,
382 "metadata": {},
383 "outputs": [],
384 "source": [
385 "reflectV g = M.fromList [((r, c) , M.findWithDefault False (r, cm - c) g) | r <- [0..rm], c <- [0..cm] ]\n",
386 " where (rm, cm) = bounds g"
387 ]
388 },
389 {
390 "cell_type": "code",
391 "execution_count": 23,
392 "metadata": {},
393 "outputs": [
394 {
395 "data": {
396 "text/plain": [
397 ".#.\n",
398 "#..\n",
399 "###"
400 ]
401 },
402 "metadata": {},
403 "output_type": "display_data"
404 }
405 ],
406 "source": [
407 "putStrLn $ showGrid $ reflectV initialGrid"
408 ]
409 },
410 {
411 "cell_type": "code",
412 "execution_count": 24,
413 "metadata": {},
414 "outputs": [],
415 "source": [
416 "transpose g = M.fromList [((c, r) , M.findWithDefault False (r, c) g) | r <- [0..rm], c <- [0..cm] ]\n",
417 " where (rm, cm) = bounds g"
418 ]
419 },
420 {
421 "cell_type": "code",
422 "execution_count": 25,
423 "metadata": {},
424 "outputs": [
425 {
426 "data": {
427 "text/plain": [
428 "..#\n",
429 "#.#\n",
430 ".##"
431 ]
432 },
433 "metadata": {},
434 "output_type": "display_data"
435 }
436 ],
437 "source": [
438 "putStrLn $ showGrid $ transpose initialGrid"
439 ]
440 },
441 {
442 "cell_type": "code",
443 "execution_count": 26,
444 "metadata": {},
445 "outputs": [],
446 "source": [
447 "allArrangements grid = map (\\f -> f grid) [ id\n",
448 " , reflectH\n",
449 " , reflectV\n",
450 " , transpose\n",
451 " , reflectH . transpose\n",
452 " , reflectV . transpose\n",
453 " , reflectH . reflectV . transpose\n",
454 " , reflectV . reflectH\n",
455 " ]"
456 ]
457 },
458 {
459 "cell_type": "code",
460 "execution_count": 27,
461 "metadata": {},
462 "outputs": [
463 {
464 "data": {
465 "text/plain": [
466 "[\".#.\\n..#\\n###\\n\",\"###\\n..#\\n.#.\\n\",\".#.\\n#..\\n###\\n\",\"..#\\n#.#\\n.##\\n\",\".##\\n#.#\\n..#\\n\",\"#..\\n#.#\\n##.\\n\",\"##.\\n#.#\\n#..\\n\",\"###\\n#..\\n.#.\\n\"]"
467 ]
468 },
469 "metadata": {},
470 "output_type": "display_data"
471 }
472 ],
473 "source": [
474 "map showGrid $ allArrangements initialGrid"
475 ]
476 },
477 {
478 "cell_type": "code",
479 "execution_count": 28,
480 "metadata": {},
481 "outputs": [
482 {
483 "data": {
484 "text/plain": [
485 "2"
486 ]
487 },
488 "metadata": {},
489 "output_type": "display_data"
490 }
491 ],
492 "source": [
493 "sampleRulesCompact = successfulParse \"../.# => ##./#../...\\n.#./..#/### => #..#/..../..../#..#\"\n",
494 "length sampleRulesCompact"
495 ]
496 },
497 {
498 "cell_type": "code",
499 "execution_count": 29,
500 "metadata": {},
501 "outputs": [],
502 "source": [
503 "expandRule rule = [Rule l (rulePost rule) | l <- allArrangements (rulePre rule)]\n",
504 "expandRules = concatMap expandRule"
505 ]
506 },
507 {
508 "cell_type": "code",
509 "execution_count": 30,
510 "metadata": {},
511 "outputs": [
512 {
513 "data": {
514 "text/plain": [
515 "[\"##.\\n#.#\\n...\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"...\\n#.#\\n##.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".##\\n#.#\\n...\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"##.\\n#..\\n.#.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".#.\\n#..\\n##.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".##\\n..#\\n.#.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".#.\\n..#\\n.##\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"...\\n#.#\\n.##\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\"]"
516 ]
517 },
518 "metadata": {},
519 "output_type": "display_data"
520 }
521 ],
522 "source": [
523 "[showGrid (rulePre r) ++ \"=>\" ++ showGrid (rulePost r) | r <- expandRule testRule]"
524 ]
525 },
526 {
527 "cell_type": "code",
528 "execution_count": 31,
529 "metadata": {},
530 "outputs": [
531 {
532 "data": {
533 "text/plain": [
534 "16"
535 ]
536 },
537 "metadata": {},
538 "output_type": "display_data"
539 }
540 ],
541 "source": [
542 "length $ expandRules sampleRulesCompact"
543 ]
544 },
545 {
546 "cell_type": "code",
547 "execution_count": 32,
548 "metadata": {},
549 "outputs": [],
550 "source": [
551 "readRules = expandRules . successfulParse"
552 ]
553 },
554 {
555 "cell_type": "code",
556 "execution_count": 33,
557 "metadata": {
558 "scrolled": true
559 },
560 "outputs": [
561 {
562 "data": {
563 "text/plain": [
564 "[Rule (fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),False),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),True),((1,0),False),((1,1),False),((1,2),True),((2,0),False),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),True),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),False),((0,2),True),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),False),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),True),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)])]"
565 ]
566 },
567 "metadata": {},
568 "output_type": "display_data"
569 }
570 ],
571 "source": [
572 "sampleRules = readRules \"../.# => ##./#../...\\n.#./..#/### => #..#/..../..../#..#\"\n",
573 "sampleRules"
574 ]
575 },
576 {
577 "cell_type": "code",
578 "execution_count": 125,
579 "metadata": {},
580 "outputs": [],
581 "source": [
582 "text <- TIO.readFile \"../../data/advent21.txt\"\n",
583 "rules = readRules text"
584 ]
585 },
586 {
587 "cell_type": "code",
588 "execution_count": 126,
589 "metadata": {},
590 "outputs": [
591 {
592 "data": {
593 "text/plain": [
594 "864"
595 ]
596 },
597 "metadata": {},
598 "output_type": "display_data"
599 }
600 ],
601 "source": [
602 "length rules"
603 ]
604 },
605 {
606 "cell_type": "code",
607 "execution_count": 34,
608 "metadata": {},
609 "outputs": [],
610 "source": [
611 "apply rules grid = rulePost thisRule\n",
612 " where ri = head $ findIndices (\\r -> rulePre r == grid) rules\n",
613 " thisRule = rules!!ri"
614 ]
615 },
616 {
617 "cell_type": "code",
618 "execution_count": 37,
619 "metadata": {},
620 "outputs": [
621 {
622 "data": {
623 "text/plain": [
624 "#..#\n",
625 "....\n",
626 "....\n",
627 "#..#"
628 ]
629 },
630 "metadata": {},
631 "output_type": "display_data"
632 }
633 ],
634 "source": [
635 "putStrLn $ showGrid $ apply sampleRules initialGrid"
636 ]
637 },
638 {
639 "cell_type": "code",
640 "execution_count": 49,
641 "metadata": {},
642 "outputs": [],
643 "source": [
644 "subGrid :: Int -> Grid -> Int -> Int -> Grid\n",
645 "subGrid n g bigR bigC = M.fromList [ ((r, c), \n",
646 " M.findWithDefault False (r + rStep, c + cStep) g) \n",
647 " | r <- [0..(n - 1)], c <- [0..(n - 1)]\n",
648 " ]\n",
649 " where rStep = bigR * n\n",
650 " cStep = bigC * n"
651 ]
652 },
653 {
654 "cell_type": "code",
655 "execution_count": 50,
656 "metadata": {},
657 "outputs": [],
658 "source": [
659 "explodeGrid' :: Int -> Grid -> ExplodedGrid\n",
660 "explodeGrid' n g = M.fromList [((bigR, bigC), subGrid n g bigR bigC) | bigR <- [0..bigRm], bigC <- [0..bigCm]]\n",
661 " where (rm, cm) = bounds g\n",
662 " bigRm = (rm + 1) `div` n - 1\n",
663 " bigCm = (cm + 1) `div` n - 1"
664 ]
665 },
666 {
667 "cell_type": "code",
668 "execution_count": 107,
669 "metadata": {},
670 "outputs": [],
671 "source": [
672 "explodeGrid :: Grid -> ExplodedGrid\n",
673 "explodeGrid g = if (rm + 1) `rem` 2 == 0 \n",
674 " then explodeGrid' 2 g\n",
675 " else explodeGrid' 3 g\n",
676 " where (rm, cm) = bounds g"
677 ]
678 },
679 {
680 "cell_type": "code",
681 "execution_count": 108,
682 "metadata": {},
683 "outputs": [
684 {
685 "data": {
686 "text/plain": [
687 "fromList [((0,0),\"#.\\n..\\n\"),((0,1),\".#\\n..\\n\"),((1,0),\"..\\n#.\\n\"),((1,1),\"..\\n.#\\n\")]"
688 ]
689 },
690 "metadata": {},
691 "output_type": "display_data"
692 }
693 ],
694 "source": [
695 "testEg = explodeGrid $ apply sampleRules initialGrid\n",
696 "M.map showGrid testEg"
697 ]
698 },
699 {
700 "cell_type": "code",
701 "execution_count": 77,
702 "metadata": {},
703 "outputs": [],
704 "source": [
705 "explodedRows eg = [M.filterWithKey (\\(r, _) _ -> r == row) eg | row <- [0..rowMax] ]\n",
706 " where (rowMax, _) = bounds eg"
707 ]
708 },
709 {
710 "cell_type": "code",
711 "execution_count": 78,
712 "metadata": {},
713 "outputs": [
714 {
715 "data": {
716 "text/plain": [
717 "[fromList [((0,0),fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]),((0,1),fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)])],fromList [((1,0),fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]),((1,1),fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)])]]"
718 ]
719 },
720 "metadata": {},
721 "output_type": "display_data"
722 }
723 ],
724 "source": [
725 "explodedRows testEg"
726 ]
727 },
728 {
729 "cell_type": "code",
730 "execution_count": 79,
731 "metadata": {},
732 "outputs": [],
733 "source": [
734 "(>-<) g1 g2 = M.union g1 g2'\n",
735 " where (_, cm) = bounds g1\n",
736 " g2' = M.mapKeys (\\(r, c) -> (r, c + cm + 1)) g2"
737 ]
738 },
739 {
740 "cell_type": "code",
741 "execution_count": 80,
742 "metadata": {},
743 "outputs": [],
744 "source": [
745 "(>|<) g1 g2 = M.union g1 g2'\n",
746 " where (rm, _) = bounds g1\n",
747 " g2' = M.mapKeys (\\(r, c) -> (r + rm + 1, c)) g2"
748 ]
749 },
750 {
751 "cell_type": "code",
752 "execution_count": 81,
753 "metadata": {},
754 "outputs": [
755 {
756 "data": {
757 "text/plain": [
758 "fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]"
759 ]
760 },
761 "metadata": {},
762 "output_type": "display_data"
763 }
764 ],
765 "source": [
766 "M.findWithDefault M.empty (0, 0) testEg"
767 ]
768 },
769 {
770 "cell_type": "code",
771 "execution_count": 82,
772 "metadata": {},
773 "outputs": [
774 {
775 "data": {
776 "text/html": [
777 "<style>/* Styles used for the Hoogle display in the pager */\n",
778 ".hoogle-doc {\n",
779 "display: block;\n",
780 "padding-bottom: 1.3em;\n",
781 "padding-left: 0.4em;\n",
782 "}\n",
783 ".hoogle-code {\n",
784 "display: block;\n",
785 "font-family: monospace;\n",
786 "white-space: pre;\n",
787 "}\n",
788 ".hoogle-text {\n",
789 "display: block;\n",
790 "}\n",
791 ".hoogle-name {\n",
792 "color: green;\n",
793 "font-weight: bold;\n",
794 "}\n",
795 ".hoogle-head {\n",
796 "font-weight: bold;\n",
797 "}\n",
798 ".hoogle-sub {\n",
799 "display: block;\n",
800 "margin-left: 0.4em;\n",
801 "}\n",
802 ".hoogle-package {\n",
803 "font-weight: bold;\n",
804 "font-style: italic;\n",
805 "}\n",
806 ".hoogle-module {\n",
807 "font-weight: bold;\n",
808 "}\n",
809 ".hoogle-class {\n",
810 "font-weight: bold;\n",
811 "}\n",
812 ".get-type {\n",
813 "color: green;\n",
814 "font-weight: bold;\n",
815 "font-family: monospace;\n",
816 "display: block;\n",
817 "white-space: pre-wrap;\n",
818 "}\n",
819 ".show-type {\n",
820 "color: green;\n",
821 "font-weight: bold;\n",
822 "font-family: monospace;\n",
823 "margin-left: 1em;\n",
824 "}\n",
825 ".mono {\n",
826 "font-family: monospace;\n",
827 "display: block;\n",
828 "}\n",
829 ".err-msg {\n",
830 "color: red;\n",
831 "font-style: italic;\n",
832 "font-family: monospace;\n",
833 "white-space: pre;\n",
834 "display: block;\n",
835 "}\n",
836 "#unshowable {\n",
837 "color: red;\n",
838 "font-weight: bold;\n",
839 "}\n",
840 ".err-msg.in.collapse {\n",
841 "padding-top: 0.7em;\n",
842 "}\n",
843 ".highlight-code {\n",
844 "white-space: pre;\n",
845 "font-family: monospace;\n",
846 "}\n",
847 ".suggestion-warning { \n",
848 "font-weight: bold;\n",
849 "color: rgb(200, 130, 0);\n",
850 "}\n",
851 ".suggestion-error { \n",
852 "font-weight: bold;\n",
853 "color: red;\n",
854 "}\n",
855 ".suggestion-name {\n",
856 "font-weight: bold;\n",
857 "}\n",
858 "</style><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
859 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">M.findWithDefault M.empty (0, 1) testEg >-<\n",
860 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
861 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
862 " M.findWithDefault M.empty (0, 0) testEg</div></div>"
863 ],
864 "text/plain": [
865 "Line 1: Redundant bracket\n",
866 "Found:\n",
867 "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
868 " (M.findWithDefault M.empty (0, 0) testEg)\n",
869 "Why not:\n",
870 "M.findWithDefault M.empty (0, 1) testEg >-<\n",
871 " (M.findWithDefault M.empty (0, 0) testEg)Line 1: Redundant bracket\n",
872 "Found:\n",
873 "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
874 " (M.findWithDefault M.empty (0, 0) testEg)\n",
875 "Why not:\n",
876 "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
877 " M.findWithDefault M.empty (0, 0) testEg"
878 ]
879 },
880 "metadata": {},
881 "output_type": "display_data"
882 },
883 {
884 "data": {
885 "text/plain": [
886 "\".##.\\n....\\n\""
887 ]
888 },
889 "metadata": {},
890 "output_type": "display_data"
891 }
892 ],
893 "source": [
894 "showGrid $ (M.findWithDefault M.empty (0, 1) testEg) >-< (M.findWithDefault M.empty (0, 0) testEg)"
895 ]
896 },
897 {
898 "cell_type": "code",
899 "execution_count": 83,
900 "metadata": {},
901 "outputs": [
902 {
903 "data": {
904 "text/html": [
905 "<style>/* Styles used for the Hoogle display in the pager */\n",
906 ".hoogle-doc {\n",
907 "display: block;\n",
908 "padding-bottom: 1.3em;\n",
909 "padding-left: 0.4em;\n",
910 "}\n",
911 ".hoogle-code {\n",
912 "display: block;\n",
913 "font-family: monospace;\n",
914 "white-space: pre;\n",
915 "}\n",
916 ".hoogle-text {\n",
917 "display: block;\n",
918 "}\n",
919 ".hoogle-name {\n",
920 "color: green;\n",
921 "font-weight: bold;\n",
922 "}\n",
923 ".hoogle-head {\n",
924 "font-weight: bold;\n",
925 "}\n",
926 ".hoogle-sub {\n",
927 "display: block;\n",
928 "margin-left: 0.4em;\n",
929 "}\n",
930 ".hoogle-package {\n",
931 "font-weight: bold;\n",
932 "font-style: italic;\n",
933 "}\n",
934 ".hoogle-module {\n",
935 "font-weight: bold;\n",
936 "}\n",
937 ".hoogle-class {\n",
938 "font-weight: bold;\n",
939 "}\n",
940 ".get-type {\n",
941 "color: green;\n",
942 "font-weight: bold;\n",
943 "font-family: monospace;\n",
944 "display: block;\n",
945 "white-space: pre-wrap;\n",
946 "}\n",
947 ".show-type {\n",
948 "color: green;\n",
949 "font-weight: bold;\n",
950 "font-family: monospace;\n",
951 "margin-left: 1em;\n",
952 "}\n",
953 ".mono {\n",
954 "font-family: monospace;\n",
955 "display: block;\n",
956 "}\n",
957 ".err-msg {\n",
958 "color: red;\n",
959 "font-style: italic;\n",
960 "font-family: monospace;\n",
961 "white-space: pre;\n",
962 "display: block;\n",
963 "}\n",
964 "#unshowable {\n",
965 "color: red;\n",
966 "font-weight: bold;\n",
967 "}\n",
968 ".err-msg.in.collapse {\n",
969 "padding-top: 0.7em;\n",
970 "}\n",
971 ".highlight-code {\n",
972 "white-space: pre;\n",
973 "font-family: monospace;\n",
974 "}\n",
975 ".suggestion-warning { \n",
976 "font-weight: bold;\n",
977 "color: rgb(200, 130, 0);\n",
978 "}\n",
979 ".suggestion-error { \n",
980 "font-weight: bold;\n",
981 "color: red;\n",
982 "}\n",
983 ".suggestion-name {\n",
984 "font-weight: bold;\n",
985 "}\n",
986 "</style><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
987 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">M.findWithDefault M.empty (0, 1) testEg >|<\n",
988 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
989 " (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
990 " M.findWithDefault M.empty (0, 0) testEg</div></div>"
991 ],
992 "text/plain": [
993 "Line 1: Redundant bracket\n",
994 "Found:\n",
995 "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
996 " (M.findWithDefault M.empty (0, 0) testEg)\n",
997 "Why not:\n",
998 "M.findWithDefault M.empty (0, 1) testEg >|<\n",
999 " (M.findWithDefault M.empty (0, 0) testEg)Line 1: Redundant bracket\n",
1000 "Found:\n",
1001 "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
1002 " (M.findWithDefault M.empty (0, 0) testEg)\n",
1003 "Why not:\n",
1004 "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
1005 " M.findWithDefault M.empty (0, 0) testEg"
1006 ]
1007 },
1008 "metadata": {},
1009 "output_type": "display_data"
1010 },
1011 {
1012 "data": {
1013 "text/plain": [
1014 "\".#\\n..\\n#.\\n..\\n\""
1015 ]
1016 },
1017 "metadata": {},
1018 "output_type": "display_data"
1019 }
1020 ],
1021 "source": [
1022 "showGrid $ (M.findWithDefault M.empty (0, 1) testEg) >|< (M.findWithDefault M.empty (0, 0) testEg)"
1023 ]
1024 },
1025 {
1026 "cell_type": "code",
1027 "execution_count": 88,
1028 "metadata": {},
1029 "outputs": [],
1030 "source": [
1031 "contractExploded :: ExplodedGrid -> Grid\n",
1032 "contractExploded gs = foldl1 (>|<) $ map (foldl1 (>-<)) rows\n",
1033 " where rows = explodedRows gs"
1034 ]
1035 },
1036 {
1037 "cell_type": "code",
1038 "execution_count": 90,
1039 "metadata": {},
1040 "outputs": [
1041 {
1042 "data": {
1043 "text/plain": [
1044 "\"#..#\\n....\\n....\\n#..#\\n\""
1045 ]
1046 },
1047 "metadata": {},
1048 "output_type": "display_data"
1049 }
1050 ],
1051 "source": [
1052 "showGrid $ contractExploded testEg"
1053 ]
1054 },
1055 {
1056 "cell_type": "code",
1057 "execution_count": 94,
1058 "metadata": {},
1059 "outputs": [
1060 {
1061 "data": {
1062 "text/plain": [
1063 "##.##.\n",
1064 "#..#..\n",
1065 "......\n",
1066 "##.##.\n",
1067 "#..#..\n",
1068 "......"
1069 ]
1070 },
1071 "metadata": {},
1072 "output_type": "display_data"
1073 }
1074 ],
1075 "source": [
1076 "putStrLn $ showGrid $ contractExploded $ M.map (apply sampleRules) testEg"
1077 ]
1078 },
1079 {
1080 "cell_type": "code",
1081 "execution_count": 128,
1082 "metadata": {},
1083 "outputs": [],
1084 "source": [
1085 "applyOnce rules g = contractExploded $ M.map (apply rules) $ explodeGrid g"
1086 ]
1087 },
1088 {
1089 "cell_type": "code",
1090 "execution_count": 135,
1091 "metadata": {},
1092 "outputs": [
1093 {
1094 "data": {
1095 "text/plain": [
1096 ".#.#.#.#..##..#.##\n",
1097 ".#.#...#..##....##\n",
1098 "..####..##..####..\n",
1099 "..#.#..##.###.#.#.\n",
1100 "....#..##.###...#.\n",
1101 "###..##..#..###..#\n",
1102 "..#.##..#.##.##...\n",
1103 "....##....##.##.##\n",
1104 "####..####..#..##.\n",
1105 "#.#.#.#.#.#.....#.\n",
1106 "#...#.#...#..##.#.\n",
1107 "###..####..###...#\n",
1108 "..#.##..#.##..#.##\n",
1109 "....##....##....##\n",
1110 "####..####..####..\n",
1111 "#.#.#.#.#.#.#.#.#.\n",
1112 "#...#.#...#.#...#.\n",
1113 "###..####..####..#"
1114 ]
1115 },
1116 "metadata": {},
1117 "output_type": "display_data"
1118 }
1119 ],
1120 "source": [
1121 "putStrLn $ showGrid $ (!! 5) $ iterate (applyOnce rules) initialGrid"
1122 ]
1123 },
1124 {
1125 "cell_type": "code",
1126 "execution_count": 131,
1127 "metadata": {},
1128 "outputs": [
1129 {
1130 "data": {
1131 "text/plain": [
1132 ".#\n",
1133 "##"
1134 ]
1135 },
1136 "metadata": {},
1137 "output_type": "display_data"
1138 }
1139 ],
1140 "source": [
1141 "putStrLn $ showGrid $ (!(1, 2)) $ explodeGrid $ last $ take 3 $ iterate (applyOnce rules) initialGrid"
1142 ]
1143 },
1144 {
1145 "cell_type": "code",
1146 "execution_count": 136,
1147 "metadata": {},
1148 "outputs": [],
1149 "source": [
1150 "countLit = M.size . M.filter id"
1151 ]
1152 },
1153 {
1154 "cell_type": "code",
1155 "execution_count": 137,
1156 "metadata": {},
1157 "outputs": [
1158 {
1159 "data": {
1160 "text/plain": [
1161 "5"
1162 ]
1163 },
1164 "metadata": {},
1165 "output_type": "display_data"
1166 }
1167 ],
1168 "source": [
1169 "countLit initialGrid"
1170 ]
1171 },
1172 {
1173 "cell_type": "code",
1174 "execution_count": 142,
1175 "metadata": {},
1176 "outputs": [
1177 {
1178 "data": {
1179 "text/plain": [
1180 "##.##.\n",
1181 "#..#..\n",
1182 "......\n",
1183 "##.##.\n",
1184 "#..#..\n",
1185 "......"
1186 ]
1187 },
1188 "metadata": {},
1189 "output_type": "display_data"
1190 }
1191 ],
1192 "source": [
1193 "putStrLn $ showGrid $ (!! 2) $ iterate (applyOnce sampleRules) initialGrid"
1194 ]
1195 },
1196 {
1197 "cell_type": "code",
1198 "execution_count": 143,
1199 "metadata": {},
1200 "outputs": [
1201 {
1202 "data": {
1203 "text/plain": [
1204 "12"
1205 ]
1206 },
1207 "metadata": {},
1208 "output_type": "display_data"
1209 }
1210 ],
1211 "source": [
1212 "countLit $ (!! 2) $ iterate (applyOnce sampleRules) initialGrid"
1213 ]
1214 },
1215 {
1216 "cell_type": "code",
1217 "execution_count": 144,
1218 "metadata": {},
1219 "outputs": [
1220 {
1221 "data": {
1222 "text/plain": [
1223 "158"
1224 ]
1225 },
1226 "metadata": {},
1227 "output_type": "display_data"
1228 }
1229 ],
1230 "source": [
1231 "countLit $ (!! 5) $ iterate (applyOnce rules) initialGrid"
1232 ]
1233 },
1234 {
1235 "cell_type": "code",
1236 "execution_count": 145,
1237 "metadata": {},
1238 "outputs": [
1239 {
1240 "data": {
1241 "text/plain": [
1242 "2301762"
1243 ]
1244 },
1245 "metadata": {},
1246 "output_type": "display_data"
1247 }
1248 ],
1249 "source": [
1250 "countLit $ (!! 18) $ iterate (applyOnce rules) initialGrid"
1251 ]
1252 },
1253 {
1254 "cell_type": "code",
1255 "execution_count": null,
1256 "metadata": {},
1257 "outputs": [],
1258 "source": []
1259 }
1260 ],
1261 "metadata": {
1262 "kernelspec": {
1263 "display_name": "Haskell",
1264 "language": "haskell",
1265 "name": "haskell"
1266 },
1267 "language_info": {
1268 "codemirror_mode": "ihaskell",
1269 "file_extension": ".hs",
1270 "name": "haskell",
1271 "version": "8.0.2"
1272 }
1273 },
1274 "nbformat": 4,
1275 "nbformat_minor": 2
1276 }