module Language.Pck.Cpu.Memory (
InstImage
, DataImage
, ImemArray
, DmemArray
, IAddress
, DAddress
, DValue
, initImem
, presetImem
, modifyImems
, fetchImem
, getInstImage
, extractImems
, initDmem
, presetDmem
, getDmem
, modifyDmem
, modifyDmems
, getDataImage
, extractDmems
) where
import Data.Array (Array, listArray, (//), (!), elems, assocs)
import Language.Pck.Cpu.Config
import Language.Pck.Cpu.Instruction
type IAddress = Int
type InstImage = [(IAddress, [Inst])]
type ImemArray = Array IAddress Inst
imemSize, imemMin, imemMax :: Int
imemSize = cfgImemSize cpuConfig
imemMin = cfgImemStart cpuConfig
imemMax = imemMin + imemSize 1
initImem :: ImemArray
initImem = listArray(imemMin, imemMax) $ replicate imemSize UNDEF
presetImem :: InstImage -> ImemArray
presetImem = foldl modifyImems initImem
modifyImems :: ImemArray -> (IAddress, [Inst]) -> ImemArray
modifyImems ary (start, insts) = ary // zip [start .. imemMax] insts
fetchImem :: ImemArray -> IAddress -> Inst
fetchImem ary ad = ary ! ad'
where ad' = ad `rem` (imemMax + 1)
getInstImage :: ImemArray -> InstImage
getInstImage ary = [(ad, val)]
where ary' = assocs ary
ad = fst $ head ary'
val = elems ary
extractImems :: InstImage -> IAddress -> Int -> [Inst]
extractImems img ad cnt = take cnt $ drop beg vals
where (start, vals):_ = img
beg = ad start
type DAddress = Int
type DValue = Int
type DataImage = [(DAddress, [DValue])]
type DmemArray = Array DAddress DValue
dmemSize, dmemMin, dmemMax :: Int
dmemSize = cfgDmemSize cpuConfig
dmemMin = cfgDmemStart cpuConfig
dmemMax = dmemMin + dmemSize 1
initDmem :: DmemArray
initDmem = listArray (dmemMin,dmemMax) $ replicate dmemSize 0
presetDmem :: DataImage -> DmemArray
presetDmem = foldl modifyDmems initDmem
getDmem :: DmemArray -> DAddress -> DValue
getDmem ary ad = ary ! ad'
where ad' = ad `rem` (dmemMax + 1)
modifyDmem :: DmemArray -> DAddress -> DValue -> DmemArray
modifyDmem ary ad dat = ary // [(ad', dat)]
where ad' = ad `rem` (dmemMax + 1)
modifyDmems :: DmemArray -> (DAddress, [DValue]) -> DmemArray
modifyDmems ary (start, vals) = ary // zip [start .. dmemMax] vals
getDataImage :: DmemArray -> DataImage
getDataImage ary = [(ad, val)]
where ary' = assocs ary
ad = fst $ head ary'
val = elems ary
extractDmems :: DataImage -> DAddress -> Int -> [DValue]
extractDmems img ad cnt = take cnt $ drop beg vals
where (start, vals):_ = img
beg = ad start