Advent of Code, Day 2
In the 2nd day of Advent of Code, the task is to interpret “Intcode” programs.
Quoted from AoC:
An Intcode program is a list of integers separated by commas (like 1,0,0,3,99). To run one, start by looking at the first integer (called position 0). Here, you will find an opcode - either 1, 2, or 99. The opcode indicates what to do; for example, 99 means that the program is finished and should immediately halt. Encountering an unknown opcode means something went wrong.
The opcodes are:
- 1 - Add
- 2 - Multiply
- 99 - Halt
Here’s my solution in Haskell:
module Day2 where
import Data.Vector (Vector, fromList, head, (!), (//))
import Data.List.Split (splitOn)
type Intcode = Vector Int
data Op = Add | Mult | Halt
intToOp :: Int -> Op
intToOp 1 = Add
intToOp 2 = Mult
intToOp 99 = Halt
intToOp x = error $ "invalid opCode, should not happen" ++ show x
eval :: Intcode -> Intcode
eval intcode = go intcode 0
where
go intcode currentIndex =
let
op = intToOp $ intcode ! currentIndex
v1Pos = intcode ! (currentIndex + 1)
v2Pos = intcode ! (currentIndex + 2)
savePos = intcode ! (currentIndex + 3)
nextIndex = currentIndex + 4
v1 = intcode ! v1Pos
v2 = intcode ! v2Pos
in
case op of
Add -> go (intcode // [(savePos, (v1 + v2))]) nextIndex
Mult -> go (intcode // [(savePos, (v1 * v2))]) nextIndex
Halt -> intcode
part1 :: IO ()
part1 = do
input <- readFile "../input/day2.txt"
let intcode = fromList (read <$> splitOn "," input)
let result = eval $ intcode // [(1, 12), (2, 2)]
putStrLn $ show $ result ! 0
part2 :: IO ()
part2 = do
input <- readFile "../input/day2.txt"
let memory = fromList (read <$> splitOn "," input)
let inputs = [(i, j) | i <- [0..99], j <- [0..99]]
let results = fmap (\(noun, verb) -> (eval $ memory // [(1, noun), (2, verb)], noun, verb)) inputs
let (result, noun, verb) = Prelude.head $ filter (\(res, _, _) -> (res ! 0) == 19690720) results
putStrLn $ show $ 100 * noun + verb
In the eval
function, you might notice that I don’t check if the indices are within the bounds of the vector. Wont this blow up when we get to the end of the intcode? Nope.
Haskell is a lazy language, it doesn’t evaluate thing until it’s needed. And when he program gets to a Halt (99), it doesn’t need the other stuff (v1Pos, v2Pos etc), and thus it doesn’t evaluate them.
Pretty cool.
I also did the meat of the problem in Clojure:
(defn apply-op [op v1-pos v2-pos save-pos intcode]
(let [v1 (nth intcode v1-pos)
v2 (nth intcode v2-pos)]
(update intcode save-pos (constantly (op v1 v2)))))
(defn eval-intcode [intcode]
(loop [current-position 0
intcode intcode]
(let [[opcode v1-pos v2-pos save-pos]
(vec (drop current-position intcode))]
(condp = opcode
1 (recur
(+ current-position 4)
(apply-op + v1-pos v2-pos save-pos intcode))
2 (recur
(+ current-position 4)
(apply-op * v1-pos v2-pos save-pos intcode))
99 intcode))))