Done day 21
[advent-of-code-17.git] / src / advent21 / advent21.ipynb
diff --git a/src/advent21/advent21.ipynb b/src/advent21/advent21.ipynb
new file mode 100644 (file)
index 0000000..82fb65b
--- /dev/null
@@ -0,0 +1,1276 @@
+{
+ "cells": [
+  {
+   "cell_type": "code",
+   "execution_count": 1,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "{-# LANGUAGE NegativeLiterals #-}\n",
+    "{-# LANGUAGE FlexibleContexts #-}\n",
+    "{-# LANGUAGE OverloadedStrings #-}\n",
+    "{-# LANGUAGE TypeFamilies #-}\n",
+    "{-# LANGUAGE BangPatterns #-}"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 2,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "import Data.Text (Text)\n",
+    "import qualified Data.Text as T\n",
+    "import qualified Data.Text.IO as TIO\n",
+    "\n",
+    "import Text.Megaparsec hiding (State)\n",
+    "import qualified Text.Megaparsec.Lexer as L\n",
+    "import Text.Megaparsec.Text (Parser)\n",
+    "import qualified Control.Applicative as CA\n",
+    "-- import Data.Functor (void)\n",
+    "\n",
+    "import qualified Data.Map.Strict as M\n",
+    "import Data.Map.Strict ((!))\n",
+    "\n",
+    "-- import Data.Vector ((!), (//))\n",
+    "-- import qualified Data.Vector as V\n",
+    "\n",
+    "import Data.List \n",
+    "import qualified Data.Functor as F"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 3,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "type Grid = M.Map (Int, Int) Bool\n",
+    "-- type Grid = [[Char]]\n",
+    "-- type Grid = [[Bool]]\n",
+    "\n",
+    "type ExplodedGrid = M.Map (Int, Int) Grid\n",
+    "\n",
+    "data Rule = Rule Grid Grid deriving (Eq, Show)\n",
+    "\n",
+    "rulePre (Rule g _) = g\n",
+    "rulePost (Rule _ g) = g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 38,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "onlySpace = (char ' ') <|> (char '\\t')\n",
+    "\n",
+    "sc :: Parser ()\n",
+    "sc = L.space (skipSome onlySpace) CA.empty CA.empty"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 5,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "lexeme  = L.lexeme sc\n",
+    "\n",
+    "symbol = L.symbol sc\n",
+    "rowSep = symbol \"/\"\n",
+    "ruleJoin = symbol \"=>\"\n",
+    "\n",
+    "-- present :: Parser Bool\n",
+    "present = id True <$ symbol \"#\"\n",
+    "\n",
+    "-- absent :: Parser Bool\n",
+    "absent = id False <$ symbol \".\"\n",
+    "\n",
+    "rulesP = ruleP `sepBy` space\n",
+    "ruleP = Rule <$> gridP <*> (ruleJoin *> gridP)\n",
+    "\n",
+    "gridP = gridify <$> rowP `sepBy` rowSep\n",
+    "    where gridify g = M.fromList $ concat \n",
+    "                                    [map (\\(c, v) -> ((r, c), v)) nr | \n",
+    "                                             (r, nr) <- zip [0..] \n",
+    "                                                            [zip [0..] r | r <- g]]\n",
+    "\n",
+    "\n",
+    "rowP = some (present <|> absent)\n",
+    " \n",
+    "successfulParse :: Text -> [Rule]\n",
+    "successfulParse input = \n",
+    "        case parse rulesP \"input\" input of\n",
+    "                Left  _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err\n",
+    "                Right instructions  -> instructions"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 6,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)])"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "parseTest ruleP \"#./.. => .##/.##/#..\""
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 7,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "parseTest ruleP \"##./#.#/... => #.#./.#../.##./...#\""
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 8,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "testRule = head $ successfulParse  \"##./#.#/... => #.#./.#../.##./...#\""
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 9,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "testRule"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 10,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "parseTest rulesP \"#./.. => .##/.##/#..\\n##./#.#/... => #.#./.#../.##./...#\""
+   ]
+  },
+  {
+   "cell_type": "markdown",
+   "metadata": {},
+   "source": [
+    "Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) \n",
+    "     (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False),((2,3),True),((2,4),True),((2,5),False),((3,0),True),((3,1),False),((3,2),True),((4,0),False),((4,1),False),((4,2),False)]),\n",
+    "     \n",
+    "Rule (fromList []) \n",
+    "     (fromList [((0,0),True),((0,1),False),((0,2),True),((0,3),False),((1,0),False),((1,1),True),((1,2),False),((1,3),False),((2,0),False),((2,1),True),((2,2),True),((2,3),False),((3,0),False),((3,1),False),((3,2),False),((3,3),True)])"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 11,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "g = [[False,True,True],[False,True,True],[True,False,False]]"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 12,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[((0,0),False),((0,1),True),((0,2),True),((1,0),False),((1,1),True),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "concat [map (\\(c, v) -> ((r, c), v)) nr | (r, nr) <- zip [0..] [zip [0..] r | r <- g]]"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 53,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "bounds :: M.Map (Int, Int) a -> (Int, Int)\n",
+    "bounds grid = (maximum $ map fst $ M.keys grid, maximum $ map snd $ M.keys grid)"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 54,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "(3,3)"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "bounds (rulePost testRule)"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 15,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "showGrid g = unlines [[showChar $ M.findWithDefault False (r, c) g | \n",
+    "                c <- [0..cm] ] | r <- [0..rm] ]\n",
+    "    where (rm, cm) = bounds g\n",
+    "          showChar True = '#'\n",
+    "          showChar False = '.'"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 16,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "#.#.\n",
+       ".#..\n",
+       ".##.\n",
+       "...#"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ rulePost testRule"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 17,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "initialGrid = case parse gridP \"\" \".#./..#/###\" of \n",
+    "                Left _ -> M.empty \n",
+    "                Right g -> g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 18,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),False),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),True)]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 19,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       ".#.\n",
+       "..#\n",
+       "###"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 20,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "reflectH g = M.fromList [((r, c) , M.findWithDefault False (rm - r, c) g) | r <- [0..rm], c <- [0..cm] ]\n",
+    "    where (rm, cm) = bounds g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 21,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "###\n",
+       "..#\n",
+       ".#."
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ reflectH initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 22,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "reflectV g = M.fromList [((r, c) , M.findWithDefault False (r, cm - c) g) | r <- [0..rm], c <- [0..cm] ]\n",
+    "    where (rm, cm) = bounds g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 23,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       ".#.\n",
+       "#..\n",
+       "###"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ reflectV initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 24,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "transpose g = M.fromList [((c, r) , M.findWithDefault False (r, c) g) | r <- [0..rm], c <- [0..cm] ]\n",
+    "    where (rm, cm) = bounds g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 25,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "..#\n",
+       "#.#\n",
+       ".##"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ transpose initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 26,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "allArrangements grid = map (\\f -> f grid) [ id\n",
+    "                                          , reflectH\n",
+    "                                          , reflectV\n",
+    "                                          , transpose\n",
+    "                                          , reflectH . transpose\n",
+    "                                          , reflectV . transpose\n",
+    "                                          , reflectH . reflectV . transpose\n",
+    "                                          , reflectV . reflectH\n",
+    "                                          ]"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 27,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[\".#.\\n..#\\n###\\n\",\"###\\n..#\\n.#.\\n\",\".#.\\n#..\\n###\\n\",\"..#\\n#.#\\n.##\\n\",\".##\\n#.#\\n..#\\n\",\"#..\\n#.#\\n##.\\n\",\"##.\\n#.#\\n#..\\n\",\"###\\n#..\\n.#.\\n\"]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "map showGrid $ allArrangements initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 28,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "2"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "sampleRulesCompact = successfulParse \"../.# => ##./#../...\\n.#./..#/### => #..#/..../..../#..#\"\n",
+    "length sampleRulesCompact"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 29,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "expandRule rule = [Rule l (rulePost rule) | l <- allArrangements (rulePre rule)]\n",
+    "expandRules = concatMap expandRule"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 30,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[\"##.\\n#.#\\n...\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"...\\n#.#\\n##.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".##\\n#.#\\n...\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"##.\\n#..\\n.#.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".#.\\n#..\\n##.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".##\\n..#\\n.#.\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\".#.\\n..#\\n.##\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\",\"...\\n#.#\\n.##\\n=>#.#.\\n.#..\\n.##.\\n...#\\n\"]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "[showGrid (rulePre r) ++ \"=>\" ++ showGrid (rulePost r) | r <- expandRule testRule]"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 31,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "16"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "length $ expandRules sampleRulesCompact"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 32,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "readRules = expandRules . successfulParse"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 33,
+   "metadata": {
+    "scrolled": true
+   },
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[Rule (fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]) (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),False),((2,2),False)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),False),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),True),((1,0),False),((1,1),False),((1,2),True),((2,0),False),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),False),((2,0),True),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),False),((0,2),True),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),True),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),False),((0,1),True),((0,2),True),((1,0),True),((1,1),False),((1,2),True),((2,0),False),((2,1),False),((2,2),True)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),False),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),True),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),False),((1,0),True),((1,1),False),((1,2),True),((2,0),True),((2,1),False),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)]),Rule (fromList [((0,0),True),((0,1),True),((0,2),True),((1,0),True),((1,1),False),((1,2),False),((2,0),False),((2,1),True),((2,2),False)]) (fromList [((0,0),True),((0,1),False),((0,2),False),((0,3),True),((1,0),False),((1,1),False),((1,2),False),((1,3),False),((2,0),False),((2,1),False),((2,2),False),((2,3),False),((3,0),True),((3,1),False),((3,2),False),((3,3),True)])]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "sampleRules = readRules \"../.# => ##./#../...\\n.#./..#/### => #..#/..../..../#..#\"\n",
+    "sampleRules"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 125,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "text <- TIO.readFile \"../../data/advent21.txt\"\n",
+    "rules = readRules text"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 126,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "864"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "length rules"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 34,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "apply rules grid = rulePost thisRule\n",
+    "    where ri = head $ findIndices (\\r -> rulePre r == grid) rules\n",
+    "          thisRule = rules!!ri"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 37,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "#..#\n",
+       "....\n",
+       "....\n",
+       "#..#"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ apply sampleRules initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 49,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "subGrid :: Int -> Grid -> Int -> Int -> Grid\n",
+    "subGrid n g bigR bigC = M.fromList [ ((r, c), \n",
+    "                                      M.findWithDefault False (r + rStep, c + cStep) g) \n",
+    "                                   | r <- [0..(n - 1)], c <- [0..(n - 1)]\n",
+    "                                   ]\n",
+    "    where rStep = bigR * n\n",
+    "          cStep = bigC * n"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 50,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "explodeGrid' :: Int -> Grid -> ExplodedGrid\n",
+    "explodeGrid' n g = M.fromList [((bigR, bigC), subGrid n g bigR bigC) | bigR <- [0..bigRm], bigC <- [0..bigCm]]\n",
+    "    where (rm, cm) = bounds g\n",
+    "          bigRm = (rm + 1) `div` n - 1\n",
+    "          bigCm = (cm + 1) `div` n - 1"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 107,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "explodeGrid :: Grid -> ExplodedGrid\n",
+    "explodeGrid g = if (rm + 1) `rem` 2 == 0 \n",
+    "                then explodeGrid' 2 g\n",
+    "                else explodeGrid' 3 g\n",
+    "    where (rm, cm) = bounds g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 108,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "fromList [((0,0),\"#.\\n..\\n\"),((0,1),\".#\\n..\\n\"),((1,0),\"..\\n#.\\n\"),((1,1),\"..\\n.#\\n\")]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "testEg = explodeGrid $ apply sampleRules initialGrid\n",
+    "M.map showGrid testEg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 77,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "explodedRows eg = [M.filterWithKey (\\(r, _) _ -> r == row) eg | row <- [0..rowMax] ]\n",
+    "    where (rowMax, _) = bounds eg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 78,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "[fromList [((0,0),fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]),((0,1),fromList [((0,0),False),((0,1),True),((1,0),False),((1,1),False)])],fromList [((1,0),fromList [((0,0),False),((0,1),False),((1,0),True),((1,1),False)]),((1,1),fromList [((0,0),False),((0,1),False),((1,0),False),((1,1),True)])]]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "explodedRows testEg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 79,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "(>-<) g1 g2 = M.union g1 g2'\n",
+    "    where (_, cm) = bounds g1\n",
+    "          g2' = M.mapKeys (\\(r, c) -> (r, c + cm + 1)) g2"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 80,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "(>|<) g1 g2 = M.union g1 g2'\n",
+    "    where (rm, _) = bounds g1\n",
+    "          g2' = M.mapKeys (\\(r, c) -> (r + rm + 1, c)) g2"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 81,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "fromList [((0,0),True),((0,1),False),((1,0),False),((1,1),False)]"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "M.findWithDefault M.empty (0, 0) testEg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 82,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/html": [
+       "<style>/* Styles used for the Hoogle display in the pager */\n",
+       ".hoogle-doc {\n",
+       "display: block;\n",
+       "padding-bottom: 1.3em;\n",
+       "padding-left: 0.4em;\n",
+       "}\n",
+       ".hoogle-code {\n",
+       "display: block;\n",
+       "font-family: monospace;\n",
+       "white-space: pre;\n",
+       "}\n",
+       ".hoogle-text {\n",
+       "display: block;\n",
+       "}\n",
+       ".hoogle-name {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-head {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-sub {\n",
+       "display: block;\n",
+       "margin-left: 0.4em;\n",
+       "}\n",
+       ".hoogle-package {\n",
+       "font-weight: bold;\n",
+       "font-style: italic;\n",
+       "}\n",
+       ".hoogle-module {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-class {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".get-type {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "font-family: monospace;\n",
+       "display: block;\n",
+       "white-space: pre-wrap;\n",
+       "}\n",
+       ".show-type {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "font-family: monospace;\n",
+       "margin-left: 1em;\n",
+       "}\n",
+       ".mono {\n",
+       "font-family: monospace;\n",
+       "display: block;\n",
+       "}\n",
+       ".err-msg {\n",
+       "color: red;\n",
+       "font-style: italic;\n",
+       "font-family: monospace;\n",
+       "white-space: pre;\n",
+       "display: block;\n",
+       "}\n",
+       "#unshowable {\n",
+       "color: red;\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".err-msg.in.collapse {\n",
+       "padding-top: 0.7em;\n",
+       "}\n",
+       ".highlight-code {\n",
+       "white-space: pre;\n",
+       "font-family: monospace;\n",
+       "}\n",
+       ".suggestion-warning { \n",
+       "font-weight: bold;\n",
+       "color: rgb(200, 130, 0);\n",
+       "}\n",
+       ".suggestion-error { \n",
+       "font-weight: bold;\n",
+       "color: red;\n",
+       "}\n",
+       ".suggestion-name {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       "</style><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">M.findWithDefault M.empty (0, 1) testEg >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  M.findWithDefault M.empty (0, 0) testEg</div></div>"
+      ],
+      "text/plain": [
+       "Line 1: Redundant bracket\n",
+       "Found:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)\n",
+       "Why not:\n",
+       "M.findWithDefault M.empty (0, 1) testEg >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)Line 1: Redundant bracket\n",
+       "Found:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)\n",
+       "Why not:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >-<\n",
+       "  M.findWithDefault M.empty (0, 0) testEg"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    },
+    {
+     "data": {
+      "text/plain": [
+       "\".##.\\n....\\n\""
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "showGrid $ (M.findWithDefault M.empty (0, 1) testEg) >-< (M.findWithDefault M.empty (0, 0) testEg)"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 83,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/html": [
+       "<style>/* Styles used for the Hoogle display in the pager */\n",
+       ".hoogle-doc {\n",
+       "display: block;\n",
+       "padding-bottom: 1.3em;\n",
+       "padding-left: 0.4em;\n",
+       "}\n",
+       ".hoogle-code {\n",
+       "display: block;\n",
+       "font-family: monospace;\n",
+       "white-space: pre;\n",
+       "}\n",
+       ".hoogle-text {\n",
+       "display: block;\n",
+       "}\n",
+       ".hoogle-name {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-head {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-sub {\n",
+       "display: block;\n",
+       "margin-left: 0.4em;\n",
+       "}\n",
+       ".hoogle-package {\n",
+       "font-weight: bold;\n",
+       "font-style: italic;\n",
+       "}\n",
+       ".hoogle-module {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".hoogle-class {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".get-type {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "font-family: monospace;\n",
+       "display: block;\n",
+       "white-space: pre-wrap;\n",
+       "}\n",
+       ".show-type {\n",
+       "color: green;\n",
+       "font-weight: bold;\n",
+       "font-family: monospace;\n",
+       "margin-left: 1em;\n",
+       "}\n",
+       ".mono {\n",
+       "font-family: monospace;\n",
+       "display: block;\n",
+       "}\n",
+       ".err-msg {\n",
+       "color: red;\n",
+       "font-style: italic;\n",
+       "font-family: monospace;\n",
+       "white-space: pre;\n",
+       "display: block;\n",
+       "}\n",
+       "#unshowable {\n",
+       "color: red;\n",
+       "font-weight: bold;\n",
+       "}\n",
+       ".err-msg.in.collapse {\n",
+       "padding-top: 0.7em;\n",
+       "}\n",
+       ".highlight-code {\n",
+       "white-space: pre;\n",
+       "font-family: monospace;\n",
+       "}\n",
+       ".suggestion-warning { \n",
+       "font-weight: bold;\n",
+       "color: rgb(200, 130, 0);\n",
+       "}\n",
+       ".suggestion-error { \n",
+       "font-weight: bold;\n",
+       "color: red;\n",
+       "}\n",
+       ".suggestion-name {\n",
+       "font-weight: bold;\n",
+       "}\n",
+       "</style><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">M.findWithDefault M.empty (0, 1) testEg >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-name\" style=\"clear:both;\">Redundant bracket</div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Found:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)</div></div><div class=\"suggestion-row\" style=\"float: left;\"><div class=\"suggestion-warning\">Why Not:</div><div class=\"highlight-code\" id=\"haskell\">(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  M.findWithDefault M.empty (0, 0) testEg</div></div>"
+      ],
+      "text/plain": [
+       "Line 1: Redundant bracket\n",
+       "Found:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)\n",
+       "Why not:\n",
+       "M.findWithDefault M.empty (0, 1) testEg >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)Line 1: Redundant bracket\n",
+       "Found:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  (M.findWithDefault M.empty (0, 0) testEg)\n",
+       "Why not:\n",
+       "(M.findWithDefault M.empty (0, 1) testEg) >|<\n",
+       "  M.findWithDefault M.empty (0, 0) testEg"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    },
+    {
+     "data": {
+      "text/plain": [
+       "\".#\\n..\\n#.\\n..\\n\""
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "showGrid $ (M.findWithDefault M.empty (0, 1) testEg) >|< (M.findWithDefault M.empty (0, 0) testEg)"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 88,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "contractExploded :: ExplodedGrid -> Grid\n",
+    "contractExploded gs = foldl1 (>|<) $ map (foldl1 (>-<)) rows\n",
+    "    where rows = explodedRows gs"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 90,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "\"#..#\\n....\\n....\\n#..#\\n\""
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "showGrid $ contractExploded testEg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 94,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "##.##.\n",
+       "#..#..\n",
+       "......\n",
+       "##.##.\n",
+       "#..#..\n",
+       "......"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ contractExploded $ M.map (apply sampleRules) testEg"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 128,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "applyOnce rules g = contractExploded $ M.map (apply rules) $ explodeGrid g"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 135,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       ".#.#.#.#..##..#.##\n",
+       ".#.#...#..##....##\n",
+       "..####..##..####..\n",
+       "..#.#..##.###.#.#.\n",
+       "....#..##.###...#.\n",
+       "###..##..#..###..#\n",
+       "..#.##..#.##.##...\n",
+       "....##....##.##.##\n",
+       "####..####..#..##.\n",
+       "#.#.#.#.#.#.....#.\n",
+       "#...#.#...#..##.#.\n",
+       "###..####..###...#\n",
+       "..#.##..#.##..#.##\n",
+       "....##....##....##\n",
+       "####..####..####..\n",
+       "#.#.#.#.#.#.#.#.#.\n",
+       "#...#.#...#.#...#.\n",
+       "###..####..####..#"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ (!! 5) $ iterate (applyOnce rules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 131,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       ".#\n",
+       "##"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ (!(1, 2)) $ explodeGrid $ last $ take 3 $ iterate (applyOnce rules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 136,
+   "metadata": {},
+   "outputs": [],
+   "source": [
+    "countLit = M.size . M.filter id"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 137,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "5"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "countLit initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 142,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "##.##.\n",
+       "#..#..\n",
+       "......\n",
+       "##.##.\n",
+       "#..#..\n",
+       "......"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "putStrLn $ showGrid $ (!! 2) $ iterate (applyOnce sampleRules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 143,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "12"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "countLit $ (!! 2) $ iterate (applyOnce sampleRules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 144,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "158"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "countLit $ (!! 5) $ iterate (applyOnce rules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": 145,
+   "metadata": {},
+   "outputs": [
+    {
+     "data": {
+      "text/plain": [
+       "2301762"
+      ]
+     },
+     "metadata": {},
+     "output_type": "display_data"
+    }
+   ],
+   "source": [
+    "countLit $ (!! 18) $ iterate (applyOnce rules) initialGrid"
+   ]
+  },
+  {
+   "cell_type": "code",
+   "execution_count": null,
+   "metadata": {},
+   "outputs": [],
+   "source": []
+  }
+ ],
+ "metadata": {
+  "kernelspec": {
+   "display_name": "Haskell",
+   "language": "haskell",
+   "name": "haskell"
+  },
+  "language_info": {
+   "codemirror_mode": "ihaskell",
+   "file_extension": ".hs",
+   "name": "haskell",
+   "version": "8.0.2"
+  }
+ },
+ "nbformat": 4,
+ "nbformat_minor": 2
+}