13
submitted 8 months ago* (last edited 8 months ago) by CameronDev@programming.dev to c/advent_of_code@programming.dev

Day 20: Pulse

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

you are viewing a single comment's thread
view the rest of the comments
[-] lwhjp 1 points 8 months ago

Haskell

Very cute. There's one like this every year...

I suppose I could write some code to replicate what I did by hand, but I guess that would be missing the point? (And I don't want to think about this problem any more)

Solution

{-# LANGUAGE BinaryLiterals #-}
{-# LANGUAGE TupleSections #-}

import Control.Monad
import Control.Monad.State.Strict
import Data.List
import Data.List.Split
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map

data Module = Broadcast | FlipFlop | Conjoin

type Connection = (Module, [String])

readConnection :: String -> (String, Connection)
readConnection s =
  let [a, b] = splitOn " -> " s
      outs = splitOn ", " b
      (name, m) = case a of
        "broadcaster" -> (a, Broadcast)
        ('%' : n) -> (n, FlipFlop)
        ('&' : n) -> (n, Conjoin)
   in (name, (m, outs))

type Signal = (String, String, Bool)

buildNetwork :: [(String, Connection)] -> ([Signal] -> State (Map (String, String) Bool) [Signal], Map (String, String) Bool)
buildNetwork input = (go, initState)
  where
    network = Map.fromList input
    initState = Map.fromList $ do
      (src, (_, outs)) <- input
      out <- outs
      case network Map.!? out of
        Just (Conjoin, _) -> return ((out, src), False)
        _ -> mempty
    go :: [Signal] -> State (Map (String, String) Bool) [Signal]
    go [] = return []
    go sigs = (sigs ++) <$> (mapM dispatch sigs >>= go . concat)
    dispatch :: Signal -> State (Map (String, String) Bool) [Signal]
    dispatch (src, dest, v) =
      case network Map.!? dest of
        Just (Broadcast, outs) -> return $ map (dest,,v) outs
        Just (FlipFlop, outs)
          | v -> return []
          | otherwise -> do
              newState <- gets (maybe True not . (Map.!? (dest, dest)))
              modify (Map.insert (dest, dest) newState)
              return $ map (dest,,newState) outs
        Just (Conjoin, outs) -> do
          modify (Map.insert (dest, src) v)
          mem <- gets (Map.filterWithKey (\(n, _) _ -> n == dest))
          return $ map (dest,,not $ and mem) outs
        _ -> return []

part1 :: [(String, Connection)] -> Int
part1 input =
  let (go, initState) = buildNetwork input
      sigs = concat $ evalState (replicateM 1000 $ go [("button", "broadcaster", False)]) initState
      (hi, lo) = partition (\(_, _, v) -> v) sigs
   in length lo * length hi

part2 _ =
  foldl1'
    lcm
    -- by inspection
    [ 0b111101011001,
      0b111111010011,
      0b111010110111,
      0b111011101111
    ]

main = do
  input <- map readConnection . lines <$> readFile "input20"
  print $ part1 input
  print $ part2 input

this post was submitted on 20 Dec 2023
13 points (100.0% liked)

Advent Of Code

736 readers
1 users here now

An unofficial home for the advent of code community on programming.dev!

Advent of Code is an annual Advent calendar of small programming puzzles for a variety of skill sets and skill levels that can be solved in any programming language you like.

AoC 2023

Solution Threads

M T W T F S S
1 2 3
4 5 6 7 8 9 10
11 12 13 14 15 16 17
18 19 20 21 22 23 24
25

Rules/Guidelines

Relevant Communities

Relevant Links

Credits

Icon base by Lorc under CC BY 3.0 with modifications to add a gradient

console.log('Hello World')

founded 1 year ago
MODERATORS