array-forth-0.2.1.4: A simple interpreter for arrayForth, the language used on GreenArrays chips.

Safe HaskellNone
LanguageHaskell98

Language.ArrayForth.State

Description

This module defines types and functions for working with the state of a single core.

The most important type is State, which contains all the information about the core. This includes the registers, the memory, both stacks and communication ports. Right now, it's just a big record; in the future, I might make it more polymorphic using lenses.

There are also some useful types and functions for working with the memory of a chip and its communication channels.

Synopsis

Documentation

data Memory Source

The chip's RAM, ROM and IO channels. The RAM and ROM should each contain 64 words.

For now, input and output is split into two different types, even though they're combined on the physical chip. I'm simply not sure how to handle the case that both chips simultaneously write to the same channel.

Constructors

Memory 

Instances

emptyMem :: Memory Source

Memory with RAM and ROM zeroed out and nothing on the communication channels.

memSize :: Num a => a Source

The number of words in memory. Both ram and rom are this size. For some reason, the ram and rom address spaces are *double* this size respectively, wrapping around at the half-way point.

data State Source

A state representing the registers, stacks, memory and communication channels of a core. Note that all the fields are strict; they should also be unboxed thanks to -funbox-strict-fields (set in the .cabal file).

For now, this is just a record; however, I might rewrite it to use lenses in the near future.

Constructors

State 

Fields

a :: !F18Word
 
b :: !F18Word
 
p :: !F18Word
 
r :: !F18Word
 
s :: !F18Word
 
t :: !F18Word
 
i :: !(Maybe F18Word)

the i register can be Nothing if it is blocked on a communication port.

dataStack :: !Stack
 
returnStack :: !Stack
 
memory :: !Memory
 

Instances

startState :: State Source

The state corresponding to a core with no programs loaded and no instructions executed.

incrP :: State -> State Source

Increment the p register for the given state. If p is in RAM or ROM, this wraps p as appropriate. If p is in IO, this does nothing and p remains unchanged.

next :: State -> Maybe Instrs Source

The next word of instructions to execute in the given state. Returns Nothing if p is blocked on a communication channel.

dpop :: State -> (State, F18Word) Source

Pops the data stack of the given state, updating s and t.

dpush :: State -> F18Word -> State Source

Push a word onto the data stack, updating s and t.

rpop :: State -> (State, F18Word) Source

Pops the return stack of the given state, updating r.

rpush :: State -> F18Word -> State Source

Push a word onto the return stack, updating r.

toMem :: (Integral a, Integral b) => a -> b Source

Force an address to be in range of memory: [0,64), also converting between different integral types.

(!) :: Memory -> F18Word -> Maybe F18Word Source

Read the memory at a location given by a Forth word. Returns Nothing if blocked on a communication channel.

set :: State -> F18Word -> F18Word -> State Source

Set the memory using Forth words. A state with anything in the output channel remains blocked until one of the active ports is read.

blocked :: State -> Bool Source

Is the state is blocked because it has written to a port? Note that this does *not* consider being blocked on a read!

setProgram :: F18Word -> NativeProgram -> State -> State Source

Loads the given program into memory at the given starting position.

loadMemory :: F18Word -> [F18Word] -> State -> State Source

Load the given memory words into the state starting at the given address.

sendInput :: Port -> F18Word -> State -> State Source

Sets the input value at the given port.