--- /dev/null
+-- Writeup at https://work.njae.me.uk/2021/12/09/advent-of-code-2021-day-9/
+
+import Data.Array.IArray
+import Data.Char
+import Linear (V2(..), (^+^))
+
+type Coord = V2 Int
+type Grid = Array Coord Octopus
+
+data Octopus = Octopus Int Bool
+ deriving (Ord, Eq, Show)
+
+main :: IO ()
+main =
+ do text <- readFile "data/advent11.txt"
+ let grid = mkGrid text
+ print $ part1 grid
+ print $ part2 grid
+
+mkGrid :: String -> Grid
+mkGrid text = listArray ((V2 0 0), (V2 r c)) $ map mkOct $ concat rows
+ where rows = lines text
+ r = length rows - 1
+ c = (length $ head rows) - 1
+ mkOct e = Octopus (digitToInt e) False
+
+part1 grid = snd $ (simulate grid) !! 100
+
+part2 grid = length $ takeWhile notSyncronised $ simulate grid
+ where notSyncronised (g, _) = not $ simultaneous g
+
+simulate :: Grid -> [(Grid, Int)]
+simulate grid = iterate step (grid, 0)
+
+step :: (Grid, Int) -> (Grid, Int)
+step (grid0, flashCount0) = (grid3, flashCount0 + numFlashers)
+ where grid1 = increment grid0
+ triggers = findFlashers grid1
+ grid2 = flash grid1 triggers
+ flashers = findFlashers grid2
+ numFlashers = length flashers
+ grid3 = resetFlashers grid2 flashers
+
+
+simultaneous grid = all zeroOct $ elems grid
+ where zeroOct (Octopus 0 _) = True
+ zeroOct _ = False
+
+increment :: Grid -> Grid
+increment = amap incrementOne
+
+incrementSome grid locations = grid // (zip locations incrementedOcts)
+ where incrementedOcts = map (incrementOne . (grid !)) locations
+
+incrementOne (Octopus energy flashed) = Octopus (energy + 1) flashed
+
+
+findFlashers :: Grid -> [Coord]
+findFlashers = map fst . filter (overpowered . snd) . assocs
+ where overpowered (Octopus energy _) = energy > 9
+
+
+flash grid [] = grid
+flash grid (here:agenda)
+ | flashed == True = flash grid agenda
+ | energy <= 9 = flash grid agenda
+ | otherwise = flash grid'' agenda'
+ -- set this as flashed
+ -- increment neighbours
+ -- add negighbours to agenda
+ where Octopus energy flashed = grid ! here
+ nbrs = neighbours grid here
+ octopus' = Octopus (energy + 1) True
+ agenda' = nbrs ++ agenda
+ grid' = grid // [(here, octopus')]
+ grid'' = incrementSome grid' nbrs
+
+resetFlashers :: Grid -> [Coord] -> Grid
+resetFlashers grid locations = grid // (zip locations resetOcts)
+ where resetOcts = repeat (Octopus 0 False)
+
+
+neighbours :: Grid -> Coord -> [Coord]
+neighbours grid here = filter (inRange (bounds grid))
+ [ here ^+^ (V2 r c)
+ | r <- [-1, 0, 1]
+ , c <- [-1, 0, 1]
+ , (r, c) /= (0, 0)
+ ]