lwhjp

joined 1 month ago
[โ€“] lwhjp@piefed.blahaj.zone 2 points 3 days ago* (last edited 3 days ago)

Haskell

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  

That's fascinating, thank you!

I mean... it can?

It's pretty awesome, actually.

Haskell

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  

Yay! Spiro sucks.

Haskell

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  
[โ€“] lwhjp@piefed.blahaj.zone 1 points 1 week ago* (last edited 1 week ago)

Haskell

A nice dynamic programming problem in part 3.

import Data.List  
import Data.List.Split  
import Data.Map.Lazy qualified as Map  
import Data.Maybe  

readInput s =  
  let (names : _ : rules) = lines s  
   in (splitOn "," names, map readRule rules)  
  where  
    readRule s =  
      let [[c], post] = splitOn " > " s  
       in (c, map head $ splitOn "," post)  

validBy rules name = all (`check` name) rules  
  where  
    check (c, cs) = all (`elem` cs) . following c  
    following c s = [b | (a : b : _) <- tails s, a == c]  

part1 (names, rules) = fromJust $ find (validBy rules) names  

part2 (names, rules) =  
  sum $ map fst $ filter (validBy rules . snd) $ zip [1 ..] names  

part3 (names, rules) =  
  sum . map go . filter (validBy rules) $ dedup names  
  where  
    dedup xs =  
      filter (\x -> not $ any (\y -> x /= y && y `isPrefixOf` x) xs) xs  
    go n = count (length n) (last n)  
    gen 11 _ = 1  
    gen len c =  
      (if len >= 7 then (1 +) else id)  
        . maybe 0 (sum . map (count (len + 1)))  
        $ lookup c rules  
    count =  
      curry . (Map.!) . Map.fromList $  
        [ ((k, c), gen k c)  
          | k <- [1 .. 11],  
            c <- map fst rules ++ concatMap snd rules  
        ]  

main = do  
  readFile "everybody_codes_e2025_q07_p1.txt" >>= putStrLn . part1 . readInput  
  readFile "everybody_codes_e2025_q07_p2.txt" >>= print . part2 . readInput  
  readFile "everybody_codes_e2025_q07_p3.txt" >>= print . part3 . readInput  

Haskell

It took me an embarrassingly long time to figure out what was going on with this one.

You could go a bit faster by splitting the list into beginning/middle/end parts, but I like the simplicity of this approach.

import Control.Monad (forM_)  
import Data.Char (toUpper)  
import Data.IntMap.Strict qualified as IntMap  
import Data.List (elemIndices)  
import Data.Map qualified as Map  

{-  
  f is a function which, given a lookup function and an index  
  returns the number of mentors for the novice at that position.  
  The lookup function returns the number of knights up to but  
  not including a specified position.  
-}  
countMentorsWith f input = Map.fromList [(c, go c) | c <- "abc"]  
  where  
    go c =  
      let knights = elemIndices (toUpper c) input  
          counts = IntMap.fromDistinctAscList $ zip knights [1 ..]  
          preceding = maybe 0 snd . (`IntMap.lookupLT` counts)  
       in sum $ map (f preceding) $ elemIndices c input  

part1 = (Map.! 'a') . countMentorsWith id  

part2 = sum . countMentorsWith id  

part3 d r = sum . countMentorsWith nearby . concat . replicate r  
  where  
    nearby lookup i = lookup (i + d + 1) - lookup (i - d)  

main =  
  forM_  
    [ ("everybody_codes_e2025_q06_p1.txt", part1),  
      ("everybody_codes_e2025_q06_p2.txt", part2),  
      ("everybody_codes_e2025_q06_p3.txt", part3 1000 1000)  
    ]  
    $ \(input, solve) -> readFile input >>= print . solve  

Buying nail polish to do furniture repairs because it would be a shame to let the rest go to waste...

/just cis things

Haha, yes that's exactly right!

 

It took a few tries to figure out a good technique, but I'm reasonably happy with how they turned out. They look OK from a distance, anyway.

I forgot that "weekdays" for a US website means something different for me here in UTC+9.

This was surprisingly fiddly, but I think I managed to do it reasonably neatly.

import Control.Arrow  
import Data.Foldable  
import Data.List (sortBy)  
import Data.List.Split  
import Data.Maybe  
import Data.Ord  

data Fishbone  
  = Fishbone (Maybe Int) Int (Maybe Int) Fishbone  
  | Empty  
  deriving (Eq)  

instance Ord Fishbone where  
  compare = comparing numbers  

readInput :: String -> [(Int, Fishbone)]  
readInput = map readSword . lines  
  where  
    readSword = (read *** build) . break (== ':')  
    build = foldl' insert Empty . map read . splitOn "," . tail  

insert bone x =  
  case bone of  
    (Fishbone l c r next)  
      | isNothing l && x < c -> Fishbone (Just x) c r next  
      | isNothing r && x > c -> Fishbone l c (Just x) next  
      | otherwise -> Fishbone l c r $ insert next x  
    Empty -> Fishbone Nothing x Nothing Empty  

spine (Fishbone _ c _ next) = c : spine next  
spine Empty = []  

numbers :: Fishbone -> [Int]  
numbers (Fishbone l c r next) =  
  (read $ concatMap show $ catMaybes [l, Just c, r])  
    : numbers next  
numbers Empty = []  

quality :: Fishbone -> Int  
quality = read . concatMap show . spine  

part1, part2, part3 :: [(Int, Fishbone)] -> Int  
part1 = quality . snd . head  
part2 = uncurry (-) . (maximum &&& minimum) . map (quality . snd)  
part3 = sum . zipWith (*) [1 ..] . map fst . sortBy (flip compareSwords)  
  where  
    compareSwords =  
      comparing (quality . snd)  
        <> comparing snd  
        <> comparing fst  

main =  
  forM_  
    [ ("everybody_codes_e2025_q05_p1.txt", part1),  
      ("everybody_codes_e2025_q05_p2.txt", part2),  
      ("everybody_codes_e2025_q05_p3.txt", part3)  
    ]  
    $ \(input, solve) -> readFile input >>= print . solve . readInput  
 

It's nice, but it's a pain to set so I mostly just have it in a ponytail. Plus it takes forever to grow out.

 

It'll put something on your chest, but it probably isn't hair.

(This is a joke: don't actually eat estradiol gel)

 
view more: next โ€บ