Day 22
[advent-of-code-17.git] / src / advent22 / advent22b.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 Prelude hiding (Left, Right)\n",
23 "import Data.List\n",
24 "import qualified Data.Map as M"
25 ]
26 },
27 {
28 "cell_type": "code",
29 "execution_count": 3,
30 "metadata": {},
31 "outputs": [],
32 "source": [
33 "type Point = (Int, Int)\n",
34 "\n",
35 "data Flag = Clean | Weakened | Infected | Flagged deriving (Show, Eq)\n",
36 "\n",
37 "type Infection = M.Map Point Flag\n",
38 "\n",
39 "data Direction = Up | Right | Down | Left deriving (Show, Eq, Enum)\n",
40 "\n",
41 "data World = World { infected :: Infection\n",
42 " , position :: Point\n",
43 " , direction :: Direction\n",
44 " , infectionCount :: Int\n",
45 " } deriving (Eq, Show)\n",
46 " "
47 ]
48 },
49 {
50 "cell_type": "code",
51 "execution_count": 4,
52 "metadata": {},
53 "outputs": [],
54 "source": [
55 "text <- readFile \"../../data/advent22.txt\"\n",
56 "grid = lines text"
57 ]
58 },
59 {
60 "cell_type": "code",
61 "execution_count": 5,
62 "metadata": {},
63 "outputs": [],
64 "source": [
65 "sampleGrid = lines \"..#\\n#..\\n...\\n\""
66 ]
67 },
68 {
69 "cell_type": "code",
70 "execution_count": 7,
71 "metadata": {},
72 "outputs": [],
73 "source": [
74 "initialInfected g = M.fromList [((r, c), Infected) | r <- [0..(length g - 1)], c <- [0..((length . head) g - 1)],\n",
75 " g!!r!!c == '#']"
76 ]
77 },
78 {
79 "cell_type": "code",
80 "execution_count": 8,
81 "metadata": {},
82 "outputs": [
83 {
84 "data": {
85 "text/plain": [
86 "fromList [((0,2),Infected),((1,0),Infected)]"
87 ]
88 },
89 "metadata": {},
90 "output_type": "display_data"
91 }
92 ],
93 "source": [
94 "initialInfected sampleGrid"
95 ]
96 },
97 {
98 "cell_type": "code",
99 "execution_count": 9,
100 "metadata": {},
101 "outputs": [],
102 "source": [
103 "initialPosition g = (length g `div` 2, (length . head) g `div` 2)"
104 ]
105 },
106 {
107 "cell_type": "code",
108 "execution_count": 10,
109 "metadata": {},
110 "outputs": [
111 {
112 "data": {
113 "text/plain": [
114 "(1,1)"
115 ]
116 },
117 "metadata": {},
118 "output_type": "display_data"
119 }
120 ],
121 "source": [
122 "initialPosition sampleGrid"
123 ]
124 },
125 {
126 "cell_type": "code",
127 "execution_count": 11,
128 "metadata": {},
129 "outputs": [],
130 "source": [
131 "leftOf Up = Left\n",
132 "leftOf x = pred x\n",
133 "\n",
134 "rightOf Left = Up\n",
135 "rightOf x = succ x"
136 ]
137 },
138 {
139 "cell_type": "code",
140 "execution_count": 12,
141 "metadata": {},
142 "outputs": [
143 {
144 "data": {
145 "text/plain": [
146 "Down"
147 ]
148 },
149 "metadata": {},
150 "output_type": "display_data"
151 }
152 ],
153 "source": [
154 "leftOf Left"
155 ]
156 },
157 {
158 "cell_type": "code",
159 "execution_count": 13,
160 "metadata": {},
161 "outputs": [],
162 "source": [
163 "delta :: Direction -> Point\n",
164 "delta Up = (-1, 0)\n",
165 "delta Right = (0, 1)\n",
166 "delta Down = (1, 0)\n",
167 "delta Left = (0, -1)"
168 ]
169 },
170 {
171 "cell_type": "code",
172 "execution_count": 14,
173 "metadata": {},
174 "outputs": [],
175 "source": [
176 "(+:) (r, c) (dr, dc) = (r + dr, c + dc)"
177 ]
178 },
179 {
180 "cell_type": "code",
181 "execution_count": 15,
182 "metadata": {},
183 "outputs": [],
184 "source": [
185 "initialWorld grid = World \n",
186 " { infected = initialInfected grid\n",
187 " , position = initialPosition grid\n",
188 " , direction = Up\n",
189 " , infectionCount = 0\n",
190 " }"
191 ]
192 },
193 {
194 "cell_type": "code",
195 "execution_count": 16,
196 "metadata": {},
197 "outputs": [
198 {
199 "data": {
200 "text/plain": [
201 "World {infected = fromList [((0,2),Infected),((1,0),Infected)], position = (1,1), direction = Up, infectionCount = 0}"
202 ]
203 },
204 "metadata": {},
205 "output_type": "display_data"
206 }
207 ],
208 "source": [
209 "initialWorld sampleGrid"
210 ]
211 },
212 {
213 "cell_type": "code",
214 "execution_count": 17,
215 "metadata": {},
216 "outputs": [],
217 "source": [
218 "step world = World {infected = inf', position = pos', direction = dir', infectionCount = ic'}\n",
219 " where here = position world\n",
220 " stateHere = M.findWithDefault Clean here (infected world)\n",
221 " dir' = case stateHere of \n",
222 " Clean -> leftOf (direction world)\n",
223 " Weakened -> direction world\n",
224 " Infected -> rightOf (direction world)\n",
225 " Flagged -> rightOf (rightOf (direction world))\n",
226 " stateHere' = case stateHere of \n",
227 " Clean -> Weakened\n",
228 " Weakened -> Infected\n",
229 " Infected -> Flagged\n",
230 " Flagged -> Clean\n",
231 " inf' = M.insert here stateHere' (infected world)\n",
232 " \n",
233 " ic' = if stateHere' == Infected then infectionCount world + 1\n",
234 " else infectionCount world\n",
235 " pos' = here +: delta dir'"
236 ]
237 },
238 {
239 "cell_type": "code",
240 "execution_count": 19,
241 "metadata": {},
242 "outputs": [
243 {
244 "data": {
245 "text/plain": [
246 "World {infected = fromList [((0,2),Infected),((1,0),Flagged),((1,1),Weakened)], position = (0,0), direction = Up, infectionCount = 0}"
247 ]
248 },
249 "metadata": {},
250 "output_type": "display_data"
251 }
252 ],
253 "source": [
254 "step $ step $ initialWorld sampleGrid"
255 ]
256 },
257 {
258 "cell_type": "code",
259 "execution_count": 21,
260 "metadata": {},
261 "outputs": [],
262 "source": [
263 "progress n = (!! n) . iterate step "
264 ]
265 },
266 {
267 "cell_type": "code",
268 "execution_count": 25,
269 "metadata": {
270 "scrolled": true
271 },
272 "outputs": [
273 {
274 "data": {
275 "text/plain": [
276 "World {infected = fromList [((0,-1),Weakened),((0,0),Weakened),((0,2),Infected),((1,-1),Infected),((1,0),Clean),((1,1),Weakened)], position = (1,-2), direction = Left, infectionCount = 1}"
277 ]
278 },
279 "metadata": {},
280 "output_type": "display_data"
281 }
282 ],
283 "source": [
284 "progress 7 $ initialWorld sampleGrid"
285 ]
286 },
287 {
288 "cell_type": "code",
289 "execution_count": 26,
290 "metadata": {
291 "scrolled": true
292 },
293 "outputs": [
294 {
295 "data": {
296 "text/plain": [
297 "26"
298 ]
299 },
300 "metadata": {},
301 "output_type": "display_data"
302 }
303 ],
304 "source": [
305 "infectionCount $ progress 100 $ initialWorld sampleGrid"
306 ]
307 },
308 {
309 "cell_type": "code",
310 "execution_count": 27,
311 "metadata": {
312 "scrolled": true
313 },
314 "outputs": [
315 {
316 "data": {
317 "text/plain": [
318 "2511944"
319 ]
320 },
321 "metadata": {},
322 "output_type": "display_data"
323 }
324 ],
325 "source": [
326 "infectionCount $ progress 10000000 $ initialWorld sampleGrid"
327 ]
328 },
329 {
330 "cell_type": "code",
331 "execution_count": 28,
332 "metadata": {
333 "scrolled": true
334 },
335 "outputs": [
336 {
337 "data": {
338 "text/plain": [
339 "2512008"
340 ]
341 },
342 "metadata": {},
343 "output_type": "display_data"
344 }
345 ],
346 "source": [
347 "infectionCount $ progress 10000000 $ initialWorld grid"
348 ]
349 },
350 {
351 "cell_type": "code",
352 "execution_count": null,
353 "metadata": {},
354 "outputs": [],
355 "source": []
356 }
357 ],
358 "metadata": {
359 "kernelspec": {
360 "display_name": "Haskell",
361 "language": "haskell",
362 "name": "haskell"
363 },
364 "language_info": {
365 "codemirror_mode": "ihaskell",
366 "file_extension": ".hs",
367 "name": "haskell",
368 "version": "8.0.2"
369 }
370 },
371 "nbformat": 4,
372 "nbformat_minor": 2
373 }