Day 8
[advent-of-code-17.git] / src / advent08 / advent08.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": 2,
16 "metadata": {},
17 "outputs": [],
18 "source": [
19 "import Text.Parsec \n",
20 "import Text.ParserCombinators.Parsec.Number\n",
21 "import qualified Data.Map.Strict as M"
22 ]
23 },
24 {
25 "cell_type": "code",
26 "execution_count": 3,
27 "metadata": {},
28 "outputs": [],
29 "source": [
30 "data Instruction = Instruction \n",
31 " { register :: String\n",
32 " , direction :: String\n",
33 " , change :: Int\n",
34 " , conditionRegister :: String\n",
35 " , operation :: String\n",
36 " , comparator :: Int\n",
37 " } deriving (Show, Eq)"
38 ]
39 },
40 {
41 "cell_type": "code",
42 "execution_count": 4,
43 "metadata": {},
44 "outputs": [],
45 "source": [
46 "type Memory = M.Map String Int"
47 ]
48 },
49 {
50 "cell_type": "code",
51 "execution_count": 5,
52 "metadata": {},
53 "outputs": [],
54 "source": [
55 "onlySpaces = many (oneOf \" \\t\")\n",
56 "symP = (many lower) <* onlySpaces\n",
57 "operationP = (many1 (oneOf \"!<>=\")) <* onlySpaces"
58 ]
59 },
60 {
61 "cell_type": "code",
62 "execution_count": 6,
63 "metadata": {},
64 "outputs": [],
65 "source": [
66 "iFile = iLine `sepBy` newline \n",
67 "iLine = instructify <$> symP \n",
68 " <*> symP \n",
69 " <*> int \n",
70 " <*> ( onlySpaces *> string \"if\" *> onlySpaces *> symP )\n",
71 " <*> operationP \n",
72 " <*> int\n",
73 " where instructify r d c cr o p = Instruction { register = r\n",
74 " , direction = d\n",
75 " , change = c\n",
76 " , conditionRegister = cr\n",
77 " , operation = o\n",
78 " , comparator = p\n",
79 " }"
80 ]
81 },
82 {
83 "cell_type": "code",
84 "execution_count": 7,
85 "metadata": {},
86 "outputs": [],
87 "source": [
88 "parseFile :: String -> Either ParseError [Instruction]\n",
89 "parseFile input = parse iFile \"(unknown)\" input\n",
90 "\n",
91 "parseLine :: String -> Either ParseError Instruction\n",
92 "parseLine input = parse iLine \"(unknown)\" input\n",
93 "\n",
94 "successfulParse :: Either ParseError [a] -> [a]\n",
95 "successfulParse (Left _) = []\n",
96 "successfulParse (Right a) = a"
97 ]
98 },
99 {
100 "cell_type": "code",
101 "execution_count": 8,
102 "metadata": {},
103 "outputs": [
104 {
105 "data": {
106 "text/plain": [
107 "Right (Instruction {register = \"b\", direction = \"inc\", change = 5, conditionRegister = \"a\", operation = \">\", comparator = 1})"
108 ]
109 },
110 "metadata": {},
111 "output_type": "display_data"
112 }
113 ],
114 "source": [
115 "parseLine \"b inc 5 if a > 1\""
116 ]
117 },
118 {
119 "cell_type": "code",
120 "execution_count": 9,
121 "metadata": {},
122 "outputs": [],
123 "source": [
124 "sampleT = \"b inc 5 if a > 1\\na inc 1 if b < 5\\nc dec -10 if a >= 1\\nc inc -20 if c == 10\""
125 ]
126 },
127 {
128 "cell_type": "code",
129 "execution_count": 10,
130 "metadata": {},
131 "outputs": [
132 {
133 "data": {
134 "text/plain": [
135 "[Instruction {register = \"b\", direction = \"inc\", change = 5, conditionRegister = \"a\", operation = \">\", comparator = 1},Instruction {register = \"a\", direction = \"inc\", change = 1, conditionRegister = \"b\", operation = \"<\", comparator = 5},Instruction {register = \"c\", direction = \"dec\", change = -10, conditionRegister = \"a\", operation = \">=\", comparator = 1},Instruction {register = \"c\", direction = \"inc\", change = -20, conditionRegister = \"c\", operation = \"==\", comparator = 10}]"
136 ]
137 },
138 "metadata": {},
139 "output_type": "display_data"
140 }
141 ],
142 "source": [
143 "sample = successfulParse $ parseFile sampleT\n",
144 "sample"
145 ]
146 },
147 {
148 "cell_type": "code",
149 "execution_count": 11,
150 "metadata": {},
151 "outputs": [],
152 "source": [
153 "conditionEval :: Int -> String -> Int -> Bool\n",
154 "conditionEval reg op val\n",
155 " | op == \"==\" = reg == val\n",
156 " | op == \"<\" = reg < val\n",
157 " | op == \">\" = reg > val\n",
158 " | op == \"<=\" = reg <= val\n",
159 " | op == \">=\" = reg >= val\n",
160 " | op == \"!=\" = reg /= val"
161 ]
162 },
163 {
164 "cell_type": "code",
165 "execution_count": 12,
166 "metadata": {},
167 "outputs": [],
168 "source": [
169 "-- effectiveChange :: String -> Int -> Int\n",
170 "-- effectiveChange dir val\n",
171 "-- | dir == \"inc\" = val\n",
172 "-- | dir == \"dec\" = - val"
173 ]
174 },
175 {
176 "cell_type": "code",
177 "execution_count": 30,
178 "metadata": {},
179 "outputs": [],
180 "source": [
181 "effectiveChange :: String -> Int -> Int\n",
182 "effectiveChange \"inc\" val = val\n",
183 "effectiveChange \"dec\" val = -val"
184 ]
185 },
186 {
187 "cell_type": "code",
188 "execution_count": 32,
189 "metadata": {},
190 "outputs": [],
191 "source": [
192 "processInstruction memory instruction = memory'\n",
193 " where v = M.findWithDefault 0 (register instruction) memory\n",
194 " cv = M.findWithDefault 0 (conditionRegister instruction) memory\n",
195 " condition = conditionEval cv (operation instruction) (comparator instruction)\n",
196 " delta = effectiveChange (direction instruction) (change instruction)\n",
197 " memory' = if condition\n",
198 " then M.insert (register instruction) (v + delta) memory\n",
199 " else memory"
200 ]
201 },
202 {
203 "cell_type": "code",
204 "execution_count": 33,
205 "metadata": {},
206 "outputs": [],
207 "source": [
208 "processInstructions = foldl processInstruction M.empty "
209 ]
210 },
211 {
212 "cell_type": "code",
213 "execution_count": 34,
214 "metadata": {},
215 "outputs": [
216 {
217 "data": {
218 "text/plain": [
219 "fromList [(\"a\",1),(\"c\",-10)]"
220 ]
221 },
222 "metadata": {},
223 "output_type": "display_data"
224 }
225 ],
226 "source": [
227 "processInstructions sample"
228 ]
229 },
230 {
231 "cell_type": "code",
232 "execution_count": 47,
233 "metadata": {},
234 "outputs": [],
235 "source": [
236 "largestValue m \n",
237 " | M.null m = 0\n",
238 " | otherwise = maximum $ M.elems m"
239 ]
240 },
241 {
242 "cell_type": "code",
243 "execution_count": 48,
244 "metadata": {},
245 "outputs": [
246 {
247 "data": {
248 "text/plain": [
249 "1"
250 ]
251 },
252 "metadata": {},
253 "output_type": "display_data"
254 }
255 ],
256 "source": [
257 "largestValue $ processInstructions sample"
258 ]
259 },
260 {
261 "cell_type": "code",
262 "execution_count": 49,
263 "metadata": {},
264 "outputs": [],
265 "source": [
266 "part1 = largestValue . processInstructions"
267 ]
268 },
269 {
270 "cell_type": "code",
271 "execution_count": 50,
272 "metadata": {},
273 "outputs": [],
274 "source": [
275 "-- part1 = processInstructions"
276 ]
277 },
278 {
279 "cell_type": "code",
280 "execution_count": 51,
281 "metadata": {},
282 "outputs": [],
283 "source": [
284 "main :: IO ()\n",
285 "main = do \n",
286 " text <- readFile \"../../data/advent08.txt\"\n",
287 " let instrs = successfulParse $ parseFile text\n",
288 " print $ part1 instrs"
289 ]
290 },
291 {
292 "cell_type": "code",
293 "execution_count": 52,
294 "metadata": {},
295 "outputs": [
296 {
297 "data": {
298 "text/plain": [
299 "4647"
300 ]
301 },
302 "metadata": {},
303 "output_type": "display_data"
304 }
305 ],
306 "source": [
307 "main"
308 ]
309 },
310 {
311 "cell_type": "code",
312 "execution_count": 53,
313 "metadata": {},
314 "outputs": [],
315 "source": [
316 "processInstructionH (highest, memory) instruction = (highest', memory')\n",
317 " where memory' = processInstruction memory instruction\n",
318 " h = largestValue memory'\n",
319 " highest' = if h > highest then h else highest"
320 ]
321 },
322 {
323 "cell_type": "code",
324 "execution_count": 54,
325 "metadata": {},
326 "outputs": [],
327 "source": [
328 "processInstructionsH = foldl processInstructionH (0, M.empty)"
329 ]
330 },
331 {
332 "cell_type": "code",
333 "execution_count": 55,
334 "metadata": {},
335 "outputs": [
336 {
337 "data": {
338 "text/plain": [
339 "(10,fromList [(\"a\",1),(\"c\",-10)])"
340 ]
341 },
342 "metadata": {},
343 "output_type": "display_data"
344 }
345 ],
346 "source": [
347 "processInstructionsH sample"
348 ]
349 },
350 {
351 "cell_type": "code",
352 "execution_count": 56,
353 "metadata": {},
354 "outputs": [],
355 "source": [
356 "part2 = fst . processInstructionsH"
357 ]
358 },
359 {
360 "cell_type": "code",
361 "execution_count": 57,
362 "metadata": {},
363 "outputs": [],
364 "source": [
365 "main :: IO ()\n",
366 "main = do \n",
367 " text <- readFile \"../../data/advent08.txt\"\n",
368 " let instrs = successfulParse $ parseFile text\n",
369 " print $ part1 instrs\n",
370 " print $ part2 instrs"
371 ]
372 },
373 {
374 "cell_type": "code",
375 "execution_count": 58,
376 "metadata": {},
377 "outputs": [
378 {
379 "data": {
380 "text/plain": [
381 "4647\n",
382 "5590"
383 ]
384 },
385 "metadata": {},
386 "output_type": "display_data"
387 }
388 ],
389 "source": [
390 "main"
391 ]
392 },
393 {
394 "cell_type": "code",
395 "execution_count": null,
396 "metadata": {},
397 "outputs": [],
398 "source": []
399 }
400 ],
401 "metadata": {
402 "kernelspec": {
403 "display_name": "Haskell",
404 "language": "haskell",
405 "name": "haskell"
406 },
407 "language_info": {
408 "codemirror_mode": "ihaskell",
409 "file_extension": ".hs",
410 "name": "haskell",
411 "version": "8.0.2"
412 }
413 },
414 "nbformat": 4,
415 "nbformat_minor": 2
416 }