[Haskell-cafe] state and exception or types again...

Udo Stenzel u.stenzel at web.de
Tue Aug 29 06:10:22 EDT 2006


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20060829/008ce2bd/attachment.bin


More information about the Haskell-Cafe mailing list