[Haskell-cafe] state and exception or types again...
Andrea Rossato
mailing_list at istitutocolli.org
Mon Aug 28 15:22:50 EDT 2006
Il Mon, Aug 28, 2006 at 08:23:15PM +0200, Andrea Rossato ebbe a scrivere:
The previous code was not complete, and so testable.
at the end there is the output.
there it is:
module Monads where
data Term = Con Int
| Add Term Term
deriving (Show)
type State = Int
type Output = String
formatLine :: Term -> Int -> Output
formatLine t a = "eval (" ++ show t ++ ") <= " ++ show a ++ " - "
data Eval_SOI a = Raise { unPackMSOIandRun :: State -> (a, State, Output) }
| SOIE { unPackMSOIandRun :: State -> (a, State, Output) }
instance Monad Eval_SOI where
return a = SOIE (\s -> (a, s, ""))
m >>= f = SOIE (\x ->
let (a, y, s1) = unPackMSOIandRun m x in
case f a of
SOIE nextRun -> let (b, z, s2) = nextRun y in
(b, z, s1 ++ s2)
Raise e1 -> e1 y --only this happens
)
-- (>>=) m f = case m of
-- Raise e -> error "ciao" -- why this is not going to happen?
-- SOIE a -> SOIE (\x ->
-- let (a, y, s1) = unPackMSOIandRun m x in
-- let (b, z, s2) = unPackMSOIandRun (f a) y in
-- (b, z, s1 ++ s2))
incSOIstate :: Eval_SOI ()
incSOIstate = SOIE (\s -> ((), s + 1, ""))
print_SOI :: Output -> Eval_SOI ()
print_SOI x = SOIE (\s -> ((),s, x))
raise x e = Raise (\s -> (x,s,e))
eval_SOI :: Term -> Eval_SOI Int
eval_SOI (Con a) = do incSOIstate
print_SOI (formatLine (Con a) a)
return a
eval_SOI (Add t u) = do a <- eval_SOI t
b <- eval_SOI u
incSOIstate
print_SOI (formatLine (Add t u) (a + b))
if (a + b) == 42
then raise (a+b) " = The Ultimate Answer!!"
else return (a + b)
runEval exp = case eval_SOI exp of
Raise a -> a 0
SOIE p -> let (result, state, output) = p 0 in
(result,state,output) --"Result = " ++ show result ++ " Recursions = " ++ show state ++ " Output = " ++ output
--runEval (Add (Con 10) (Add (Con 28) (Add (Con 40) (Con 2))))
will produce
(80,7,"eval (Con 10) <= 10 - eval (Con 28) <= 28 - eval (Con 40) <= 40 - eval (Con 2) <= 2 - = The Ultimate Answer!!eval (Add (Con 28) (Add (Con 40) (Con 2))) <= 70 - eval (Add (Con 10) (Add (Con 28) (Add (Con 40) (Con 2)))) <= 80 - ")
thats is:
"eval (Con 10) <= 10 -
eval (Con 28) <= 28 -
eval (Con 40) <= 40 -
eval (Con 2) <= 2 - = The Ultimate Answer!!
eval (Add (Con 28) (Add (Con 40) (Con 2))) <= 70 -
eval (Add (Con 10) (Add (Con 28) (Add (Con 40) (Con 2)))) <= 80 -
"
More information about the Haskell-Cafe
mailing list