Day 16
[advent-of-code-17.git] / src / advent16 / advent16.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 "source": [
21 "import Prelude hiding ((++))\n",
22 "import Data.Text (Text)\n",
23 "import qualified Data.Text as T\n",
24 "import qualified Data.Text.IO as TIO\n",
25 "\n",
26 "import Text.Megaparsec hiding (State)\n",
27 "import qualified Text.Megaparsec.Lexer as L\n",
28 "import Text.Megaparsec.Text (Parser)\n",
29 "import qualified Control.Applicative as CA\n",
30 "\n",
31 "import Control.Monad.State.Lazy\n",
32 "import Control.Monad.Reader\n",
33 "\n",
34 "import Data.Vector.Unboxed ((!), (++), (//))\n",
35 "import qualified Data.Vector.Unboxed as V\n",
36 "\n",
37 "import qualified Data.IntMap as M"
38 ]
39 },
40 {
41 "cell_type": "code",
42 "execution_count": 3,
43 "metadata": {},
44 "outputs": [],
45 "source": [
46 "data Step = Spin Int\n",
47 " | Exchange Int Int\n",
48 " | Partner Char Char\n",
49 " deriving (Show, Eq)\n",
50 "\n",
51 "type Dancers = V.Vector Char\n",
52 "\n",
53 "type DanceHistory = M.IntMap Dancers\n",
54 "\n",
55 "type HistoryRecorder = ReaderT [Step] (State DanceHistory) DanceHistory"
56 ]
57 },
58 {
59 "cell_type": "code",
60 "execution_count": 4,
61 "metadata": {},
62 "outputs": [
63 {
64 "data": {
65 "text/plain": [
66 "\"abcdefghijklmnop\""
67 ]
68 },
69 "metadata": {},
70 "output_type": "display_data"
71 }
72 ],
73 "source": [
74 "['a'..'p']"
75 ]
76 },
77 {
78 "cell_type": "code",
79 "execution_count": 5,
80 "metadata": {},
81 "outputs": [],
82 "source": [
83 "sc :: Parser ()\n",
84 "sc = L.space (skipSome spaceChar) CA.empty CA.empty\n",
85 "\n",
86 "lexeme = L.lexeme sc\n",
87 "\n",
88 "int :: Parser Int\n",
89 "int = read <$> some digitChar\n",
90 "\n",
91 "symb = L.symbol sc\n",
92 "comma = char ','\n",
93 "dancer = oneOf ['a'..'p']\n",
94 "\n",
95 "stepsP = stepP `sepBy` comma\n",
96 "\n",
97 "\n",
98 "stepP = (try spinP) <|> (try exchangeP) <|> partnerP\n",
99 "\n",
100 "spinP = Spin <$> (symb \"s\" *> int)\n",
101 "exchangeP = Exchange <$> (symb \"x\" *> int) <*> (symb \"/\" *> int)\n",
102 "partnerP = Partner <$> (symb \"p\" *> dancer) <*> (symb \"/\" *> dancer)\n",
103 "\n",
104 "successfulParse :: Text -> [Step]\n",
105 "successfulParse input = \n",
106 " case parse stepsP \"input\" input of\n",
107 " Left err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err\n",
108 " Right steps -> steps"
109 ]
110 },
111 {
112 "cell_type": "code",
113 "execution_count": 6,
114 "metadata": {},
115 "outputs": [
116 {
117 "data": {
118 "text/plain": [
119 "[Partner 'o' 'k',Exchange 4 0,Spin 12,Exchange 7 6]"
120 ]
121 },
122 "metadata": {},
123 "output_type": "display_data"
124 }
125 ],
126 "source": [
127 "successfulParse $ T.pack \"po/k,x4/0,s12,x7/6\""
128 ]
129 },
130 {
131 "cell_type": "code",
132 "execution_count": 7,
133 "metadata": {},
134 "outputs": [],
135 "source": [
136 "startingDancers :: Dancers\n",
137 "startingDancers = V.fromList ['a'..'p'] "
138 ]
139 },
140 {
141 "cell_type": "code",
142 "execution_count": 8,
143 "metadata": {},
144 "outputs": [
145 {
146 "data": {
147 "text/plain": [
148 "\"abcdefghijklmnop\""
149 ]
150 },
151 "metadata": {},
152 "output_type": "display_data"
153 }
154 ],
155 "source": [
156 "startingDancers"
157 ]
158 },
159 {
160 "cell_type": "code",
161 "execution_count": 9,
162 "metadata": {},
163 "outputs": [],
164 "source": [
165 "spin :: Int -> Dancers -> Dancers\n",
166 "spin n dancers = back ++ front\n",
167 " where (front, back) = V.splitAt n' dancers\n",
168 " n' = V.length dancers - n"
169 ]
170 },
171 {
172 "cell_type": "code",
173 "execution_count": 10,
174 "metadata": {},
175 "outputs": [
176 {
177 "data": {
178 "text/plain": [
179 "\"nopabcdefghijklm\""
180 ]
181 },
182 "metadata": {},
183 "output_type": "display_data"
184 }
185 ],
186 "source": [
187 "spin 3 startingDancers"
188 ]
189 },
190 {
191 "cell_type": "code",
192 "execution_count": 11,
193 "metadata": {},
194 "outputs": [],
195 "source": [
196 "exchange :: Int -> Int -> Dancers -> Dancers\n",
197 "exchange a b dancers = dancers // [(a, dancers!b), (b, dancers!a)]"
198 ]
199 },
200 {
201 "cell_type": "code",
202 "execution_count": 12,
203 "metadata": {},
204 "outputs": [
205 {
206 "data": {
207 "text/plain": [
208 "\"aocdefghijklmnbp\""
209 ]
210 },
211 "metadata": {},
212 "output_type": "display_data"
213 }
214 ],
215 "source": [
216 "exchange 1 14 startingDancers"
217 ]
218 },
219 {
220 "cell_type": "code",
221 "execution_count": 13,
222 "metadata": {},
223 "outputs": [],
224 "source": [
225 "partner :: Char -> Char -> Dancers -> Dancers\n",
226 "partner a b dancers = exchange a' b' dancers\n",
227 " where a' = V.head $ V.elemIndices a dancers\n",
228 " b' = V.head $ V.elemIndices b dancers"
229 ]
230 },
231 {
232 "cell_type": "code",
233 "execution_count": 14,
234 "metadata": {},
235 "outputs": [
236 {
237 "data": {
238 "text/plain": [
239 "\"abkdefghijclmnop\""
240 ]
241 },
242 "metadata": {},
243 "output_type": "display_data"
244 }
245 ],
246 "source": [
247 "partner 'c' 'k' startingDancers"
248 ]
249 },
250 {
251 "cell_type": "code",
252 "execution_count": 15,
253 "metadata": {},
254 "outputs": [],
255 "source": [
256 "runDance :: [Step] -> State Dancers Dancers\n",
257 "runDance [] = do dancers <- get\n",
258 " return dancers\n",
259 "runDance (step:steps) = \n",
260 " do dancers <- get\n",
261 " let dancers' = case step of\n",
262 " Spin n -> spin n dancers\n",
263 " Exchange a b -> exchange a b dancers\n",
264 " Partner a b -> partner a b dancers\n",
265 " put dancers'\n",
266 " runDance steps\n",
267 " "
268 ]
269 },
270 {
271 "cell_type": "code",
272 "execution_count": 16,
273 "metadata": {},
274 "outputs": [],
275 "source": [
276 "part1 :: [Step] -> Dancers\n",
277 "part1 instrs = evalState (runDance instrs) startingDancers"
278 ]
279 },
280 {
281 "cell_type": "code",
282 "execution_count": 17,
283 "metadata": {},
284 "outputs": [],
285 "source": [
286 "main :: IO ()\n",
287 "main = do \n",
288 " text <- TIO.readFile \"../../data/advent16.txt\"\n",
289 " let instrs = successfulParse text\n",
290 " print $ part1 instrs\n",
291 "-- print $ part2 instrs"
292 ]
293 },
294 {
295 "cell_type": "code",
296 "execution_count": 18,
297 "metadata": {},
298 "outputs": [
299 {
300 "data": {
301 "text/plain": [
302 "\"giadhmkpcnbfjelo\""
303 ]
304 },
305 "metadata": {},
306 "output_type": "display_data"
307 }
308 ],
309 "source": [
310 "main"
311 ]
312 },
313 {
314 "cell_type": "code",
315 "execution_count": 47,
316 "metadata": {},
317 "outputs": [],
318 "source": [
319 "emptyHistory :: DanceHistory\n",
320 "emptyHistory = M.singleton 0 startingDancers\n",
321 "-- emptyHistory = M.empty"
322 ]
323 },
324 {
325 "cell_type": "code",
326 "execution_count": 52,
327 "metadata": {},
328 "outputs": [],
329 "source": [
330 "recordDance :: Dancers -> HistoryRecorder\n",
331 "recordDance dancers = \n",
332 " do\n",
333 " history <- get\n",
334 " instrs <- ask\n",
335 " let dancers' = evalState (runDance instrs) dancers\n",
336 " if dancers' == startingDancers && (not (history == emptyHistory))\n",
337 " then return history\n",
338 " else do \n",
339 "-- instrs <- ask\n",
340 "-- let dancers' = evalState (runDance instrs) dancers\n",
341 " let history' = M.insert (M.size history) dancers' history\n",
342 " put history'\n",
343 " recordDance dancers'"
344 ]
345 },
346 {
347 "cell_type": "code",
348 "execution_count": 63,
349 "metadata": {},
350 "outputs": [],
351 "source": [
352 "part2 instrs = (M.!) history (1000000000 `rem` M.size history)\n",
353 " where history = evalState (runReaderT (recordDance startingDancers) instrs) emptyHistory"
354 ]
355 },
356 {
357 "cell_type": "code",
358 "execution_count": 64,
359 "metadata": {},
360 "outputs": [],
361 "source": [
362 "main :: IO ()\n",
363 "main = do \n",
364 " text <- TIO.readFile \"../../data/advent16.txt\"\n",
365 " let instrs = successfulParse text\n",
366 " print $ part1 instrs\n",
367 " print $ part2 instrs"
368 ]
369 },
370 {
371 "cell_type": "code",
372 "execution_count": 65,
373 "metadata": {},
374 "outputs": [
375 {
376 "data": {
377 "text/plain": [
378 "\"giadhmkpcnbfjelo\"\n",
379 "\"njfgilbkcoemhpad\""
380 ]
381 },
382 "metadata": {},
383 "output_type": "display_data"
384 }
385 ],
386 "source": [
387 "main"
388 ]
389 },
390 {
391 "cell_type": "code",
392 "execution_count": null,
393 "metadata": {},
394 "outputs": [],
395 "source": []
396 }
397 ],
398 "metadata": {
399 "kernelspec": {
400 "display_name": "Haskell",
401 "language": "haskell",
402 "name": "haskell"
403 },
404 "language_info": {
405 "codemirror_mode": "ihaskell",
406 "file_extension": ".hs",
407 "name": "haskell",
408 "version": "8.0.2"
409 }
410 },
411 "nbformat": 4,
412 "nbformat_minor": 2
413 }