[Haskell-cafe] ST.Lazy vs ST.Strict
Tobias Olausson
tobsan at gmail.com
Tue May 5 15:42:00 EDT 2009
This simple implementation of CPU does not behave as expected in the
latest version of ghc using ST.Lazy since it updates the `pc` in the
wrong order.
When we use ghc-6.8 the code works as expected both with lazy and strict ST.
How is that? How do we fix this so we can use ghc-6.10.
-- ------------------------------------------------------------------
module Main where
import Control.Monad.Reader
import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Data.Array.ST
import Int
data Refs s = Refs
{ memory :: STArray s Int8 Int8
, pc :: STRef s Int8
}
type CPU s a = ReaderT (Refs s) (ST s) a
type Address = Int8
type OPCode = Int8
alterVar v f = asks v >>= lift . flip modifySTRef f
getVar v = asks v >>= lift . readSTRef
setVar v a = asks v >>= lift . flip writeSTRef a
readMem :: Int8 -> CPU s Int8
readMem addr = asks memory >>= lift . flip readArray addr
writeMem :: Address -> Int8 -> CPU s ()
writeMem addr v = asks memory >>= \r -> lift $ writeArray r addr v
fetch :: CPU s OPCode
fetch = getVar pc >>= \v -> alterVar pc (+1) >> readMem v
execute :: OPCode -> CPU s ()
execute op = case op of
0x4 -> alterVar pc (+100) -- should run this
_ -> error "should never match this"
initCPU :: ST s (Refs s)
initCPU = do
m <- newArray_ (0,30)
p <- newSTRef 0
return (Refs m p)
main :: IO ()
main = do
print $ runST (initCPU >>= runReaderT m)
where
m = do
writeMem 0 0x4
writeMem 1 0x10
op <- fetch
execute op
getVar pc
More information about the Haskell-Cafe
mailing list