3
\$\begingroup\$

Today I solved the Advent of Code - Day 8 challenge in Haskell. Although the code runs fine and produces the correct results, I'm sure there are lots of improvements to be made, as I am a Haskell beginner.

The Challenge

The challenge is to build a "CPU" that can parse and execute instructions such as these:

a dec -186 if b != -2
a inc 585 if c >= 9

In the example above, a, b and c are registers. You don't know upfront what are the registers of your particular CPU, but it is specified that all registers start with the value 0. So I modeled the whole thing as a Data.Map String Int, where the String represents the register name and the Int is the value.

The goal is to execute a number of such instructions on a new CPU (all registers having the value 0) and answer two questions:

  • at the end, what is the maximum value stored in any register?
  • what is the maximum value stored in a register during the entire process?

The Code

The full code with some tests is available on Github, but I also pasted it below.

The thing that bothers me the most is how I handled the comparisons (>=, ==, !=, etc.). It feels like there's a lot more code than needs to be, but don't know what the best solution for that is.

I could have mapped directly from the textual representation to the corresponding comparison functions (>=, (==), (/=), etc.). But I modeled it like this because I wanted Condition and Instruction to derive Eq and Show, so I would be able to test the parse function, making equality assertions on instances of the Instruction type.

import Test.Hspec
import qualified Data.Map as M
import Data.Maybe
type Register = String
data Comparison = Eq | Neq | Gt | Gte | Lt | Lte
 deriving (Eq, Show)
type Condition = (String, Comparison, Int)
data Instruction = Instruction Register Int Condition deriving (Eq, Show)
type CPU = M.Map Register Int
operation :: Comparison -> (Int -> Int -> Bool)
operation Eq = (==)
operation Neq = (/=)
operation Gt = (>)
operation Gte = (>=)
operation Lt = (<)
operation Lte = (<=)
getVal :: CPU -> Register -> Int
getVal cpu r = fromMaybe 0 (M.lookup r cpu)
eval :: CPU -> Condition -> Bool
eval cpu (reg, comp, val) = op x val
 where op = operation comp
 x = getVal cpu reg
exec :: CPU -> Instruction -> CPU
exec cpu (Instruction reg incr cond) | eval cpu cond = M.insert reg newval cpu
 | otherwise = cpu
 where newval = getVal cpu reg + incr
parse :: String -> Instruction
parse str = Instruction reg incr (condreg, comp, val)
 where [reg, op, incdecstr, _, condreg, compstr, valstr] = words str
 incdec = read incdecstr
 incr = if op == "dec" then (-incdec) else incdec
 val = read valstr
 comp = case compstr of
 "==" -> Eq
 "!=" -> Neq
 ">" -> Gt
 ">=" -> Gte
 "<" -> Lt
 "<=" -> Lte
highest :: CPU -> Int
highest cpu | M.null cpu = 0
 | otherwise = maximum (M.elems cpu)
testCPU :: CPU
testCPU = M.fromList [("a", 10),
 ("b", 20)]
getInstructions :: IO [Instruction]
getInstructions = do
 text <- readFile "input/day8.in"
 return $ map parse $ lines text
