Advent of Code 2022 - Day 10: Cathode-Ray Tube
In today's double feature, we're tackling Day 10: Cathod-Ray Tube. The challenge is to use a list of assembly-code-like instructions to simulate the state of a small device.
Catching strong 2019 vibes...
Parsing the instructions
Parsing this input line by line is typical of most days. We split it into lines, and then create a small Parsec parser that can convert those lines to a data type. The data type then allows us to do pattern matching in our other "business logic" functions.
There are two small notes today:
- I unwrapped the result with
fromRight []
so that my tests don't need to operate on Eithers. This did, however, cause me to miss a parsing error for some time, as it was silently replaced with a valid-but-empty list of instructions. - Our
parseInt
function needed to be expanded to handle negative numbers. Whoops!parseInt = read <$> many1 (char '-' <|> digit)
Here's the rest of the parsing code:
import Data.Either
import Input
import Text.ParserCombinators.Parsec
data Instruction = Noop | Addx Int
deriving (Show, Eq)
parseInstruction :: GenParser Char u Instruction
parseInstruction = parseNoop <|> parseAddx
where
parseNoop = try $ string "noop" >> return Noop
parseAddx = try $ string "addx " >> Addx <$> parseInt
input :: IO [Instruction]
input = fromRight [] . traverse (parse parseInstruction "") . lines <$> readDay 2022 10
Running Instructions With State
We have a list of instructions and a register, and our goal is to simulate "cycles." We need a way to keep track of the result of each cycle and the state of the register for the next cycle. We can do that with the State monad!
With the State monad, we define each computation as a function from some previous state, to both a value and an updated state. We can chain these computations together, and each will receive the state from the previous computation.
Since we need to know the value of the register at any arbitrary cycle, let's have each instruction return a list of those values. The noop instruction takes one cycle to complete, so it will return a list with just one of the register value in it. The addx instruction takes two cycles, so it will return a list of length 2.
noop :: State Int [Int]
noop = do
x <- get
return [x]
addx :: Int -> State Int [Int]
addx v = do
x <- get
put (x + v) -- Update the register for the next instruction
return [x, x] -- Takes 2 cycles to complete
step :: Instruction -> State Int [Int]
step Noop = noop
step (Addx v) = addx v
Part 1 - Compute and inspect
For part 1, we want to run our computation and inspect the value at particular cycles. We'll use a function compute
to calculate a list of Int pairs. Let's look at the code first:
compute :: [Instruction] -> [(Int, Int)]
compute = zip [1 ..] . flip evalState 1 . fmap concat . traverse step
What is this doing?
traverse step
: Look at the type of traverse:traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
Step is our function from Instruction to State Int [Int]. Our second argument comes from
compute
and is a list of Instructions. Our return type is then a State Int [[Int]]. In other words, a computation that can be given an initial state and result in a list of lists of register values.fmap concat
: Flatten our list-of-lists into a single list of register values. We usefmap
to concatenate the value inside the State monad (which is also a Functor).flip evalState 1
: Run our stateful computation with the initial register value of 1.zip [1 ..]
: Attach the cycle count to each register value. This will make it easier to find the 20th, 60th, etc.
Part 1 - Signal Strength
With all that in place, the only remaining piece of Part 1 is to compute the signal strength:
part1 :: [Instruction] -> Int
part1 = sum . fmap signalStrength . compute
where
signalStrength (i, x)
| i `mod` 40 == 20 && i <= 220 = i * x
| otherwise = 0
Part 2 - Rendering Sprites
Part 2 sounds much more complicated than it turns out to be. We have our computation all ready to go, so we just need to see if the cycle instruction and register value correspond to painting a pixel or not. The cycle instruction is 1-indexed, so we need to subtract 1 and modulo the length of the line (40). If that's within 1 of the register value, we paint a pixel.
Advent of Code examples use .
and #
to represent dark and light squares. I've learned my lesson over the years, and will use the much clearer '⬛' and '🟩'.
part2 :: [Instruction] -> String
part2 = unlines . chunksOf 40 . fmap render . compute
where
render (i, x) = if abs (x - ((i - 1) `mod` 40)) <= 1 then '🟩' else '⬛'
Full Code
module AOC2022.Day10 (spec) where
import Control.Monad.State.Lazy
import Data.Either
import Data.List.Split
import Input
import Test.Hspec
import Text.ParserCombinators.Parsec hiding (State)
input :: IO [Instruction]
input = fromRight [] . traverse (parse parseInstruction "") . lines <$> readDay 2022 10
spec :: IO ()
spec = hspec $ do
describe "Day 10" $ do
describe "Part 1" $ do
it "runs on custom input" $ do
myInput <- input
part1 myInput `shouldBe` 0 -- redacted
describe "Part 2" $ do
it "runs on custom input" $ do
myInput <- input
part2 myInput `shouldBe` "" --redacted
data Instruction = Noop | Addx Int
deriving (Show, Eq)
parseInstruction :: GenParser Char u Instruction
parseInstruction = parseNoop <|> parseAddx
where
parseNoop = try $ string "noop" >> return Noop
parseAddx = try $ string "addx " >> Addx <$> parseInt
noop :: State Int [Int]
noop = do
x <- get
return [x]
addx :: Int -> State Int [Int]
addx v = do
x <- get
put (x + v) -- Update the register
return [x, x] -- Takes 2 cycles to complete
step :: Instruction -> State Int [Int]
step Noop = noop
step (Addx v) = addx v
compute :: [Instruction] -> [(Int, Int)]
compute = zip [1 ..] . flip evalState 1 . fmap concat . traverse step
part1 :: [Instruction] -> Int
part1 = sum . fmap signalStrength . compute
where
signalStrength (i, x)
| i `mod` 40 == 20 && i <= 220 = i * x
| otherwise = 0
part2 :: [Instruction] -> String
part2 = unlines . chunksOf 40 . fmap render . compute
where
render (i, x) = if abs (x - ((i - 1) `mod` 40)) <= 1 then '🟩' else '⬛'
Advent of Code 2022 Series
This post is part of a series describing my Haskell solutions to Advent of Code 2022.
Next: Day 11: Monkey in the Middle Previous: Day 9: Rope Bridge
Cheers!