state and exception or types again...

Hello! Sorry if I keep bothering, but I'm still trying to understand types and monads. Now I'm trying to create a statefull evaluator, with output and exception, but I'm facing a problem I seem not to be able to conceptually solve. Take the code below. Now, in order to get it run (and try to debug) the Eval_SOI type has a Raise constructor that produces the same type of SOIE. Suppose instead it should be constructing something like Raise "something". Moreover, I wrote a second version of >>=, commented out. This is just to help me illustrate to problem I'm facing. Now, >>= is suppose to return Raise if "m" is matched against Raise (second version commented out). If "m" matches SOIE it must return a SOIE only if "f a" does not returns a Raise (output must be concatenated). I seem not to be able to find a way out. Moreover, I cannot understand if a way out can be possibly found. Something suggests me it could be related to that Raise "something". But my feeling is that functional programming could be something out of the reach of my mind... by the way, I teach Law, so perhaps you'll forgive me...;-) If you can help me to understand this problem all I can promise is that I'll mention your help in the tutorial I'm trying to write on "the monadic way"... that seems to lead me nowhere. Thanks for your kind attention. Andrea the code: 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 --Is it right? ) -- (>>=) 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))))

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 - "

Andrea Rossato wrote:
Now I'm trying to create a statefull evaluator, with output and exception, but I'm facing a problem I seem not to be able to conceptually solve.
data Eval_SOI a = Raise { unPackMSOIandRun :: State -> (a, State, Output) } | SOIE { unPackMSOIandRun :: State -> (a, State, Output) }
If you instead consider that you want the wrapped function to evaluate to a result that allows you to continue, or a result that is an exception, then you could use a flag to record whether or not an exception occurred eg: data Eval_SOI a = SOIE {runSOIE :: State -> (a, State, Output, Bool)} where the 4th element of the tuple is True iff we can continue or False iff an exception occurred.
raise x e = Raise (\s -> (x,s,e))
raise x e = SOIE {\s -> (x, s, e, False)} instance Monad Eval_SOI where return a = SOIE (\s -> (a, s, "", True)) m >>= f = SOIE $ \x -> let r1@(a, y, o1, ok1) = runSOIE m x in if ok1 then let (b, z, o2, ok2) = runSOIE (f a) y in (b, z, o1 ++ o2, ok2) else r1 ie if runSOIE m x does not result in an exception then we continue with the second computation otherwise we just return the exception (r1) immediately. Note I have not tested the above code so it may have a bug in it (also I renamed s1 and s2 to o1 and o2 to avoid confusion with the use of "s" to mean "state")... Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
data Eval_SOI a = SOIE {runSOIE :: State -> (a, State, Output, Bool)}
seems simple and neat...
else r1
ie if runSOIE m x does not result in an exception then we continue with the second computation otherwise we just return the exception (r1) immediately.
well, I thought that this was not possible: (>>=) :: m a -> (a -> m b) -> m b This is why I think that two constructors are needed, but with two constructors is not possible...;-) I'm trying to dig into this problem also to see if it has to do with monad laws. But probably this is just a late night guess. Thanks for your kind attention. Best regards, Andrea

Andrea Rossato wrote:
Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
data Eval_SOI a = SOIE {runSOIE :: State -> (a, State, Output, Bool)}
well, I thought that this was not possible: (>>=) :: m a -> (a -> m b) -> m b
And you are right. In case of an exception, you don't have a 'b' to return, so you cannot construct the result (unless you put 'undefined' in there, which is just silly). Do it this way: data Eval_SOI a = SOIE {runSOIE :: State -> (Maybe a, State, Output)} instance Monad Eval_SOI where return a = SOIE $ \s -> (Just a, s, []) fail _ = SOIE $ \s -> (Nothing, s, []) m >>= k = SOIE $ \s0 -> let r@(ma, s1, o1) = runSOIE m s0 (mb, s2, o2) = runSOIE (k (fromJust ma)) s1 in case ma of Nothing -> r Just _ -> (mb, s2, o1 ++ o2) output w = SOIE $ \s -> (Just (), s, w) put s = SOIE $ \_ -> (Just (), s, []) get = SOIE $ \s -> (Just s, s, []) I don't think it's unmanageably complicated, but still not as clean and modular as using monad transformers.
This is why I think that two constructors are needed, but with two constructors is not possible...;-)
Indeed. Here they are Nothing and Just. In principle, Maybe is equivalent to a pair of a Bool and something else, but that only works in an untyped language.
I'm trying to dig into this problem also to see if it has to do with monad laws.
Uhh... no. You should prove them, though. (Try it, doing this is quite instructive.) Udo. -- "In the software business there are many enterprises for which it is not clear that science can help them; that science should try is not clear either." -- E. W. Dijkstra

Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
where the 4th element of the tuple is True iff we can continue or False iff an exception occurred.
I'm starting to believe that the best method is just take the way StateT takes... without reinventing the wheel... Regards, Andrea

