Copyright | (c) Eric Mertens 2019 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe |
Language | Haskell2010 |
Intcode is a virtual machine environment defined to have some arithmetic, conditional jumps, and simple input and output facilities.
The instruction set is designed with independently selectable address modes for each of its input and output parameters. The architecture is designed to be simple to implement while powerful enough to write interesting programs efficiently. The addition of a relative base pointer makes it easy to implement function calls in the language.
This Intcode architecture is defined across multiple Advent of Code 2019 tasks: 2, 5, 7, and 9
Common use modes:
- Machine construction:
new
- List functions:
intcodeToList
,effectList
- Individual machine step processing:
Step
,step
- Input/output interpretation:
Effect
,run
Submodules:
- Intcode.Machine exposes the implementation details of the interpreter state.
- Intcode.Parse provides a parser for intcode text files.
- Intcode.Opcode provides types and the decoder for opcodes.
Synopsis
- intcodeToList :: [Int] -> [Int] -> [Int]
- data Machine
- (!) :: Machine -> Int -> Int
- new :: [Int] -> Machine
- set :: Int -> Int -> Machine -> Machine
- memoryList :: Machine -> [Int]
- data Effect
- run :: Machine -> Effect
- (>>>) :: Effect -> Effect -> Effect
- followedBy :: Effect -> Effect -> Effect
- feedInput :: [Int] -> Effect -> Effect
- effectList :: Effect -> [Int] -> [Int]
- data Step
- step :: Machine -> Step
- data IntcodeFault = IntcodeFault
- runIO :: Effect -> IO ()
- hRunIO :: Handle -> Handle -> Effect -> IO ()
Simple list interface
Run a given memory image as a list transducer.
Use effectList
when you want to provide a specific Effect
.
Throws: IntcodeFault
when machine faults or too few inputs are provided.
>>>
intcodeToList [3,12,6,12,15,1,13,14,13,4,13,99,-1,0,1,9] <$> [[0],[10]]
[[0],[1]]
>>>
intcodeToList [3,3,1105,-1,9,1101,0,0,12,4,12,99,1] <$> [[0],[10]]
[[0],[1]]
>>>
:{
>>>
intcodeToList
>>>
[3,21,1008,21,8,20,1005,20,22,107,8,21,20,1006,20,31,
>>>
1106,0,36,98,0,0,1002,21,125,20,4,20,1105,1,46,104,
>>>
999,1105,1,46,1101,1000,1,20,4,20,1105,1,46,98,99]
>>>
<$> [[7],[8],[9]]
>>>
:}
[[999],[1000],[1001]]
Machine state
Machine state is comprised of the program counter, relative base pointer, and memory.
- Interact with registers using:
jmp
,addRelBase
- Interact with memory using: (
!
),set
- Build new machines with:
new
Updates to memory are stored separately from the initial values
which can enable equality comparisons to be relatively efficient.
This efficiency comes from being able to compare the inital memory
using only pointer equality when two machines are created by the
same call to new
.
Construct machine from a list of initial values starting at address 0. Program counter and relative base start at 0.
Generate a list representation of memory starting from zero. This can get big for sparsely filled memory using large addresses. Returned values start at position 0.
>>>
memoryList (set 8 10 (new [1,2,3]))
[1,2,3,0,0,0,0,0,10]
Big-step semantics
Possible effects from running a machine
run :: Machine -> Effect Source #
Big-step semantics of virtual machine. The implementation details
of Machine
are abstracted away and the program behavior can be
observed by interpreting the various Effect
constructors.
>>>
run (new [1102,34915192,34915192,7,4,7,99,0])
Output 1219070632396864 Halt
>>>
run (new [3,1,99])
Input <function>
Effect operations
(>>>) :: Effect -> Effect -> Effect infixl 9 Source #
Compose two effects together. Outputs from first argument are used as inputs to the second effect. Composed effect halts when the second machine halts.
>>>
let mult n = Input (\i -> Output (i*n) Halt)
>>>
let add n = Input (\i -> Output (i+n) Halt)
>>>
effectList (mult 3 >>> add 1) [4]
[13]
followedBy :: Effect -> Effect -> Effect Source #
Run first effect until it halts, then run the second effect.
>>>
Output 1 Halt `followedBy` Output 2 Halt
Output 1 (Output 2 Halt)
>>>
Output 1 Halt `followedBy` Fault
Output 1 Fault
>>>
Fault `followedBy` undefined
Fault
Provide an input to the first occurrence of an input request in a program effect. It is considered a fault if a program terminates before using the input.
>>>
feedInput [5,6] (Input (\x -> Input (\y -> Output (x*y) Halt)))
Output 30 Halt
>>>
feedInput [7] Halt
Fault
Evaluate a program's effect as a function from a list of inputs to a list of outputs.
Throws: IntcodeFault
when machine faults or too few inputs are provided.
Small-step semantics
Result of small-step semantics.
Exceptions
data IntcodeFault Source #
Error when a machine fails to decode an instruction.
Instances
Eq IntcodeFault Source # | |
Defined in Intcode (==) :: IntcodeFault -> IntcodeFault -> Bool # (/=) :: IntcodeFault -> IntcodeFault -> Bool # | |
Ord IntcodeFault Source # | |
Defined in Intcode compare :: IntcodeFault -> IntcodeFault -> Ordering # (<) :: IntcodeFault -> IntcodeFault -> Bool # (<=) :: IntcodeFault -> IntcodeFault -> Bool # (>) :: IntcodeFault -> IntcodeFault -> Bool # (>=) :: IntcodeFault -> IntcodeFault -> Bool # max :: IntcodeFault -> IntcodeFault -> IntcodeFault # min :: IntcodeFault -> IntcodeFault -> IntcodeFault # | |
Read IntcodeFault Source # | |
Defined in Intcode readsPrec :: Int -> ReadS IntcodeFault # readList :: ReadS [IntcodeFault] # | |
Show IntcodeFault Source # | |
Defined in Intcode showsPrec :: Int -> IntcodeFault -> ShowS # show :: IntcodeFault -> String # showList :: [IntcodeFault] -> ShowS # | |
Exception IntcodeFault Source # | |
Defined in Intcode |
ASCII I/O interface
runIO :: Effect -> IO () Source #
Run intcode program using stdio. Non-ASCII outputs are printed as integers.
Note that input and output is affected by handle buffering modes.
>>>
runIO (run (new [104,72,104,101,104,108,104,108,104,111,104,33,104,10,99]))
Hello!
>>>
runIO (run (new [104,-50,104,1000,99]))
<<-50>> <<1000>>