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

2009-11-30 Thread Edward Z. Yang
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-29 Thread Jose Iborra

On 28/11/2009, at 22:08, Edward Z. Yang wrote:

 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.
 

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?


 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?
 

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.


 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?

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.

Thanks,
pepe___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-28 Thread Edward Z. Yang
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe