[Haskell-cafe] control-monad-failure and mtl

Edward Z. Yang ezyang at MIT.EDU
Sat Nov 28 16:08:59 EST 2009


Hello folks,

I took advantage of Thanksgiving weekend to port my application to use
Control.Monad.Failure, and learned (slightly painfully) that I still
needed to pick some mechanism to instantiate my failure monads as.
After the experience, I have three questions/comments:

1. Why isn't there an instance for Either in mtl? (There is one for
Transformers.  The error message left me very puzzled there: the docs
clearly claimed the instance existed, and only a little source code
diving elucidated the situation.)  Copying the instance declaration
from the transformers version seems to fix it.

2. I was having difficulty instantiating MonadFailure as an ErrorT
for an arbitrary monad.  Here is an example:

    {-# LANGUAGE PackageImports, FlexibleContexts #-}

    import "mtl" Control.Monad.Error
    import "mtl" Control.Monad.State
    import Control.Monad.Failure

    data MyError = MyError String
    instance Error MyError where
        strMsg = MyError

    type MyMonad = ErrorT MyError (State Integer)

    failureFunction :: MonadFailure MyError m => Integer -> m Integer
    failureFunction 0 = failure $ MyError "Cannot use zero"
    failureFunction n = return (n - 1)

    -- instantiate
    monadicFunction :: MyMonad Integer
    monadicFunction = failureFunction 23

Which results in the following error:

    failure.hs:19:18:
        No instance for (MonadFailure
                           MyError (ErrorT MyError (State Integer)))
          arising from a use of `failureFunction' at failure.hs:19:18-35
        Possible fix:
          add an instance declaration for
          (MonadFailure MyError (ErrorT MyError (State Integer)))
        In the expression: failureFunction 23
        In the definition of `monadicFunction':
            monadicFunction = failureFunction 23

Which seems to contradict the documentation and source code, which states:

    Instances: [...]
        (Error e, Monad m) => MonadFailure e (ErrorT e m)

How do I misunderstand?

3. In a motivating example, one of the goals of MonadFailure is to let
us mix the error code of third-party modules into the generic failure mode.
Control.Monad.Failure appears to give the machinery for instantiating a generic
failure monad, but it doesn't have any facilities for the opposite direction:
that is, marshalling a specific error form into the generic error form.  Am I
mistaken, and if not, would it be a welcome addition to the library?

Cheers,
Edward


More information about the Haskell-Cafe mailing list