0813c7f6a1165e388887015fb7a7df78b6a67181
[advent-of-code-17.git] / src / advent25 / advent25.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 #-}"
13 ]
14 },
15 {
16 "cell_type": "code",
17 "execution_count": 2,
18 "metadata": {},
19 "outputs": [],
20 "source": [
21 "-- import Prelude hiding ((++))\n",
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 "\n",
31 "import qualified Data.Map as M\n",
32 "import Data.Map ((!))\n",
33 "\n",
34 "import Control.Monad (when, unless)\n",
35 "import Control.Monad.State.Lazy\n",
36 "import Control.Monad.Reader\n",
37 "import Control.Monad.Writer"
38 ]
39 },
40 {
41 "cell_type": "code",
42 "execution_count": 3,
43 "metadata": {},
44 "outputs": [],
45 "source": [
46 "type TuringState = String\n",
47 "\n",
48 "type Tape = M.Map Integer Bool\n",
49 "\n",
50 "data StateTransition = StateTransition { writeValue :: Bool\n",
51 " , newState :: TuringState\n",
52 " , tapeMovement :: Integer\n",
53 " } deriving (Show, Eq)\n",
54 "\n",
55 "type RuleTrigger = (TuringState, Bool)\n",
56 "\n",
57 "type Rules = M.Map RuleTrigger StateTransition\n",
58 "\n",
59 "data Machine = Machine { state :: TuringState\n",
60 " , tape :: Tape\n",
61 " , tapeLocation :: Integer\n",
62 " , stepsRemaining :: Integer\n",
63 " } \n",
64 " deriving (Show, Eq)\n",
65 "\n",
66 "emptyMachine = Machine {state = \"unknown\", tape = M.empty, tapeLocation = 0, stepsRemaining = 0}\n",
67 "\n",
68 "type ProgrammedMachine = ReaderT Rules (State Machine) Int"
69 ]
70 },
71 {
72 "cell_type": "code",
73 "execution_count": 4,
74 "metadata": {},
75 "outputs": [],
76 "source": [
77 "sc :: Parser ()\n",
78 "sc = L.space (skipSome spaceChar) CA.empty CA.empty\n",
79 "\n",
80 "lexeme = L.lexeme sc\n",
81 "integer = lexeme L.integer\n",
82 "symbol = L.symbol sc\n",
83 "fullstop = symbol \".\"\n",
84 "\n",
85 "commandP = between (symbol \"-\") fullstop\n",
86 "\n",
87 "writeValueP = (symbol \"1\" *> pure True) <|> (symbol \"0\" *> pure False)\n",
88 "writeP = commandP ((symbol \"Write the value\") *> writeValueP)\n",
89 "\n",
90 "directionP = (symbol \"left\" *> pure -1) <|> (symbol \"right\" *> pure 1)\n",
91 "tapeMovementP = commandP ((symbol \"Move one slot to the\") *> directionP)\n",
92 "\n",
93 "newStateP = commandP ((symbol \"Continue with state\") *> (some letterChar))\n",
94 "\n",
95 "stateTransitionP = stify <$> writeP <*> tapeMovementP <*> newStateP\n",
96 " where stify w t s = StateTransition {writeValue = w, newState = s, tapeMovement = t}\n",
97 " \n",
98 "currentValueP = (symbol \"If the current value is\") *> writeValueP <* (symbol \":\")\n",
99 " \n",
100 "stateWhenP = (,) <$> currentValueP <*> stateTransitionP\n",
101 " \n",
102 "stateDefP = (symbol \"In state\") *> (some letterChar) <* (symbol \":\")\n",
103 " \n",
104 "stateRulesP = rulify <$> stateDefP <*> (stateWhenP `sepBy` space)\n",
105 " where rulify s ts = M.fromList $ map (\\(v, t) -> ((s, v), t)) ts\n",
106 " \n",
107 "manyStateRulesP = M.unions <$> (stateRulesP `sepBy` space)\n",
108 "\n",
109 "startStateP = (symbol \"Begin in state\") *> (some letterChar) <* fullstop\n",
110 "stepsP = (symbol \"Perform a diagnostic checksum after\") *> integer <* (symbol \"steps\") <* fullstop\n",
111 "\n",
112 "machineDescriptionP = machineify <$> startStateP <*> stepsP <*> manyStateRulesP\n",
113 " where machineify initial limit rules = \n",
114 " ( emptyMachine { state = initial, stepsRemaining = limit }\n",
115 " , rules\n",
116 " )"
117 ]
118 },
119 {
120 "cell_type": "code",
121 "execution_count": 5,
122 "metadata": {},
123 "outputs": [
124 {
125 "data": {
126 "text/plain": [
127 "True"
128 ]
129 },
130 "metadata": {},
131 "output_type": "display_data"
132 }
133 ],
134 "source": [
135 "parseTest writeP \"- Write the value 1.\""
136 ]
137 },
138 {
139 "cell_type": "code",
140 "execution_count": 6,
141 "metadata": {},
142 "outputs": [
143 {
144 "data": {
145 "text/plain": [
146 "1"
147 ]
148 },
149 "metadata": {},
150 "output_type": "display_data"
151 }
152 ],
153 "source": [
154 "parseTest tapeMovementP \"- Move one slot to the right.\""
155 ]
156 },
157 {
158 "cell_type": "code",
159 "execution_count": 7,
160 "metadata": {},
161 "outputs": [
162 {
163 "data": {
164 "text/plain": [
165 "\"Fallow\""
166 ]
167 },
168 "metadata": {},
169 "output_type": "display_data"
170 }
171 ],
172 "source": [
173 "parseTest newStateP \"- Continue with state Fallow.\""
174 ]
175 },
176 {
177 "cell_type": "code",
178 "execution_count": 8,
179 "metadata": {},
180 "outputs": [
181 {
182 "data": {
183 "text/plain": [
184 "StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1}"
185 ]
186 },
187 "metadata": {},
188 "output_type": "display_data"
189 }
190 ],
191 "source": [
192 "parseTest stateTransitionP \"- Write the value 1.\\n - Move one slot to the right.\\n - Continue with state B.\""
193 ]
194 },
195 {
196 "cell_type": "code",
197 "execution_count": 9,
198 "metadata": {},
199 "outputs": [
200 {
201 "data": {
202 "text/plain": [
203 "(True,StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1})"
204 ]
205 },
206 "metadata": {},
207 "output_type": "display_data"
208 }
209 ],
210 "source": [
211 "parseTest stateWhenP \"If the current value is 1:\\n - Write the value 1.\\n - Move one slot to the right.\\n - Continue with state B.\""
212 ]
213 },
214 {
215 "cell_type": "code",
216 "execution_count": 10,
217 "metadata": {},
218 "outputs": [
219 {
220 "data": {
221 "text/plain": [
222 "\"A\""
223 ]
224 },
225 "metadata": {},
226 "output_type": "display_data"
227 }
228 ],
229 "source": [
230 "parseTest stateDefP \"In state A:\""
231 ]
232 },
233 {
234 "cell_type": "code",
235 "execution_count": 11,
236 "metadata": {},
237 "outputs": [
238 {
239 "data": {
240 "text/plain": [
241 "[(False,StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1}),(True,StateTransition {writeValue = False, newState = \"F\", tapeMovement = -1})]"
242 ]
243 },
244 "metadata": {},
245 "output_type": "display_data"
246 }
247 ],
248 "source": [
249 "parseTest (stateWhenP `sepBy` space) \"If the current value is 0:\\n - Write the value 1.\\n - Move one slot to the right.\\n - Continue with state B.\\n If the current value is 1:\\n - Write the value 0.\\n - Move one slot to the left.\\n - Continue with state F.\\n\""
250 ]
251 },
252 {
253 "cell_type": "code",
254 "execution_count": 12,
255 "metadata": {},
256 "outputs": [
257 {
258 "data": {
259 "text/plain": [
260 "fromList [((\"A\",False),StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1}),((\"A\",True),StateTransition {writeValue = False, newState = \"F\", tapeMovement = -1})]"
261 ]
262 },
263 "metadata": {},
264 "output_type": "display_data"
265 }
266 ],
267 "source": [
268 "parseTest stateRulesP \"In state A:\\nIf the current value is 0:\\n - Write the value 1.\\n - Move one slot to the right.\\n - Continue with state B.\\n If the current value is 1:\\n - Write the value 0.\\n - Move one slot to the left.\\n - Continue with state F.\\n\""
269 ]
270 },
271 {
272 "cell_type": "code",
273 "execution_count": 13,
274 "metadata": {},
275 "outputs": [
276 {
277 "data": {
278 "text/plain": [
279 "\"A\""
280 ]
281 },
282 "metadata": {},
283 "output_type": "display_data"
284 }
285 ],
286 "source": [
287 "parseTest startStateP \"Begin in state A.\""
288 ]
289 },
290 {
291 "cell_type": "code",
292 "execution_count": 14,
293 "metadata": {},
294 "outputs": [
295 {
296 "data": {
297 "text/plain": [
298 "12994925"
299 ]
300 },
301 "metadata": {},
302 "output_type": "display_data"
303 }
304 ],
305 "source": [
306 "parseTest stepsP \"Perform a diagnostic checksum after 12994925 steps.\""
307 ]
308 },
309 {
310 "cell_type": "code",
311 "execution_count": 15,
312 "metadata": {},
313 "outputs": [],
314 "source": [
315 "successfulParse :: Text -> (Machine, Rules)\n",
316 "successfulParse input = \n",
317 " case parse machineDescriptionP \"input\" input of\n",
318 " Left _error -> (emptyMachine, M.empty)\n",
319 " Right machineRules -> machineRules"
320 ]
321 },
322 {
323 "cell_type": "code",
324 "execution_count": 16,
325 "metadata": {},
326 "outputs": [
327 {
328 "data": {
329 "text/plain": [
330 "(Machine {state = \"A\", tape = fromList [], tapeLocation = 0, stepsRemaining = 12994925},fromList [((\"A\",False),StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1}),((\"A\",True),StateTransition {writeValue = False, newState = \"F\", tapeMovement = -1}),((\"B\",False),StateTransition {writeValue = False, newState = \"C\", tapeMovement = 1}),((\"B\",True),StateTransition {writeValue = False, newState = \"D\", tapeMovement = 1}),((\"C\",False),StateTransition {writeValue = True, newState = \"D\", tapeMovement = -1}),((\"C\",True),StateTransition {writeValue = True, newState = \"E\", tapeMovement = 1}),((\"D\",False),StateTransition {writeValue = False, newState = \"E\", tapeMovement = -1}),((\"D\",True),StateTransition {writeValue = False, newState = \"D\", tapeMovement = -1}),((\"E\",False),StateTransition {writeValue = False, newState = \"A\", tapeMovement = 1}),((\"E\",True),StateTransition {writeValue = True, newState = \"C\", tapeMovement = 1}),((\"F\",False),StateTransition {writeValue = True, newState = \"A\", tapeMovement = -1}),((\"F\",True),StateTransition {writeValue = True, newState = \"A\", tapeMovement = 1})])"
331 ]
332 },
333 "metadata": {},
334 "output_type": "display_data"
335 }
336 ],
337 "source": [
338 "text <- TIO.readFile \"../../data/advent25.txt\"\n",
339 "successfulParse text"
340 ]
341 },
342 {
343 "cell_type": "code",
344 "execution_count": 24,
345 "metadata": {},
346 "outputs": [
347 {
348 "data": {
349 "text/plain": [
350 "(Machine {state = \"A\", tape = fromList [], tapeLocation = 0, stepsRemaining = 6},fromList [((\"A\",False),StateTransition {writeValue = True, newState = \"B\", tapeMovement = 1}),((\"A\",True),StateTransition {writeValue = False, newState = \"B\", tapeMovement = -1}),((\"B\",False),StateTransition {writeValue = True, newState = \"A\", tapeMovement = -1}),((\"B\",True),StateTransition {writeValue = True, newState = \"A\", tapeMovement = 1})])"
351 ]
352 },
353 "metadata": {},
354 "output_type": "display_data"
355 }
356 ],
357 "source": [
358 "text <- TIO.readFile \"advent25sample.txt\"\n",
359 "(sampleMachine, sampleRules) = successfulParse text\n",
360 "(sampleMachine, sampleRules)"
361 ]
362 },
363 {
364 "cell_type": "code",
365 "execution_count": 26,
366 "metadata": {},
367 "outputs": [
368 {
369 "data": {
370 "text/html": [
371 "<style>/* Styles used for the Hoogle display in the pager */\n",
372 ".hoogle-doc {\n",
373 "display: block;\n",
374 "padding-bottom: 1.3em;\n",
375 "padding-left: 0.4em;\n",
376 "}\n",
377 ".hoogle-code {\n",
378 "display: block;\n",
379 "font-family: monospace;\n",
380 "white-space: pre;\n",
381 "}\n",
382 ".hoogle-text {\n",
383 "display: block;\n",
384 "}\n",
385 ".hoogle-name {\n",
386 "color: green;\n",
387 "font-weight: bold;\n",
388 "}\n",
389 ".hoogle-head {\n",
390 "font-weight: bold;\n",
391 "}\n",
392 ".hoogle-sub {\n",
393 "display: block;\n",
394 "margin-left: 0.4em;\n",
395 "}\n",
396 ".hoogle-package {\n",
397 "font-weight: bold;\n",
398 "font-style: italic;\n",
399 "}\n",
400 ".hoogle-module {\n",
401 "font-weight: bold;\n",
402 "}\n",
403 ".hoogle-class {\n",
404 "font-weight: bold;\n",
405 "}\n",
406 ".get-type {\n",
407 "color: green;\n",
408 "font-weight: bold;\n",
409 "font-family: monospace;\n",
410 "display: block;\n",
411 "white-space: pre-wrap;\n",
412 "}\n",
413 ".show-type {\n",
414 "color: green;\n",
415 "font-weight: bold;\n",
416 "font-family: monospace;\n",
417 "margin-left: 1em;\n",
418 "}\n",
419 ".mono {\n",
420 "font-family: monospace;\n",
421 "display: block;\n",
422 "}\n",
423 ".err-msg {\n",
424 "color: red;\n",
425 "font-style: italic;\n",
426 "font-family: monospace;\n",
427 "white-space: pre;\n",
428 "display: block;\n",
429 "}\n",
430 "#unshowable {\n",
431 "color: red;\n",
432 "font-weight: bold;\n",
433 "}\n",
434 ".err-msg.in.collapse {\n",
435 "padding-top: 0.7em;\n",
436 "}\n",
437 ".highlight-code {\n",
438 "white-space: pre;\n",
439 "font-family: monospace;\n",
440 "}\n",
441 ".suggestion-warning { \n",
442 "font-weight: bold;\n",
443 "color: rgb(200, 130, 0);\n",
444 "}\n",
445 ".suggestion-error { \n",
446 "font-weight: bold;\n",
447 "color: red;\n",
448 "}\n",
449 ".suggestion-name {\n",
450 "font-weight: bold;\n",
451 "}\n",
452 "</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\">(tapeLocation m) + (tapeMovement transition)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">tapeLocation m + (tapeMovement transition)</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\">(tapeLocation m) + (tapeMovement transition)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">(tapeLocation m) + tapeMovement transition</div></div>"
453 ],
454 "text/plain": [
455 "Line 7: Redundant bracket\n",
456 "Found:\n",
457 "(tapeLocation m) + (tapeMovement transition)\n",
458 "Why not:\n",
459 "tapeLocation m + (tapeMovement transition)Line 7: Redundant bracket\n",
460 "Found:\n",
461 "(tapeLocation m) + (tapeMovement transition)\n",
462 "Why not:\n",
463 "(tapeLocation m) + tapeMovement transition"
464 ]
465 },
466 "metadata": {},
467 "output_type": "display_data"
468 }
469 ],
470 "source": [
471 "executeStep = \n",
472 " do rules <- ask\n",
473 " m <- get\n",
474 " let tapeHere = M.findWithDefault False (tapeLocation m) (tape m)\n",
475 " let transition = rules!(state m, tapeHere)\n",
476 " let tape' = M.insert (tapeLocation m) (writeValue transition) (tape m)\n",
477 " let loc' = (tapeLocation m) + (tapeMovement transition)\n",
478 " let state' = newState transition\n",
479 " let steps' = stepsRemaining m - 1\n",
480 " let m' = m {state = state', tape = tape', tapeLocation = loc', stepsRemaining = steps'}\n",
481 " put m'\n",
482 " "
483 ]
484 },
485 {
486 "cell_type": "code",
487 "execution_count": 27,
488 "metadata": {},
489 "outputs": [],
490 "source": [
491 "executeSteps = \n",
492 " do m <- get\n",
493 " unless (stepsRemaining m == 0) $\n",
494 " do executeStep\n",
495 " executeSteps"
496 ]
497 },
498 {
499 "cell_type": "code",
500 "execution_count": 28,
501 "metadata": {},
502 "outputs": [
503 {
504 "data": {
505 "text/html": [
506 "<style>/* Styles used for the Hoogle display in the pager */\n",
507 ".hoogle-doc {\n",
508 "display: block;\n",
509 "padding-bottom: 1.3em;\n",
510 "padding-left: 0.4em;\n",
511 "}\n",
512 ".hoogle-code {\n",
513 "display: block;\n",
514 "font-family: monospace;\n",
515 "white-space: pre;\n",
516 "}\n",
517 ".hoogle-text {\n",
518 "display: block;\n",
519 "}\n",
520 ".hoogle-name {\n",
521 "color: green;\n",
522 "font-weight: bold;\n",
523 "}\n",
524 ".hoogle-head {\n",
525 "font-weight: bold;\n",
526 "}\n",
527 ".hoogle-sub {\n",
528 "display: block;\n",
529 "margin-left: 0.4em;\n",
530 "}\n",
531 ".hoogle-package {\n",
532 "font-weight: bold;\n",
533 "font-style: italic;\n",
534 "}\n",
535 ".hoogle-module {\n",
536 "font-weight: bold;\n",
537 "}\n",
538 ".hoogle-class {\n",
539 "font-weight: bold;\n",
540 "}\n",
541 ".get-type {\n",
542 "color: green;\n",
543 "font-weight: bold;\n",
544 "font-family: monospace;\n",
545 "display: block;\n",
546 "white-space: pre-wrap;\n",
547 "}\n",
548 ".show-type {\n",
549 "color: green;\n",
550 "font-weight: bold;\n",
551 "font-family: monospace;\n",
552 "margin-left: 1em;\n",
553 "}\n",
554 ".mono {\n",
555 "font-family: monospace;\n",
556 "display: block;\n",
557 "}\n",
558 ".err-msg {\n",
559 "color: red;\n",
560 "font-style: italic;\n",
561 "font-family: monospace;\n",
562 "white-space: pre;\n",
563 "display: block;\n",
564 "}\n",
565 "#unshowable {\n",
566 "color: red;\n",
567 "font-weight: bold;\n",
568 "}\n",
569 ".err-msg.in.collapse {\n",
570 "padding-top: 0.7em;\n",
571 "}\n",
572 ".highlight-code {\n",
573 "white-space: pre;\n",
574 "font-family: monospace;\n",
575 "}\n",
576 ".suggestion-warning { \n",
577 "font-weight: bold;\n",
578 "color: rgb(200, 130, 0);\n",
579 "}\n",
580 ".suggestion-error { \n",
581 "font-weight: bold;\n",
582 "color: red;\n",
583 "}\n",
584 ".suggestion-name {\n",
585 "font-weight: bold;\n",
586 "}\n",
587 "</style><div class=\"suggestion-name\" style=\"clear:both;\">Eta reduce</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">part1 rules machine0\n",
588 " = runState (runReaderT executeSteps rules) machine0</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">part1 rules = runState (runReaderT executeSteps rules)</div></div>"
589 ],
590 "text/plain": [
591 "Line 1: Eta reduce\n",
592 "Found:\n",
593 "part1 rules machine0\n",
594 " = runState (runReaderT executeSteps rules) machine0\n",
595 "Why not:\n",
596 "part1 rules = runState (runReaderT executeSteps rules)"
597 ]
598 },
599 "metadata": {},
600 "output_type": "display_data"
601 }
602 ],
603 "source": [
604 "part1 rules machine0 = \n",
605 " runState (\n",
606 " runReaderT executeSteps\n",
607 " rules \n",
608 " ) \n",
609 " machine0"
610 ]
611 },
612 {
613 "cell_type": "code",
614 "execution_count": 29,
615 "metadata": {},
616 "outputs": [
617 {
618 "data": {
619 "text/plain": [
620 "((),Machine {state = \"B\", tape = fromList [(0,True)], tapeLocation = 1, stepsRemaining = 5})"
621 ]
622 },
623 "metadata": {},
624 "output_type": "display_data"
625 }
626 ],
627 "source": [
628 "runState ( runReaderT executeStep sampleRules ) sampleMachine"
629 ]
630 },
631 {
632 "cell_type": "code",
633 "execution_count": 33,
634 "metadata": {},
635 "outputs": [],
636 "source": [
637 "main :: IO ()\n",
638 "main = do \n",
639 " text <- TIO.readFile \"../../data/advent25.txt\"\n",
640 " let (machine0, rules) = successfulParse text\n",
641 " let (result, machinef) = part1 rules machine0\n",
642 " print $ M.size $ M.filter id $ tape machinef\n"
643 ]
644 },
645 {
646 "cell_type": "code",
647 "execution_count": 31,
648 "metadata": {},
649 "outputs": [],
650 "source": [
651 "-- main :: IO ()\n",
652 "-- main = do \n",
653 "-- text <- TIO.readFile \"advent25sample.txt\"\n",
654 "-- let (machine0, rules) = successfulParse text\n",
655 "-- let (result, machinef) = part1 rules machine0\n",
656 "-- print $ M.size $ M.filter id $ tape machinef\n"
657 ]
658 },
659 {
660 "cell_type": "code",
661 "execution_count": null,
662 "metadata": {},
663 "outputs": [],
664 "source": [
665 "main"
666 ]
667 },
668 {
669 "cell_type": "code",
670 "execution_count": null,
671 "metadata": {},
672 "outputs": [],
673 "source": []
674 }
675 ],
676 "metadata": {
677 "kernelspec": {
678 "display_name": "Haskell",
679 "language": "haskell",
680 "name": "haskell"
681 },
682 "language_info": {
683 "codemirror_mode": "ihaskell",
684 "file_extension": ".hs",
685 "name": "haskell",
686 "version": "8.0.2"
687 }
688 },
689 "nbformat": 4,
690 "nbformat_minor": 2
691 }