

That’s not quite the key observation…
spoiler
Many of the productions end in an element which does not appear on the left-hand side. That acts as a flag which tells you where to look for substitutions.
Hi, I’m Amy.
✨ New 🏳️⚧️ improved ♀️ version 👩❤️👩 out 🏳️🌈 now! 🎊
I live in Japan. Talk to me about Haskell, Scheme, and Linux.
日本語も通じます。


That’s not quite the key observation…
Many of the productions end in an element which does not appear on the left-hand side. That acts as a flag which tells you where to look for substitutions.


This is pretty ugly. I got rather fed up after trying out various heuristics when the test case passed but actual data didn’t.
import Control.Arrow
import Data.Function
import Data.Ix
import Data.List
import Data.Ord
readInput :: String -> [(Int, Int)]
readInput = map ((read *** (read . tail)) . break (== ',')) . lines
pairs = concatMap (\(x : xs) -> map (x,) xs) . init . tails
toRange ((a, b), (c, d)) = ((min a c, min b d), (max a c, max b d))
onTiles loop rect = cornersInside && not crossingEdges
where
cornersInside =
let ((a, b), (c, d)) = rect
in inside (a, d) && inside (c, b)
verticalEdges = sortOn (Down . fst . fst) $ filter (uncurry ((==) `on` fst)) loop
inside (x, y) =
let intersecting ((a, b), (_, d)) = a <= x && inRange (min b d, max b d) y
in maybe False (uncurry ((>) `on` snd)) $ find intersecting verticalEdges
crossingEdges =
let ((a, b), (c, d)) = rect
in any (crossingLoop . toRange) $
[ ((a, b), (c, b)),
((c, b), (c, d)),
((c, d), (a, d)),
((a, d), (a, b))
]
crossingLoop ((a, b), (c, d))
| a == c = anyEdge (\((e, f), (g, h)) -> f == h && f > b && f < d && g > a && e < c)
| b == d = anyEdge (\((e, f), (g, h)) -> e == g && e > a && e < c && h > b && f < d)
anyEdge = flip any $ map toRange loop
main = do
input <- readInput <$> readFile "input09"
let rects = pairs input
loop = zip (last input : input) input
go = print . maximum . map (rangeSize . toRange)
go rects
go $ filter (onTiles loop) rects


Oh gosh, I remember this one. Working backwards is a good idea. In addition, you can just look at the start of the string when trying substitutions. I don’t think that’s valid in general, but it worked for me in this case.
There’s another trick you can do if you look carefully at the input data. I didn’t implement it in my solution because I didn’t spot it myself, but it essentially makes the problem trivial.


I was late to the part on this one and forgot to post my solution :3
import Data.List
readInput = map readMove . lines
where
readMove (d : ds) =
let n = read ds :: Int
in case d of
'L' -> -n
'R' -> n
part1 = length . filter ((== 0) . (`mod` 100)) . scanl' (+) 50
part2 = fst . foldl' count (0, 50)
where
count (z, p) d =
let (q, r) = (p + d) `divMod` 100
a = if p == 0 && d < 0 then -1 else 0
b = if r == 0 && d < 0 then 1 else 0
in (z + abs q + a + b, r)
main = do
input <- readInput <$> readFile "input01"
print $ part1 input
print $ part2 input


Thank you! ☺️


