[Haskell-cafe] control-monad-failure and mtl
Edward Z. Yang
ezyang at MIT.EDU
Mon Nov 30 16:08:54 EST 2009
Excerpts from Jose Iborra's message of Sun Nov 29 10:41:50 -0500 2009:
> There is indeed an Monad instance for Either in mtl,
> declared in the module Control.Monad.Error.
> I can't explain why your compiler cannot find it.
> Can you paste a blurb of code somewhere?
{-# LANGUAGE PackageImports, FlexibleContexts #-}
import "mtl" Control.Monad.Error
import Control.Monad.Failure
import Control.Monad.Failure.MTL
data MyError = MyError String
instance Error MyError where
strMsg = MyError
failureFunction :: MonadFailure MyError m => Integer -> m Integer
failureFunction 0 = failure $ MyError "Cannot use zero"
failureFunction n = return (n - 1)
-- instantiate
eitherFunction :: Either MyError Integer
eitherFunction = failureFunction 23
Which results in:
either.hs:17:17:
No instance for (MonadFailure MyError (Either MyError))
arising from a use of `failureFunction' at either.hs:17:17-34
Possible fix:
add an instance declaration for
(MonadFailure MyError (Either MyError))
In the expression: failureFunction 23
In the definition of `eitherFunction':
eitherFunction = failureFunction 23
> You need to import Control.Monad.Failure.MTL in order to bring the MTL
> instances into scope.
> The reason for this is that we provide instances both for MTL and transformers
> in the same
> package. These have to live in different modules to avoid a conflict due to the
> duplicated
> monad instance for Either.
Great, that fixed it! Where is this documented, or is this one of those conventions
that I'm supposed to know about? ;-)
> Very likely. Existing error handling packages such as control-monad-exception
> and attempt
> already provide this feature to convert other error forms into their specific
> error types.
> If this can be abstracted cleanly for a generic form of failure,
> then I would definitely support including it in control-monad-failure.
I was thinking about this, and I think the answer is basically yes, especially
if we assume that we're dealing with the monads Error e => Either e or
Either String which cover a big swath (most specifically Parsec, which I care
about). This is very much a "encylopedia" style problem.
I don't know if Haskell is powerful enough to get us the ability to have
such conversions be transparent though.
Cheers,
Edward
More information about the Haskell-Cafe
mailing list