Day 23 done
[advent-of-code-17.git] / src / advent23 / advent23.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 {
21 "data": {
22 "text/html": [
23 "<style>/* Styles used for the Hoogle display in the pager */\n",
24 ".hoogle-doc {\n",
25 "display: block;\n",
26 "padding-bottom: 1.3em;\n",
27 "padding-left: 0.4em;\n",
28 "}\n",
29 ".hoogle-code {\n",
30 "display: block;\n",
31 "font-family: monospace;\n",
32 "white-space: pre;\n",
33 "}\n",
34 ".hoogle-text {\n",
35 "display: block;\n",
36 "}\n",
37 ".hoogle-name {\n",
38 "color: green;\n",
39 "font-weight: bold;\n",
40 "}\n",
41 ".hoogle-head {\n",
42 "font-weight: bold;\n",
43 "}\n",
44 ".hoogle-sub {\n",
45 "display: block;\n",
46 "margin-left: 0.4em;\n",
47 "}\n",
48 ".hoogle-package {\n",
49 "font-weight: bold;\n",
50 "font-style: italic;\n",
51 "}\n",
52 ".hoogle-module {\n",
53 "font-weight: bold;\n",
54 "}\n",
55 ".hoogle-class {\n",
56 "font-weight: bold;\n",
57 "}\n",
58 ".get-type {\n",
59 "color: green;\n",
60 "font-weight: bold;\n",
61 "font-family: monospace;\n",
62 "display: block;\n",
63 "white-space: pre-wrap;\n",
64 "}\n",
65 ".show-type {\n",
66 "color: green;\n",
67 "font-weight: bold;\n",
68 "font-family: monospace;\n",
69 "margin-left: 1em;\n",
70 "}\n",
71 ".mono {\n",
72 "font-family: monospace;\n",
73 "display: block;\n",
74 "}\n",
75 ".err-msg {\n",
76 "color: red;\n",
77 "font-style: italic;\n",
78 "font-family: monospace;\n",
79 "white-space: pre;\n",
80 "display: block;\n",
81 "}\n",
82 "#unshowable {\n",
83 "color: red;\n",
84 "font-weight: bold;\n",
85 "}\n",
86 ".err-msg.in.collapse {\n",
87 "padding-top: 0.7em;\n",
88 "}\n",
89 ".highlight-code {\n",
90 "white-space: pre;\n",
91 "font-family: monospace;\n",
92 "}\n",
93 ".suggestion-warning { \n",
94 "font-weight: bold;\n",
95 "color: rgb(200, 130, 0);\n",
96 "}\n",
97 ".suggestion-error { \n",
98 "font-weight: bold;\n",
99 "color: red;\n",
100 "}\n",
101 ".suggestion-name {\n",
102 "font-weight: bold;\n",
103 "}\n",
104 "</style><span class='err-msg'>&lt;interactive&gt;:1:1: error:<br/> Failed to load interface for ‘Data.Numbers.Primes’</span>"
105 ],
106 "text/plain": [
107 "<interactive>:1:1: error:\n",
108 " Failed to load interface for ‘Data.Numbers.Primes’\n",
109 " Use -v to see a list of the files searched for."
110 ]
111 },
112 "metadata": {},
113 "output_type": "display_data"
114 }
115 ],
116 "source": [
117 "-- import Prelude hiding ((++))\n",
118 "import Data.Text (Text)\n",
119 "import qualified Data.Text as T\n",
120 "import qualified Data.Text.IO as TIO\n",
121 "\n",
122 "import Text.Megaparsec hiding (State)\n",
123 "import qualified Text.Megaparsec.Lexer as L\n",
124 "import Text.Megaparsec.Text (Parser)\n",
125 "import qualified Control.Applicative as CA\n",
126 "\n",
127 "import qualified Data.Map.Strict as M\n",
128 "import Data.Map.Strict ((!))\n",
129 "\n",
130 "import Control.Monad (when)\n",
131 "import Control.Monad.State.Lazy\n",
132 "import Control.Monad.Reader\n",
133 "import Control.Monad.Writer\n",
134 "\n",
135 "import Data.Numbers.Primes"
136 ]
137 },
138 {
139 "cell_type": "code",
140 "execution_count": 3,
141 "metadata": {},
142 "outputs": [],
143 "source": [
144 "data Location = Literal Integer | Register Char deriving (Show, Eq)\n",
145 "data Instruction = Set Location Location \n",
146 " | Sub Location Location \n",
147 " | Mul Location Location\n",
148 " | Jnz Location Location\n",
149 " deriving (Show, Eq)\n",
150 "\n",
151 "data Machine = Machine { registers :: M.Map Char Integer\n",
152 " , pc :: Int\n",
153 " } \n",
154 " deriving (Show, Eq)\n",
155 "\n",
156 "type ProgrammedMachine = WriterT [String] (ReaderT [Instruction] (State Machine)) ()"
157 ]
158 },
159 {
160 "cell_type": "code",
161 "execution_count": 4,
162 "metadata": {},
163 "outputs": [],
164 "source": [
165 "emptyMachine = Machine {registers = M.empty, pc = 0}"
166 ]
167 },
168 {
169 "cell_type": "code",
170 "execution_count": 5,
171 "metadata": {},
172 "outputs": [],
173 "source": [
174 "sc :: Parser ()\n",
175 "sc = L.space (skipSome spaceChar) CA.empty CA.empty\n",
176 "\n",
177 "lexeme = L.lexeme sc\n",
178 "\n",
179 "integer = lexeme L.integer\n",
180 "signedInteger = L.signed sc integer\n",
181 "\n",
182 "symbol = L.symbol sc\n",
183 "\n",
184 "-- reg :: Parser String\n",
185 "-- reg = id <$> some letterChar\n",
186 "\n",
187 "reg = lexeme (some letterChar)\n",
188 "\n",
189 "location = (Literal <$> signedInteger) <|> register\n",
190 "register = (Register . head) <$> reg\n",
191 "\n",
192 "instructionsP = instructionP `sepBy` space\n",
193 "instructionP = choice [setP, subP, mulP, jnzP]\n",
194 "\n",
195 "setP = Set <$> (try (symbol \"set\") *> register) <*> location\n",
196 "subP = Sub <$> (try (symbol \"sub\") *> register) <*> location\n",
197 "mulP = Mul <$> (try (symbol \"mul\") *> register) <*> location\n",
198 "jnzP = Jnz <$> (try (symbol \"jnz\") *> location) <*> location\n",
199 "\n",
200 "successfulParse :: Text -> [Instruction]\n",
201 "successfulParse input = \n",
202 " case parse instructionsP \"input\" input of\n",
203 " Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err\n",
204 " Right instructions -> instructions"
205 ]
206 },
207 {
208 "cell_type": "code",
209 "execution_count": 6,
210 "metadata": {},
211 "outputs": [],
212 "source": [
213 "sample = T.pack \"set a 1\\nsub a 2\\nmul a a\\njnz a 5\""
214 ]
215 },
216 {
217 "cell_type": "code",
218 "execution_count": 7,
219 "metadata": {},
220 "outputs": [
221 {
222 "data": {
223 "text/plain": [
224 "[Set (Register 'a') (Literal 1),Sub (Register 'a') (Literal 2),Mul (Register 'a') (Register 'a'),Jnz (Register 'a') (Literal 5)]"
225 ]
226 },
227 "metadata": {},
228 "output_type": "display_data"
229 }
230 ],
231 "source": [
232 "sampleInstructions = successfulParse sample\n",
233 "sampleInstructions"
234 ]
235 },
236 {
237 "cell_type": "code",
238 "execution_count": 8,
239 "metadata": {},
240 "outputs": [],
241 "source": [
242 "isMul :: Instruction -> Bool\n",
243 "isMul (Mul _ _ ) = True\n",
244 "isMul _ = False"
245 ]
246 },
247 {
248 "cell_type": "code",
249 "execution_count": 9,
250 "metadata": {},
251 "outputs": [],
252 "source": [
253 "isJnz :: Instruction -> Bool\n",
254 "isJnz (Jnz _ _ ) = True\n",
255 "isJnz _ = False"
256 ]
257 },
258 {
259 "cell_type": "code",
260 "execution_count": 10,
261 "metadata": {},
262 "outputs": [],
263 "source": [
264 "evaluate :: Machine -> Location -> Integer\n",
265 "evaluate _ (Literal i) = i\n",
266 "evaluate m (Register r) = M.findWithDefault 0 r (registers m)"
267 ]
268 },
269 {
270 "cell_type": "code",
271 "execution_count": 11,
272 "metadata": {},
273 "outputs": [],
274 "source": [
275 "applyInstruction :: Instruction -> Machine -> Machine\n",
276 "\n",
277 "applyInstruction (Set (Register a) b) m = m {registers = reg', pc = pc'}\n",
278 " where pc' = pc m + 1\n",
279 " y = evaluate m b\n",
280 " reg' = M.insert a y $ registers m\n",
281 "\n",
282 "applyInstruction (Sub (Register a) b) m = m {registers = reg', pc = pc'}\n",
283 " where pc' = pc m + 1\n",
284 " x = evaluate m (Register a) \n",
285 " y = evaluate m b\n",
286 " reg' = M.insert a (x - y) $ registers m\n",
287 "\n",
288 "applyInstruction (Mul (Register a) b) m = m {registers = reg', pc = pc'}\n",
289 " where pc' = pc m + 1\n",
290 " x = evaluate m (Register a) \n",
291 " y = evaluate m b\n",
292 " reg' = M.insert a (x * y) $ registers m\n",
293 "\n",
294 "applyInstruction (Jnz a b) m = m {pc = pc'}\n",
295 " where x = evaluate m a\n",
296 " y = evaluate m b\n",
297 " pc' = if x /= 0 then pc m + (fromIntegral y) else pc m + 1"
298 ]
299 },
300 {
301 "cell_type": "code",
302 "execution_count": 28,
303 "metadata": {},
304 "outputs": [],
305 "source": [
306 "executeInstructionPeep :: ProgrammedMachine\n",
307 "executeInstructionPeep =\n",
308 " do instrs <- ask\n",
309 " m <- get\n",
310 " let sample1 = take (length sample1Target) $ drop (pc m) $ instrs\n",
311 " if sample1 == sample1Target\n",
312 " -- then trace (\"Peeping 1 \" ++ (show m) ++ \" to \" ++ (show m1)) m1\n",
313 " then do let reg1 = M.union (M.fromList [ ('d', 2), ('e', evaluate m (Register 'b'))\n",
314 " , ('f', 0), ('g', 0)\n",
315 " ]) \n",
316 " (registers m)\n",
317 " let m1 = m {registers = reg1, pc = pc m + (length sample1)}\n",
318 " put m1\n",
319 " else executeInstruction\n",
320 " where \n",
321 "-- sample1 = take (length sample1Target) $ drop (pc m) $ instrs\n",
322 " sample1Target = [ Set (Register 'b') (Literal 4)\n",
323 " , Set (Register 'f') (Literal 1)\n",
324 " , Set (Register 'd') (Literal 2)\n",
325 " , Set (Register 'e') (Literal 2)\n",
326 " , Set (Register 'g') (Register 'd')\n",
327 " , Mul (Register 'g') (Register 'e')\n",
328 " , Sub (Register 'g') (Register 'b')\n",
329 " , Jnz (Register 'g') (Literal 2)\n",
330 " , Set (Register 'f') (Literal 0)\n",
331 " , Sub (Register 'e') (Literal (-1))\n",
332 " , Set (Register 'g') (Register 'e')\n",
333 " , Sub (Register 'g') (Register 'b')\n",
334 " , Jnz (Register 'g') (Literal (-8))\n",
335 " ]\n",
336 "-- reg1 = M.union (M.fromList [ ('d', 2), ('e', evaluate m (Register 'b'))\n",
337 "-- , ('f', 0), ('g', 0)\n",
338 "-- ]) \n",
339 "-- (registers m)\n",
340 "-- m1 = m {registers = reg1, pc = pc m + (length sample1)}\n",
341 " "
342 ]
343 },
344 {
345 "cell_type": "code",
346 "execution_count": 29,
347 "metadata": {},
348 "outputs": [],
349 "source": [
350 "executeInstruction :: ProgrammedMachine\n",
351 "executeInstruction =\n",
352 " do instrs <- ask\n",
353 " m <- get\n",
354 " let instr = instrs!!(pc m)\n",
355 "-- tell [(\"pc = \" ++ show (pc m))]\n",
356 " put (applyInstruction instr m)"
357 ]
358 },
359 {
360 "cell_type": "code",
361 "execution_count": 30,
362 "metadata": {},
363 "outputs": [],
364 "source": [
365 "executeInstructions = \n",
366 " do instrs <- ask\n",
367 " m <- get\n",
368 " when (pc m >= 0 && pc m < length instrs)\n",
369 " $\n",
370 " do when (isMul $ instrs !! pc m) (tell [\"mul\"])\n",
371 " when (isJnz $ instrs !! pc m) (tell [show m])\n",
372 "-- executeInstructionPeep\n",
373 " executeInstruction\n",
374 " executeInstructions"
375 ]
376 },
377 {
378 "cell_type": "code",
379 "execution_count": 39,
380 "metadata": {},
381 "outputs": [],
382 "source": [
383 "executeInstructionsPeep = \n",
384 " do instrs <- ask\n",
385 " m <- get\n",
386 " when (pc m >= 0 && pc m < length instrs)\n",
387 " $\n",
388 " do -- when (isMul $ instrs !! pc m) (tell [\"mul\"])\n",
389 " -- when (isJnz $ instrs !! pc m) (tell [show m])\n",
390 " executeInstructionPeep\n",
391 " executeInstructionsPeep"
392 ]
393 },
394 {
395 "cell_type": "code",
396 "execution_count": null,
397 "metadata": {},
398 "outputs": [],
399 "source": []
400 },
401 {
402 "cell_type": "code",
403 "execution_count": 40,
404 "metadata": {},
405 "outputs": [
406 {
407 "data": {
408 "text/plain": [
409 "(((),[\"mul\",\"Machine {registers = fromList [('a',1)], pc = 3}\"]),Machine {registers = fromList [('a',1)], pc = 8})"
410 ]
411 },
412 "metadata": {},
413 "output_type": "display_data"
414 }
415 ],
416 "source": [
417 "runState (runReaderT (runWriterT executeInstructions) sampleInstructions ) emptyMachine"
418 ]
419 },
420 {
421 "cell_type": "code",
422 "execution_count": 41,
423 "metadata": {},
424 "outputs": [
425 {
426 "data": {
427 "text/plain": [
428 "(((),[\"mul\",\"Machine {registers = fromList [('a',1)], pc = 3}\"]),Machine {registers = fromList [('a',1)], pc = 8})"
429 ]
430 },
431 "metadata": {},
432 "output_type": "display_data"
433 }
434 ],
435 "source": [
436 "runState (\n",
437 " runReaderT (\n",
438 " runWriterT executeInstructions\n",
439 " ) \n",
440 " (take 7 sampleInstructions) \n",
441 " ) \n",
442 " emptyMachine"
443 ]
444 },
445 {
446 "cell_type": "code",
447 "execution_count": 42,
448 "metadata": {},
449 "outputs": [
450 {
451 "data": {
452 "text/plain": [
453 "[Set (Register 'a') (Literal 1),Sub (Register 'a') (Literal 2),Mul (Register 'a') (Register 'a'),Jnz (Register 'a') (Literal 5)]"
454 ]
455 },
456 "metadata": {},
457 "output_type": "display_data"
458 }
459 ],
460 "source": [
461 "sampleInstructions"
462 ]
463 },
464 {
465 "cell_type": "code",
466 "execution_count": 43,
467 "metadata": {},
468 "outputs": [],
469 "source": [
470 "part1 instructions = \n",
471 " runState (\n",
472 " runReaderT (\n",
473 " runWriterT executeInstructions\n",
474 " ) \n",
475 " instructions \n",
476 " ) \n",
477 " emptyMachine"
478 ]
479 },
480 {
481 "cell_type": "code",
482 "execution_count": 44,
483 "metadata": {},
484 "outputs": [],
485 "source": [
486 "main :: IO ()\n",
487 "main = do \n",
488 " text <- TIO.readFile \"../../data/advent23.txt\"\n",
489 " let instrs = successfulParse text\n",
490 " let ((result, l), machinef) = part1 instrs\n",
491 "-- print $ head l\n",
492 " print $ length $ filter (== \"mul\") l\n",
493 "-- print $ part2 instrs"
494 ]
495 },
496 {
497 "cell_type": "code",
498 "execution_count": 45,
499 "metadata": {},
500 "outputs": [
501 {
502 "data": {
503 "text/plain": [
504 "6724"
505 ]
506 },
507 "metadata": {},
508 "output_type": "display_data"
509 }
510 ],
511 "source": [
512 "main"
513 ]
514 },
515 {
516 "cell_type": "code",
517 "execution_count": 46,
518 "metadata": {},
519 "outputs": [
520 {
521 "data": {
522 "text/html": [
523 "<style>/* Styles used for the Hoogle display in the pager */\n",
524 ".hoogle-doc {\n",
525 "display: block;\n",
526 "padding-bottom: 1.3em;\n",
527 "padding-left: 0.4em;\n",
528 "}\n",
529 ".hoogle-code {\n",
530 "display: block;\n",
531 "font-family: monospace;\n",
532 "white-space: pre;\n",
533 "}\n",
534 ".hoogle-text {\n",
535 "display: block;\n",
536 "}\n",
537 ".hoogle-name {\n",
538 "color: green;\n",
539 "font-weight: bold;\n",
540 "}\n",
541 ".hoogle-head {\n",
542 "font-weight: bold;\n",
543 "}\n",
544 ".hoogle-sub {\n",
545 "display: block;\n",
546 "margin-left: 0.4em;\n",
547 "}\n",
548 ".hoogle-package {\n",
549 "font-weight: bold;\n",
550 "font-style: italic;\n",
551 "}\n",
552 ".hoogle-module {\n",
553 "font-weight: bold;\n",
554 "}\n",
555 ".hoogle-class {\n",
556 "font-weight: bold;\n",
557 "}\n",
558 ".get-type {\n",
559 "color: green;\n",
560 "font-weight: bold;\n",
561 "font-family: monospace;\n",
562 "display: block;\n",
563 "white-space: pre-wrap;\n",
564 "}\n",
565 ".show-type {\n",
566 "color: green;\n",
567 "font-weight: bold;\n",
568 "font-family: monospace;\n",
569 "margin-left: 1em;\n",
570 "}\n",
571 ".mono {\n",
572 "font-family: monospace;\n",
573 "display: block;\n",
574 "}\n",
575 ".err-msg {\n",
576 "color: red;\n",
577 "font-style: italic;\n",
578 "font-family: monospace;\n",
579 "white-space: pre;\n",
580 "display: block;\n",
581 "}\n",
582 "#unshowable {\n",
583 "color: red;\n",
584 "font-weight: bold;\n",
585 "}\n",
586 ".err-msg.in.collapse {\n",
587 "padding-top: 0.7em;\n",
588 "}\n",
589 ".highlight-code {\n",
590 "white-space: pre;\n",
591 "font-family: monospace;\n",
592 "}\n",
593 ".suggestion-warning { \n",
594 "font-weight: bold;\n",
595 "color: rgb(200, 130, 0);\n",
596 "}\n",
597 ".suggestion-error { \n",
598 "font-weight: bold;\n",
599 "color: red;\n",
600 "}\n",
601 ".suggestion-name {\n",
602 "font-weight: bold;\n",
603 "}\n",
604 "</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\">runTest instructions machine0\n",
605 " = runState\n",
606 " (runReaderT (runWriterT executeInstructions) instructions)\n",
607 " machine0</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">runTest instructions\n",
608 " = runState\n",
609 " (runReaderT (runWriterT executeInstructions) instructions)</div></div>"
610 ],
611 "text/plain": [
612 "Line 1: Eta reduce\n",
613 "Found:\n",
614 "runTest instructions machine0\n",
615 " = runState\n",
616 " (runReaderT (runWriterT executeInstructions) instructions)\n",
617 " machine0\n",
618 "Why not:\n",
619 "runTest instructions\n",
620 " = runState\n",
621 " (runReaderT (runWriterT executeInstructions) instructions)"
622 ]
623 },
624 "metadata": {},
625 "output_type": "display_data"
626 }
627 ],
628 "source": [
629 "runTest instructions machine0 = \n",
630 " runState (\n",
631 " runReaderT (\n",
632 " runWriterT executeInstructions\n",
633 " ) \n",
634 " instructions \n",
635 " ) \n",
636 " machine0"
637 ]
638 },
639 {
640 "cell_type": "code",
641 "execution_count": 47,
642 "metadata": {},
643 "outputs": [
644 {
645 "data": {
646 "text/html": [
647 "<style>/* Styles used for the Hoogle display in the pager */\n",
648 ".hoogle-doc {\n",
649 "display: block;\n",
650 "padding-bottom: 1.3em;\n",
651 "padding-left: 0.4em;\n",
652 "}\n",
653 ".hoogle-code {\n",
654 "display: block;\n",
655 "font-family: monospace;\n",
656 "white-space: pre;\n",
657 "}\n",
658 ".hoogle-text {\n",
659 "display: block;\n",
660 "}\n",
661 ".hoogle-name {\n",
662 "color: green;\n",
663 "font-weight: bold;\n",
664 "}\n",
665 ".hoogle-head {\n",
666 "font-weight: bold;\n",
667 "}\n",
668 ".hoogle-sub {\n",
669 "display: block;\n",
670 "margin-left: 0.4em;\n",
671 "}\n",
672 ".hoogle-package {\n",
673 "font-weight: bold;\n",
674 "font-style: italic;\n",
675 "}\n",
676 ".hoogle-module {\n",
677 "font-weight: bold;\n",
678 "}\n",
679 ".hoogle-class {\n",
680 "font-weight: bold;\n",
681 "}\n",
682 ".get-type {\n",
683 "color: green;\n",
684 "font-weight: bold;\n",
685 "font-family: monospace;\n",
686 "display: block;\n",
687 "white-space: pre-wrap;\n",
688 "}\n",
689 ".show-type {\n",
690 "color: green;\n",
691 "font-weight: bold;\n",
692 "font-family: monospace;\n",
693 "margin-left: 1em;\n",
694 "}\n",
695 ".mono {\n",
696 "font-family: monospace;\n",
697 "display: block;\n",
698 "}\n",
699 ".err-msg {\n",
700 "color: red;\n",
701 "font-style: italic;\n",
702 "font-family: monospace;\n",
703 "white-space: pre;\n",
704 "display: block;\n",
705 "}\n",
706 "#unshowable {\n",
707 "color: red;\n",
708 "font-weight: bold;\n",
709 "}\n",
710 ".err-msg.in.collapse {\n",
711 "padding-top: 0.7em;\n",
712 "}\n",
713 ".highlight-code {\n",
714 "white-space: pre;\n",
715 "font-family: monospace;\n",
716 "}\n",
717 ".suggestion-warning { \n",
718 "font-weight: bold;\n",
719 "color: rgb(200, 130, 0);\n",
720 "}\n",
721 ".suggestion-error { \n",
722 "font-weight: bold;\n",
723 "color: red;\n",
724 "}\n",
725 ".suggestion-name {\n",
726 "font-weight: bold;\n",
727 "}\n",
728 "</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\">runTestPeep instructions machine0\n",
729 " = runState\n",
730 " (runReaderT (runWriterT executeInstructionsPeep) instructions)\n",
731 " machine0</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">runTestPeep instructions\n",
732 " = runState\n",
733 " (runReaderT (runWriterT executeInstructionsPeep) instructions)</div></div>"
734 ],
735 "text/plain": [
736 "Line 1: Eta reduce\n",
737 "Found:\n",
738 "runTestPeep instructions machine0\n",
739 " = runState\n",
740 " (runReaderT (runWriterT executeInstructionsPeep) instructions)\n",
741 " machine0\n",
742 "Why not:\n",
743 "runTestPeep instructions\n",
744 " = runState\n",
745 " (runReaderT (runWriterT executeInstructionsPeep) instructions)"
746 ]
747 },
748 "metadata": {},
749 "output_type": "display_data"
750 }
751 ],
752 "source": [
753 "runTestPeep instructions machine0 = \n",
754 " runState (\n",
755 " runReaderT (\n",
756 " runWriterT executeInstructionsPeep\n",
757 " ) \n",
758 " instructions \n",
759 " ) \n",
760 " machine0"
761 ]
762 },
763 {
764 "cell_type": "code",
765 "execution_count": 48,
766 "metadata": {},
767 "outputs": [
768 {
769 "data": {
770 "text/plain": [
771 "[Set (Register 'b') (Literal 4),Set (Register 'f') (Literal 1),Set (Register 'd') (Literal 2),Set (Register 'e') (Literal 2),Set (Register 'g') (Register 'd'),Mul (Register 'g') (Register 'e'),Sub (Register 'g') (Register 'b'),Jnz (Register 'g') (Literal 2),Set (Register 'f') (Literal 0),Sub (Register 'e') (Literal (-1)),Set (Register 'g') (Register 'e'),Sub (Register 'g') (Register 'b'),Jnz (Register 'g') (Literal (-8))]"
772 ]
773 },
774 "metadata": {},
775 "output_type": "display_data"
776 }
777 ],
778 "source": [
779 "peepTest1T = T.pack \"set b 4\\nset f 1\\nset d 2\\nset e 2\\nset g d\\nmul g e\\nsub g b\\njnz g 2\\nset f 0\\nsub e -1\\nset g e\\nsub g b\\njnz g -8\"\n",
780 "peepTest1 = successfulParse peepTest1T\n",
781 "peepTest1"
782 ]
783 },
784 {
785 "cell_type": "code",
786 "execution_count": 49,
787 "metadata": {},
788 "outputs": [
789 {
790 "data": {
791 "text/plain": [
792 "[\"mul\",\"Machine {registers = fromList [('b',4),('d',2),('e',2),('f',1),('g',0)], pc = 7}\",\"Machine {registers = fromList [('b',4),('d',2),('e',3),('f',0),('g',-1)], pc = 12}\",\"mul\",\"Machine {registers = fromList [('b',4),('d',2),('e',3),('f',0),('g',2)], pc = 7}\",\"Machine {registers = fromList [('b',4),('d',2),('e',4),('f',0),('g',0)], pc = 12}\"]"
793 ]
794 },
795 "metadata": {},
796 "output_type": "display_data"
797 }
798 ],
799 "source": [
800 "((v, t), m) = runTest peepTest1 emptyMachine\n",
801 "t"
802 ]
803 },
804 {
805 "cell_type": "code",
806 "execution_count": 50,
807 "metadata": {},
808 "outputs": [],
809 "source": [
810 "text <- TIO.readFile \"../../data/advent23.txt\"\n",
811 "let fullInstrs = successfulParse text"
812 ]
813 },
814 {
815 "cell_type": "code",
816 "execution_count": 51,
817 "metadata": {},
818 "outputs": [
819 {
820 "data": {
821 "text/plain": [
822 "[Set (Register 'b') (Literal 84),Set (Register 'c') (Register 'b'),Jnz (Register 'a') (Literal 2),Jnz (Literal 1) (Literal 5),Mul (Register 'b') (Literal 100),Sub (Register 'b') (Literal (-100000)),Set (Register 'c') (Register 'b'),Sub (Register 'c') (Literal (-17000)),Set (Register 'f') (Literal 1),Set (Register 'd') (Literal 2),Set (Register 'e') (Literal 2),Set (Register 'g') (Register 'd'),Mul (Register 'g') (Register 'e'),Sub (Register 'g') (Register 'b'),Jnz (Register 'g') (Literal 2),Set (Register 'f') (Literal 0),Sub (Register 'e') (Literal (-1)),Set (Register 'g') (Register 'e'),Sub (Register 'g') (Register 'b'),Jnz (Register 'g') (Literal (-8)),Sub (Register 'd') (Literal (-1)),Set (Register 'g') (Register 'd'),Sub (Register 'g') (Register 'b'),Jnz (Register 'g') (Literal (-13)),Jnz (Register 'f') (Literal 2),Sub (Register 'h') (Literal (-1)),Set (Register 'g') (Register 'b'),Sub (Register 'g') (Register 'c'),Jnz (Register 'g') (Literal 2),Jnz (Literal 1) (Literal 3),Sub (Register 'b') (Literal (-17)),Jnz (Literal 1) (Literal (-23))]"
823 ]
824 },
825 "metadata": {},
826 "output_type": "display_data"
827 }
828 ],
829 "source": [
830 "fullInstrs"
831 ]
832 },
833 {
834 "cell_type": "code",
835 "execution_count": 52,
836 "metadata": {},
837 "outputs": [
838 {
839 "data": {
840 "text/plain": [
841 "Machine {registers = fromList [('b',84),('c',84),('d',84),('e',84),('f',0),('g',0),('h',1)], pc = 32}"
842 ]
843 },
844 "metadata": {},
845 "output_type": "display_data"
846 }
847 ],
848 "source": [
849 "((v, t), m) = runTest fullInstrs emptyMachine\n",
850 "m"
851 ]
852 },
853 {
854 "cell_type": "code",
855 "execution_count": 53,
856 "metadata": {},
857 "outputs": [
858 {
859 "data": {
860 "text/plain": [
861 "Machine {registers = fromList [('b',84),('c',84),('d',84),('e',84),('f',0),('g',0),('h',1)], pc = 32}"
862 ]
863 },
864 "metadata": {},
865 "output_type": "display_data"
866 }
867 ],
868 "source": [
869 "((v, t), m) = runTestPeep fullInstrs emptyMachine\n",
870 "m"
871 ]
872 },
873 {
874 "cell_type": "code",
875 "execution_count": null,
876 "metadata": {},
877 "outputs": [],
878 "source": [
879 "((v, t), m) = runTestPeep fullInstrs (emptyMachine {registers = M.fromList [('a', 1)]})\n",
880 "m"
881 ]
882 },
883 {
884 "cell_type": "code",
885 "execution_count": null,
886 "metadata": {},
887 "outputs": [],
888 "source": []
889 }
890 ],
891 "metadata": {
892 "kernelspec": {
893 "display_name": "Haskell",
894 "language": "haskell",
895 "name": "haskell"
896 },
897 "language_info": {
898 "codemirror_mode": "ihaskell",
899 "file_extension": ".hs",
900 "name": "haskell",
901 "version": "8.0.2"
902 }
903 },
904 "nbformat": 4,
905 "nbformat_minor": 2
906 }