Skip to content

Instantly share code, notes, and snippets.

@saevarb
Created December 2, 2019 19:13
Show Gist options
  • Save saevarb/1164ede0dd9e01fda1bdf1ff0d229dae to your computer and use it in GitHub Desktop.
Save saevarb/1164ede0dd9e01fda1bdf1ff0d229dae to your computer and use it in GitHub Desktop.
{-# LANGUAGE FlexibleContexts #-}
module Day2 where
import Prelude hiding (read)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Vector as V
import Data.Maybe (mapMaybe)
import Control.Monad.State (liftM2, modify, gets, execState)
import Data.List (find)
import Util
data Opcode
= Add Int Int Int
| Mul Int Int Int
| Halt
deriving (Show, Read, Eq)
data Program
= Program
{ memory :: !(V.Vector Int)
, program :: ![Opcode]
}
deriving (Show, Read, Eq)
parse :: [Int] -> Program
parse input =
Program
{ memory = V.fromList input
, program = mapMaybe parseChunk . chunk 4 $ input
}
where
parseChunk [1, x, y, o] = return $ Add x y o
parseChunk [2, x, y, o] = return $ Mul x y o
parseChunk (99:_) = return Halt
parseChunk _ = Nothing
eval :: Program -> Int -> Int -> Program
eval p noun verb = execState (setup >> mapM step (program p)) p
where
setup = do
write 1 noun
write 2 verb
step (Add x y o) = liftM2 (+) (read x) (read y) >>= write o
step (Mul x y o) = liftM2 (*) (read x) (read y) >>= write o
step Halt = return ()
read x = gets ((V.! x) . memory)
write d x = modify (\s -> s { memory = memory s V.// [(d, x)] })
run :: IO ()
run = do
inp <- readInput "day2" (T.split (== ','))
let parsed = parse inp
result = eval parsed 12 2
putStrLn "Part 1:"
print $ memory result V.! 0
putStrLn "Part 2:"
print $ part2 parsed
where
part2 parsed = find
( (== 19690720)
. (V.! 0)
. memory
. uncurry (eval parsed)
) inputs
inputs = [(x, y) | x <- [0 .. 99], y <- [0 .. 99]]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment