Day 8 in progress
This commit is contained in:
parent
a0ec7f0b63
commit
54ddd70f1d
1 changed files with 69 additions and 1 deletions
70
day8/main.hs
70
day8/main.hs
|
@ -1,10 +1,78 @@
|
|||
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
||||
#! nix-shell -p ghcid
|
||||
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [shower])"
|
||||
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [pretty-simple vector containers])"
|
||||
#! nix-shell -i "ghcid -c 'ghci -Wall' -T main"
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
import Text.Pretty.Simple
|
||||
-- import Data.List.NonEmpty (NonEmpty(..))
|
||||
-- import qualified Data.List.NonEmpty as NE
|
||||
import Data.Vector (Vector)
|
||||
import Debug.Trace (trace)
|
||||
import Data.List (unfoldr)
|
||||
import qualified Data.Vector as V
|
||||
|
||||
data Op = OpNop
|
||||
| OpJmp !Int
|
||||
| OpAcc !Int
|
||||
deriving (Show, Ord, Eq)
|
||||
|
||||
data VMState = VMRun
|
||||
deriving (Show, Ord, Eq)
|
||||
|
||||
data VirtualMachine = VM
|
||||
{ pgmCounter :: !Int
|
||||
, pgmAccumulator :: !Int
|
||||
, pgmInstructions :: Vector Op
|
||||
, vmState :: VMState
|
||||
}
|
||||
deriving (Show, Ord, Eq)
|
||||
|
||||
initialVM :: Vector Op -> VirtualMachine
|
||||
initialVM ins = VM 1 0 ins VMRun
|
||||
|
||||
stepVM :: VirtualMachine -> Maybe (VirtualMachine, VirtualMachine)
|
||||
stepVM vm@(VM c a ins VMRun) = Just (vm, go (ins V.! (c-1)))
|
||||
where
|
||||
go OpNop = VM (c+1) a ins VMRun
|
||||
go (OpJmp n) = VM (c+n) a ins VMRun
|
||||
go (OpAcc n) = VM (c+1) (a+n) ins VMRun
|
||||
|
||||
exampleData :: [String]
|
||||
exampleData =
|
||||
[ "nop +0"
|
||||
, "acc +1"
|
||||
, "jmp +4"
|
||||
, "acc +3"
|
||||
, "jmp -3"
|
||||
, "acc -99"
|
||||
, "acc +1"
|
||||
, "jmp -4"
|
||||
, "acc +6"
|
||||
]
|
||||
|
||||
vmFromInput :: [String] -> VirtualMachine
|
||||
vmFromInput input = initialVM (ins input)
|
||||
where
|
||||
ins = V.fromList . (map (parseOp . (\(x,y)-> (x,tail y)) . break (== ' ')))
|
||||
parseOp :: (String,String) -> Op
|
||||
parseOp ("nop",_) = OpNop
|
||||
parseOp ("acc",'+':s) = OpAcc (read s :: Int)
|
||||
parseOp ("jmp",'+':s) = OpJmp (read s :: Int)
|
||||
parseOp ("acc",s) = OpAcc (read s :: Int)
|
||||
parseOp ("jmp",s) = OpJmp (read s :: Int)
|
||||
parseOp s@_ = trace (show s) $ undefined
|
||||
|
||||
-- Find smallest looping prefix in list of Int, returns associated pgmAccumulator
|
||||
solvePart1 :: VirtualMachine -> Int
|
||||
solvePart1 vm = undefined vm
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
putStrLn "Day 8 - Part 1"
|
||||
putStrLn ":: Tests"
|
||||
pPrint exampleData
|
||||
print $ take 10 $ (\vm -> (pgmCounter vm, pgmAccumulator vm)) <$> unfoldr stepVM (vmFromInput exampleData)
|
||||
putStrLn ":: Solving part 1"
|
||||
print $ solvePart1 (vmFromInput exampleData)
|
||||
|
|
Loading…
Reference in a new issue