This commit is contained in:
orion kindel
2025-12-04 15:02:22 -06:00
parent b3ea0cc44e
commit 2ede2f5095
4 changed files with 319 additions and 3 deletions

198
src/Day4.purs Normal file
View File

@@ -0,0 +1,198 @@
module Day4 where
import Prelude
import Control.Monad.Error.Class (liftEither)
import Control.Monad.Rec.Class (Step(..), tailRec)
import Data.Bifunctor (lmap)
import Data.BigInt as BigInt
import Data.Foldable (foldl, or, sum)
import Data.FoldableWithIndex (foldlWithIndex)
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Day4.Grid as Grid
import Day4.Paper as Paper
import Effect (Effect)
import Effect.Console as Console
import Effect.Exception (error)
main :: Effect Unit
main = do
Console.log "=== Day 4 ==="
run exampleInput <#> ("[exampl] " <> _) >>= Console.log
run fullInput <#> ("[actual] " <> _) >>= Console.log
Console.log ""
run :: String -> Effect String
run input = do
paper <- liftEither $ lmap (error <<< show) $ Paper.parsePaper input
let
part1 = foldl (\n a -> if a then n + 1 else n) 0 $ Paper.canRemove paper
part2 =
let
f (removed /\ paper') =
let
toRemove = Paper.canRemove paper'
toRemoveCt = foldl (\n a -> if a then n + 1 else n) 0 toRemove
in
if toRemoveCt == 0 then
Done removed
else
Loop $ (removed + toRemoveCt) /\ foldlWithIndex (\(x /\ y) grid a -> if a then Grid.update (x /\ y) Nothing grid else grid) paper' toRemove
in
tailRec f (0 /\ paper)
pure $ "part1(" <> show part1 <> ") part2(" <> show part2 <> ")"
exampleInput :: String
exampleInput = """..@@.@@@@.
@@@.@.@.@@
@@@@@.@.@@
@.@@@@..@.
@@.@@@@.@@
.@@@@@@@.@
.@.@.@.@@@
@.@@@.@@@@
.@@@@@@@@.
@.@.@@@.@."""
fullInput :: String
fullInput = """@@@..@@.@@.@.@@@.@@@...@@@@@@.@@@@@@.@@@@.@..@@@.@@.@@@..@@@@.@@..@@@@@..@@@.@@@.@.@...@@@..@.@@@.@.@..@@@.@@.@.@.@@..@@@@@...@.@@@.@@@@.@@.
@@.@.@@@@@@@@.@@@.@@@@.@@@@@.@@@@@@@@..@..@@@@...@@@@@.@.@.@@@@.@@@@@@@@@.@..@.@.@@.@@@.@.@.@@@@@@@@@@@@.@@.@@.@.@@@.@@@..@.@@@@@.@..@.@@@.@
@@@@@@@@.@.@@@..@@@.@@.@@@@.@@..@.@.@@@@@@@@@@@@..@..@.@@@@@@.@.@@@@@@@@@.@.@@@@@.@@.@...@.@@@@.@@@@@@@.@@@@@@@@@..@.@.@@@@..@.@@@.@..@.@.@@
@...@@@@.@@.@..@...@.@@@@@@@.@.@.@...@@@@@.@.@@@.....@.@@.@.@@.@.@@@.@.@.@@@@@@@..@@..@.@@@@.@@@@.@@...@@@@@...@@.@@@@@@@@..@.@.@@.@@@@@@@@.
@@.@....@@.@@@.@....@@@@@@@@@@.@..@@@@.@@@@.....@..@@.@@@@@@@@@.@.@.@@@@@.@.@.@..@..@@@.@@.@@@@@@.@@.@@@.@.@..@.@.@@@.@.@.@@@@@.@@.@.@@@....
@.@.@@@@@@@@@@@@@....@.@.@@.@@.@@@@..@.@@@@@@@@@@@.@@@@@@@@@@@@@.@.@@@@..@.@@@@..@@@@..@@@@...@@@@@@.@.@@.@@@@..@.@@.@.@.@...@@....@@@@@@@@@
..@@@@.@@@.@.@@@@@@@@@@@.@@@@@@.@.@@@@@@@..@.@@@@@@@.@@@@@.@@@@@.@.@@@@@.@.@@@@@@@@.@@@@@@.@@..@@@.@@..@..@@.@.@.@@@.@@..@@@@@@.@..@.@@@.@..
@.@...@@@.@@...@.@@@.@@..@@@@@@..@@@@..@@.@@.@@@@@...@.@@@@.@@.@@@@@.@.@....@.@@.@@.@@@@@.@..@@@@@@@..@@.@.@@@@.@@.@@.@@@@@@@..@@@@.@@@..@@.
@@.@.@@@@@.@@@@.@.@@@@@@@.@.@@@@@@@@.@.@@@@@@@...@.@.@@@.@@@@@@@.@.@@@@..@@@.@...@@@@@.@@@..@@@@.@@@@@@.@@@.@..@.@@.@@@@@.@...@@@@....@@@.@.
@@@.@@@.@@..@@.@@@@@@.@@.@.@@@@@..@@@..@@@@@@@@@@@..@@@@.@@@...@@@@@@.@@.@.@.@.@@@..@.@@@.@@@.@@.......@.@@@..@@@@.@@@@@..@.@@@.@@@@@@.@@@@@
@...@@.@@@@@@..@@@@@@@@@@@...@.@.@.@@@@@@.@.@@@@..@..@@@..@@@@@@.@@..@...@.@@@@@@@@@@@@..@.@@.@.@@.@@@..@..@..@.@.@@@@@@@@@@.@@@.@@@.@@@@@@@
@.@@..@@.@@@.@@@@@@@@@....@@.@.@@@@.@@..@@.@@.@@@.@@@@.@@@@@..@.@.@@@..@.@@@.@@@@@.@@@..@@..@.@@@@@@..@.@@@.@@@..@@.@.@.@@..@@@@@@@.@@@@.@.@
@@..@.@@@.@@@...@@@@@@@@@..@@@@@@@.@@.@@.@.@@@@@...@@..@@@@.@.@@.@@@@.@.@@@.@.@.@@.@@@@.@..@.@@@@..@.@@@.@@@..@@@@.@@@@.@@@@@@@@...@@@@@@@@@
.@@@@...@@@@@.@.@.@@@@.@.@@.@@@@@@@@@@@@@@@@@.@@@.@@@@@@.@@@.@@.@@@@@@@@.@.@@.@@@@.@@@@@@@.@@@.@@@@@@@@@@..@@@.@.@.@@.@@@@@@@@@@.@@...@@@@.@
@@@@@@.@@@@@..@...@@@.@@.@@.@...@.@@..@.@@.@@@.@@@@@@.@.@@...@@@..@.@.@@@@@..@@@.@@.@.@@@@.@.@@@..@..@..@@.@@.@@@.@..@.@@..@@.@..@@@@.@@@.@.
@@@@@@@@..@@@@@@@.@@@.@@@@@@@..@@@@..@@@@@@@@@@@@..@.@@.@@@..@@@@@@.@.@@@@@.@@@...@...@@@@@.@@@..@.@@@.@@@@@@.@.@@.@.@@@..@.@.@..@.@@@...@.@
@@@@..@@...@@..@@@@@...@@.@@@@@.@@@@@.@@@@@.@@.@@@.@.@.@.@@@@.@@@@@@..@@@.@@..@@..@@.@.@.@.@@...@.@@@@@@...@..@@...@@@.@.@@@..@.@@@.@..@@.@@
@...@.@@@..@@@.@..@@.@@.@.@@@@@@@@@@@@.@.....@.@..@@.@.....@...@@@..@....@@@@@.@@@@..@.@@@.@..@@@@@@@..@.@@.@@@.@@.@@@@@@.@..@@..@@@@@@@@@@@
...@.@@.@.@@.@@@@@.@@@@@@..@@@@..@.@.@@@.@@.@@@@.@@@..@.@@@@.@@.@.@@.@@.@.@@@@@@..@@.@@@@@@@.@@.@@@.@.@@...@.@@.@@...@.@@@@.@@@@@@...@@.@@@@
@@..@@@...@.@@.......@@...@@@.@.@@.@.@@@@@.@@.@@@@@..@@@.@@@@@@@@.@@@@@@@....@.@@.@@@@.@@@.@@@@@@@@@@@@@@@.@.@@@..@..@@@@.@@.@..@@@.@@@.@.@.
..@..@@@.@.@@.@..@@@@@@..@.@@...@@.@@.@.@@.@@@@@@@..@@..@..@@@@@..@.@..@@..@@@@@@@@.@@@.@@@@@@@@.@@@@@@@.@@@@.@.@@@@@.@.@@@@@..@@@@.@.@@@@@@
.@@@@@@@@@.@.@.@..@@@.@@.@@@.@@@@@@@...@@@.@@@@@.@.@@@@@@..@@.@..@.@@@@.@@@@@@.@@....@@.@..@..@@@@@@..@@@.@@@..@@.@.@@@@.@@...@@.@@@.@@@@.@@
@@@.@.@@@@..@....@@.@.....@@@.@.@@.@@@@@.@.@.@@.@@@.@@@..@@@@@@..@@@@..@.@.@@@.@@@@@@@@@.@@@@@.@@@@@..@@@@@@@@@@..@.@.@.@@@@@@@.@@.@@.@.@.@@
@@@@@@.@@@@.@@@@@@@@@...@@@@..@@@@@.@@@.@@..@@@.@@@.@@.@@@@..@.@@@@@@.@@.@@..@.@..@...@@..@@@.@...@@.@@.@@@.@.@.@@@@@@@@....@@.@.@@@@@@@@@.@
@.@@@...@.@@@@.@..@....@@@@.@@@@.@@@@..@@@...@.@.@@@@@..@@..@..@.@@..@.@@@@@.@.@@...@@@@.@@@@@@@@@@@@@.@@@@.@.@@@@.@@@@.@@..@@@..@@@@.@@@.@.
....@@@.@@@@@@.@@.@.@@....@@.@...@..@@@@@.@@@.@@.@@@@..@@@@@.@@@.@@@.@.@.@..@@@@.@@@@@@.@...@..@.@@@@..@.@@@@.@@.@.@@..@....@.@@@@...@@@...@
.@@@@@@..@...@@@@.@@@.@.@@@..@.@@@@.@@@.@@@..@....@@@@@@.@@......@.@@...@@@@@@.@..@@@@@.@@@@.@..@@@.@@.@.@@@@.@@.@@@@@@@@.@...@@@@@@@.@@...@
..@@@@@.@@@@@@@@@.@@@@@...@.@@@@.@@@@@.....@@@@..@@@@.@@@@@@@@@.@.@....@@..@@@@@@..@@..@@@.@@@@.@@@..@..@@.@.@.@.@....@@@@.@@@.@@.@.@..@@..@
@@@@@@@@@@..@@@.@....@.@@.@@..@@@.@@.@@@@@.@..@@@..@@@.@@....@@@@@.@@..@@.@.@.@@@.@..@@@@..@@@@@.@@@@@@@@@@@@.@@.@@.@@@@.@@@.@@@@@@..@....@@
@@@@@@..@.@@@@@@@@..@@.@.@.@@@@.@@@.@@@@@@.@@@@@@@@@@@.@@@@@.@.@@.@@@@..@.@@@.@@..@..@@.@.@@....@....@.@@.@@@@@@@@.@.@.@.@.@@@...@.@@..@@@.@
.@@@@@@.@.@..@@@@@.@@@@@@@@@.@..@.@.@@@.@.@@@@....@@@@@@@..@.@..@@@.@@..@@.@.@@@@@@@@.@@@@.@.@@@...@.@@@@@@@@.@.@@@.@.@@@.@.@@@..@@@@@.@@@.@
@.@@.@.@@..@.@@@...@@@@@.@@@@@@@@@@@@.@@@@@@@.@@.@.@@@@@@.@@@...@@..@@.@@@@@@.@..@@@@@.....@@.@@@.@@..@@@.@.@..@@@.@@@@@@@@.@.@...@.@.@@@@@@
@.@@@@...@..@@.@.@@.@.@@....@@@@@@@@@@@@@..@.@@@@.@@@@@@@.@@@@@.@...@@.@@@..@@@@@@@.@..@@@@@.@@....@@@@@@@@@.@@.@@@@@..@.@@.@@@@..@....@@@@.
@@@@.@@@.@.@..@@@@@@.@@.....@@...@@@@@@...@.@@..@@@@..@.@@.@@.@.@@..@@.@@@@@@@.@@@.@@@.....@..@.@.@@@@.@.@@.@@@.@...@@@@@@@@@@@.@@.@@.@@@@@@
@.@@@@@...@@@@@@...@@@.@@@.@..@@@@...@@@@@.@@@@@.@..@...@.@@@.@.@@@.@@@@..@@@..@@@@.@...@.@@@.@@@..@@@..@@.@@@@..@@@@@@@.@.@@@@....@..@..@@@
@@@.@.@@@@@.@.@...@@@.@@.@.....@@.@@.@@@@@..@@@.@@@.....@@@@@@@@@@@@..@@@@@@..@@.@@@@@.@@@@..@.@@@.@@@@@@...@@.@@@@.@@..@..@.@.@@.@@@@.@.@@.
@@@.@.@@@@.@..@@..@.@.@@@.@.@@@@.@.@...@@.....@@@@@@@.@.@.@.@@.@@@@@@@@@@.@@.@@.@@@@@@@@@@@.@@@.@@.@@@@@@@@.@@@@@@.@.@@@@.@.@..@@@.@@@..@..@
@@.@.@.@@@@.@@@.@@@@@@@@..@@@@@.@@@@@@@..@@@.....@@@.@@.@.@.@..@.@@.@@@@.@.@@@.@@..@@.@.@@.@@.@..@@@.@@@@....@.@@@@@.@@@@@@@@@@.@.@..@@@@@@.
...@@@.@@@@.@@@@@@..@@@@..@.@..@.@.@..@.@.@@@.@@@@..@@@.@.@@@@.@.@@.@@@@@.@@@@@.@.@.@.@@@@@@.@@@.@@.@@@..@@@@@@@@...@.@@@@@.@.@@@@@..@@@@..@
.@..@...@.@@..@@.@.@@.@.@..@.@@@@.@.@@@.@@@@..@..@.@.@.@@@.@.@.@.@.@@@@@@.@.@@.@@@.@@@@@@@....@@@@@.@@@@@..@@@@.@@@.@@@.@.@...@@..@.@@@@@..@
@@@@.@@...@.@@@@..@@@@@.@@@..@.@.@@@..@@@@@@.@@@@@.@@@@.@..@@@@..@@@@@@@@@@.@@@.@.@@@.@@.@.@@@@@.@.@...@@.@...@@@.@@...@@@@@.@@@@@@.@.@.@.@@
.@.@@@.@@@@@@@.@@@.@@@@@.@@@.@@.@....@@@..@@@@@.@@..@.@@@@@@@...@@@@@.@....@.@..@@.@@@@...@.@.@..@.@@@@@@.@.@@@.@..@.@@...@@@@.@.@..@@..@@@@
@@.@@.@@@@@@.@.@@@.@@@@@@@..@@@@@@@.@@.@@..@@@.@@@@@@@@@@@..@@@@.@@@@@.@@@@@.@@.@...@@@@@.@@@@.@@@@@...@@@@@...@@@@.@@@@.@@@@@@@@@@@.@@@@@@@
.@.@@.@.@@@.@@...@.....@@@@.@@@.@@.@@@@@@.@.@.@..@@@@@..@.@@@@..@@.@@@@@@.@@@.@.@.@@@.@.@@@@@.@@@@@.@@@@.@@..@@@.@.@.@@@@..@.@..@@@@..@.@@@.
.@@@@@@@@...@@.@@.@@@.@....@@@@@@@@@@..@@@@@.@@.@@@@@@@@.@@.@@@....@@@@@.@@@.@..@.@@@..@..@@@@@.@.@.@@@@.@@@.@@@@.@@@@@@@@@@@.@.@...@@.@.@@@
@@@@.@@@@@@@.@..@@..@@@@.@.@.@.@...@@@@@.@@@@..@.@..@@@.@@@@.@@...@@@..@...@.@@.@@.@@@@.@.@@.@@@@@..@@@@..@@..@@.@..@@@@.@.@@@.@@@.@@@@@.@@@
@..@@@@@.@@@..@@@@.@.@@@@.@.@..@@@@@@@@.@..@.@@.@@@.@@.@@.@@@.@@@@@@.@@..@@@@@@..@@.@..@@@@.@.@.@@@@@@...@@.@.@.@@@@@.@@@..@@.@.@.@@@..@@.@@
@@@@..@@@.@@@@@.@..@.@..@@@.....@@@@.@@.@..@.@@..@.@@@@@..@@@@@.@.@@..@@.@@@@.@@.@....@.@@@.@@@@.@@@@.@@@@.@@@@.@.@@@@@.@@@@@.@@@@@@@@.@.@@.
.@@@@@@@@.@@@....@@@@.@@@@@@@@@@@@@@.@@.@.@@@.@@@@@@@@@..@..@@@@@@@@@@@.@.@.@@@@@.@@@@...@@@@...@@@@@@@@@@.@.@@@@@@@@@..@@@@@..@.@@@@@@@@.@@
@@@@.@.@@.@...@.@@@@.@@@@@@..@@.@..@.@@@.@@@@@.@@.@.@@@.@.@@..@@.@@@@@@@.@.@..@@@.@@.@@@@@@.....@@.@.@@@.@.....@@..@@@@@@@@@@.@@@@.@@.@..@@.
@@.@..@@.@@..@@.@@@@.@@..@..@@.....@..@@@@@@@@@@@.@..@@@@@.....@.@@@@@@.@@@@@@..@@@.@@@.@@@.@.@@.@.@.@@@.@@..@..@@@..@@.@.@@@@@.@@.@@...@...
.@.@@@.@@@@.@.@@.@.@@@.@..@@@@@@@...@@@..@@@..@.@@@@@...@.@.@@@@@.@@@.@@@@...@@@@@@.@@..@@@@@.@.@.@@.@.@@@@@@.@@@@.@.@@@@@@..@@...@@.@@..@.@
@@@@.@@@..@.@@@@@@@@@@@...@@@.@..@..@...@.@@.@@@@@@@@.@@@.@@@@@@@@@.@@@@@@@@@@.@@@.@@@@...@.@.@@.@@@.@@.@@@@..@.@@@@@@.@@@.@.@@.@@.@@@@@@..@
@@@@..@@@..@...@.....@....@@@@..@.@@@@.@@.@@.@@@@.@..@@.@.@@@@@@@..@..@@@@..@@@@@@@@@@@@@@@@@.@@@@@.@.@@@@@.@@@..@@@@@@@@...@@..@@@@.@@.@.@@
.@..@@.@.@@@@...@..@@@@.@@@@@.@@@@@@....@@@.@@.@..@.@.@.@..@@@@@..@@.@@@@.@.@@@@@@@...@@@@@@@..@@@@@..@.@@@..@@...@@@@.@@@..@...@.@@@@@@@.@.
@.@@@@.@.@.@.@@@@@@.@@@..@@.@.@@@.@@..@.@@@@..@@@@@@..@@.@..@.@@@@.@@@@.@....@@..@@.@@.@.@.@@...@@@@...@@.@@@.@@.@@@@@@.@@.@@.@@@@@@@.@@@@..
@.@@@@@.@@@@@@@@@@@@@@@@@@@...@.@@@@.@@@@@@.@.@@@@@..@@@@...@@@@@@.@@.@..@.@@.@@.@@@@@.@@@@@.@@@.@@@.@@@..@.@@@@...@@@@@.@@.@@@@.@@@@@@@@@.@
@..@@.@@.@..@...@@@@..@@@@@@.@...@...@.@@@@@@.@.@.@@..@.@.@@.@@@@@@.@.@.@..@@@@@..@.@@@@@@.@@@.@@@@@@@@@@.@.@@@@..@..@.@.@@@.@@@@@..@@@@@.@.
.@@@@@@.@@@.@@....@...@@.@.@@@@@@.@@@@@@@......@@@@@.@@@...@@.@@.@@@...@..@@@@....@.@@@..@@@@@@.@@@@@@.@@@@@@@.@@.....@@@@@...@@.@@@@@.@@@@@
@@@@@@.@@.@.@@@@.@@@@@@@....@@@@.@@@@.@@@.@@@..@@@..@.@@@@..@@.@@.@@@.@.@...@..@.@..@..@@..@..@@.@@@@@@.@....@@.@@.@.@.@@@@@....@..@@@..@@.@
.@.@..@@.@@@..@@@@@@@..@..@.@@@@.@....@@@@@@..@@@@@.@@@.@@@@@@.@@@@@.@..@@@.@@@@@@@.@.@@.@@@@@@@@@..@.@@.@.@@@.@..@@@@@.@.@@.@@@..@@@@@@.@..
@@@@......@.@@@.@.@@.@..@.@.@@@@@.@@@@@@.@@@@@.@@..@@@@@.@@@@@.....@@.@@@@@@.@..@@@...@@@.@.@..@@@@.@@@@@.@@..@@@@@.@@@@@@.@@.@...@@@.@..@@.
@@@@@..@@@.@@@@@.@@@@@@..@@@@...@@@@@@....@.@..@.@.@..@.@@@.@.@.@.@@@@.@@..@@.@.@.@.@@@@@@@@..@@.@@@@.@@@.....@@@@@..@@@@@@@.@.@@@@.@.@...@@
@.@@@..@@@..@@.@@@@@@@@...@@@@.@@@..@@@.@@@@..@@..@.@@..@@@@@..@@.@.@....@@@@.@.@@@.@.@.@@.@@@@.@.@.@@@@@..@@@@@@@@..@@.@...@@..@@.@@.@..@..
...@@.@@.@.@@@@@.@@@..@.....@@..@@.@@.@@.@@.@...@.@....@@.@@@.....@@@@@.@@@@@@@.@@@@@.@.@@@...@@@@.@@.@.@.@@..@@..@@..@..@@..@.@.@.@@@@@..@.
@@.@@@@@.@.@@@@..@@@@@@@@@..@@@@@.@@.@@..@.@@.@@..@.@@...@@@@@@.@@...@@@@@@@.@@@@..@.@@.@@..@@.@..@@@.@@@.@..@@@.@.@@@@.@@@@..@.@@...@@@@@@.
@@@@...@@..@@..@@@@@@..@...@@@@..@@@@.@@@@@@.@.@@@@@..@@@@@@..@@@..@@.@@@@@@@@@.@...@@@@.@@@...@@@@@..@@@..@.@..@..@@.@@.@..@@@...@...@@@@@.
.@.@@..@@.@@.@@...@@.@..@@@.@@@@@@.@.@@.@@@@..@.@@@.@..@@@@@.@@@@.@..@@.@..@..@@@.@..@@@@@@..@.@@@@@@@@@.@.@@.@@@@.@@@.@@.@@..@@.@@.@@@@@.@@
.@@.@@@@...@@@@..@.@@@@@.@..@.@.@.@.@@@@@....@.@..@@@@@@@@@@..@@@@@@@.....@@.@@@.@.@@@@@@...@..@@.@@@..@@..@@@@...@.@@@...@@@@@..@..@@@@@@@.
@..@.@@@@@@@@....@@@@@@....@@@.@@@.@@@@@@.@@@@@.@..@@@@@...@@@@.@.@@@@..@@@@@@@.@@.@@@@@.@@@@.@@.@@@@@@@@@@@@@@.@@@@..@@.@@.@.@@.@..@@@.@@@@
...@@.@@.@@@@@@@..@@...@@@@.@@@@@...@.@@@@@@@...@@.@@....@@@..@.@@@..@@..@.@.@@@@...@@@@@@@.@@@..@@@..@@@@.@..@.@..@@.@....@@@.@@@@..@..@.@@
@...@.@@.@@@@@@@@@@@@@@@@@@.@@@.@..@@..@@.@@.....@.@@.@@..@@@.@.@@@.@.@@..@@@.@..@@.@@@@@@.@@@@@@.@@@@@.@.@@@@.@@..@@.@@.@@@.@..@@@@..@@.@@@
@@.@.@@@@@@@@...@.@@@@@..@@.@....@@@@@..@.@@@.@.@@@.@@.@@@@.@@@@.@..@@@.@@@@@.@@.@@@@@@..@........@.@.@@..@.@@..@@@@.@@..@@@@@.@@@@.@.@@....
@@@@.@...@@.@.@@..@..@@.@..@@..@@@.@@@.@@@@@@@..@@@@@@@@@@.@@@@.@@.....@@@@@.@...@@@@.@@@@.@@.@@@@.@..@@@@.@.@@@.@@@.@@@@@@@.@.@...@...@.@.@
.@...@@@.@@@@.@@..@@...@@@@@@@.@@.@@.@@@@@@@.@@@.@@.@@@@..@...@@.@@..@..@.@@@@@...@@@@@@@@@@.@@.@@.@@@......@.@@@@@@.@.@@@@@@@@@.@@@.@.@.@.@
@@@@@.@.@@@@@..@@.@@@@.@@@.@@@@@...@.@@.@@..@.@@.@.@@@@@..@.@@@.@@..@@@.@@..@...@.@@@@@@@@....@@@@@@@.@@..@@@.@@@@@@@..@.@.@@.@@@@@@@@@..@@@
@@@@@@@@@@@@.@@@@.@@@@@.@@.@@@@.@.@@@@@@.@.@@@@...@@@@..@@.@.@.@@.@...@..@..@@.@.@..@@@@@.@@@@@@@@.@.@@@@@..@..@.@@.@.@@.@@.@.@@.@@.@..@.@@.
@.@@..@@@@@.@@@@..@.@.@.@@@@.@@.@@@.@@@@@@.@@@@.@.@@.@@@@@..@.@.@.@@.@.@...@@..@.@@.@@@.@.@..@@@@@.@@@@@@@@@.@@@@.@.@@.@@@..@@@@@..@.@@@@.@@
..@@@@@..@..@..@@@@@@.....@.@@@@@@@@...@@....@.@@@..@..@.@@@@@@@@@.@.@@.@@@.@@@@.@@..@@.@@..@.@...@@.@@.@@.@@.@@@.@@@@.@.@@@@.@...@@@@.@@@@@
.@@@..@..@.@@@..@.@@@..@.@.@.@@@@@@@@@..@@@.@..@@..@.@@@@.@@.@@@....@@.@@@@.@@.@@@.@@.@@@@@@@.@.@@@.@..@@@@@.@.@@.@@..@.@.@.@.@.@.@.@@.@@.@@
@@@@@@...@.@@.@.@..@@@..@.@.@.@@..@@.@@.@.@@@@..@@.@@.@.@.@@....@@@@@.....@@.@@@.@@.@@@@@@@@@@@@@@@@@..@@.@..@@@.@@..@@.@@@@@@.@.@@@@@@@@.@.
@@.@@..@@@.@@.@@..@.@@@@...@@@.@@..@@@@@@.@@@@@.@@.@@.@@@.@@..@..@.@@.@@@..@@@@@@@..@...@..@@..@@@@@..@@..@@.@.@@.@@@@...@.@@@@.@@.@@@.@.@..
@@@@@@@@.@.@.@@@.@.@...@.@@@@@@@..@@@.@.@@.@@@..@@@...@.@@@@@@@@@.@..@@@.@.@@@@@@.@.@.@.@...@@@@.@@@@@@.@@.@@@@.@@@@@@.@@.@@@.@@@.@@@@@...@.
.@@@@@.@@.@@.@.@.@@@..@..@.@@@@@@...@@..@@.@..@@@@@@@@..@.@.@@..@.@.@....@@@@@.@.@@@@..@.@@@@@@@....@.@.@.@..@@.@..@@@@.@....@@@@.@.@..@@.@@
@.@@@@@@@@.@@@...@@.@.@.@@.@@@.@..@@..@..@@@.....@@...@@@@@@@@@.@@@..@@.@.@@@..@@@..@..@@@..@@@@@@@@..@@.@@@@.@@...@@.@.@.@@@@@@.@@@.@@@@.@@
.@@..@.@@@@@@.@@@..@@@.@..@@@@@@@@..@@@..@.@@@.@.@.@@@@@@@@.@@@@.@.@@.@..@.@@@@...@..@@@@@@@..@@.@@.@@@.@@@@@@..@@@.@@.@@.@.@@.@.@@@@@@.@@@@
@.@.......@..@@......@.@.@@@.@@.@@@.@@@.@.@@@.@.@.@.@..@.@.@@@..@@@.@@@@@...@.@.@@@..@.@.@@.@.@.@@.@.....@@@@.@@@@@.@@.@.@@@@....@..@@@.@@@@
@@.@@@@@@..@@@.@@@@@...@@.@@.@.@@@@@.@@.@@..@@@.@@@@@@...@@.@@@@.....@@@@..@@.@.@.@.@@..@..@@@.@@@@@.@@.@.....@@@@.@@..@...@@.@@..@.@@@@@.@.
.@@@@@@@@@.@..@..@@.@@@.....@.@@@@@@@@@..@@@.@@.@..@@@@.@@...@.@.@@@@@@....@.@@.@.@@@.@.@@@.@.@.@.@@@.@@@@@@@@@@@.@@.@@@@@@@@@@.@@@@..@@@.@@
...@..@@@.@@@@@@@...@@@..@..@..@.@..@@...@.@@@@..@@.@@@..@.@@.@.@.@.@...@.@@.@..@@.@@@......@@@.@.@@@@.@..@@..@..@@.@.@..@...@@@.@@@@.@@.@@@
@.@@..@@@@@@@.@@@@@.@.@@@.@@@@@@@@@@.@@@@@@@.@....@@..@@.@@@@@@@@@..@@.@.@.@@@.@@@.@@.@.@...@@.@@.@@@.@@@.@.@.@@@.@.@@@@@.@@.@.@@@@.@@@@@.@@
.@@.@@@@.@@..@@@@@@@@@@@@.@....@@@....@@.@..@.@.@@@@.@.@@..@.@@@@.@.@@@.@.@@...@@@.@.@@.@..@.@.@.@@@.@@@@@.@@.@@@@@.@@..@@.@@@@@@.@@@@@.@.@@
@.@@@.@@.@@@.@@@@@..@@@.@@@@@.@@...@.@..@@@@@@..@...@.@@.@@@@..@@@.@.@@.@@@.@@.@@@@.@@.@@.@@....@@@@@@@@@@@..@@.@.....@.@@@@..@@@@@@@..@@@.@
...@@@@@.@..@@.@@..@..@@@@.@....@@@@.@..@.@@@.@@..@@@.@.@.@...@@@@@.@.@@@@....@.@.@@.@@@@@.@@@.@.@@@.@@@@@@@.@..@@@.@@@@@@@..@@@@@.@@@.@@@@@
.@@.@@@@@.@@@@@@.@@..@@.@@@@.@@@@@@@.@@@.@@@.@@@......@@.@@@@@@@@@@@@@@@@@@@@.....@@.@...@@..@@.@.@.@@@@@@@@.@@@@@..@..@.@@@@@.@.@@..@@.@.@.
.@..@.@.@@@.@.@.@.@.@@@@.@@@...@.@.@.@@@.@@.@.@@..@.@@@...@@@@@@@@@@@.@@..@@@@@@@@@@.@@@@@@.@@@@..@@.@.@@@@.@@@......@.@...@@@@@..@@.@@@@@..
@..@@@@@.@@@@@@...@@@..@..@@@@@@.@.@@..@@@@.@..@@@@@.@@@..@@@@@@@@@@@@@@.@.@.@@.@@...@@@@@@@@@.@..@@..@@@@.@@@@@.@@.@@@@@@@@.@@@.....@...@@@
@.@@..@@..@@.@@..@@@@@.@.@@.@@..@@@.@.@@@.@.@.@..@@.@...@@@.@@@@@.@...@..@@..@.@@.@@@@@@@@@@...@@@@..@@@@@@@@@.@.@..@@@@.@...@@@.@..@@.@@@.@
.@@@@.@@.@@.@@@.@@@@@@.@.@.@@@.@@.@@@@..@@@@.@.@.@@.@@@@@.....@@.@.@.@.@@@@@.@@@@@@.@@@@.@@@.@@@@@.@..@..@@@.@.@@@@@@@..@@.@...@..@@@@@@...@
@@@@@.@@@@@@.@@@@@..@.@@...@@@@@@@@@@@@...@..@@.@..@@.@@..@...@@.@@@@@@@@@@@.@@..@..@@@@@@@@@.@.@@@@.@.@.@....@..@@@@...@@.@.@@.@@.@@.@@@.@@
@@.@@@@.@@@@.@@.@@.@@@@@@@..@@@.@@@.@@..@@@@@@@..@@@...@@@@.@@.@@@..@@@.@@..@@@.@@@@.@@@@@@@@@@.@.@@@@@@@@@..@@@@.@@@.@@@@.@@@@@@..@.@@@@@.@
@.@@@@.@.@.@@..@@@..@.@....@@@@@.@.@@.@..@@@@@@@@@..@.@@@..@@.@@@@@@@@@..@@....@@@@@.@@.@.@@@...@.@@@.@@.@@.@@@.@@.@..@.@.@@.@@@@@@@.@@@@.@@
@@...@@@..@@@@.@.@@@..@@@@.@@.@..@.@@..@@@.@@@@@@@@@@@@@@@@@@@@@@.@@@@..@.@@.@.@@@@.@@@..@@.@@@..@@@.@@.@.@@@.@@@.@...@@@.@@.@@.@@...@@...@@
@.@@@.@@@@@@@@@.@@@....@..@......@@@.@@.@..@@@.@@@@@@.@@..@@@@@@@@@..@@@..@@..@@@.@.@.@@@@@.@@@.@@@@@@@.@@.@@@@.@..@@.@@..@@.@@@@@@.@..@.@.@
@@..@...@@@@@@@..@@.@.@@.@@@@@..@@..@@..@@.@..@..@@@@..@.@@.@@@@..@..@@.@@@@.@@@@@.@@.@.@@.@@...@@@@@@@@@...@@@@.@@..@@@@@@@@.@.@@.@@.@..@@@
.@@@.@.@.@.@@@@@@...@@...@@.@.@@.@@@@@.@.@@@@@@@..@@.@@..@.@@.@.@.@.@...@@@@@..@.@@@@.@@@@.@@@@@@@...@.@...@.@@@@@.@.@.@.@@..@.@..@@@@.@@@@.
.@@@.@.@@@@@@@.@@@.@.@.@...@.@@..@@@.@@@@@....@@@@...@@@.@.@@.@@@@..@@@@@@.@.@@.@.@....@@@@..@@@@@@@.@@@@@@.....@@.@@@@@@.....@.@.@@@@@.@@@.
@@.@...@@@@@@..@.@@@@@..@@..@@.@@@.@@@@.@@@@.@@@@@@@@@@@@.@.@.@@.@@@@@..@@.@.@.@@@...@@@@@....@@.@.@@.@..@@@.@@@@.@@@@@@@@.@@@@...@.@@@@.@.@
@@@@@...@@...@.@@@.@@.@@@@@@@@@@@@@.@..@@@...@.@@@@@@.@.@..@@@..@@@@..@.@@@.@@@@@...@@...@@..@@..@@.@.@..@@...@@@.@@@..@@@..@@@.@.@@@.@@@@.@
..@.@@@..@@@.@@@..@@.@@.@@@@@...@@.@@..@@@.@@@@.@@...@@.@@@@@@@@@@@@@@.@@..@@..@@@@@@..@.@..@@@@@@@....@@...@@@@@@@@@@.@@@.@@@@@@@..@.@....@
@@@@..@@@@@@@@@@@@@@@@@@@...@.@@@@@@@@@.@.@@@@.@.@@@....@@@@@.@@...@...@@@@...@@@@.@.@@.@@.@@..@@@.@..@..@..@@@@@@..@.@@@..@@.@@..@@.@@...@.
.@@..@@.@@.@@@@..@@@.....@@@@@@@@.@@.@@.@..@@.@@@....@..@@@.@@@.@.@@@@@@@@@.@..@@@@.@.@.@@@@@..@@.@..@@.@@..@.@.@@@.@.@@@@@@@@@@@@@@.@@..@@@
.@@@@.@..@@.@@@.@@@@@.@@@...@@@.@@@..@.@.@@@@..@.@@@.@..@.@......@.@@@.@@@.@@@@..@.@.@.@.@@@...@@@@.@.@@.@@..@@@@@.@@@@..@....@@.@@@@.@@...@
@@@@@....@@@@.@.@.@@@@@@@@@@@@@.@@..@@..@@@@@@...@@.@@@.@@@@.@@...@@.@..@@.@@.@.@@@.@@@.@@@@.@.@@.@@@@@@.@@@@.@.@.@@@@...@@@@.@@.@@@.@@...@.
@.@@.@.@@@...@@@....@@.@.@@@@.@@@....@.@..@.@@@@.@@....@@@....@@@@@@@@@...@@@@@@@@@@.@@.@@@@@@@@.@@@....@..@.@@@.@@@@@..@..@.@....@@...@..@@
.@.@@..@@@.@.@@@@@.@@.@..@.@@..@..@@@@@@@.@@@..@@@@..@@@@@@.@@.@...@..@@@@@@@@@@@......@.@...@@.@.@.@@@.@@@@...@.@@.@@.....@@.@.@@.@.@...@@.
@@@@@.@@.@@@.@@@@...@@@..@@@.@@@@.@@@@@@@.@@@.@@@.@.@@.@@.@@@.@@@..@.@.@@..@@@...@.@@.@@@.@@@@.@@@.@@..@@@....@..@@@@@.@@.@.@..@@@@@@@@@@@@@
@@@@.@.@@@.@@@....@.@....@.@..@@@@@@@@..@@@..@@.@.@..@.@@@@@.@@@..@.@.@@@.@.@.@..@@..@@@@@.@@@@@@@..@@@@@...@.@@@@.@.@..@.@@@@..@.@@..@@.@@.
@.@@@@@@@@@...@.@@@....@....@.........@@@@@@.@@..@@@....@@@@@@..@@.@@@@@.@@..@@@@.@.@.@@.@..@@@.@.@..@@@@@.@@@@@.@@@@.@.@@@@@..@@@@.@@@@@.@@
@..@@...@@..@@@@@.@@@@..@@.@.@.@@.@@@.@@@.@@@@.@@@@.@@@@.@@.@..@@@@@@.@@.@.@@@@..@@@@@@@@.@.@..@@.@@@@.@@@..@@@...@@.@@@..@@.@..@@@@@.@.@@.@
.@@.@.@@.@@..@.@@.@@.....@@.@@...@@.@..@@@.@@@..@@@@..@@..@@..@..@@@@@@@@...@.@.@..@.@...@@@@@.@@@@..@@@@@@.@..@@@@@@@.@@@@.@@@@@@@.@@@@.@@.
...@@@@@.@@@@@@@.@@@..@@@...@.@@@@@@.@@.@@@.@@@@.@@@@@@.@@.@.@..@@.@@.@..@.@@@@@.@..@.@@@@@@@@..@@@@@@.@..@@@@@..@@@@@@@.@@..@@@.@@@@.@@@@.@
....@.@@@....@.@@@@...@@...@@.@@@..@@..@.@@@@@..@.@..@@@@.@@@.....@@@.@.@@.@@..@.@@.@..@.@@@..@@@@@.@@@.@@.@@@.@@..@@..@.@@.@.@@@@@@@@.@@@@.
@@@.@.@@.@@@@.@@@@@@@.@..@@.@..@@@.@.@@.@@@.@@@@.@.@@.@.@@@@.@@@@...@@..@.@@@@@..@.@@@@@@@.@...@@@@@@..@.@@@@@@.@@.@...@.@@.@@@@@@@.@@.@@@.@
@..@.@.@@@@@@@.@.@@.@@@...@..@.@.@@.@@@@.@@@.@@.@.@.@@@@@@@@@@..@@.@@@.@@.@.@@..@@@@.@@@@@..@.@.@..@@@@@.@...@@@@@@....@.@@@@@.@..@...@@@.@.
@@@@..@..@.@@.@.@.@@@@@@.@@@.@..@.@@@@@@@.@@@@.@@@@@@..@.@.@...@@@...@@@.....@.@@.@.@@@.@@@@.@@.@@..@@@....@@.@.@.@...@.@@@@..@@@@@.@@@@.@@@
...@.@@@@@@.@@@@.@.@@.@.@.@@@@.@.@@@.@.@@@@@@@@@@.@..@.@@@..@@..@@@.@.@@@@@.@@.@@@@@@@@@@.@@@.@@@@.@@.@@.@..@@@..@@.@.@.@.@@@.@@@@@...@@@.@@
.@@.@.@@@..@@.@@@@@.@@@@@.@..@@.@@@..@.@@..@@@@@....@.@@.@.@@@@@@@.@..@@@@@.@@.@@@@.@@.@.@@.@@@@@@.@@....@.@.@.@.@@.@@@.@@@@@@@@@@.@..@.@..@
.@.@@@@@.@@.@@@@@.@@@.@@@@.@@@@.@@@.@@@.@.@@.@@@@@.@@@@@..@@..@@..@@@@@.@.@@@.@@@.@@..@.@@@.@.@@@@@@..@@@.@@@@@.@@@.@..@@@@@...@.@@....@@@..
....@..@..@@@.@.@..@@..@@.@.@@@@.@@@....@@.@@.....@.@@@.@@.@@@.@@@.@..@@@@@@@.@@.@@@@@@..@.@@.@@@@.@.@@@@.@@@@..@@..@@@..@.@..@@.@@@@.@@@@@.
@@...@@@@@@@.@@....@@.@.@.@@..@...@@@@@@...@@.@@@..@@.@@@..@@@@.@..@@@......@@@@.@@.@@@.@@.@.@@@@..@@@@.@@@.@@...@.@@.@@@@@.@@@@@@...@@..@@@
@@@@.@@@@.@.@@.@@.@@@@@..@.@@@.@@@@.@..@@.@..@.@@@@.@...@@.@..@.@@.@@@@@@.@.@@@@@@@.@@@@@.@@.@.@@@.@..@@@@@@@@@@...@@.@@@@@@@@@@@..@..@@@.@@
..@@@@.@@@.@@.@@@@@@@@@@@.@@@@@@@@.@@@@@@.@@..@@@@..@@@..@@@@...@@@.@@@@@@@@@.@@@.@@@..@@@@@@.@@@@@@@@@@@.@@@@.@.@@@..@@@@.@@@@@@@@@@@@@@@.@
@@@@@@@@...@.@@.@@.@@..@@.@@@..@@@..@@@.@.@.@@.@@@.@@........@@.@@@@@..@@@@@.@.@.@@@@.@.@@..@@@@@@@@@@@..@@@@@..@@@...@@@@@..@..@.@@@.@@..@.
@.@.@...@@@@..@@@.@@@@@.@..@.@@.@.@@.@.@@.@@@@@@@@@@.@@@@.@@@@.@@@...@.@@.@@@@@@@@@@...@@...@.@@@....@..@@@.@@@@@..@.@.@@@@@.@@@@...@..@@@.@
.@.@@....@@..@@@.@@@@@...@@@@@@@@.@.@@..@@@.@@..@@@@@@.@@@@@@..@@@@..@@@@@.@@@..@@@@@.@@.@.@@@@@..@@@@..@.@..@.@@@@..@@@@@@@@.@...@.@@@.@@@@
.@@..@@@@@.@@@.@@@@..@@@....@@@@...@.@@@@.@.@.@@@@.@....@@@@@@.@.@.@@@@.@@@..@@@@@..@@@.@@.@.@.@@...@@..@.@..@@@@@@@@.@..@..@@@@@@..@@@.@.@@
@@@..@@@.@@@@.@@...@.@@@@..@@@@@@@@@@@.@@@.@@.@@@@.@@@.@@.@@.@.....@@@@.@@..@.@@@.@.@@@..@@@.@@@@@.@@.@@@.@.@@@@@@@@@...@@..@.@@@@@.@.@.@.@.
.@....@@@@..@.@@@@@@@.@@@...@@...@@@@@@@.@.@@.@@...@@@.@@@.@.@..@..@@@@@..@@@@@@@@@.@....@@@@...@@@..@.@....@.@@@@@.@@@..@@@@..@@@..@@@.@@@.
@@..@@..@@@@.@@..@..@@@.@@.@.@@@@@@@@@@@@@@.@@@@@@@.@@.@@@@@@.@@.@.@@.@@@..@@.@.@@@@@@@..@@...@@..@.@@.@@@@@@@@.@@.@@@@.@@@..@@@@@@....@@@.@"""

69
src/Day4/Grid.purs Normal file
View File

@@ -0,0 +1,69 @@
module Day4.Grid where
import Prelude
import Control.Alternative (guard)
import Data.Array (mapWithIndex)
import Data.Array as Array
import Data.Foldable (class Foldable, all, foldMap, foldl, foldr)
import Data.FoldableWithIndex (class FoldableWithIndex, foldMapWithIndex)
import Data.FunctorWithIndex (class FunctorWithIndex)
import Data.Maybe (Maybe, fromMaybe)
import Data.Tuple.Nested (type (/\), (/\))
type Coord = Int /\ Int
data Grid a = Grid Int Int (Array (Array a))
instance Show a => Show (Grid a) where
show (Grid x y grid) = show x <> "x" <> show y <> "\n" <> (Array.intercalate "\n" $ map (Array.intercalate " " <<< map show) grid)
instance Functor Grid where
map f (Grid x y a) = Grid x y $ map (map f) a
instance FunctorWithIndex Coord Grid where
mapWithIndex f grid@(Grid x y _) = Grid x y $ map (map (\(i /\ a) -> f i a)) $ indexed' grid
instance Foldable Grid where
foldl f b (Grid _ _ a) = foldl f b $ Array.concat a
foldr f b (Grid _ _ a) = foldr f b $ Array.concat a
foldMap f (Grid _ _ a) = foldMap f $ Array.concat a
instance FoldableWithIndex Coord Grid where
foldlWithIndex f b = foldl (\b' (i /\ a) -> f i b' a) b <<< indexed
foldrWithIndex f b = foldr (\(i /\ a) b' -> f i a b') b <<< indexed
foldMapWithIndex f = foldMap (\(i /\ a) -> f i a) <<< indexed
mkGrid :: forall a. Array (Array a) -> Maybe (Grid a)
mkGrid xs = do
let dimy = Array.length xs
x0 <- Array.head xs
let dimx = Array.length x0
guard $ all (eq dimx <<< Array.length) xs
pure $ Grid dimx dimy xs
update :: forall a. Coord -> a -> Grid a -> Grid a
update (x /\ y) a (Grid xdim ydim grid) =
Grid xdim ydim (fromMaybe grid $ Array.modifyAt y (\as -> fromMaybe as $ Array.updateAt x a as) grid)
indexed :: forall a. Grid a -> Array (Coord /\ a)
indexed (Grid _ _ a) =
flip foldMapWithIndex a \y ->
mapWithIndex \x v ->
(x /\ y) /\ v
indexed' :: forall a. Grid a -> Array (Array (Coord /\ a))
indexed' (Grid _ _ a) =
flip mapWithIndex a \y ->
mapWithIndex \x v ->
(x /\ y) /\ v
neighbors :: forall a. Coord -> Grid a -> Array (Coord /\ a)
neighbors (x /\ y) grid =
let
yPad = 1
xPad = 1
in do
row <- Array.slice (max 0 $ y - yPad) (y + yPad + 1) $ indexed' grid
coord /\ a <- Array.slice (max 0 $ x - xPad) (x + xPad + 1) row
guard $ coord /= (x /\ y)
pure $ coord /\ a

47
src/Day4/Paper.purs Normal file
View File

@@ -0,0 +1,47 @@
module Day4.Paper where
import Prelude
import Control.Alt ((<|>))
import Data.Array as Array
import Data.Either (Either)
import Data.Filterable (filter)
import Data.FoldableWithIndex (foldlWithIndex)
import Data.FunctorWithIndex (mapWithIndex)
import Data.List as List
import Data.Maybe (Maybe(..), isJust)
import Data.Tuple (snd)
import Data.Tuple.Nested ((/\))
import Day4.Grid (Grid)
import Day4.Grid as Grid
import Parsing (Parser)
import Parsing (runParser, ParseError, liftMaybe) as Parse
import Parsing.Combinators (many, sepBy) as Parse
import Parsing.String (string) as Parse
data PaperRoll = PaperRoll
instance Show PaperRoll where
show _ = "@"
canRemove :: Grid (Maybe PaperRoll) -> Grid Boolean
canRemove grid =
let
f _ Nothing = false
f (x /\ y) (Just _) =
(_ < 4) $ Array.length $ filter (isJust <<< snd) $ Grid.neighbors (x /\ y) grid
in
mapWithIndex f grid
parsePaper :: String -> Either Parse.ParseError (Grid (Maybe PaperRoll))
parsePaper = flip Parse.runParser parser
parser :: Parser String (Grid (Maybe PaperRoll))
parser =
let
roll =
(Parse.string "." $> Nothing) <|> (Parse.string "@" $> Just PaperRoll)
row =
List.toUnfoldable <$> Parse.many roll
in do
rows <- List.toUnfoldable <$> Parse.sepBy row (Parse.string "\n")
Parse.liftMaybe (const "array dimension mismatch") $ Grid.mkGrid rows

View File

@@ -5,10 +5,12 @@ import Prelude
import Day1 as Day1
import Day2 as Day2
import Day3 as Day3
import Day4 as Day4
import Effect (Effect)
main :: Effect Unit
main = do
Day1.main
Day2.main
Day3.main
when false $ Day1.main
when false $ Day2.main
when false $ Day3.main
when false $ Day4.main