From: Neil Smith Date: Mon, 12 Dec 2016 16:36:21 +0000 (+0000) Subject: Day 12 X-Git-Url: https://git.njae.me.uk/?p=advent-of-code-16.git;a=commitdiff_plain;h=22109336eb81722af230c53ef5938475a846efb8 Day 12 --- diff --git a/advent12.hs b/advent12.hs new file mode 100644 index 0000000..21ed32d --- /dev/null +++ b/advent12.hs @@ -0,0 +1,133 @@ +import Text.Parsec hiding (State) +import Text.ParserCombinators.Parsec.Number +import Control.Applicative ((<$), (<*), (*>), (<*>), liftA) +import Data.List (partition, union, intersect, tails) +import Data.Char (isDigit) +import Control.Monad.State.Lazy + +data Location = Literal Int | Register Char deriving (Show) +data Instruction = Cpy Location Location | + Inc Location | + Dec Location | + Jnz Location Int + deriving (Show) + +data Machine = Machine { a :: Int + , b :: Int + , c :: Int + , d :: Int + , pc :: Int + , instructions :: [Instruction]} + deriving (Show) + +emptyMachine :: Machine +emptyMachine = Machine {a=0, b=0, c=0, d=0, pc=0, instructions=[]} + +main :: IO () +main = do + text <- readFile "advent12.txt" + let instructions = successfulParse $ parseIfile text + part1 instructions + part2 instructions + + +part1 :: [Instruction] -> IO () +part1 instrs = + do let m0 = emptyMachine {instructions=instrs} + let mf = snd $ runState runMachine m0 + print (a mf) + +part2 :: [Instruction] -> IO () +part2 instrs = + do let m0 = emptyMachine {instructions=instrs, c=1} + let mf = snd $ runState runMachine m0 + print (a mf) + + + +runMachine :: State Machine () +runMachine = + do m <- get + if (pc m) >= (length $ instructions m) + then return () + else do executeStep + runMachine + +executeStep :: State Machine () +executeStep = + do m <- get + let i = (instructions m)!!(pc m) + put (executeInstruction i m) + +executeInstruction :: Instruction -> Machine -> Machine +executeInstruction (Inc (Register r)) m = m' {pc=pc1} + where pc1 = (pc m) + 1 + v = evaluate m (Register r) + m' = writeValue m (Register r) (v+1) +executeInstruction (Dec (Register r)) m = m' {pc=pc1} + where pc1 = (pc m) + 1 + v = evaluate m (Register r) + m' = writeValue m (Register r) (v-1) +executeInstruction (Cpy s d) m = m' {pc=pc1} + where pc1 = (pc m) + 1 + v = evaluate m s + m' = writeValue m d v +executeInstruction (Jnz s d) m + | v == 0 = m {pc=pc1} + | otherwise = m {pc=pcj} + where pc1 = (pc m) + 1 + pcj = (pc m) + d + v = evaluate m s + + +evaluate :: Machine -> Location -> Int +evaluate _ (Literal i) = i +evaluate m (Register r) = + case r of + 'a' -> (a m) + 'b' -> (b m) + 'c' -> (c m) + 'd' -> (d m) + +writeValue :: Machine -> Location -> Int -> Machine +writeValue m (Literal i) _ = m +writeValue m (Register r) v = + case r of + 'a' -> m {a=v} + 'b' -> m {b=v} + 'c' -> m {c=v} + 'd' -> m {d=v} + + +instructionFile = instructionLine `endBy` newline +-- instructionLine = choice [cpyL, incL, decL, jnzL] +instructionLine = incL <|> decL <|> cpyL <|> jnzL + +incL = incify <$> (string "inc" *> spaces *> (oneOf "abcd")) + where incify r = Inc (Register r) +decL = decify <$> (string "dec" *> spaces *> (oneOf "abcd")) + where decify r = Dec (Register r) +cpyL = cpyify <$> (string "cpy" *> spaces *> ((many1 letter) <|> (many1 digit))) + <*> (spaces *> (oneOf "abcd")) + where cpyify s r = Cpy (readLocation s) (Register r) +jnzL = jnzify <$> (string "jnz" *> spaces *> ((many1 letter) <|> (many1 digit))) + <*> (spaces *> int) + where jnzify r d = Jnz (readLocation r) d + + +readLocation :: String -> Location +readLocation l + | all (isDigit) l = Literal (read l) + | otherwise = Register (head l) + + + +parseIfile :: String -> Either ParseError [Instruction] +parseIfile input = parse instructionFile "(unknown)" input + +parseIline :: String -> Either ParseError Instruction +parseIline input = parse instructionLine "(unknown)" input + +successfulParse :: Either ParseError [a] -> [a] +successfulParse (Left _) = [] +successfulParse (Right a) = a \ No newline at end of file diff --git a/advent12.txt b/advent12.txt new file mode 100644 index 0000000..538e9ea --- /dev/null +++ b/advent12.txt @@ -0,0 +1,23 @@ +cpy 1 a +cpy 1 b +cpy 26 d +jnz c 2 +jnz 1 5 +cpy 7 c +inc d +dec c +jnz c -2 +cpy a c +inc a +dec b +jnz b -2 +cpy c b +dec d +jnz d -6 +cpy 18 c +cpy 11 d +inc a +dec d +jnz d -2 +dec c +jnz c -5 diff --git a/day12.html b/day12.html new file mode 100644 index 0000000..7ded008 --- /dev/null +++ b/day12.html @@ -0,0 +1,154 @@ + + + + +Day 12 - Advent of Code 2016 + + + + + + +

