class Monad m => MonadError e m | m -> e where
   throwError :: e -> m a
   catchError :: m a -> (e -> m a) -> m a
..
power of TwoCont? I mean, it still seems like there's an operation
missing that supplies new left and right continuations at once.

i guess, instead of one DiMonad with two sets of operations, i'd prefer to have two separate Monads with the ability to connect them, so that failure in one is success in the other, but i guess we need some way to tell which is which.

using MonadError to handle error continuations on top of a Monad
to handle success continuation is a lot like using a MonadReader to
hold error continuations on top of the base Monad. consider

   class (Monad m) => MonadReader r m | m -> r where
     ask :: m r
     local :: (r -> r) -> m a -> m a

where  r = e -> m a. then

   throwError = \e->ask >>= \h->h e
   catchError m h = local (const h) m

in other words, supplying both continuations is straightforward,
although syntactic sugar only supports supplying one, in line with the bias towards one of the two continuations:

m `doubleBind` (s,f) = m `catchError` f >>= s i find myself doing something like this frequently, whenever i use constructs like

    m >>= \x-> a x `mplus` b x
   m >>= maybe a b
   m >>= either a b

btw, it might be useful if throwing an error would reverse the roles of the two continuations, instead of throwing away the success continuation.

then the error handler itself could either return (abandoning the original
success continuation) or throw (resuming the original  continuation).
that would interfere with the use of throw to pass on unhandled errors,
but then we could be more specific about which direction to throw.

claus

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to