Andrea Rossato wrote:
Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
where the 4th element of the tuple is True iff we can continue or False iff an exception occurred.
I'm starting to believe that the best method is just take the way StateT takes... without reinventing the wheel...
The solution I gave was very close to being correct. I enclose a tested example below - you'll need to adapt it to do evaluation but it shows an exception being raised. module Test where import Control.Monad -- When we raise an exception we use (undefined) so that -- the result type is the same as whatever the result type -- would be for the other computation. But this means we -- need to tell Haskell how to print out the tuple so that it -- doesn't give an exception when trying to print out -- undefined (!), hence we replace the tuple with a data type -- so we can define our own Show instance data Result a = Result a State Output Bool instance Show a => Show (Result a) where show (Result a s o True) = "Good " ++ show a ++ " " ++ show s ++ " " ++ show o show (Result _ s o _) = "Bad " ++ show s ++ " " ++ show o -- We only have one constructor so can use a newtype for -- efficiency newtype Eval_SOI a = SOIE {runSOIE :: State -> Result a} type State = Int type Output = String -- I used braces instead of parens in my previous post -- Note that we return undefined as the "result" because this -- is the only value which belongs to all types in Haskell raise e = SOIE (\s -> Result undefined s e False) instance Monad Eval_SOI where return a = SOIE (\s -> Result a s "" True) m >>= f = SOIE $ \x -> let Result a y o1 ok1 = runSOIE m x in if ok1 then let Result b z o2 ok2 = runSOIE (f a) y in Result b z (o1 ++ o2) ok2 else Result undefined y o1 False display t = SOIE(\s -> Result () s t True) test = runSOIE (do display "hello" raise "Exception" display "Foo" ) 0 In the definition of (>>=), we need to explicitly return (undefined) when the first computation has raised an exception, so that the result type unifies with the result type when no exception occurs. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Il Tue, Aug 29, 2006 at 07:45:46AM +0100, Brian Hulley ebbe a scrivere:
Andrea Rossato wrote:
Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
where the 4th element of the tuple is True iff we can continue or False iff an exception occurred.
I'm starting to believe that the best method is just take the way StateT takes... without reinventing the wheel...
The solution I gave was very close to being correct. I enclose a tested example below - you'll need to adapt it to do evaluation but it shows an exception being raised.
I said I think that the StateT approach is the one to take only because I believe that the complexity of the definition of >>= is getting unmanageable, that is, as far as I understand, contrary to the spirit of haskell, and functional programming in general. so, start getting my hands dirty in monadic combinations is probably the best for improving my knowledge of haskell and functional programming. what do you think? Thank you very much for your kind attention and the greatly illuminating examples! Best regards, Andrea

