Hi, I’m Amy.

✨ New 🏳️‍⚧️ improved ♀️ version 👩‍❤️‍👩 out 🏳️‍🌈 now! 🎊

I live in Japan. Talk to me about Haskell, Scheme, and Linux.

日本語も通じます。

  • 3 Posts
  • 26 Comments
Joined 29 days ago
cake
Cake day: October 17th, 2025

help-circle

  • 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  
    


  • 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  
    


  • 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  
    




  • 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  
    

  • I liked this one!

    import Control.Arrow  
    import Control.Monad  
    import Data.List  
    import Data.Ratio  
    
    simpleTrain = uncurry (%) . (head &&& last) . map read  
    
    compoundTrain input =  
      let a = read $ head input  
          z = read $ last input  
          gs =  
            map  
              ( uncurry (%)  
                  . (read *** read . tail)  
                  . break (== '|')  
              )  
              $ (tail . init) input  
       in foldl' (/) (a % z) gs  
    
    part1, part2, part3 :: [String] -> Integer  
    part1 = floor . (2025 *) . simpleTrain  
    part2 = ceiling . (10000000000000 /) . simpleTrain  
    part3 = floor . (100 *) . compoundTrain  
    
    main =  
      forM_  
        [ ("everybody_codes_e2025_q04_p1.txt", part1),  
          ("everybody_codes_e2025_q04_p2.txt", part2),  
          ("everybody_codes_e2025_q04_p3.txt", part3)  
        ]  
        $ \(input, solve) -> readFile input >>= print . solve . lines  
    

  • I thought this was going to be the knapsack problem, but no.

    import Control.Monad  
    import Data.List.Split  
    import qualified Data.Set as Set  
    import qualified Data.Multiset as MSet  
    
    part1, part2, part3 :: [Int] -> Int  
    part1 = sum . Set.fromList  
    part2 = sum . Set.take 20 . Set.fromList  
    part3 = maximum . MSet.toCountMap . MSet.fromList  
    
    main =  
      forM_  
        [ ("everybody_codes_e2025_q03_p1.txt", part1),  
          ("everybody_codes_e2025_q03_p2.txt", part2),  
          ("everybody_codes_e2025_q03_p3.txt", part3)  
        ]  
        $ \(input, solve) ->  
          readFile input >>= print . solve . map read . splitOn ","  
    

  • It’s gradually coming back to me. The Haskell Complex type doesn’t work particularly nicely as an integer, plus the definition of division is more like “scale”, so I just went with my own type.

    Then I forgot which of div and quot I should use, and kept getting nearly the right answer :/

    import Data.Ix  
    
    data CNum = CNum !Integer !Integer  
    
    instance Show CNum where  
      show (CNum x y) = "[" ++ show x ++ "," ++ show y ++ "]"  
    
    cadd, cmul, cdiv :: CNum -> CNum -> CNum  
    (CNum x1 y1) `cadd` (CNum x2 y2) = CNum (x1 + x2) (y1 + y2)  
    (CNum x1 y1) `cmul` (CNum x2 y2) = CNum (x1 * x2 - y1 * y2) (x1 * y2 + y1 * x2)  
    (CNum x1 y1) `cdiv` (CNum x2 y2) = CNum (x1 `quot` x2) (y1 `quot` y2)  
    
    part1 a = iterate op (CNum 0 0) !! 3  
      where  
        op x = ((x `cmul` x) `cdiv` CNum 10 10) `cadd` a  
    
    countEngraved = length . filter engrave  
      where  
        engrave p =  
          let rs = take 100 $ tail $ iterate (op p) (CNum 0 0)  
           in all (\(CNum x y) -> abs x <= 1000000 && abs y <= 1000000) rs  
        op p r = ((r `cmul` r) `cdiv` CNum 100000 100000) `cadd` p  
    
    part2 a =  
      countEngraved  
        . map (\(y, x) -> a `cadd` CNum (x * 10) (y * 10))  
        $ range ((0, 0), (100, 100))  
    
    part3 a =  
      countEngraved  
        . map (\(y, x) -> a `cadd` CNum x y)  
        $ range ((0, 0), (1000, 1000))  
    
    main = do  
      print $ part1 $ CNum 164 56  
      print $ part2 $ CNum (-21723) 67997  
      print $ part3 $ CNum (-21723) 67997  
    

  • Ooh, challenges! Here we go!

    I haven’t really written any Haskell since last year’s AoC, and boy am I rusty.

    import Control.Monad  
    import Data.List  
    import Data.List.Split  
    import Data.Vector qualified as V  
    
    readInput s =  
      let [names, _, moves] = splitOn "," <$> lines s  
       in (names, map readMove moves)  
      where  
        readMove (d : s) =  
          let n = read s :: Int  
           in case d of  
                'L' -> -n  
                'R' -> n  
    
    addWith f = (f .) . (+)  
    
    part1 names moves =  
      names !! foldl' (addWith $ clamp (length names)) 0 moves  
      where  
        clamp n x  
          | x < 0 = 0  
          | x >= n = n - 1  
          | otherwise = x  
    
    part2 names moves =  names !! (sum moves `mod` length names)  
    
    part3 names moves =  
      V.head  
        . foldl' exchange (V.fromList names)  
        $ map (`mod` length names) moves  
      where  
        exchange v k = v V.// [(0, v V.! k), (k, V.head v)]  
    
    main =  
      forM_  
        [ ("everybody_codes_e2025_q01_p1.txt", part1),  
          ("everybody_codes_e2025_q01_p2.txt", part2),  
          ("everybody_codes_e2025_q01_p3.txt", part3)  
        ]  
        $ \(input, solve) ->  
          readFile input >>= putStrLn . uncurry solve . readInput  
    





  • Yeah, it’s scary, right? Your whole life has been turned inside out.

    Your wife being supportive will make things so much easier as you figure out what you want to do going forward.

    There’s no rush. You can take things as slow as you need; do as little or as much as you feel comfortable with. It’s also possible your feelings about what you want will change going forward. That’s pretty normal.

    It’s also very normal for the pressure (do you know what I mean?) that caused your egg to crack to suddenly ease up, and make you start doubting yourself: whether you really want or deserve this. So be ready for that. Don’t forget that you’ve felt this way all your life!

    And welcome to the fold! We’ve all been through exactly where you are right now.