main = hspec $ do
 describe "CPU" $ do
 it "can parse instructions" $ do
 parse "d dec 461 if oiy <= 1" `shouldBe`
 Instruction "d" (-461) ("oiy", Lte, 1)
 parse "eai inc 302 if pce >= -6317" `shouldBe`
 Instruction "eai" 302 ("pce", Gte, (-6317))
 it "can read register values" $ do
 getVal testCPU "a" `shouldBe` 10
 getVal testCPU "b" `shouldBe` 20
 it "new registers start at 0" $ do
 getVal testCPU "unknown_reg" `shouldBe` 0
 it "can evaluate conditions" $ do
 eval testCPU ("a", Gt , 9) `shouldBe` True
 eval testCPU ("a", Lt , 10) `shouldBe` False
 eval testCPU ("a", Lte, 10) `shouldBe` True
 eval testCPU ("a", Gte, 11) `shouldBe` False
 eval testCPU ("a", Gte, 10) `shouldBe` True
 eval testCPU ("a", Eq , 10) `shouldBe` True
 eval testCPU ("a", Neq, 10) `shouldBe` False
 eval testCPU ("b", Eq , 10) `shouldBe` False
 eval testCPU ("b", Neq, 10) `shouldBe` True
 describe "instruction execution" $ do
 it "registers are affected" $ do
 let instr = Instruction "a" 1 ("a", Gt, 0)
 let cpu' = exec testCPU instr
 getVal cpu' "a" `shouldBe` 11
 it "registers are unchanged if condition is false" $ do
 let instr = Instruction "a" 1 ("a", Gt, 100000)
 let cpu' = exec testCPU instr
 cpu' `shouldBe` testCPU
 describe "questions" $ do
 it "answers Q1" $ do
 instrs <- getInstructions
 let cpu = M.fromList []
 let finalState = foldl exec cpu instrs
 putStrLn "The highest value after all instructions:"
 print $ highest finalState
 it "answers Q2" $ do
 instrs <- getInstructions
 let cpu = M.fromList []
 let (_, maxval) = foldl step (cpu, 0) instrs
 where step (c, oldmax) i = let c' = exec c i
 newmax = max oldmax (highest c')
 in (c', newmax)
 putStrLn "The highest value ever:"
 print $ maxval
asked Dec 8, 2017 at 19:33
\$\endgroup\$
2
  • \$\begingroup\$ FWIW, it looks similar to my attempt github.com/ploeh/advent-of-code-2017/blob/master/Day08/… \$\endgroup\$ Commented Dec 8, 2017 at 19:43
  • 1
    \$\begingroup\$ @MarkSeemann Thank you for your remark! BTW, I love your code, especially the parsing part. \$\endgroup\$ Commented Dec 9, 2017 at 13:12

1 Answer 1

3
\$\begingroup\$

The code itself looks fine, most of what I could say boils down to personal taste. So instead, I'm gonna take a step back and instead review the general way how you've decided to solve the problem - which is something I enjoy doing with Haskell code.

Your flow of data

Your current main is just your testing code, so let's mentally change that to something like "read instructions from a file given as argument and execute those". (Note: this is not actual Haskell code)

What are the required steps to get from "some lines in a file" to "okay, what's the highest value in any register?"?

  • map parse . lines to get a list of Instructions
  • exec to evaluate an Instruction given a CPU
  • umm... foldr (\ no wait, exec (exe.. that can't be...

The problem I see is that there is no easy way to execute multiple instructions. There's a small hotfix for that; swap the order of arguments for exec so you can do exec firstInstruction $ exec secondInstruction $ exec thirdInstruction cpu, but that's not that great either.

What happens in a CPU stays in a CPU

You can't modify values inplace, there's always a copy that's returned back - that's the way Haskell works. But this is one of the cases where it certainly would be nice to manipulate values, your CPU that is.

Introducing: State!

State (found in Control.Monad.State) is a handy monad to do exactly that - carry around a modifiable state on which you can perform many actions.

Let's think about what type of actions there actually are... honestly, there's just incrementing by some value. Easy enough then, let's write some code!

increaseRegisterBy :: Register -> Int -> State CPU ()
increaseRegisterBy reg incr = do
 cpu <- get
 cpu' = if reg `member` cpu
 then adjust (+ incr) reg cpu
 else insert reg incr cpu
 put cpu'

What that code does is:

  • get the current State
  • Increase the value in reg by incr
  • put that new value as the state to be used in subsequent calls

So if you'd have a sequence of increments like increaseRegisterBy "a" 255 >> increaseRegisterBy "a" (-255), you would get nothing out of it because those two cancel out. But you don't need to explicitly carry around the state, which is nice!

Becoming a president, or: Running the state

When it comes to state, there's three functions to use which do different things:

  • runState :: State s a -> s -> (a, s)
  • evalState :: State s a -> s -> a
  • execState :: State s a -> s -> s

The State CPU () written earlier corresponds to the State s a. s is the type of the state to carry around, a is the result of the monadic action. Since we don't care about any results, we've put it as (). If you wanted to return the new value of the modified register, you'd have to set that signature as Register -> Int -> State CPU Int.

Since we only care about the final state (for now), we should use execState, which returns the final state when it's done working the registers.

Autobots: Roll out! Transforming your Instruction

Now that we've got a way to run flashy increaseRegisterBy-actions, let's build those from your Instruction.

What we need is a function runInstruction :: Instruction -> State CPU (), which takes in an instruction and runs that instruction on the current state. Or to be precise, which returns a new function which then can be run using execState. Trippy! What does that function need to do?

  • Evaluate the condition
  • If it's true, do the stuff
  • If not, go home. Or just do nothing.

To put that into code:

runInstruction :: Instruction -> State CPU ()
runInstruction (Instruction reg incr cond) = do
 cpu <- get
 when (eval cpu cond) (increaseRegisterBy reg incr)

We get the current CPU, if eval cpu cond evaluates to true, we execute increaseRegisterBy reg incr. If not, nothing happens. That's why monads are awesome!

To glue it all together, executing a single instruction and getting the final CPU would look something like execState (runInstruction yourInstruction) startCpu.

But wait, there's more (than one instruction)

Just like when or the State monad, there's another beauty hidden in Control.Monad to use: sequence (or it's forgetful brother sequence_).

sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()

In more human terms, sequence_ takes a list (which is something Foldable) of monadic actions (m a) and produces a single monadic action which does not return anything (m ()). The intermediate results of each action are lost, but since we don't have any, we don't care.

Putting it all together

To be able to neatly execute a list of Instructions, you'd have something like this:

executeInstructions :: [Instruction] -> CPU
executeInstructions is = execState (sequence_ $ map runInstruction is) M.empty
runInstruction :: Instruction -> State CPU ()
runInstruction (Instruction reg incr cond) = do
 cpu <- get
 when (eval cpu cond) (increaseRegisterBy reg incr)
increaseRegisterBy :: Register -> Int -> State CPU ()
increaseRegisterBy reg incr = do
 cpu <- get
 cpu' = if reg `member` cpu
 then adjust (+ incr) reg cpu
 else insert reg incr cpu
 put cpu'

We want YOU to monad!

Your task, of course, would now be to actually implement your code using the State monad and all it's goodies from Control.Monad. Maybe take a look around that module, you might see interesting stuff.

As an exercise, you could rewrite the runInstruction-stuff to actually return something; maybe a tuple (Register, Int) to show which value was just supplied. You could then (by grouping and maximuming) find out the maximum value for each register.

Oh, and try to swap that main for the "read instructions from a file given as argument and execute those"-thingy. IO is a monad too, after all!

But what about the rest?

Looks fine by me, although I would have done the parsing using megaparsec, because I really like that library. It's overkill for something like this, though.

answered Dec 15, 2017 at 19:50
\$\endgroup\$
1
  • \$\begingroup\$ Thank you for taking the time to write such an elaborate answer! It opens new pathways for me in the quest to understand this wonderful language. I will definitely play more with my solution and adjust it taking your suggestions into accout. \$\endgroup\$ Commented Dec 17, 2017 at 12:44

Your Answer

Draft saved
Draft discarded

Sign up or log in

Sign up using Google
Sign up using Email and Password

Post as a guest

Required, but never shown

Post as a guest

Required, but never shown

By clicking "Post Your Answer", you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.