18

I am struggling with the best way to report errors in a set of functions that should compose nicely, in a library I'm working on.

Concretely, I have functions that look like:

foo, bar, baz :: a -> Maybe a

where foo can fail in only one way (a good fit for Maybe), but bar and baz can fail in two different ways each (good fits for Either BarErrors and Either BazErrors).

One solution is to create:

data AllTheErrors = TheFooError
                  | BarOutOfBeer
                  | BarBurnedDown
                  | ...

and make all the functions return Either AllTheErrors, which expresses the range of errors that might be raised by a composed sequence of these functions at the expense of expressing the range of errors possible for each individual function.

Is there a way I can get both? Maybe with something other than monadic composition? Or with type families (waves hands)...?

jberryman
  • 16,334
  • 5
  • 42
  • 83

1 Answers1

16

The Control.Monad.Exception library allows strongly typed exceptions to be used in non IO code. This allows functions to throw errors, and easily compose with functions that throw different errors. For example:

{-# LANGUAGE RankNTypes, MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
import Prelude hiding (catch)
import Control.Monad.Exception


data FooException = FooException deriving (Show, Typeable)
instance Exception FooException

data BarErrors = BarErrors deriving (Show, Typeable)
instance Exception BarErrors

data BazErrors = BazErrors deriving (Show, Typeable)
instance Exception BazErrors

-- sample functions    
foo :: (Throws FooException l) => a -> EM l a
foo a = return a


bar :: (Throws BarErrors l) => a -> EM l a
bar _ = throw BarErrors

baz :: (Throws BazErrors l) => a -> EM l a
baz a = return a


-- using all at once:

allAtOnce :: (Throws FooException l, Throws BarErrors l, Throws BazErrors l) =>
             a -> EM l String
allAtOnce x = do
  _ <- foo x
  _ <- bar x
  _ <- baz x
  return "success!"

-- now running the code, catching the exceptions:

run :: a -> String
run x = runEM $ allAtOnce x `catch` (\(_ :: FooException) -> return "foo failed")
        `catch` (\BarErrors -> return "bar failed")
        `catch` (\BazErrors -> return "baz failed")


-- run 3 results in "bar failed"

See also the papers Explicitly Typed Exceptions for Haskell and An Extensible Dynamically-Typed Hierarchy of Exceptions for more details on using this library.

David Miani
  • 14,518
  • 2
  • 47
  • 66
  • After doing some research, what I think will suit my library is to define my library's functions polymorphically in the `Failure` class from the 'failure' package, here: http://hackage.haskell.org/package/failure . That lets me express the kinds of exceptions that can be raised in the type sig, and gives my users the option of using something simple like `Maybe`, or something more robust like control-monad-exception (which provides an instance). Thanks again. – jberryman Dec 12 '11 at 17:47