Day 7, eventually
[advent-of-code-17.git] / src / advent07 / advent07.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 #-}"
11 ]
12 },
13 {
14 "cell_type": "code",
15 "execution_count": 113,
16 "metadata": {},
17 "outputs": [],
18 "source": [
19 "import Text.Parsec \n",
20 "import Text.ParserCombinators.Parsec.Number\n",
21 "import Data.List (partition, intersect, sortBy, groupBy, sort, group, (\\\\))\n",
22 "import qualified Data.Set as S\n",
23 "import Data.Function (on)"
24 ]
25 },
26 {
27 "cell_type": "code",
28 "execution_count": 151,
29 "metadata": {},
30 "outputs": [],
31 "source": [
32 "import Debug.Trace"
33 ]
34 },
35 {
36 "cell_type": "code",
37 "execution_count": 3,
38 "metadata": {},
39 "outputs": [],
40 "source": [
41 "data Programx = Programx String Int [String]\n",
42 " deriving (Show, Eq)\n",
43 "\n",
44 "name (Programx n _ _) = n \n",
45 "weight (Programx _ w _) = w\n",
46 "supports (Programx _ _ s) = s"
47 ]
48 },
49 {
50 "cell_type": "code",
51 "execution_count": 4,
52 "metadata": {},
53 "outputs": [],
54 "source": [
55 "data Treex = Treex Programx [Treex] Int deriving (Show, Eq)\n",
56 "root (Treex p _ _) = p\n",
57 "trees (Treex _ t _) = t\n",
58 "tWeight (Treex _ _ w) = w"
59 ]
60 },
61 {
62 "cell_type": "code",
63 "execution_count": 5,
64 "metadata": {},
65 "outputs": [],
66 "source": [
67 "onlySpaces = many (oneOf \" \\t\")\n",
68 "parens = between (string \"(\") (string \")\")\n",
69 "sym = many lower\n",
70 "commaSep sym = sym `sepBy` (onlySpaces *> string \",\" *> onlySpaces)"
71 ]
72 },
73 {
74 "cell_type": "code",
75 "execution_count": 6,
76 "metadata": {},
77 "outputs": [],
78 "source": [
79 "mFile = mLine `sepBy` newline \n",
80 "mLine = Programx <$> sym <*> (onlySpaces *> (parens int)) <*> supportsP\n",
81 "supportsP = (onlySpaces *> (string \"->\") *> onlySpaces *> (commaSep sym)) <|> (pure [])"
82 ]
83 },
84 {
85 "cell_type": "code",
86 "execution_count": 7,
87 "metadata": {},
88 "outputs": [],
89 "source": [
90 "parseFile :: String -> Either ParseError [Programx]\n",
91 "parseFile input = parse mFile \"(unknown)\" input\n",
92 "\n",
93 "parseLine :: String -> Either ParseError Programx\n",
94 "parseLine input = parse mLine \"(unknown)\" input\n",
95 "\n",
96 "successfulParse :: Either ParseError [a] -> [a]\n",
97 "successfulParse (Left _) = []\n",
98 "successfulParse (Right a) = a"
99 ]
100 },
101 {
102 "cell_type": "code",
103 "execution_count": 8,
104 "metadata": {},
105 "outputs": [
106 {
107 "data": {
108 "text/plain": [
109 "Right (Programx \"kuvqhnm\" 77 [])"
110 ]
111 },
112 "metadata": {},
113 "output_type": "display_data"
114 }
115 ],
116 "source": [
117 "parseLine \"kuvqhnm (77)\""
118 ]
119 },
120 {
121 "cell_type": "code",
122 "execution_count": 9,
123 "metadata": {},
124 "outputs": [
125 {
126 "data": {
127 "text/plain": [
128 "Right (Programx \"dihjv\" 2158 [\"gausx\",\"ncdmp\",\"hozgrub\"])"
129 ]
130 },
131 "metadata": {},
132 "output_type": "display_data"
133 }
134 ],
135 "source": [
136 "parseLine \"dihjv (2158) -> gausx, ncdmp, hozgrub\""
137 ]
138 },
139 {
140 "cell_type": "code",
141 "execution_count": 10,
142 "metadata": {},
143 "outputs": [],
144 "source": [
145 "sample = \"pbga (66)\\nxhth (57)\\nebii (61)\\nhavc (66)\\nktlj (57)\\nfwft (72) -> ktlj, cntj, xhth\\nqoyq (66)\\npadx (45) -> pbga, havc, qoyq\\ntknk (41) -> ugml, padx, fwft\\njptl (61)\\nugml (68) -> gyxo, ebii, jptl\\ngyxo (61)\\ncntj (57)\""
146 ]
147 },
148 {
149 "cell_type": "code",
150 "execution_count": 11,
151 "metadata": {},
152 "outputs": [],
153 "source": [
154 "-- sample = \"pbga (66)\\nxhth (57)\""
155 ]
156 },
157 {
158 "cell_type": "code",
159 "execution_count": 12,
160 "metadata": {},
161 "outputs": [
162 {
163 "data": {
164 "text/plain": [
165 "\"pbga (66)\\nxhth (57)\\nebii (61)\\nhavc (66)\\nktlj (57)\\nfwft (72) -> ktlj, cntj, xhth\\nqoyq (66)\\npadx (45) -> pbga, havc, qoyq\\ntknk (41) -> ugml, padx, fwft\\njptl (61)\\nugml (68) -> gyxo, ebii, jptl\\ngyxo (61)\\ncntj (57)\""
166 ]
167 },
168 "metadata": {},
169 "output_type": "display_data"
170 }
171 ],
172 "source": [
173 "print sample"
174 ]
175 },
176 {
177 "cell_type": "code",
178 "execution_count": 13,
179 "metadata": {},
180 "outputs": [
181 {
182 "data": {
183 "text/plain": [
184 "[Programx \"pbga\" 66 [],Programx \"xhth\" 57 [],Programx \"ebii\" 61 [],Programx \"havc\" 66 [],Programx \"ktlj\" 57 [],Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"],Programx \"qoyq\" 66 [],Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"],Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"],Programx \"jptl\" 61 [],Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"],Programx \"gyxo\" 61 [],Programx \"cntj\" 57 []]"
185 ]
186 },
187 "metadata": {},
188 "output_type": "display_data"
189 }
190 ],
191 "source": [
192 "successfulParse $ parseFile sample"
193 ]
194 },
195 {
196 "cell_type": "code",
197 "execution_count": 14,
198 "metadata": {},
199 "outputs": [],
200 "source": [
201 "programs :: [Programx] -> S.Set String\n",
202 "programs = S.fromList . map name"
203 ]
204 },
205 {
206 "cell_type": "code",
207 "execution_count": 15,
208 "metadata": {},
209 "outputs": [
210 {
211 "data": {
212 "text/plain": [
213 "fromList [\"cntj\",\"ebii\",\"fwft\",\"gyxo\",\"havc\",\"jptl\",\"ktlj\",\"padx\",\"pbga\",\"qoyq\",\"tknk\",\"ugml\",\"xhth\"]"
214 ]
215 },
216 "metadata": {},
217 "output_type": "display_data"
218 }
219 ],
220 "source": [
221 "pr = programs $ successfulParse $ parseFile sample\n",
222 "pr"
223 ]
224 },
225 {
226 "cell_type": "code",
227 "execution_count": 16,
228 "metadata": {},
229 "outputs": [],
230 "source": [
231 "supported :: [Programx] -> S.Set String\n",
232 "supported = S.unions . map (S.fromList . supports)"
233 ]
234 },
235 {
236 "cell_type": "code",
237 "execution_count": 17,
238 "metadata": {},
239 "outputs": [
240 {
241 "data": {
242 "text/plain": [
243 "fromList [\"cntj\",\"ebii\",\"fwft\",\"gyxo\",\"havc\",\"jptl\",\"ktlj\",\"padx\",\"pbga\",\"qoyq\",\"ugml\",\"xhth\"]"
244 ]
245 },
246 "metadata": {},
247 "output_type": "display_data"
248 }
249 ],
250 "source": [
251 "su = supported $ successfulParse $ parseFile sample\n",
252 "su"
253 ]
254 },
255 {
256 "cell_type": "code",
257 "execution_count": 18,
258 "metadata": {},
259 "outputs": [
260 {
261 "data": {
262 "text/plain": [
263 "\"tknk\""
264 ]
265 },
266 "metadata": {},
267 "output_type": "display_data"
268 }
269 ],
270 "source": [
271 "print $ head $ S.elems $ S.difference pr su"
272 ]
273 },
274 {
275 "cell_type": "code",
276 "execution_count": 19,
277 "metadata": {},
278 "outputs": [],
279 "source": [
280 "part1 :: [Programx] -> String\n",
281 "part1 progs = head $ S.elems $ S.difference pr su\n",
282 " where su = supported progs\n",
283 " pr = programs progs"
284 ]
285 },
286 {
287 "cell_type": "code",
288 "execution_count": 20,
289 "metadata": {},
290 "outputs": [],
291 "source": [
292 "main :: IO ()\n",
293 "main = do \n",
294 " text <- readFile \"../../data/advent07.txt\"\n",
295 " let progs = successfulParse $ parseFile text\n",
296 " print $ part1 progs"
297 ]
298 },
299 {
300 "cell_type": "code",
301 "execution_count": 21,
302 "metadata": {},
303 "outputs": [
304 {
305 "data": {
306 "text/plain": [
307 "\"vtzay\""
308 ]
309 },
310 "metadata": {},
311 "output_type": "display_data"
312 }
313 ],
314 "source": [
315 "main"
316 ]
317 },
318 {
319 "cell_type": "code",
320 "execution_count": 28,
321 "metadata": {},
322 "outputs": [],
323 "source": [
324 "makeSingletons :: [Programx] -> ([Treex], [Programx])\n",
325 "makeSingletons programs = (trees, others)\n",
326 " where (sPrograms, others) = partition isLeaf programs\n",
327 " isLeaf pr = null $ supports pr\n",
328 " trees = map makeSTree sPrograms\n",
329 " makeSTree pr = Treex pr [] (weight pr)"
330 ]
331 },
332 {
333 "cell_type": "code",
334 "execution_count": 29,
335 "metadata": {},
336 "outputs": [
337 {
338 "data": {
339 "text/plain": [
340 "([Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"qoyq\" 66 []) [] 66,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61,Treex (Programx \"cntj\" 57 []) [] 57],[Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"],Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"],Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"],Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]])"
341 ]
342 },
343 "metadata": {},
344 "output_type": "display_data"
345 }
346 ],
347 "source": [
348 "makeSingletons $ successfulParse $ parseFile sample"
349 ]
350 },
351 {
352 "cell_type": "code",
353 "execution_count": 42,
354 "metadata": {},
355 "outputs": [],
356 "source": [
357 "makeTree :: [Treex] -> Programx -> Treex\n",
358 "makeTree trees program = Treex program subtrees (w + (weight program))\n",
359 " where subtrees = filter (\\t -> (name $ root t) `elem` (supports program)) trees\n",
360 " w = sum $ map tWeight subtrees"
361 ]
362 },
363 {
364 "cell_type": "code",
365 "execution_count": 43,
366 "metadata": {},
367 "outputs": [],
368 "source": [
369 "addTreeLayer :: [Treex] -> [Programx] -> ([Treex], [Programx])\n",
370 "addTreeLayer trees programs = (trees', programs')\n",
371 " where (sPrograms, others) = partition isSupporter programs\n",
372 " isSupporter pr = not $ null $ (supports pr) `intersect` roots\n",
373 " roots = map (name . root) trees\n",
374 " trees' = map (makeTree trees) sPrograms\n",
375 " newRoots = map root trees'\n",
376 " programs' = programs \\\\ newRoots\n"
377 ]
378 },
379 {
380 "cell_type": "code",
381 "execution_count": 44,
382 "metadata": {},
383 "outputs": [
384 {
385 "data": {
386 "text/plain": [
387 "([Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"qoyq\" 66 []) [] 66,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61,Treex (Programx \"cntj\" 57 []) [] 57],[Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"],Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"],Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"],Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]])"
388 ]
389 },
390 "metadata": {},
391 "output_type": "display_data"
392 }
393 ],
394 "source": [
395 "(leaves, others) = makeSingletons $ successfulParse $ parseFile sample\n",
396 "(leaves, others)"
397 ]
398 },
399 {
400 "cell_type": "code",
401 "execution_count": 45,
402 "metadata": {},
403 "outputs": [
404 {
405 "data": {
406 "text/plain": [
407 "([Treex (Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"]) [Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"cntj\" 57 []) [] 57] 243,Treex (Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"]) [Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"qoyq\" 66 []) [] 66] 243,Treex (Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]) [Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61] 251],[Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"]])"
408 ]
409 },
410 "metadata": {},
411 "output_type": "display_data"
412 }
413 ],
414 "source": [
415 "(trs, oths) = addTreeLayer leaves others\n",
416 "(trs, oths)"
417 ]
418 },
419 {
420 "cell_type": "code",
421 "execution_count": 46,
422 "metadata": {},
423 "outputs": [
424 {
425 "data": {
426 "text/plain": [
427 "3"
428 ]
429 },
430 "metadata": {},
431 "output_type": "display_data"
432 }
433 ],
434 "source": [
435 "length trs"
436 ]
437 },
438 {
439 "cell_type": "code",
440 "execution_count": 47,
441 "metadata": {},
442 "outputs": [
443 {
444 "data": {
445 "text/plain": [
446 "1"
447 ]
448 },
449 "metadata": {},
450 "output_type": "display_data"
451 }
452 ],
453 "source": [
454 "length oths"
455 ]
456 },
457 {
458 "cell_type": "code",
459 "execution_count": 52,
460 "metadata": {},
461 "outputs": [
462 {
463 "data": {
464 "text/plain": [
465 "([Treex (Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"]) [Treex (Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"]) [Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"cntj\" 57 []) [] 57] 243,Treex (Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"]) [Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"qoyq\" 66 []) [] 66] 243,Treex (Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]) [Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61] 251] 778],[])"
466 ]
467 },
468 "metadata": {},
469 "output_type": "display_data"
470 }
471 ],
472 "source": [
473 "(trs', oths') = addTreeLayer trs oths\n",
474 "(trs', oths')"
475 ]
476 },
477 {
478 "cell_type": "code",
479 "execution_count": 49,
480 "metadata": {},
481 "outputs": [
482 {
483 "data": {
484 "text/plain": [
485 "[243,243,251]"
486 ]
487 },
488 "metadata": {},
489 "output_type": "display_data"
490 }
491 ],
492 "source": [
493 "map tWeight trs"
494 ]
495 },
496 {
497 "cell_type": "code",
498 "execution_count": 173,
499 "metadata": {},
500 "outputs": [],
501 "source": [
502 "balancedTree :: Treex -> Bool\n",
503 "balancedTree tr \n",
504 " | null $ trees tr = True\n",
505 " | otherwise = (1==) $ S.size $ S.fromList $ map tWeight $ trees tr"
506 ]
507 },
508 {
509 "cell_type": "code",
510 "execution_count": 174,
511 "metadata": {},
512 "outputs": [
513 {
514 "data": {
515 "text/plain": [
516 "[True,True,True,True,True,True,True,True,True]"
517 ]
518 },
519 "metadata": {},
520 "output_type": "display_data"
521 }
522 ],
523 "source": [
524 "map balancedTree leaves"
525 ]
526 },
527 {
528 "cell_type": "code",
529 "execution_count": 175,
530 "metadata": {},
531 "outputs": [
532 {
533 "data": {
534 "text/plain": [
535 "[True,True,True]"
536 ]
537 },
538 "metadata": {},
539 "output_type": "display_data"
540 }
541 ],
542 "source": [
543 "map balancedTree trs"
544 ]
545 },
546 {
547 "cell_type": "code",
548 "execution_count": 176,
549 "metadata": {},
550 "outputs": [
551 {
552 "data": {
553 "text/plain": [
554 "[False]"
555 ]
556 },
557 "metadata": {},
558 "output_type": "display_data"
559 }
560 ],
561 "source": [
562 "map balancedTree trs'"
563 ]
564 },
565 {
566 "cell_type": "code",
567 "execution_count": 177,
568 "metadata": {},
569 "outputs": [],
570 "source": [
571 "treesByWeight :: Treex -> [Treex]\n",
572 "treesByWeight = sortBy (compare `on` tWeight) . trees"
573 ]
574 },
575 {
576 "cell_type": "code",
577 "execution_count": 178,
578 "metadata": {},
579 "outputs": [
580 {
581 "data": {
582 "text/plain": [
583 "[243,243,251]"
584 ]
585 },
586 "metadata": {},
587 "output_type": "display_data"
588 }
589 ],
590 "source": [
591 "map tWeight $ treesByWeight $ head trs'"
592 ]
593 },
594 {
595 "cell_type": "code",
596 "execution_count": 179,
597 "metadata": {},
598 "outputs": [],
599 "source": [
600 "oddWeight :: Treex -> Int\n",
601 "oddWeight = tWeight . head . head .filter (\\g -> length g == 1) . groupBy ((==) `on` tWeight) . trees"
602 ]
603 },
604 {
605 "cell_type": "code",
606 "execution_count": 180,
607 "metadata": {},
608 "outputs": [],
609 "source": [
610 "oddWeight :: Treex -> Int\n",
611 "oddWeight = head . head .filter (\\g -> length g == 1) . group . sort . map tWeight . trees"
612 ]
613 },
614 {
615 "cell_type": "code",
616 "execution_count": 181,
617 "metadata": {},
618 "outputs": [
619 {
620 "data": {
621 "text/plain": [
622 "251"
623 ]
624 },
625 "metadata": {},
626 "output_type": "display_data"
627 }
628 ],
629 "source": [
630 "oddWeight $ head trs'"
631 ]
632 },
633 {
634 "cell_type": "code",
635 "execution_count": 182,
636 "metadata": {},
637 "outputs": [],
638 "source": [
639 "-- oddMajorityWeight :: Treex -> (Int, Int)\n",
640 "oddMajorityWeight = extractWeights . oddMajority . groups\n",
641 " where groups = group . sort . map tWeight . trees\n",
642 " oddMajority = partition (\\g -> length g == 1)\n",
643 " extractWeights (o, m) = (head $ head o, head $ head m)"
644 ]
645 },
646 {
647 "cell_type": "code",
648 "execution_count": 183,
649 "metadata": {},
650 "outputs": [
651 {
652 "data": {
653 "text/plain": [
654 "(251,243)"
655 ]
656 },
657 "metadata": {},
658 "output_type": "display_data"
659 }
660 ],
661 "source": [
662 "oddMajorityWeight $ head trs'"
663 ]
664 },
665 {
666 "cell_type": "code",
667 "execution_count": 184,
668 "metadata": {},
669 "outputs": [
670 {
671 "data": {
672 "text/plain": [
673 "68"
674 ]
675 },
676 "metadata": {},
677 "output_type": "display_data"
678 }
679 ],
680 "source": [
681 "weight $ root $ head $ filter (\\t -> tWeight t == 251) $ trees $ head trs' "
682 ]
683 },
684 {
685 "cell_type": "code",
686 "execution_count": 185,
687 "metadata": {},
688 "outputs": [
689 {
690 "data": {
691 "text/plain": [
692 "60"
693 ]
694 },
695 "metadata": {},
696 "output_type": "display_data"
697 }
698 ],
699 "source": [
700 "68 - 251 + 243"
701 ]
702 },
703 {
704 "cell_type": "code",
705 "execution_count": 202,
706 "metadata": {},
707 "outputs": [],
708 "source": [
709 "checkTrees :: ([Treex], [Programx]) -> Int\n",
710 "checkTrees (partTrees, programs) =\n",
711 " if all balancedTree partTrees\n",
712 " then trace (show $ length partTrees) checkTrees $ addTreeLayer partTrees programs\n",
713 " else \n",
714 " oddTreeWeight - oddWeight + majorityWeight\n",
715 " where \n",
716 " unbalancedTree = head $ filter (not . balancedTree) partTrees\n",
717 " (oddWeight, majorityWeight) = oddMajorityWeight unbalancedTree\n",
718 " unbalancedSubtrees = trees unbalancedTree\n",
719 " oddTreeWeight = weight $ root $ head $ filter (\\t -> tWeight t == oddWeight) $ trees unbalancedTree"
720 ]
721 },
722 {
723 "cell_type": "code",
724 "execution_count": 188,
725 "metadata": {},
726 "outputs": [
727 {
728 "data": {
729 "text/plain": [
730 "Treex (Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"]) [Treex (Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"]) [Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"cntj\" 57 []) [] 57] 243,Treex (Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"]) [Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"qoyq\" 66 []) [] 66] 243,Treex (Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]) [Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61] 251] 778"
731 ]
732 },
733 "metadata": {},
734 "output_type": "display_data"
735 }
736 ],
737 "source": [
738 "ubt = head $ filter (not . balancedTree) trs'\n",
739 "ubt"
740 ]
741 },
742 {
743 "cell_type": "code",
744 "execution_count": 189,
745 "metadata": {},
746 "outputs": [
747 {
748 "data": {
749 "text/plain": [
750 "[Treex (Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"]) [Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"cntj\" 57 []) [] 57] 243,Treex (Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"]) [Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"qoyq\" 66 []) [] 66] 243,Treex (Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]) [Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61] 251]"
751 ]
752 },
753 "metadata": {},
754 "output_type": "display_data"
755 }
756 ],
757 "source": [
758 "trees ubt"
759 ]
760 },
761 {
762 "cell_type": "code",
763 "execution_count": 238,
764 "metadata": {},
765 "outputs": [
766 {
767 "data": {
768 "text/plain": [
769 "([Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"qoyq\" 66 []) [] 66,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61,Treex (Programx \"cntj\" 57 []) [] 57],[Programx \"fwft\" 72 [\"ktlj\",\"cntj\",\"xhth\"],Programx \"padx\" 45 [\"pbga\",\"havc\",\"qoyq\"],Programx \"tknk\" 41 [\"ugml\",\"padx\",\"fwft\"],Programx \"ugml\" 68 [\"gyxo\",\"ebii\",\"jptl\"]])"
770 ]
771 },
772 "metadata": {},
773 "output_type": "display_data"
774 }
775 ],
776 "source": [
777 "sglPrs = makeSingletons $ successfulParse $ parseFile sample\n",
778 "sglPrs"
779 ]
780 },
781 {
782 "cell_type": "code",
783 "execution_count": 239,
784 "metadata": {},
785 "outputs": [
786 {
787 "data": {
788 "text/plain": [
789 "[Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"qoyq\" 66 []) [] 66,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61,Treex (Programx \"cntj\" 57 []) [] 57]"
790 ]
791 },
792 "metadata": {},
793 "output_type": "display_data"
794 }
795 ],
796 "source": [
797 "fst sglPrs"
798 ]
799 },
800 {
801 "cell_type": "code",
802 "execution_count": 240,
803 "metadata": {},
804 "outputs": [
805 {
806 "data": {
807 "text/plain": [
808 "60"
809 ]
810 },
811 "metadata": {},
812 "output_type": "display_data"
813 }
814 ],
815 "source": [
816 "checkTrees sglPrs"
817 ]
818 },
819 {
820 "cell_type": "code",
821 "execution_count": 242,
822 "metadata": {},
823 "outputs": [
824 {
825 "data": {
826 "text/plain": [
827 "True"
828 ]
829 },
830 "metadata": {},
831 "output_type": "display_data"
832 }
833 ],
834 "source": [
835 "all balancedTree leaves"
836 ]
837 },
838 {
839 "cell_type": "code",
840 "execution_count": 243,
841 "metadata": {},
842 "outputs": [
843 {
844 "data": {
845 "text/plain": [
846 "[Treex (Programx \"pbga\" 66 []) [] 66,Treex (Programx \"xhth\" 57 []) [] 57,Treex (Programx \"ebii\" 61 []) [] 61,Treex (Programx \"havc\" 66 []) [] 66,Treex (Programx \"ktlj\" 57 []) [] 57,Treex (Programx \"qoyq\" 66 []) [] 66,Treex (Programx \"jptl\" 61 []) [] 61,Treex (Programx \"gyxo\" 61 []) [] 61,Treex (Programx \"cntj\" 57 []) [] 57]"
847 ]
848 },
849 "metadata": {},
850 "output_type": "display_data"
851 }
852 ],
853 "source": [
854 "leaves"
855 ]
856 },
857 {
858 "cell_type": "code",
859 "execution_count": 244,
860 "metadata": {},
861 "outputs": [
862 {
863 "data": {
864 "text/plain": [
865 "True"
866 ]
867 },
868 "metadata": {},
869 "output_type": "display_data"
870 }
871 ],
872 "source": [
873 "balancedTree $ head leaves"
874 ]
875 },
876 {
877 "cell_type": "code",
878 "execution_count": 245,
879 "metadata": {},
880 "outputs": [
881 {
882 "data": {
883 "text/plain": [
884 "Treex (Programx \"pbga\" 66 []) [] 66"
885 ]
886 },
887 "metadata": {},
888 "output_type": "display_data"
889 }
890 ],
891 "source": [
892 "head leaves"
893 ]
894 },
895 {
896 "cell_type": "code",
897 "execution_count": 246,
898 "metadata": {},
899 "outputs": [],
900 "source": [
901 "-- part2 :: [Programx] -> Int\n",
902 "part2 = checkTrees . makeSingletons \n",
903 "-- part2 prs = all balancedTree $ fst $ addTreeLayer ts os\n",
904 "-- where (ts, os) = makeSingletons prs"
905 ]
906 },
907 {
908 "cell_type": "code",
909 "execution_count": 247,
910 "metadata": {},
911 "outputs": [],
912 "source": [
913 "main :: IO ()\n",
914 "main = do \n",
915 " text <- readFile \"../../data/advent07.txt\"\n",
916 " let progs = successfulParse $ parseFile text\n",
917 "-- print $ part1 progs\n",
918 " print $ part2 progs"
919 ]
920 },
921 {
922 "cell_type": "code",
923 "execution_count": 248,
924 "metadata": {},
925 "outputs": [
926 {
927 "data": {
928 "text/html": [
929 "<style>/* Styles used for the Hoogle display in the pager */\n",
930 ".hoogle-doc {\n",
931 "display: block;\n",
932 "padding-bottom: 1.3em;\n",
933 "padding-left: 0.4em;\n",
934 "}\n",
935 ".hoogle-code {\n",
936 "display: block;\n",
937 "font-family: monospace;\n",
938 "white-space: pre;\n",
939 "}\n",
940 ".hoogle-text {\n",
941 "display: block;\n",
942 "}\n",
943 ".hoogle-name {\n",
944 "color: green;\n",
945 "font-weight: bold;\n",
946 "}\n",
947 ".hoogle-head {\n",
948 "font-weight: bold;\n",
949 "}\n",
950 ".hoogle-sub {\n",
951 "display: block;\n",
952 "margin-left: 0.4em;\n",
953 "}\n",
954 ".hoogle-package {\n",
955 "font-weight: bold;\n",
956 "font-style: italic;\n",
957 "}\n",
958 ".hoogle-module {\n",
959 "font-weight: bold;\n",
960 "}\n",
961 ".hoogle-class {\n",
962 "font-weight: bold;\n",
963 "}\n",
964 ".get-type {\n",
965 "color: green;\n",
966 "font-weight: bold;\n",
967 "font-family: monospace;\n",
968 "display: block;\n",
969 "white-space: pre-wrap;\n",
970 "}\n",
971 ".show-type {\n",
972 "color: green;\n",
973 "font-weight: bold;\n",
974 "font-family: monospace;\n",
975 "margin-left: 1em;\n",
976 "}\n",
977 ".mono {\n",
978 "font-family: monospace;\n",
979 "display: block;\n",
980 "}\n",
981 ".err-msg {\n",
982 "color: red;\n",
983 "font-style: italic;\n",
984 "font-family: monospace;\n",
985 "white-space: pre;\n",
986 "display: block;\n",
987 "}\n",
988 "#unshowable {\n",
989 "color: red;\n",
990 "font-weight: bold;\n",
991 "}\n",
992 ".err-msg.in.collapse {\n",
993 "padding-top: 0.7em;\n",
994 "}\n",
995 ".highlight-code {\n",
996 "white-space: pre;\n",
997 "font-family: monospace;\n",
998 "}\n",
999 ".suggestion-warning { \n",
1000 "font-weight: bold;\n",
1001 "color: rgb(200, 130, 0);\n",
1002 "}\n",
1003 ".suggestion-error { \n",
1004 "font-weight: bold;\n",
1005 "color: red;\n",
1006 "}\n",
1007 ".suggestion-name {\n",
1008 "font-weight: bold;\n",
1009 "}\n",
1010 "</style><span class='err-msg'>Prelude.head: empty list</span>"
1011 ],
1012 "text/plain": [
1013 "Prelude.head: empty list"
1014 ]
1015 },
1016 "metadata": {},
1017 "output_type": "display_data"
1018 }
1019 ],
1020 "source": [
1021 "main"
1022 ]
1023 },
1024 {
1025 "cell_type": "code",
1026 "execution_count": null,
1027 "metadata": {},
1028 "outputs": [],
1029 "source": []
1030 }
1031 ],
1032 "metadata": {
1033 "kernelspec": {
1034 "display_name": "Haskell",
1035 "language": "haskell",
1036 "name": "haskell"
1037 },
1038 "language_info": {
1039 "codemirror_mode": "ihaskell",
1040 "file_extension": ".hs",
1041 "name": "haskell",
1042 "version": "8.0.2"
1043 }
1044 },
1045 "nbformat": 4,
1046 "nbformat_minor": 2
1047 }