There are too many error handling conventions used in library code!

Pepe Iborra mnislaih at gmail.com
Mon Mar 12 11:54:53 EDT 2007


>
> Here's a quick and dirty implementation for discussion. It  
> compiles, but I
> haven't tested it.
>
> Rob Dockins
>
[snip]

I was in the mood for coding yesterday, so I've got some code to show  
too.
I have this little problem with overdesigning things; my code looks  
pretty at the user side, but relies too much on type classes hackery.  
So type errors will probably look awful. But at least it should be  
useful as an idea of what would be desirable to have.

Here are four examples, each in a different monad, that use the  
different variants of myDiv in the original example by Eric Kidd:

 > inMaybe :: Maybe Float
 > inMaybe = do
 >   a <- myDiv2 1 0
 >   b <- absorb (myDiv3 1 2)   -- absorb the Either monad
 >   c <- myDiv4 1 2
 > --  d <- absorb (myDiv5 1 2)   -- This is going to be tricky: a  
MonadError m
 > --  <- absorb (myDiv6 1 2)    -- cant do: cant absorb the IO Monad  
of course
 >   e <- absorb (myDiv8' 1 2)
 >   return (b + c + e)

 > inEither :: Either String Float
 > inEither = do
 >   a <- absorb$ myDiv2 1 0    -- absorb the Maybe monad
 >   b <- myDiv3 1 2
 >   c <- myDiv4 1 2
 > --  d <- absorb (myDiv5 1 2)   -- This is going to be tricky: a  
MonadError m
 > --  <- absorb (myDiv6 1 2)    -- cant do: cant absorb the IO Monad  
of course
 >   e <- absorb (myDiv8' 1 2)   -- absorb the ErrorT [] monad. This  
is rather funny
 >   return (b + c + e)

 > instance MorphError CustomError String where morphError = show
 > instance MorphError CE.Exception CustomError --TODO define a mapping

 > inIO :: IO Float
 > inIO = do
 >   a <- absorb$ myDiv2 1 0   -- absorb the Maybe monad
 >   b <- absorb$ myDiv3 1 2   -- absorb the Either monad
 >   c <- myDiv4 1 2
 > --   d <- absorb (myDiv5 1 2)   -- This is going to be tricky: a  
MonadError m
 >   ble <- absorb (myDiv6 1 2)
 >   e  <- absorb (myDiv8 1 2)
 >   e' <- absorb (myDiv8' 1 2)
 >   return (b + c + e)

 > inErrIO :: ErrIO Float
 > inErrIO = do
 >   a <- absorb$ myDiv2 1 1   -- absorb the Maybe monad
 >   b <- absorb$ myDiv3 1 2   -- absorb the Either monad
 >   c <- myDiv4 1 2
 > --  d <- absorb (myDiv5 1 2)   -- This is going to be tricky: a  
MonadError m
 >   ble <- absorb (myDiv6 1 0)
 >   e <- absorb (myDiv8 1 2)
 >   return (b + c + e)

And here are the three combinators of Robert Dockins' code. I didn't  
work on the liftWriter combinator as it seemed too specific, but  
could be done too:

 > liftMaybe :: (Monad m) => Maybe a -> ErrorDynT m a
 > liftMaybe = absorb

 > liftEither :: (Monad m, Typeable e) => Either e a -> ErrorDynT m a
 > liftEither = absorb

 > liftErrorT :: (Monad m, Typeable e) => ErrorT e m a -> ErrorDynT m a
 > liftErrorT = absorb


Now, the heart of the idea is a MonadAbsorb class that allows to mix  
monads, the semantics of which is left to the instances. But of  
course, it only makes sense to mix two monads when the target one  
'contains' the other somehow.

 > class (Monad m1, Monad m2) => AbsorbMonad m1 m2 where absorb :: m1  
a -> m2 a

You don't want to see my code for the instances, it is a nightmare of  
type class hackery. I managed to reduce the overlappings reasonably  
thanks to Oleg-tricks, but that means that error messages are  
unforgiving.
/me cries for Chameleon-style type errors in GHC.
(No animals were sacrificed to the evil gods of FDs during the make  
of this library)

Since we need to merge different error ADTs, the relevant instances  
for AbsorbMonad make use of another class that provides this:

 > class MorphError e e'   where morphError :: e -> e'

MorphError is evidently in need of a new name, but the concept is  
very useful to avoid having a hierarchy of Eithers when dealing with  
libraries. Just define what a ConnError and a ParseError mean to your  
personal error type:

data CustomError = ... | ConnProblem ConnError | ... | ParseProblem  
String (Int,Int) | ...

instance MorphError ParseError CustomError where morphError  
(ParseError pos msgs) = ParseProblem (unlines msgs) pos

instance MorphError ConnError CustomError where morphError e =  
ConnProblem e


I've cabalized and uploaded the code to a Darcs repo at the URL  
below. It compfiles fine with 6.6 and 6.7 here.  I'll be delighted to  
accept patches improving the code (especially regarding the instances  
for AbsorbMonad).

http://darcs.pepeiborra.com/AbsorbMonad/

If anything else, we could use it as starting point for a benchmark  
suite of type error debugging in Haskell, a la 'buggy nofib' but for  
types :)

Cheers
peep


More information about the Libraries mailing list