
Hello, This is my first post to the Haskell Café, and I'm hoping the issue I'm tackling here isn't one that's been thoroughly explored elsewhere. If that's the case, I'll apologize in advance for my insufficient google chops. Otherwise, here goes... I do a lot of work within the error monad. Having read Eric Kidd's blog on error reporting in Haskell (http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-erro...), I'm always a bit paranoid about dealing with errors in the most generic, flexible way possible. As a result, a lot of the functions I use that could result in errors have signatures along these lines: couldThrowError :: (Error e, MonadError e m) => t1 -> t2 -> m t3 The way I figure it, this means that I can use these functions within any particular MonadError, which keeps me happy if I decide to change implementations at any particular point during development. Usually, I use these couldThrowError functions in a standard do block. Something along the lines of: couldThrowError :: (Error e, MonadError e m) => t1 -> t2 -> m t3 couldThrowError = do x <- processWithPossibleError t1 y <- processWithPossibleError t2 ... return (z :: t3) Things stay generic at this level. I can still choose any MonadError implementation I want, and if any of the computations in the do block throws an Error, the whole function short-circuits. Often enough, however, I don't want this kind of short-circuiting behavior. 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: groupErrors :: (Error e, MonadError e m) => [Either String a] -> m [a] groupErrors eithers = case partitionEithers eithers of ([], xs) -> return xs (es, _) -> strError $ unlines es The problem, though, is that running this function now causes type inference to provide "Either String" as my MonadError implementation. If any of the potential error sources are dealing with a different concrete implementation, I'm stuck! It would be nice if I could stay generic. I made an effort at this that you can see below, but it strikes me as very awkward. collectErrors :: (Monoid e, Error e, MonadError e m) => m a -> m [a] -> m [a] collectErrors m1 m2 = do m1r <- (m1 `catchError` (\e1 -> (m2 `catchError` (\e2 -> throwError $ mappend e1 e2)) >> throwError e1)) m2r <- m2 return $ m1r : m2r groupErrors' :: (Monoid e, Error e, MonadError e m) => [m a] -> m [a] groupErrors' = foldr collectErrors (return []) As you can see, I now require an error type that implements monoid. An example I've tested is: newtype ErrorString = ES String deriving (Read, Show, Eq, Ord, Error) instance Monoid ErrorString where mempty = ES "" mappend (ES s1) (ES s2) = ES $ s1 `mappend` "\n" `mappend` s2 This seems to work, but something strikes me as being very hackish here. Maybe it's just that collectErrors looks very ugly, and in Haskell my intuition tells me that what looks ugly on the surface is often ugly down below. I suspect that I might really not be approaching this problem the right way, but after a lot of time spent wrestling with it, I'm eager to read your suggestions. Is there a better way to do groupErrors, or should I be looking at an entirely different philosophy? Thanks, Grynszpan