[Haskell-cafe] Collecting MonadError errors generically

oleg at okmij.org oleg at okmij.org
Wed Jul 14 04:48:20 EDT 2010


Leon Grynszpan wrote:
> What I want, instead, is to run a whole bunch of
> computations that may throw errors. If there are any errors, I want to
> collect them all into one big master error. If not, I want a list of
> results. Here's an example of usage:
>
> couldThrowError :: (Error e, MonadError e m) => t1 -> m t2
> getParams :: (Error e, MonadError e m) => [t1] --> m [t2]
> getParams = groupErrors . map couldThrowError
>
> I found it pretty easy to implement groupErrors for Either String:
> ...
> The problem, though, is that running this function now causes type
> inference to provide "Either String" as my MonadError implementation...
> It would be nice if I could stay generic.

You might find the following two functions useful:

> reify :: (Error e, MonadError e m) => m a -> m (Either e a)
> reify m = (m >>= return . Right) `catchError` (return . Left)
>
> -- Not needed here, but very nice to have anyway
> reflect :: (Error e, MonadError e m) => m (Either e a) -> m a
> reflect m = m >>= either throwError return

Then groupErrors can be written almost the same way you wrote for
the Either String monad -- but now generically 

> groupErrors :: (Monoid e, Error e, MonadError e m) => [m a] -> m [a]
> groupErrors lst = mapM reify lst >>= \lst ->
>    case partitionEithers lst of
>      ([],xs)  -> return xs
>      (errs,_) -> throwError (mconcat errs)

If you don't like the Monoid constraint, this is fine. But you have to
provide then some other way to group errors. For example, you could
use the new extensible exceptions.

Here is the rest of the code:

> couldThrowError :: (MonadError String m) => String -> m Int
> couldThrowError s = case reads s of
> 		      [(n,"")] -> return n
> 		      _        -> throwError $ "parse error: " ++ s ++ "\n"
>
> getParams :: (Monoid e, Error e, MonadError e m) => 
> 	     (t1 -> m t2) -> [t1] -> m [t2]
> getParams f = groupErrors . map f
>
> test :: Either String [Int]
> test = getParams couldThrowError ["1","2","a","b"]


If you wish to know more about reify and reflect, a good paper to
start is the following. Section 1.2 talks directly about exception monads.

@InProceedings{	filinski-representing,
  author	= "Andrzej Filinski",
  title		= "Representing Monads",
  pages		= "446--457",
  crossref	= "popl1994",
  url		= "http://www.diku.dk/~andrzej/papers/RM-abstract.html http://www.diku.dk/~andrzej/papers/RM.dvi http://www.diku.dk/~andrzej/papers/RM.ps.gz",
  abstract	= "We show that any monad whose unit and extension
operations are expressible as purely functional terms can be embedded
in a call-by-value language with ``composable continuations''. As part
of the development, we extend Meyer and Wand's characterization of the
relationship between continuation-passing and direct style to one for
continuation-passing vs.~general ``monadic'' style. We further show
that the composable-continuations construct can itself be represented
using ordinary, non-composable first-class continuations and a single
piece of state. Thus, in the presence of two specific computational
effects---storage and escapes---\emph{any} expressible monadic
structure (e.g., nondeterminism as represented by the list monad) can
be added as a purely definitional extension, without requiring a
reinterpretation of the whole language. The paper includes an
implementation of the construction (in Standard ML with some New
Jersey extensions) and several examples."
}

There is a follow-up:

@InProceedings{	filinski-layered,
  author	= "Andrzej Filinski",
  title		= "Representing Layered Monads",
  pages		= "175--188",
  crossref	= "popl1999",
  url		= "http://www.diku.dk/~andrzej/papers/RLM-abstract.html http://www.diku.dk/~andrzej/papers/RLM.dvi http://www.diku.dk/~andrzej/papers/RLM.ps.gz",
}

The term reification has been introduced 26 years ago:

@InProceedings{	friedman-reification,
  author	= {Daniel P. Friedman and Mitchell Wand},
  title		= {Reification: Reflection without Metaphysics},
  pages		= {348--355},
  crossref	= "lfp1984",
  abstract	= {We consider how the data structures of an
interpreter may be made available to the program it is running, and
how the program may alter its interpreter's structures. We refer to
these processes as reification and reflection. We show how these
processes may be considered as an extension of the fexpr concept in
which not only the form and the environment, but also the
continuation, are made available to the body of the procedure. We show
how such a construct can be used to effectively add an unlimited
variety of ``special forms'' to a very small base language. We
consider some trade-offs in how interpreter objects are reified. Our
version of this construct is similar to one in 3-Lisp [Smith 82, 84],
but is independent of the rest of 3-Lisp. In particular, it does not
rely on the notion of a tower of interpreters.}
}



More information about the Haskell-Cafe mailing list