Taking advantage of a neat trick for using $ rather than a lambda
[advent-of-code-17.git] / src / advent21 / advent21.hs
1 {-# LANGUAGE NegativeLiterals #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE BangPatterns #-}
6
7 import Data.Text (Text)
8 import qualified Data.Text as T
9 import qualified Data.Text.IO as TIO
10
11 import Text.Megaparsec hiding (State)
12 import qualified Text.Megaparsec.Lexer as L
13 import Text.Megaparsec.Text (Parser)
14 import qualified Control.Applicative as CA
15
16 import qualified Data.Map.Strict as M
17
18 import Data.List
19
20
21 type Grid = M.Map (Int, Int) Bool
22 type ExplodedGrid = M.Map (Int, Int) Grid
23
24 data Rule = Rule Grid Grid deriving (Eq, Show)
25
26 rulePre (Rule g _) = g
27 rulePost (Rule _ g) = g
28
29
30 initialGrid = case parse gridP "" ".#./..#/###" of
31 Left _ -> M.empty
32 Right g -> g
33
34
35 main :: IO ()
36 main = do
37 text <- TIO.readFile "data/advent21.txt"
38 let rules = readRules text
39 print $ countLit $ nthApplication rules 5
40 print $ countLit $ nthApplication rules 18
41
42
43 -- Read the rules, and expand them to all equivalent left hand sides
44 readRules :: Text -> [Rule]
45 readRules = expandRules . successfulParse
46
47
48 expandRules :: [Rule] -> [Rule]
49 expandRules = concatMap expandRule
50
51 expandRule :: Rule -> [Rule]
52 expandRule rule = [Rule l (rulePost rule) | l <- allArrangements (rulePre rule)]
53
54
55 reflectH :: Grid -> Grid
56 reflectH g = M.fromList [((r, c) , M.findWithDefault False (rm - r, c) g) | r <- [0..rm], c <- [0..cm] ]
57 where (rm, cm) = bounds g
58
59 reflectV :: Grid -> Grid
60 reflectV g = M.fromList [((r, c) , M.findWithDefault False (r, cm - c) g) | r <- [0..rm], c <- [0..cm] ]
61 where (rm, cm) = bounds g
62
63 -- awkward naming to avoid clashing with Prelude
64 transposeG :: Grid -> Grid
65 transposeG g = M.fromList [((c, r) , M.findWithDefault False (r, c) g) | r <- [0..rm], c <- [0..cm] ]
66 where (rm, cm) = bounds g
67
68
69 -- Find all the arrangments of a grid, including reflection and rotation.
70 allArrangements :: Grid -> [Grid]
71 -- allArrangements grid = map (\f -> f grid) [ id
72 allArrangements grid = map ($ grid) [ id
73 , reflectH
74 , reflectV
75 , transposeG
76 , reflectH . transposeG
77 , reflectV . transposeG
78 , reflectH . reflectV . transposeG
79 , reflectV . reflectH
80 ]
81
82
83
84 -- Count number of lit pixels
85 countLit :: Grid -> Int
86 countLit = M.size . M.filter id
87
88 -- apply the rules _n_ times
89 nthApplication :: [Rule] -> Int -> Grid
90 nthApplication rules n = (!! n) $ iterate (applyOnce rules) initialGrid
91
92 -- Apply one step of the expansion
93 applyOnce :: [Rule] -> Grid -> Grid
94 applyOnce rules g = contractExploded $ M.map (apply rules) $ explodeGrid g
95
96 -- find the appropriate rule and apply it to a grid
97 apply :: [Rule] -> Grid -> Grid
98 apply rules grid = rulePost thisRule
99 where ri = head $ findIndices (\r -> rulePre r == grid) rules
100 thisRule = rules!!ri
101
102
103 -- create the appropriate subgrids of a grid
104 explodeGrid :: Grid -> ExplodedGrid
105 explodeGrid g = if (rm + 1) `rem` 2 == 0
106 then explodeGrid' 2 g
107 else explodeGrid' 3 g
108 where (rm, _cm) = bounds g
109
110 explodeGrid' :: Int -> Grid -> ExplodedGrid
111 explodeGrid' n g = M.fromList [((bigR, bigC), subGrid n g bigR bigC) | bigR <- [0..bigRm], bigC <- [0..bigCm]]
112 where (rm, cm) = bounds g
113 bigRm = (rm + 1) `div` n - 1
114 bigCm = (cm + 1) `div` n - 1
115
116
117 subGrid :: Int -> Grid -> Int -> Int -> Grid
118 subGrid n g bigR bigC = M.fromList [ ((r, c),
119 M.findWithDefault False (r + rStep, c + cStep) g)
120 | r <- [0..(n - 1)], c <- [0..(n - 1)]
121 ]
122 where rStep = bigR * n
123 cStep = bigC * n
124
125 -- merge a set of subgrids into one
126 contractExploded :: ExplodedGrid -> Grid
127 contractExploded gs = foldl1 (>|<) $ map (foldl1 (>-<)) rows
128 where rows = explodedRows gs
129
130 -- find the rows of an exploded grid
131 explodedRows :: ExplodedGrid -> [ExplodedGrid]
132 explodedRows eg = [M.filterWithKey (\(r, _) _ -> r == row) eg | row <- [0..rowMax] ]
133 where (rowMax, _) = bounds eg
134
135 -- merge two grids horizontally
136 (>-<) :: Grid -> Grid -> Grid
137 (>-<) g1 g2 = M.union g1 g2'
138 where (_, cm) = bounds g1
139 g2' = M.mapKeys (\(r, c) -> (r, c + cm + 1)) g2
140
141 -- merge two grids vertically
142 (>|<) :: Grid -> Grid -> Grid
143 (>|<) g1 g2 = M.union g1 g2'
144 where (rm, _) = bounds g1
145 g2' = M.mapKeys (\(r, c) -> (r + rm + 1, c)) g2
146
147
148
149
150 bounds :: M.Map (Int, Int) a -> (Int, Int)
151 bounds grid = (maximum $ map fst $ M.keys grid, maximum $ map snd $ M.keys grid)
152
153
154 showGrid :: Grid -> String
155 showGrid g = unlines [[showGChar $ M.findWithDefault False (r, c) g |
156 c <- [0..cm] ] | r <- [0..rm] ]
157 where (rm, cm) = bounds g
158 showGChar True = '#'
159 showGChar False = '.'
160
161
162
163 -- really persuade Megaparsec not to include newlines in how it consume spaces.
164 onlySpace = (char ' ') <|> (char '\t')
165
166 sc :: Parser ()
167 sc = L.space (skipSome onlySpace) CA.empty CA.empty
168
169 symbol = L.symbol sc
170 rowSep = symbol "/"
171 ruleJoin = symbol "=>"
172
173 present = id True <$ symbol "#"
174 absent = id False <$ symbol "."
175
176 rulesP = ruleP `sepBy` space
177 ruleP = Rule <$> gridP <* ruleJoin <*> gridP
178
179 gridP = gridify <$> rowP `sepBy` rowSep
180 where gridify g = M.fromList $ concat
181 [map (\(c, v) -> ((r, c), v)) nr |
182 (r, nr) <- zip [0..]
183 [zip [0..] r | r <- g]]
184
185
186 rowP = some (present <|> absent)
187
188 successfulParse :: Text -> [Rule]
189 successfulParse input =
190 case parse rulesP "input" input of
191 Left _error -> []
192 Right instructions -> instructions