Day 1: Secret Entrance

Megathread guidelines

  • Keep top level comments as only solutions, if you want to say something other than a solution put it in a new post. (replies to comments can be whatever)
  • You can send code in code blocks by using three backticks, the code, and then three backticks or use something such as https://topaz.github.io/paste/ if you prefer sending it through a URL

FAQ

  • VegOwOtenks@lemmy.world
    link
    fedilink
    arrow-up
    3
    ·
    21 days ago

    The struggled with a counting solution for a long time. I submitted with a simple enumerative solution in the end but managed to get it right after some pause time:

    Haskell

    Fast to Run, Stepwise Solution
    {-# LANGUAGE LambdaCase #-}
    {-# LANGUAGE OrPatterns #-}
    module Main (main) where
    
    import Control.Monad ( (<$!>) )
    import qualified Data.List as List
    
    main :: IO ()
    main = do
      rotations <- (fmap parseRotation . init . lines) <$!> getContents
      print $ part1 rotations
      print $ part2 rotations
    
    part2 :: [Either Int Int] -> Int
    part2 rotations = let
    
        foldRotation (position, zeroCount) operation = case operation of
          Left y -> let
            (zeroPasses, y') = y `divMod` 100
            position' = (position - y') `mod` 100
            zeroCount' = zeroPasses + zeroCount + if position <= y' then fromEnum $ position /= 0 else 0
            in (position', zeroCount')
          Right y -> let
            (zeroPasses, y') = y `divMod` 100
            position' = (position + y') `mod` 100
            zeroCount' = zeroPasses + zeroCount + if y' + position >= 100 then 1 else 0
            in (position', zeroCount')
    
      in snd $ List.foldl' foldRotation (50, 0) rotations
    
    part1 :: [Either Int Int] -> Int
    part1 rotations = let
        positions = List.scanl applyRotation 50 rotations
      in List.length . filter (== 0) $ positions
    
    applyRotation :: Int -> Either Int Int -> Int
    applyRotation x = \case
      Left y -> (x - y) `mod` 100
      Right y -> (x + y) `mod` 100
    
    parseRotation :: String -> Either Int Int
    parseRotation = \case
      'R':rest -> Right $ read rest
      'L':rest -> Left $ read rest
      bad -> error $ "invalid rotation operation: " ++ bad
    
    Fast to Code, Exhaustively Enumerating Solution
    -- | Old solution enumerating all the numbers
    
    part2' :: [Either Int Int] -> Int
    part2' rotations = let
      intermediatePositions _ [] = []
      intermediatePositions x (op:ops) = case op of
        Left 0; Right 0 -> intermediatePositions x ops
        Left y -> let x' = pred x `mod` 100 in x' : intermediatePositions x' (Left (pred y) : ops)
        Right y -> let x' = succ x `mod` 100 in x' : intermediatePositions x' (Right (pred y) : ops)
      in List.length . List.filter (== 0) . intermediatePositions 50 $ rotations
    
    • Camille@lemmy.ml
      link
      fedilink
      arrow-up
      2
      ·
      21 days ago

      Why are you preferring lambda-case over plain old pattern matching as in the following snippet? I didn’t know this language feature existed and I am now curious :)

      applyRotation :: Int -> Either Int Int -> Int
      applyRotation x (Left y) = (x - y) `mod` 100
      applyRotation x (Right y) = (x + y) `mod` 100
      
      • VegOwOtenks@lemmy.world
        link
        fedilink
        English
        arrow-up
        1
        ·
        edit-2
        21 days ago

        Thank you for the excellent question. This made me reflect on my coding style and why I actually chose this. Maybe you have noticed, my usage of LambdaCase is inconsistent: I didn’t use it in the definition of foldRotation. Which happened with some refactorings (You couldn’t know that, I didn’t tell anywhere), but still.

        After going through some ‘old’ code I found that I didn’t start using it until early this year. (For context: I started doing Haskell in September 2024) But that may just coincide with me installing HLS.

        Anyway, back to the topic: I actually think it’s very elegant because it saves re-typing the function name and/or other parameters. It also easily allows me to add further arguments to the function (but only before the last one). In my mind, this is where LambdaCase shines.

        Sometimes I end up refactoring functions because it’s very hard to match on multiple arguments using LambdaCase. I also try to avoid adding arguments in the back, which might bite me later and limits flexibility a lot.

        Moaaar Backstory

        I picked it up in some forum discussion I read where somebody argued that using explicit matches litters the Codebase with re-definitions of the same functions. It makes grep-ing the source hard. I was easily influenced by this and adopted it.

        I think this is not the way I like to go about it. I would rather use Hoogle, Haddock or HLS to search in my source.