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