Done Infi puzzle
[advent-of-code-17.git] / src / infi / infi.ipynb
1 {
2 "cells": [
3 {
4 "cell_type": "markdown",
5 "metadata": {},
6 "source": [
7 "# [Bonus problem from Infi](https://aoc.infi.nl/)"
8 ]
9 },
10 {
11 "cell_type": "code",
12 "execution_count": 1,
13 "metadata": {},
14 "outputs": [],
15 "source": [
16 "{-# LANGUAGE NegativeLiterals #-}\n",
17 "{-# LANGUAGE FlexibleContexts #-}\n",
18 "{-# LANGUAGE OverloadedStrings #-}\n",
19 "{-# LANGUAGE TypeFamilies #-}"
20 ]
21 },
22 {
23 "cell_type": "code",
24 "execution_count": 95,
25 "metadata": {},
26 "outputs": [],
27 "source": [
28 "-- import Prelude hiding ((++))\n",
29 "import Data.Text (Text)\n",
30 "import qualified Data.Text as T\n",
31 "import qualified Data.Text.IO as TIO\n",
32 "\n",
33 "import Text.Megaparsec hiding (State)\n",
34 "import qualified Text.Megaparsec.Lexer as L\n",
35 "import Text.Megaparsec.Text (Parser)\n",
36 "import qualified Control.Applicative as CA\n",
37 "\n",
38 "import Data.List (nub, sort)"
39 ]
40 },
41 {
42 "cell_type": "code",
43 "execution_count": 3,
44 "metadata": {},
45 "outputs": [],
46 "source": [
47 "type Position = (Integer, Integer)"
48 ]
49 },
50 {
51 "cell_type": "code",
52 "execution_count": 5,
53 "metadata": {},
54 "outputs": [],
55 "source": [
56 "sc :: Parser ()\n",
57 "sc = L.space (skipSome spaceChar) CA.empty CA.empty\n",
58 "\n",
59 "lexeme = L.lexeme sc\n",
60 "integer = lexeme L.integer\n",
61 "signedInteger = L.signed sc integer\n",
62 "symbol = L.symbol sc\n",
63 "comma = symbol \",\"\n",
64 "\n",
65 "pointP :: Parser Position\n",
66 "pointP = (,) <$> signedInteger <* comma <*> signedInteger\n",
67 "\n",
68 "startPosP = between (symbol \"[\") (symbol \"]\") pointP\n",
69 "stepP = between (symbol \"(\") (symbol \")\") pointP\n",
70 "\n",
71 "descriptionP = (,) <$> (some startPosP) <*> (some stepP)\n",
72 "-- descriptionP = (,) <$> (startPosP `sepBy` space) <*> (stepP `sepBy` space)"
73 ]
74 },
75 {
76 "cell_type": "code",
77 "execution_count": 6,
78 "metadata": {},
79 "outputs": [
80 {
81 "data": {
82 "text/plain": [
83 "[(1,2),(3,4)]"
84 ]
85 },
86 "metadata": {},
87 "output_type": "display_data"
88 }
89 ],
90 "source": [
91 "parseTest (some stepP) \"(1,2)(3,4)\""
92 ]
93 },
94 {
95 "cell_type": "code",
96 "execution_count": 7,
97 "metadata": {},
98 "outputs": [],
99 "source": [
100 "successfulParse :: Text -> ([Position], [Position])\n",
101 "successfulParse input = \n",
102 " case parse descriptionP \"input\" input of\n",
103 " Left _error -> ([], [])\n",
104 " Right description -> description"
105 ]
106 },
107 {
108 "cell_type": "code",
109 "execution_count": 8,
110 "metadata": {},
111 "outputs": [
112 {
113 "data": {
114 "text/plain": [
115 "([(0,0),(1,1)],[(1,0),(0,-1),(0,1),(-1,0),(-1,0),(0,1),(0,-1),(1,0)])"
116 ]
117 },
118 "metadata": {},
119 "output_type": "display_data"
120 }
121 ],
122 "source": [
123 "sampleT = T.pack \"[0,0][1,1](1,0)(0,-1)(0,1)(-1,0)(-1,0)(0,1)(0,-1)(1,0)\"\n",
124 "sample = successfulParse sampleT\n",
125 "sample"
126 ]
127 },
128 {
129 "cell_type": "code",
130 "execution_count": 9,
131 "metadata": {},
132 "outputs": [],
133 "source": [
134 "chunks :: Int -> [b] -> [[b]]\n",
135 "chunks n xs = (take n xs) : if null xs' then [] else chunks n xs'\n",
136 " where xs' = drop n xs"
137 ]
138 },
139 {
140 "cell_type": "code",
141 "execution_count": 10,
142 "metadata": {},
143 "outputs": [
144 {
145 "data": {
146 "text/plain": [
147 "[\"abc\",\"def\",\"ghi\",\"jkl\"]"
148 ]
149 },
150 "metadata": {},
151 "output_type": "display_data"
152 }
153 ],
154 "source": [
155 "chunks 3 \"abcdefghijkl\""
156 ]
157 },
158 {
159 "cell_type": "code",
160 "execution_count": 11,
161 "metadata": {},
162 "outputs": [
163 {
164 "data": {
165 "text/plain": [
166 "([(0,0),(1,1)],[[(1,0),(0,-1)],[(0,1),(-1,0)],[(-1,0),(0,1)],[(0,-1),(1,0)]])"
167 ]
168 },
169 "metadata": {},
170 "output_type": "display_data"
171 }
172 ],
173 "source": [
174 "(starts, unchunkedSteps) = successfulParse sampleT\n",
175 "steps = chunks (length starts) unchunkedSteps\n",
176 "(starts, steps)"
177 ]
178 },
179 {
180 "cell_type": "code",
181 "execution_count": 15,
182 "metadata": {},
183 "outputs": [],
184 "source": [
185 "(+:) (a, b) (c, d) = (a + c, b + d)"
186 ]
187 },
188 {
189 "cell_type": "code",
190 "execution_count": 23,
191 "metadata": {},
192 "outputs": [],
193 "source": [
194 "-- applySteps = zipWith (+:)"
195 ]
196 },
197 {
198 "cell_type": "code",
199 "execution_count": 22,
200 "metadata": {},
201 "outputs": [
202 {
203 "data": {
204 "text/plain": [
205 "[(1,0),(1,0)]"
206 ]
207 },
208 "metadata": {},
209 "output_type": "display_data"
210 }
211 ],
212 "source": [
213 "zipWith (+:) starts (head steps)"
214 ]
215 },
216 {
217 "cell_type": "code",
218 "execution_count": 24,
219 "metadata": {},
220 "outputs": [
221 {
222 "data": {
223 "text/plain": [
224 "[[(0,0),(1,1)],[(1,0),(1,0)],[(1,1),(0,0)],[(0,1),(0,1)],[(0,0),(1,1)]]"
225 ]
226 },
227 "metadata": {},
228 "output_type": "display_data"
229 }
230 ],
231 "source": [
232 "scanl applySteps starts steps"
233 ]
234 },
235 {
236 "cell_type": "code",
237 "execution_count": 32,
238 "metadata": {},
239 "outputs": [
240 {
241 "data": {
242 "text/plain": [
243 "2"
244 ]
245 },
246 "metadata": {},
247 "output_type": "display_data"
248 }
249 ],
250 "source": [
251 "length $ filter ((1 ==) . length . nub) $ scanl applySteps starts steps"
252 ]
253 },
254 {
255 "cell_type": "code",
256 "execution_count": 63,
257 "metadata": {},
258 "outputs": [],
259 "source": [
260 "visited = scanl (zipWith (+:))"
261 ]
262 },
263 {
264 "cell_type": "code",
265 "execution_count": 64,
266 "metadata": {},
267 "outputs": [],
268 "source": [
269 "intersections = filter ((== 1) . length . nub)"
270 ]
271 },
272 {
273 "cell_type": "code",
274 "execution_count": 65,
275 "metadata": {},
276 "outputs": [],
277 "source": [
278 "part1 = length . intersections"
279 ]
280 },
281 {
282 "cell_type": "code",
283 "execution_count": 78,
284 "metadata": {},
285 "outputs": [],
286 "source": [
287 "bounds ps = ( minimum $ map fst ps\n",
288 " , maximum $ map fst ps\n",
289 " , minimum $ map snd ps\n",
290 " , maximum $ map snd ps\n",
291 " )"
292 ]
293 },
294 {
295 "cell_type": "code",
296 "execution_count": 118,
297 "metadata": {},
298 "outputs": [],
299 "source": [
300 "showPoints (minr, maxr, minc, maxc) ps = unlines [ [ if (r, c) `elem` ps then '*' else ' ' | r <- [minr..maxr] ] | c <- [minc..maxc] ]"
301 ]
302 },
303 {
304 "cell_type": "code",
305 "execution_count": 127,
306 "metadata": {},
307 "outputs": [],
308 "source": [
309 "main :: IO ()\n",
310 "main = do \n",
311 " text <- TIO.readFile \"../../data/infi.txt\"\n",
312 " let (starts, unchunkedSteps) = successfulParse text\n",
313 " let steps = chunks (length starts) unchunkedSteps\n",
314 " let points = visited starts steps\n",
315 " print $ part1 points\n",
316 " let bds = bounds $ nub $ concat points\n",
317 " putStrLn $ showPoints bds $ nub $ concat $ intersections points"
318 ]
319 },
320 {
321 "cell_type": "code",
322 "execution_count": 128,
323 "metadata": {},
324 "outputs": [
325 {
326 "data": {
327 "text/plain": [
328 "535\n",
329 " ***** *** \n",
330 " ********** *****\n",
331 " *********** *****\n",
332 " ********** *****\n",
333 " ***** *** \n",
334 " ***** \n",
335 " **** \n",
336 " ** ******** **** \n",
337 "**** ************** *******************\n",
338 "**** **************** *******************\n",
339 "**** ****************** *******************\n",
340 "**** ***** ***** ***** *****\n",
341 "**** **** **** **** ****\n",
342 "**** **** **** **** ****\n",
343 "**** **** **** **** ****\n",
344 "**** **** **** **** ****\n",
345 "**** **** **** **** ****\n",
346 "**** **** **** **** ****\n",
347 "**** **** **** **** ****\n",
348 "**** **** **** **** ****\n",
349 "**** **** **** **** ****\n",
350 "**** **** **** **** ****\n",
351 "** ** ** ** ** \n",
352 " \n",
353 "***** ***** *** * *** **** *** *** \n",
354 " * * * * ** * * * * * * *\n",
355 " ** * *** * * *** **** *** *** \n",
356 " * * * * ***** * * * * * * * *\n",
357 "**** * *** * *** *** *** ***"
358 ]
359 },
360 "metadata": {},
361 "output_type": "display_data"
362 }
363 ],
364 "source": [
365 "main"
366 ]
367 },
368 {
369 "cell_type": "code",
370 "execution_count": 107,
371 "metadata": {},
372 "outputs": [
373 {
374 "data": {
375 "text/plain": [
376 "\" \\n \\n\""
377 ]
378 },
379 "metadata": {},
380 "output_type": "display_data"
381 }
382 ],
383 "source": [
384 "showPoints $ nub $ concat $ visited starts steps"
385 ]
386 },
387 {
388 "cell_type": "code",
389 "execution_count": 114,
390 "metadata": {},
391 "outputs": [
392 {
393 "data": {
394 "text/plain": [
395 "[(0,0),(1,1)]"
396 ]
397 },
398 "metadata": {},
399 "output_type": "display_data"
400 }
401 ],
402 "source": [
403 "starts"
404 ]
405 },
406 {
407 "cell_type": "code",
408 "execution_count": null,
409 "metadata": {},
410 "outputs": [],
411 "source": []
412 }
413 ],
414 "metadata": {
415 "kernelspec": {
416 "display_name": "Haskell",
417 "language": "haskell",
418 "name": "haskell"
419 },
420 "language_info": {
421 "codemirror_mode": "ihaskell",
422 "file_extension": ".hs",
423 "name": "haskell",
424 "version": "8.0.2"
425 }
426 },
427 "nbformat": 4,
428 "nbformat_minor": 2
429 }