processor-creative-kit-0.1.0.1: a creation kit for instruction sets and cpu simulators and development tools

Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Pck.Cpu.State

Contents

Synopsis

Evaluation monad (State monad)

type EvalCpu a = State CpuState a Source

the cpu eval monad

Cpu state type

data CpuState Source

the cpu state (processor internal state)

This is the result type from run function.

get each values by pcFromCpuState, grFromCpuState, flFromCpuState, imemFromCpuState, dmemFromCpuState, dumpCpuState

Instances

pcFromCpuState :: CpuState -> Int Source

 > pcFromCpuState $ run [(0,[MOVI R0 7, HALT])] []
 1

grFromCpuState :: CpuState -> [Int] Source

 > grFromCpuState $ run [(0,[MOVI R0 7, HALT])] []
 [7,0,0,0,0,0,0,0]

flFromCpuState :: CpuState -> [Bool] Source

 > flFromCpuState $ run [(0,[MOVI R0 7, HALT])] []
 [False,False]

imemFromCpuState :: CpuState -> InstImage Source

 > imemFromCpuState $ run [(0,[MOVI R0 7, HALT])] []
 [(0,[MOVI R0 7,HALT,UNDEF,UNDEF,...])]

dmemFromCpuState :: CpuState -> DataImage Source

 > dmemFromCpuState $ run [(0,[MOVI R0 0, MOVI R1 10, ST R0 R1, HALT])] []
 [(0,[10,0,0,0,0,...])]

dumpCpuState :: CpuState -> String Source

dump Cpu state (without instruction image)

 > putStr $ dumpCpuState $ run [(0,[MOVI R0 7, HALT])] []
 pc : 1
 gr : [7,0,0,0,0,0,0,0]
 fl : [False,False]
 dm : [(0,[7,0,0,0,0,...])]

initCpuState :: CpuState Source

a default CpuState

initCpuStateMem :: InstImage -> DataImage -> CpuState Source

initialize CpuState by inst and data image

Result type

data ResultStat Source

the result state

Constructors

RsNormal

normal result

RsHalt

cpu halt(stop)

RsDbgBrk

debugger triggered

RsErr String

execution error

access for the Cpu state

PC(program counter)

readPc :: EvalCpu Int Source

read the pc

updatePc :: Int -> EvalCpu ResultStat Source

update the pc

Example:

 jumpRI :: Int -> EvalCpu ResultStat
 jumpRI ad = do pc <- readPc
                updatePc (pc + ad)

incPc :: EvalCpu ResultStat Source

increment the pc

General purpose registers

readGReg :: GReg -> EvalCpu Int Source

read a general purpose register

Example:

 jump :: GReg -> EvalCpu ResultStat
 jump reg = do ad <- readGReg reg
               updatePc ad

readGReg2 :: GReg -> GReg -> EvalCpu (Int, Int) Source

read general purpose register pair

updateGReg :: GReg -> Int -> EvalCpu () Source

update a general purpose register

Example:

 movpc :: GReg -> EvalCpu ResultStat
 movpc reg = do pc <- readPc
                updateGReg reg pc

Flags

readFlags :: EvalCpu FlagArray Source

read flag registers

Example:

 branchRI :: FCond -> Int -> EvalCpu ResultStat
 branchRI fcond ad  = do flags <- readFlags
                         if judgeFCond flags fcond
                            then jumpRI ad
                            else incPc

updateFlag :: Flag -> Bool -> EvalCpu () Source

update a flag

Example:

 cmpRR :: GReg -> GReg -> EvalCpu ResultStat
 cmpRR ra rb = do (ra', rb') <- readGReg2 ra rb
                  updateFlag FLZ (ra' == rb')
                  updateFlag FLC (ra' <  rb')

Instruction memory

fetchInst :: EvalCpu Inst Source

fetch an instruction from the instruction memory

Data memory

readDmem :: Int -> EvalCpu Int Source

read a data value from the data memory

Example:

 load :: GReg -> GReg -> EvalCpu ResultStat
 load ra rb = do rb' <- readGReg rb
                 ra' <- readDmem rb'
                 updateGReg ra ra'

updateDmem :: Int -> Int -> EvalCpu () Source

update the data memory

Example:

 store :: GReg -> GReg -> EvalCpu ResultStat
 store ra rb = do (ra', rb') <- readGReg2 ra rb
                  updateDmem ra' rb'