They’re getting interesting now!
import Control.Monad
import Data.List
import Data.List.Split
import Data.Ord
import Data.Set qualified as Set
readPos = (\([x, y, z] :: [Int]) -> (x, y, z)) . map read . splitOn ","
pairs = init . tails >=> (\(x : xs) -> map (x,) xs)
dist (x1, y1, z1) (x2, y2, z2) =
(x2 - x1) ^ 2 + (y2 - y1) ^ 2 + (z2 - z1) ^ 2
connect circuits (a, b) =
let (joined, rest) =
partition (\c -> a `Set.member` c || b `Set.member` c) circuits
in Set.unions joined : rest
main = do
boxes <- map readPos . lines <$> readFile "input08"
let steps =
(zip <*> tail . scanl' connect (map Set.singleton boxes)) $
sortOn (uncurry dist) (pairs boxes)
print . product . take 3 . sortOn Down . map Set.size $
(snd . last . take 1000 $ steps)
let Just (((x1, _, _), (x2, _, _)), _) =
find ((== 1) . length . snd) steps
in print $ x1 * x2


And here’s a super-simple version, because why not.
import Data.List (elemIndex, elemIndices)
import Data.Map qualified as Map
import Data.Maybe (fromJust)
import Data.Set qualified as Set
main = do
(start : rows) <- lines <$> readFile "input07"
let splitsByRow =
zipWith
( \row beams ->
Set.intersection (Map.keysSet beams)
. Set.fromDistinctAscList
$ elemIndices '^' row
)
rows
beamsByRow
beamsByRow =
scanl
( \beams splits ->
let unsplit = beams `Map.withoutKeys` splits
split = beams `Map.restrictKeys` splits
splitLeft = Map.mapKeysMonotonic pred split
splitRight = Map.mapKeysMonotonic succ split
in Map.unionsWith (+) [unsplit, splitLeft, splitRight]
)
(Map.singleton (fromJust $ elemIndex 'S' start) 1)
splitsByRow
print . sum $ map Set.size splitsByRow
print . sum $ last beamsByRow


Thanks! I try to write code to be readable by humans above all else.


That was a fun little problem.
import Data.Map qualified as Map
import Data.Set qualified as Set
import Data.Tuple (swap)
readInput s =
Map.fromDistinctAscList
[((i, j), c) | (i, l) <- zip [0 ..] $ lines s, (j, c) <- zip [0 ..] l]
beamPaths input = scanl step (Map.singleton startX 1) [startY .. endY]
where
Just (startY, startX) = lookup 'S' $ map swap $ Map.assocs input
Just ((endY, _), _) = Map.lookupMax input
step beams y =
Map.unionsWith (+) $
[ if input Map.!? (y + 1, j) == Just '^'
then Map.fromList [(j - 1, n), (j + 1, n)]
else Map.singleton j n
| (j, n) <- Map.assocs beams
]
part1 = sum . map Set.size . (zipWith (Set.\\) <*> tail) . map Map.keysSet . beamPaths
part2 = sum . last . beamPaths
main = do
input <- readInput <$> readFile "input07"
print $ part1 input
print $ part2 input


There’s probably a really clever way of abstracting just the difference between the two layouts.
import Data.Char (isSpace)
import Data.List (transpose)
import Data.List.Split (splitWhen)
op '+' = sum
op '*' = product
part1 =
sum
. map ((op . head . last) <*> (map read . init))
. (transpose . map words . lines)
part2 =
sum
. map ((op . last . last) <*> map (read . init))
. (splitWhen (all isSpace) . reverse . transpose . lines)
main = do
input <- readFile "input06"
print $ part1 input
print $ part2 input


IntSet was the wrong first choice for part 2 :3
import Control.Arrow
import Data.Foldable
import Data.Ix
readInput :: [Char] -> ([(Int, Int)], [Int])
readInput =
(map readRange *** (map read . tail))
. break (== "")
. lines
where
readRange = (read *** (read . tail)) . break (== '-')
part1 (ranges, ids) = length $ filter (\id -> any (`inRange` id) ranges) ids
part2 (ranges, _) = sum $ map rangeSize $ foldl' addRange [] ranges
where
addRange [] x = [x]
addRange (r : rs) x
| touching r x = addRange rs $ merge r x
| otherwise = r : addRange rs x
touching (a, b) (c, d) = not (b < c - 1 || a > d + 1)
merge (a, b) (c, d) = (min a c, max b d)
main = do
input <- readInput <$> readFile "input05"
print $ part1 input
print $ part2 input


Very simple, this one.
import Data.List
import Data.Set qualified as Set
readInput s =
Set.fromDistinctAscList
[ (i, j) :: (Int, Int)
| (i, l) <- zip [0 ..] (lines s),
(j, c) <- zip [0 ..] l,
c == '@'
]
accessible ps = Set.filter ((< 4) . adjacent) ps
where
adjacent (i, j) =
length . filter (`Set.member` ps) $
[ (i + di, j + dj)
| di <- [-1 .. 1],
dj <- [-1 .. 1],
(di, dj) /= (0, 0)
]
main = do
input <- readInput <$> readFile "input04"
let removed =
(`unfoldr` input) $
\ps ->
case accessible ps of
d
| Set.null d -> Nothing
| otherwise -> Just (Set.size d, ps Set.\\ d)
print $ head removed
print $ sum removed


Version 2. I realized last night that my initial approach was way more complicated than it needed to be…
import Data.List
import Data.Semigroup
maxJolt :: Int -> [Char] -> Int
maxJolt r xs = read $ go r (length xs) xs
where
go r n xs =
(\(Arg x xs) -> x : xs) . maximum $
do
(n', x : xs') <- zip (reverse [r .. n]) (tails xs)
return . Arg x $ if r == 1 then [] else go (r - 1) (n' - 1) xs'
main = do
input <- lines <$> readFile "input03"
mapM_ (print . sum . (`map` input) . maxJolt) [2, 12]


Yay, dynamic programming!
import Data.Map qualified as Map
maxJolt :: Int -> [Char] -> Int
maxJolt r xs = read $ maximize r 0
where
n = length xs
maximize =
(curry . (Map.!) . Map.fromList . (zip <*> map (uncurry go)))
[(k, o) | k <- [1 .. r], o <- [r - k .. n - k]]
go k o =
maximum $ do
(x, o') <- drop o $ zip xs [1 .. n - (k - 1)]
return . (x :) $ if k == 1 then [] else maximize (k - 1) o'
main = do
input <- lines <$> readFile "input03"
mapM_ (print . sum . (`map` input) . maxJolt) [2, 12]


Not much time for challenges right now sadly :/
import Data.Bifunctor
import Data.IntSet qualified as IntSet
import Data.List.Split
repeats bound (from, to) = IntSet.elems $ IntSet.unions $ map go [2 .. bound l2]
where
l1 = length (show from)
l2 = length (show to)
go n =
let l = max 1 $ l1 `quot` n
start = if n > l1 then 10 ^ (l - 1) else read . take l $ show from
in IntSet.fromList
. takeWhile (<= to)
. dropWhile (< from)
. map (read . concat . replicate n . show)
$ enumFrom start
main = do
input <-
map (bimap read (read . tail) . break (== '-')) . splitOn ","
<$> readFile "input02"
let go bound = sum $ concatMap (repeats bound) input
print $ go (const 2)
print $ go id


Hmm. I’m still not very happy with part 3: it’s a bit slow and messy. Doing state over the list monad for memoization doesn’t work well, so I’m enumerating all possible configurations first and taking advantage of laziness.
import Control.Monad
import Data.Bifunctor
import Data.Ix
import Data.List
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Maybe
import Data.Set.Monad (Set)
import Data.Set.Monad qualified as Set
import Data.Tuple
type Pos = (Int, Int)
readInput :: String -> ((Pos, Pos), Pos, Set Pos, Set Pos)
readInput s =
let grid =
Map.fromList
[ ((i, j), c)
| (i, cs) <- zip [0 ..] $ lines s,
(j, c) <- zip [0 ..] cs
]
in ( ((0, 0), fst $ Map.findMax grid),
fst $ fromJust $ find ((== 'D') . snd) $ Map.assocs grid,
Set.fromList $ Map.keys (Map.filter (== 'S') grid),
Set.fromList $ Map.keys (Map.filter (== '#') grid)
)
moveDragon (i, j) = Set.mapMonotonic (bimap (+ i) (+ j)) offsets
where
offsets = Set.fromList ([id, swap] <*> ((,) <$> [-1, 1] <*> [-2, 2]))
dragonMoves bounds =
iterate (Set.filter (inRange bounds) . (>>= moveDragon)) . Set.singleton
part1 n (bounds, start, sheep, _) =
(!! n)
. map (Set.size . Set.intersection sheep)
. scanl1 Set.union
$ dragonMoves bounds start
part2 n (bounds, dragonStart, sheepStart, hideouts) =
(!! n)
. map ((Set.size sheepStart -) . Set.size)
. scanl'
( \sheep eaten ->
(Set.\\ eaten)
. Set.mapMonotonic (first (+ 1))
. (Set.\\ eaten)
$ sheep
)
sheepStart
. map (Set.\\ hideouts)
$ (tail $ dragonMoves bounds dragonStart)
part3 (bounds, dragonStart, sheepStart, hideouts) =
count (dragonStart, sheepStart)
where
sheepStartByColumn = Map.fromList $ map swap $ Set.elems sheepStart
sheepConfigs =
map
( (Set.fromList . catMaybes)
. zipWith (\j -> fmap (,j)) (Map.keys sheepStartByColumn)
)
. mapM
( ((Nothing :) . map Just)
. (`enumFromTo` (fst $ snd bounds))
)
$ Map.elems sheepStartByColumn
count =
((Map.!) . Map.fromList . map ((,) <*> go))
((,) <$> range bounds <*> sheepConfigs)
go (dragon, sheep)
| null sheep = 1
| otherwise =
(sum . map count) $ do
let movableSheep =
filter (\(_, p) -> p /= dragon || Set.member p hideouts) $
map (\(i, j) -> ((i, j), (i + 1, j))) $
Set.elems sheep
sheepMoves =
if null movableSheep
then [sheep]
else do
(p1, p2) <- movableSheep
return $ Set.insert p2 $ Set.delete p1 sheep
sheep' <- sheepMoves
guard $ all (inRange bounds) sheep'
dragon' <- Set.elems $ moveDragon dragon
guard $ inRange bounds dragon'
let eaten = Set.singleton dragon' Set.\\ hideouts
return (dragon', sheep' Set.\\ eaten)
main = do
readFile "everybody_codes_e2025_q10_p1.txt" >>= print . part1 4 . readInput
readFile "everybody_codes_e2025_q10_p2.txt" >>= print . part2 20 . readInput
readFile "everybody_codes_e2025_q10_p3.txt" >>= print . part3 . readInput


Not particularly optimized but good enough.
import Control.Arrow ((***))
import Data.Array (assocs)
import Data.Function (on)
import Data.Graph
import Data.List
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Maybe
readInput :: String -> Map Int [Char]
readInput = Map.fromList . map ((read *** tail) . break (== ':')) . lines
findRelations :: Map Int [Char] -> Graph
findRelations dna =
buildG (1, Map.size dna)
. concatMap (\(x, (y, z)) -> [(x, y), (x, z)])
. mapMaybe (\x -> (x,) <$> findParents x)
$ Map.keys dna
where
findParents x =
find (isChild x) $
[(y, z) | (y : zs) <- tails $ delete x $ Map.keys dna, z <- zs]
isChild x (y, z) =
all (\(a, b, c) -> a == b || a == c) $
zip3 (dna Map.! x) (dna Map.! y) (dna Map.! z)
scores :: Map Int [Char] -> Graph -> [Int]
scores dna relations =
[similarity x y * similarity x z | (x, [y, z]) <- assocs relations]
where
similarity i j =
length . filter (uncurry (==)) $ zip (dna Map.! i) (dna Map.! j)
part1, part2, part3 :: Map Int [Char] -> Int
part1 = sum . (scores <*> findRelations)
part2 = part1
part3 = sum . maximumBy (compare `on` length) . components . findRelations
main = do
readFile "everybody_codes_e2025_q09_p1.txt" >>= print . part1 . readInput
readFile "everybody_codes_e2025_q09_p2.txt" >>= print . part2 . readInput
readFile "everybody_codes_e2025_q09_p3.txt" >>= print . part3 . readInput


Woo! I got on the leaderboard at last. I don’t think I’ve seen a problem like this one before, but fortunately it wasn’t as tricky as it seemed at first glance.
import Control.Monad
import Data.List
import Data.List.Split
import Data.Tuple
readInput :: String -> [(Int, Int)]
readInput = map fixOrder . (zip <*> tail) . map read . splitOn ","
where
fixOrder (x, y)
| x > y = (y, x)
| otherwise = (x, y)
crosses (a, b) (c, d) =
not (a == c || a == d || b == c || b == d)
&& ((a < c && c < b) /= (a < d && d < b))
part1 n = length . filter ((== n `quot` 2) . uncurry (-) . swap)
part2 n = sum . (zipWith countKnots <*> inits)
where
countKnots x strings = length $ filter (crosses x) strings
part3 n strings =
maximum [countCuts (a, b) | a <- [1 .. n - 1], b <- [a + 1 .. n]]
where
countCuts x = length $ filter (\s -> x == s || x `crosses` s) strings
main =
forM_
[ ("everybody_codes_e2025_q08_p1.txt", part1 32),
("everybody_codes_e2025_q08_p2.txt", part2 256),
("everybody_codes_e2025_q08_p3.txt", part3 256)
]
$ \(input, solve) -> readFile input >>= print . solve . readInput


deleted by creator
Haskell
Oh, this one was easy (dynamic programming at last!). Still haven’t figured out the right way to approach yesterday’s part two, though.