Advent of Code

Neil Smith (AoC++) 24*

        //2016

+ + + +
+

--- Day 12: Leonardo's Monorail ---

You finally reach the top floor of this building: a garden with a slanted glass ceiling. Looks like there are no more stars to be had.

+

While sitting on a nearby bench amidst some tiger lilies, you manage to decrypt some of the files you extracted from the servers downstairs.

+

According to these documents, Easter Bunny HQ isn't just this building - it's a collection of buildings in the nearby area. They're all connected by a local monorail, and there's another building not far from here! Unfortunately, being night, the monorail is currently not operating.

+

You remotely connect to the monorail control systems and discover that the boot sequence expects a password. The password-checking logic (your puzzle input) is easy to extract, but the code it uses is strange: it's assembunny code designed for the new computer you just assembled. You'll have to execute the code and get the password.

+

The assembunny code you've extracted operates on four registers (a, b, c, and d) that start at 0 and can hold any integer. However, it seems to make use of only a few instructions:

+
    +
  • cpy x y copies x (either an integer or the value of a register) into register y.
  • +
  • inc x increases the value of register x by one.
  • +
  • dec x decreases the value of register x by one.
  • +
  • jnz x y jumps to an instruction y away (positive means forward; negative means backward), but only if x is not zero.
  • +
+

The jnz instruction moves relative to itself: an offset of -1 would continue at the previous instruction, while an offset of 2 would skip over the next instruction.

+

For example:

+
cpy 41 a
+inc a
+inc a
+dec a
+jnz a 2
+dec a
+
+

The above code would set register a to 41, increase its value by 2, decrease its value by 1, and then skip the last dec a (because a is not zero, so the jnz a 2 skips it), leaving register a at 42. When you move past the last instruction, the program halts.

+

After executing the assembunny code in your puzzle input, what value is left in register a?

+
+

Your puzzle answer was 318009.

--- Part Two ---

As you head down the fire escape to the monorail, you notice it didn't start; register c needs to be initialized to the position of the ignition key.

+

If you instead initialize register c to be 1, what value is now left in register a?

+
+

Your puzzle answer was 9227663.

Both parts of this puzzle are complete! They provide two gold stars: **

+

At this point, you should return to your advent calendar and try another puzzle.

+

If you still want to see it, you can get your puzzle input.

+

You can also this puzzle.

+
+ + + + + + \ No newline at end of file