Skip to content

Instantly share code, notes, and snippets.

@jlouis
Created September 17, 2009 23:20
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save jlouis/188782 to your computer and use it in GitHub Desktop.
Save jlouis/188782 to your computer and use it in GitHub Desktop.
module MSM where
import Control.Monad.State
import Instructions
import Data.Array
-- MSMachine - The record for the state machine. This contains our 2 Int registers, the Int stack, and our PC.
data MSMachine = MSMachine {
stack :: [Int],
regA :: Int,
regB :: Int,
pc :: Int,
prog :: [( Int, Instruction) ]
} deriving Show
-- fetchInstr - Fetches next instruction.
fetchInstr :: State MSMachine Instruction
fetchInstr = do
state <- get
let instr = snd ((prog state)!!(pc state))
return instr
-- incrementPC -- Used after all instructions but JMP, CJMP and HALT
incrementPC :: State MSMachine ()
incrementPC = do
state <- get
put $ state {pc = (pc state) + 1}
-- here is the stdin to a list of pairs with each instruction given an instruction count.
-- the MSMachine instance: this is the MSM we work execute via runState. Program is read from STDIN.
instanceMachine = MSMachine {
stack = [],
regA = 0,
regB = 0,
pc = 0,
prog = []
}
-- loopInterp -- Infinite loop to keep the interpreter running. The interpreter will quit
loop :: State MSMachine ()
loop = do
interp
-- interp -- Simple interpreter for the MSMachine.
interp :: State MSMachine ()
interp = do
state <- get
instr <- fetchInstr
case instr of
HALT -> return ()
(PUSH n) ->
do put $ state { stack = n : (stack state) }
interp
_ -> return ()
-- loopStart -- This holds the return value of the MSMachine. Basically, this code runs the initState with the program it got from stdin.
-- loopStart :: ()
loopStart = evalState interp instanceMachine
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment