I wrote a state monad example - help me make it more Haskellic

Hi, I have written my first program using state monads and I would like some feedback from the community regarding how Haskellic it is. It's a simple simulator for a toy microprocessor. The contents of registers are the state that needs to be preserved across instruction evaluation. I have tried to implement the code dealing with monads using both >>=, >> and the do block. Also, I'd like to make the RegisterVal type Word32, but when I do that, then ================ initial_rf = [0,0,0,0] ================ this line fails to typecheck. If there are any bugs or non-idiomatic use of haskell, please let me know. Thanks and regards, Rohit ================= import Data.Word import Control.Monad.State type RegisterVal = Int type RegisterFile = [RegisterVal] type RegisterID = Int --destination comes first data Instruction = Add RegisterID RegisterID RegisterID | Sub RegisterID RegisterID RegisterID | Mov RegisterID RegisterID | Movc RegisterID RegisterVal deriving (Show) get_operand :: RegisterFile -> RegisterID -> RegisterVal get_operand registers regid = registers !! regid store_operand :: RegisterFile -> RegisterID -> RegisterVal -> RegisterFile store_operand registers regid value = (take regid registers) ++ [value] ++ (drop (regid+1) registers) eval_inst :: Instruction -> RegisterFile -> RegisterFile eval_inst (Add dstid src1id src2id) rf = rf_final where rf_final = store_operand rf dstid res --store res = op1 + op2 --evaluate (op1, op2) = (get_operand rf src1id , get_operand rf src2id) --load eval_inst (Sub dstid src1id src2id) rf = rf_final where rf_final = store_operand rf dstid res --store res = op1 - op2 --evaluate (op1, op2) = (get_operand rf src1id , get_operand rf src2id) --load eval_inst (Mov dstid srcid) rf = rf_final where rf_final = store_operand rf dstid res --store res = op1 --evaluate op1 = get_operand rf srcid --load eval_inst (Movc dstid imm) rf = rf_final where rf_final = store_operand rf dstid res --store res = imm --evaluate initial_rf :: RegisterFile initial_rf = [0,0,0,0] insts = [Movc 0 231, Movc 1 (-42), Add 2 1 0, Sub 3 1 0] execute_inst2 :: Instruction -> State RegisterFile RegisterFile {- execute_inst2 inst = get >>= \rf1 -> let rf2 = eval_inst inst rf1 in put rf2 >> return rf2 -} execute_inst2 inst = do rf1 <- get let rf2 = eval_inst inst rf1 put rf2 return rf2 execute_program2 :: [Instruction] -> State RegisterFile RegisterFile execute_program2 [] = do rf <- get put rf return rf execute_program2 (x:xs) = do rf1 <- execute_inst2 x rf2 <- execute_program2 xs put rf2 return rf2 {- execute_program2 [] = get >>= \rf -> put rf >> return rf execute_program2 (x:xs) = (execute_inst2 x) >>= \a -> (execute_program2 xs) >>= \b -> return b -} main :: IO () main = putStrLn $ show $ execState (execute_program2 insts) initial_rf -- Rohit Garg http://rpg-314.blogspot.com/

On Jul 23, 2011, at 11:56 AM, Rohit Garg wrote:
Also, I'd like to make the RegisterVal type Word32, but when I do that, then ================ initial_rf = [0,0,0,0] ================ this line fails to typecheck.
I changed the RegisterVal type to Word32. It works for me using GHCi version 7.0.2. Your code looks great!

On Sat, Jul 23, 2011 at 9:50 PM, David Place
On Jul 23, 2011, at 11:56 AM, Rohit Garg wrote:
Also, I'd like to make the RegisterVal type Word32, but when I do that, then ================ initial_rf = [0,0,0,0] ================ this line fails to typecheck.
I changed the RegisterVal type to Word32. It works for me using GHCi version 7.0.2. Your code looks great!
Ah!, I was changing the type of RegisterID as well and then it was complaining. For RegisterVal only, it works fine, thanks. -- Rohit Garg http://rpg-314.blogspot.com/

Hi Rohit, I've refactored your program a little bit. Hope you don't mind. The main change I made was, since there can only be four registers, to create explicit datatypes for each register and turn your RegisterFile datatype into a 4-tuple. The corresponding setter and getter, store_operand and get_operand have also been changed to reflect the new datatypes. This way there can never be errors with list indices etc. I've also used two new State monad functions of which you might be unaware: 1. modify :: modifies state with the given function. 2. mapM_ :: is like a "map" but takes a monadic action and applied it to the given ist. The output is stil the same as your code, but I've added a little type safety. I haven't covered every detail of the changes but if you're reading through it and get stuck, please let me know. -deech import Control.Monad.State type RegisterVal = Int data RegisterID = R1 | R2 | R3 | R4 deriving Show type RegisterFile = (RegisterVal, RegisterVal, RegisterVal, RegisterVal) get_operand :: RegisterFile -> RegisterID -> RegisterVal get_operand (r1,_,_,_) R1 = r1 get_operand (_,r2,_,_) R2 = r2 get_operand (_,_,r3,_) R3 = r3 get_operand (_,_,_,r4) R4 = r4 store_operand :: RegisterFile -> RegisterID -> RegisterVal -> RegisterFile store_operand (r1,r2,r3,r4) r v = case r of R1 -> (v,r2,r3,r4) R2 -> (r1,v,r3,r4) R3 -> (r1,r2,v,r4) R4 -> (r1,r2,r3,v) eval_inst :: Instruction -> RegisterFile -> RegisterFile eval_inst inst rf = let store_op' = store_operand rf get_op' = get_operand rf in case inst of Add dest rid1 rid2 -> store_op' dest (get_op' rid1 + get_op' rid2) Sub dest rid1 rid2 -> store_op' dest (get_op' rid1 - get_op' rid2) Mov dest rid -> store_op' dest (get_op' rid) Movc dest v -> store_op' dest v --destination comes first data Instruction = Add RegisterID RegisterID RegisterID | Sub RegisterID RegisterID RegisterID | Mov RegisterID RegisterID | Movc RegisterID RegisterVal deriving (Show) initial_rf :: RegisterFile initial_rf = (0,0,0,0) insts = [Movc R1 231, Movc R2 (-42), Add R3 R2 R1, Sub R4 R2 R1] execute_program2 :: [Instruction] -> State RegisterFile () execute_program2 = mapM_ (modify . eval_inst) main :: IO () main = putStrLn $ show $ execState (execute_program2 insts) initial_rf

Hi Aditya,
Your modifications are very nice. I didn't know about the modify
function. Now the code looks much better.
Thanks.
On Sun, Jul 24, 2011 at 12:55 AM, aditya siram
Hi Rohit, I've refactored your program a little bit. Hope you don't mind. The main change I made was, since there can only be four registers, to create explicit datatypes for each register and turn your RegisterFile datatype into a 4-tuple. The corresponding setter and getter, store_operand and get_operand have also been changed to reflect the new datatypes. This way there can never be errors with list indices etc.
I've also used two new State monad functions of which you might be unaware: 1. modify :: modifies state with the given function. 2. mapM_ :: is like a "map" but takes a monadic action and applied it to the given ist.
The output is stil the same as your code, but I've added a little type safety.
I haven't covered every detail of the changes but if you're reading through it and get stuck, please let me know.
-deech
import Control.Monad.State
type RegisterVal = Int data RegisterID = R1 | R2 | R3 | R4 deriving Show type RegisterFile = (RegisterVal, RegisterVal, RegisterVal, RegisterVal)
get_operand :: RegisterFile -> RegisterID -> RegisterVal get_operand (r1,_,_,_) R1 = r1 get_operand (_,r2,_,_) R2 = r2 get_operand (_,_,r3,_) R3 = r3 get_operand (_,_,_,r4) R4 = r4
store_operand :: RegisterFile -> RegisterID -> RegisterVal -> RegisterFile store_operand (r1,r2,r3,r4) r v = case r of R1 -> (v,r2,r3,r4) R2 -> (r1,v,r3,r4) R3 -> (r1,r2,v,r4) R4 -> (r1,r2,r3,v)
eval_inst :: Instruction -> RegisterFile -> RegisterFile eval_inst inst rf = let store_op' = store_operand rf get_op' = get_operand rf in case inst of Add dest rid1 rid2 -> store_op' dest (get_op' rid1 + get_op' rid2) Sub dest rid1 rid2 -> store_op' dest (get_op' rid1 - get_op' rid2) Mov dest rid -> store_op' dest (get_op' rid) Movc dest v -> store_op' dest v
--destination comes first data Instruction = Add RegisterID RegisterID RegisterID | Sub RegisterID RegisterID RegisterID | Mov RegisterID RegisterID | Movc RegisterID RegisterVal deriving (Show)
initial_rf :: RegisterFile initial_rf = (0,0,0,0)
insts = [Movc R1 231, Movc R2 (-42), Add R3 R2 R1, Sub R4 R2 R1]
execute_program2 :: [Instruction] -> State RegisterFile () execute_program2 = mapM_ (modify . eval_inst)
main :: IO () main = putStrLn $ show $ execState (execute_program2 insts) initial_rf
-- Rohit Garg http://rpg-314.blogspot.com/
participants (3)
-
aditya siram
-
David Place
-
Rohit Garg