Andrea Rossato wrote:
Il Tue, Aug 29, 2006 at 07:45:46AM +0100, Brian Hulley ebbe a scrivere:
Andrea Rossato wrote:
Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere:
where the 4th element of the tuple is True iff we can continue or False iff an exception occurred.
I'm starting to believe that the best method is just take the way StateT takes... without reinventing the wheel...
The solution I gave was very close to being correct. I enclose a tested example below - you'll need to adapt it to do evaluation but it shows an exception being raised.
I said I think that the StateT approach is the one to take only because I believe that the complexity of the definition of >>= is getting unmanageable, that is, as far as I understand, contrary to the spirit of haskell, and functional programming in general.
so, start getting my hands dirty in monadic combinations is probably the best for improving my knowledge of haskell and functional programming. what do you think?
Hi - Yes I agree the StateT/monad transformer approach is probably best in the long run, since by using the standard monad transformers, you will get code that will scale better to handle more complexities later, and has the advantage of being already tested so you can be sure the resulting monads will obey all the monad laws. Also, there are a lot of tutorials about how to use them to solve different problems. Just for interest, I enclose another version of the SOIE implementation which I think is closer to what you originally intended. I've used two constructors for the result to avoid having to use (undefined), but the whole function is still wrapped inside a single constructor newtype: module Test where import Control.Monad data Result a = Good a State Output | Bad State Output deriving Show newtype Eval_SOI a = SOIE {runSOIE :: State -> Result a} type State = Int type Output = String raise e = SOIE (\s -> Bad s e) instance Monad Eval_SOI where return a = SOIE (\s -> Good a s "") m >>= f = SOIE $ \x -> case runSOIE m x of Good a y o1 -> case runSOIE (f a) y of Good b z o2 -> Good b z (o1 ++ o2) Bad z o2 -> Bad z (o1 ++ o2) Bad z o2 -> Bad z o2 -- (*) display t = SOIE(\s -> Good () s t) test = runSOIE (do display "hello" raise "Exception" display "Foo" ) 0 (*) This line is essential, because the (Bad z o2) on the lhs has type (Eval_SOI a) whereas the (Bad z o2) on the rhs has type (Eval_SOI b) (given (>>=) :: m a -> (a->m b) -> m b) so something like r@(Bad z o2) -> r would not work, though the hope is that the compiler would manage to optimize out the re-construction that's needed to satisfy the type checker. I think monads can be quite difficult to understand until you see that they are just quite simple definitions of (return) and (>>=) as above, and understanding how the monad transformers are defined (by reading the source in ...\libraries\mtl\Control\Monad) means you'll be able to use them with absolute confidence rather than having a vague uneasiess that there is some "magic" involved. Happy monadic explorations! :-) Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Il Tue, Aug 29, 2006 at 10:02:38AM +0100, Brian Hulley ebbe a scrivere:
Yes I agree the StateT/monad transformer approach is probably best in the long run, since by using the standard monad transformers, you will get code that will scale better to handle more complexities later, and has the advantage of being already tested so you can be sure the resulting monads will obey all the monad laws. Also, there are a lot of tutorials about how to use them to solve different problems. ... Hi! It's been quite troublesome since there are no examples (at least I did not find any), but I implemented (copied...;-) StateT.
Below the code. What do you think (apart from names or lack of class instance: I need this code to understand what's going on and to write about it in my tutorial)? Is it quite canonical? Anything really bad?
Happy monadic explorations! :-)
Great fun indeed! Thanks for the kind help from you, guys! Andrea Here's the bit. At the end the output. module Monadi where data Term = Con Int | Add Term Term deriving (Show) eval :: Term -> Int eval (Con a) = a eval (Add a b) = eval a + eval b answer, noanswer :: Term answer = (Add (Add (Con 30) (Con 12)) (Add (Con 20) (Con 30))) noanswer = (Add (Add (Con 20) (Con 12)) (Con 11)) formatLine t a = "eval (" ++ show t ++ ") <= " ++ show a ++ " - " type Exception = String type O = String data M2 a = Ex Exception | Done {unpack :: (a,O) } deriving (Show) newtype StateT s m a = S {runStateT :: s -> m (a,s) } --S (s -> m (a,s)) instance Monad m => Monad (StateT s m) where return a = S (\s -> return (a,s)) S m1 >>= k = S (\s -> do ~(a,s1) <- m1 s let S m2 = k a m2 s1) instance Monad M2 where return a = Done (a, "") m >>= f = case m of Ex e -> Ex e Done (a, x) -> case (f a) of Ex e1 -> Ex e1 Done (b, y) -> Done (b, x ++ y) lift m = S (\s -> do x <- m return (x,s)) raise_IOE :: O -> StateT s M2 a raise_IOE e = lift (Ex e) print_IOE :: O -> StateT Int M2 () print_IOE x = lift (Done ((), x)) incState :: StateT Int M2 (M2 ()) incState = S (\s -> return (Done ((), ""), s + 1)) eval_IOE :: Term -> StateT Int M2 Int eval_IOE (Con a) = do incState print_IOE (formatLine (Con a) a) return a eval_IOE (Add t u) = do a <- eval_IOE t b <- eval_IOE u incState print_IOE (formatLine (Add t u) (a + b)) if (a+b) == 42 then raise_IOE "The Ultimate Answer Has Been Computed!! Now I'm tired!" else return (a + b) -- *Monadi> runStateT (eval_IOE answer) 0 -- Ex "The Ultimate Answer Has Been Computed!! Now I'm tired!" -- *Monadi> runStateT (eval_IOE noanswer) 0 -- Done {unpack = ((43,5),"eval (Con 20) <= 20 - eval (Con 12) <= 12 - eval (Add (Con 20) (Con 12)) <= 32 - eval (Con 11) <= 11 - eval (Add (Add (Con 20) (Con 12)) (Con 11)) <= 43 - ")} -- *Monadi>

Il Tue, Aug 29, 2006 at 10:02:38AM +0100, Brian Hulley ebbe a scrivere: Hi! Ím getting back so late because it took me a while to understand monadic transformation...
data Result a = Good a State Output | Bad State Output deriving Show
...
case runSOIE m x of Good a y o1 -> case runSOIE (f a) y of Good b z o2 -> Good b z (o1 ++ o2) Bad z o2 -> Bad z (o1 ++ o2) Bad z o2 -> Bad z o2 -- (*)
This is brilliant and highly instructive (for me at least)!! Thank you very much. Regards, Andrea
participants (3)
-
Andrea Rossato
-
Brian Hulley
-
Udo Stenzel