Day 3: Mull It Over

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

  • Quant@programming.dev
    link
    fedilink
    arrow-up
    1
    ·
    5 days ago

    Uiua

    Regex my beloved <3

    Run with example input here

    FindMul  regex "mul\\((\\d+),(\\d+)\\)"
    
    PartOne  (
      &rs  &fo "input-3.txt"
      FindMul
      /+≡(×°⊟⋕⊏1_2)
    )
    
    IdDont  ⊗□"don't()"
    
    PartTwo  (
      &rs  &fo "input-3.txt"
      regex "mul\\(\\d+,\\d+\\)|do\\(\\)|don't\\(\\)"
      (IdDont.
        1⊃↘↙
        ⊗□"do()".
        ⊂↘1
      | IdDont.
        ≠⧻,
      )
      ▽♭=0⌕□"do()".
      (×°⊟⋕⊏1_2FindMul)
      /+
    )
    
    &p "Day 3:"
    &pf "Part 1: "
    &p PartOne
    &pf "Part 2: "
    &p PartTwo
    
  • LeixB@lemmy.world
    link
    fedilink
    arrow-up
    0
    ·
    9 days ago

    Haskell

    module Main where
    
    import Control.Arrow hiding ((+++))
    import Data.Char
    import Data.Functor
    import Data.Maybe
    import Text.ParserCombinators.ReadP hiding (get)
    import Text.ParserCombinators.ReadP qualified as P
    
    data Op = Mul Int Int | Do | Dont deriving (Show)
    
    parser1 :: ReadP [(Int, Int)]
    parser1 = catMaybes <$> many ((Just <$> mul) <++ (P.get $> Nothing))
    
    parser2 :: ReadP [Op]
    parser2 = catMaybes <$> many ((Just <$> operation) <++ (P.get $> Nothing))
    
    mul :: ReadP (Int, Int)
    mul = (,) <$> (string "mul(" *> (read <$> munch1 isDigit <* char ',')) <*> (read <$> munch1 isDigit <* char ')')
    
    operation :: ReadP Op
    operation = (string "do()" $> Do) +++ (string "don't()" $> Dont) +++ (uncurry Mul <$> mul)
    
    foldOp :: (Bool, Int) -> Op -> (Bool, Int)
    foldOp (_, n) Do = (True, n)
    foldOp (_, n) Dont = (False, n)
    foldOp (True, n) (Mul a b) = (True, n + a * b)
    foldOp (False, n) _ = (False, n)
    
    part1 = sum . fmap (uncurry (*)) . fst . last . readP_to_S parser1
    part2 = snd . foldl foldOp (True, 0) . fst . last . readP_to_S parser2
    
    main = getContents >>= print . (part1 &&& part2)