How can I use `throwM` with `Except`? - haskell

There is a package transformers that features the monad Except.
This monad transformer extends a monad with the ability to throw exceptions.
There is a package exceptions that features the effect throwM.
Throw an exception. ...
So it would seem that these two should play well together. However:
λ runExcept $ throwM Overflow
<interactive>:46:13: error:
• No instance for (MonadThrow Data.Functor.Identity.Identity)
arising from a use of ‘throwM’
• In the second argument of ‘($)’, namely ‘throwM Overflow’
In the expression: runExcept $ throwM Overflow
In an equation for ‘it’: it = runExcept $ throwM Overflo
I know I can use the monad Catch. But anyway, I would like to
understand what is going on. I am not very familiar with monad transformers.

The compiler infers types this way:
Since runExcept :: Except e a -> ..., the argument of runExcept must be of type Except e a.
So, throwM Overflow :: Except e a
Except e a is a type synonym for ExceptT e Identity a.
So, throwM Overflow :: ExceptT e Identity a
Because throwM :: MonadThrow m => e -> m a, the compiler needs to find an instance of ThrowM for a type that would match ExceptT e Identity.
And look: there is such instance: MonadThrow m => MonadThrow (ExceptT e m). It matches any ExceptT e m for any m, but this m also must have an instance of MonadThrow.
Matching up the type of throwM Overflow, which is ExceptT e Identity a, and the type for which the MonadThrow instance is defined, which is Except T m, the compiler determines that m = Identity.
But wait! According to the instance definition MonadThrow m => MonadThrow (ExceptT e m), this m (which we now know to be Identity) must also have a MonadThrow instance.
So the compiler looks for that, and doesn't find it.
And displays you an error message: "No instance MonadThrow Identity"
Type class-related error messages can be vexing. The compiler doesn't always tell you the full chain of conclusions it has followed in order to reach the error. This is unfortunate, but whatchagonnado.
But the underlying problem here is that Except and throwM aren't actually compatible. That is to say, throwM throws errors in a different sense than Except contains errors. They're two different error-related mechanisms. In order to throw an Except-compatible error, use its own throwE. This should work:
> runExcept $ throwE Overflow
Left Overflow
As far as I understand at the moment, the error-handling landscape in Haskell hasn't yet settled down to a manageable state. We have Except, which got generalized to ExceptT, and then we have throw, throwTo, throwIO, throwSTM, throwE, throwError, throwM, and all of those have variants from different libraries and under different monads. Plus, the arrival of UnliftIO has complicated things even further. It sort of looks like ExceptT will be going away as a result.

Related

How to use Handlers that don't have SomeException as their argument type

When using Control.Monad.Throw (i.e. exceptions package), something that confuses me that it seem that all my my throwing and catching has to work with SomeException.
E.g.
value :: Either ExitCode String
value = throwM $ ExitFailure 23
This looks to me like it should compile, because throwM :: (Exception e, MonadThrow m) => e -> m a, and ExitCode has an instance of Exception. Even this doesn't compile:
value :: Exception e => Either e String
value = throwM $ ExitFailure 23
In fact, it only compiles when I change the signature to SomeException. I know the Exception type class has a special place re
In the documentation for Control.Exception I could see examples where they use catches with handlers of signature ArithException -> m a or similiar. I tested it and it worked.
Is this not possible when using exceptions?
EDIT
The error messages are either:
Couldn't match type ExitCode with SomeException arising from a use of throwM
or
Couldn't match type e with SomeException arising from a use of throwM
The behavior you are seeing is from the type signature of throwM:
throwM :: (Exception e, MonadThrow m) => e -> m a
And the instance for Either, which is essentially:
MonadThrow (Either SomeException)
This makes throwM:
throwM :: (Exception e) => e -> Either SomeException a
throwM for Either SomeException can take any Exception e.
However, there is no MonadThrow instance for Either ExitCode, or for forall e. Exception e => Either e.
The problem is that there isn't really a way to write an instance that's polymorphic for all e. Imagine having an instance
Exception q => MonadThrow (Either q)
This would make throwM:
throwM :: (Exception e, Exception q) => e -> Either q a
which means you have to be able to take any e and convert it into any q, which is not possible using the Exception typeclass alone.
Imagine also if there was a MonadThrow instance for Either ExitCode. That would make the type signature for throwM:
throwM :: Exeption e => e -> Either ExitCode a
which you can probably see is clearly nonsensical, since there are many instances of Exception that cannot be coerced to an ExitCode. (Try writing a function with that type signature if you don't believe me!)
If you just want short-circuting exception behavior for Either, consider:
Just use Left instead of throwM, and pattern matching for catch. If you really want to use Exception still, you can use fromException to attempt to coerce a SomeException into an Exception instance of your choice.
You can use the exceptions package, and catching will still work as long as you must assume that the exception could be any instance (SomeException)
Use MonadError and ExceptT from mtl, if you want some sort of polymorphic interface with catching ability

Satisfy the condition that 'A uniquely determines B' when using Functional Dependencies in Haskell

I am trying to write a ‘logger’ Monad Transformer. Other Monad Transformers will then be applied to it, to form a more complex monad. I want the logger function to work on all these monads, so I wrote a typeclass as follows.
class Logger e m | m -> e where
logMessage :: e -> m ()
The reason I use Functional Dependencies here, is that the monad m will explicitly contain the type e (as what it is with State monad), which stands for the message type.
The transformer ET is made an instance of typeclass Logger.
data ET e m a = ET { ... }
instance Monad m => Monad (ET e m) where
logMessage msg = ...
instance Monad m => Logger e (ET e m) where
logMessage msg = ...
Now, I want the monad T1 (T2 ... (ET m)) (which has an ET in the transformer chain) to be an instance of typeclass Logger, but it failed to compile. Below is the code.
instance (Logger e m, MonadTrans t) => Logger e (t m) where
logMessage = lift . logMessage
I thought that since t is only a Monad Transformer, and m is guaranteed to uniquely determine e, then t m should also uniquely determine e. But the compiler seems to think differently.
Test.hs:43:10: error:
? Illegal instance declaration for ‘Logger e (t m)’
The coverage condition fails in class ‘Logger’
for functional dependency: ‘m -> e’
Reason: lhs type ‘t m’ does not determine rhs type ‘e’
Un-determined variable: e
Using UndecidableInstances might help
? In the instance declaration for ‘MonadException e (t m)’
|
43 | instance (Logger e m, MonadTrans t) => Logger e (t m) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.
Can anyone explain how the extension FunctionalDependencies works, as well as how to solve this problem?
The compiler I use is The Glorious Glasgow Haskell Compilation System, version 8.2.2, on Windows 10.
The trouble is that while m -> e it doesn't follow that t m -> e because the compiler doesn't know anything about what t might do.
What you have defined is not actually a monad transformer, its a class of Logger monads. Canonically, the mtl way of approaching this would be:
Define a class (Monad m) => MonadLogger e m | m -> e (just rename your existing class).
Define newtype LoggerT e m a = LoggerT(runLoggerT :: m <...>). This is your monad transformer. runLoggerT unwraps a LoggerT action and returns a value in the inner monad m. The details of what it returns are up to you.
Create instances of Monad, MonadTrans and MonadLogger for LoggerT.
Define type Logger e = Logger e Identity
Create inductive instances for all the other mtl monad transformers.
If you take a look at the examples in the mtl library you should be able to see how its done.
Many thanks to #Carl, this problem is solved.
When I turned on the language extension Undecidable Instances (by {-# LANGUAGE UndecidableInstances #-}), this error message disappeared.
Though still I wonder why this extension is needed, for now, it really makes the code compile.

Control.Exception.Safe, why do ExceptT and Either behave so differently?

I'm trying to use Control.Exception.Safe with Control.Monad.Except.
throwString "Foo" :: Except String a
-- error, no instance for `MonadTrow Identity`
Ok, so apparently Except throws its error into its underlying monad in the transformer stack?
But why is that? Isn't Except basically designed to handle exceptions? Why this weird behavior? Why not the equivalent of Left "Foo"
EDIT:
Okay to further illustrate my problem:
I thought ExceptT e m a was to Either e a what ReaderT a m b is to a -> b. Control.Monad.Except.throwError, and catchError work exactly like Control.Exception.Safe.throw, and catch do with Either e a.
However they suddenly work different when applied to Except e a.
What do I do, when I want to use the behaviour of Either e a that is supplied by Control.Exception.Safe but in the context of monad transformers?
My context is that I do "Write yourself a Scheme in 48 hours" and wanted to generalize errors (with MonadThrow), so that I can do some IO stuff with it.
EDIT2:
Example:
data CountError = CountError deriving (Show, Except)
x :: String -> ExceptT CountError (Writer [String]) Int
x str = do { lift $ writer (length "str", return str); }
Now this count characters and collects the strings in the writer. This could be extended however much you want. The error could signal "wrong character in string", or "too many characters", or whatever.
y :: MonadThrow m => m a
y = throw CountError
This is a very general exception, which I could use for composition with any other kind of exception, except for ExceptT:
y >> x
-- No instance for MonadThrow Identity
-- But what I want is (Left CountError, [])
Ok, so apparently Except throws its error into its underlying monad in the transformer stack?
As I said in the comment: Except doesn't "throw it's error into the underlying monad", that's just what the MonadThrow instances is doing.
But why is that?
The instance of MonadThrow can not throw a String exception into ExceptT e for all types e and rather than have an instance just for ExceptT String it appears the author lifted to throw an exception on the next higher monad.
Isn't Except basically designed to handle exceptions?
Indeed Except is designed to allow for failure in exceptional cases.
Being pedantic, I'd call it an alternative to exceptions. A monad plumbing an alternative notion of return (an error case) and calling itself "Except" doesn't actually mean any of the typical exception options, such as a low level stack unwinding, is in use.
Why this weird behavior?
Because of the MonadThrow instance, which is re-exported from Control.Monad.Throw:
-- | Throws exceptions into the base monad.
instance MonadThrow m => MonadThrow (ExceptT e m) where
throwM = lift . throwM
Why not the equivalent of Left "Foo"
Because then the instance would have to be for ExceptT String instead of ExceptT e. Or, that is why I think the author of exceptions (Edward Kmett) decided on this design.
Instead, consider using Control.Monad.Except.throwError which does what it sounds like you want.
What do I do, when I want to use the behaviour of Either e a that is supplied by Control.Exception.Safe but in the context of monad transformers?
What "behavior of Either e a are you talking about? How is what you are looking for different from throwError? As far as I can tell, you are looking for an unnecessary extra layer of abstraction.
This is a bit of an old question but I think there is room to improve on this answer as I recently ran into this topic at work. Let's see, I believe that your expectation of having ExceptT behave similar to Either makes sense, but unfortunately the author of MonadThrow chose a different stance and decided that "passing" the decision on how to "throw" a failure to the underlying monad (or transformer) was the right way to go. Without attempting to speculate why decision was made, I agree that this behavior defeats the purpose of using a "failable" transformer such as 'MaybeT' or 'ExceptT' as an instance of an error class like MonadThrow, which is to give "Maybe" or "Either" like semantics to a different monad.
For this reason I have donned my flame vest and took a stab at Control.Monad.Failable , which would do exactly what you (and I) would expect, which is to return something like Left e where e is an instance of Exception.
Control.Monad.Failable

MonadPlus instance for Control.Eff when Exc is member

In monad transformers, we have
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m)
In extensible effects, there is no such thing as
instance (Monoid e) => MonadPlus (Eff (Exc e :> r))
I've tried implementing it, in vain. Here is what I have so far:
instance (Monoid e) => MonadPlus (Eff (Exc e :> r)) where
mzero = throwExc mempty
a `mplus` b = undefined $ do
resultA <- runExc a
case resultA of
Left l -> runExc b
Right r -> return $ Right r
There are 2 issues:
for mzero, GHC complains as follows:
Could not deduce (Monoid e0) arising from a use of ‘mempty’
from the context (Monad (Eff (Exc e :> r)), Monoid e)
Why doesn't GHC match e0 with e ?
Answer (provided in comment): turn on ScopedTypeVariables
for mplus, undefined should be replaced with the inverse function of runExc, but I can't find it in the API of extensible-effects. Did I miss something ?
Rationale: I want to be able to write a <|> b within Member (Exc e) r => Eff r a, meaning:
try a
if a throws ea, try b
if b throws eb, then throw mappend ea eb
This requires an Alternative instance, which is why I am attempting to implement a MonadPlus instance in the first place.
Note: I'm using GHC 7.8.3 .
Thank you in advance for your help.
I think you may be confused about extensible effects and the desired
instance MonadPlus (Eff (Exc e :> r)) shows the confusion.
If you wish to build a non-deterministic computation and also throw
exceptions, you can do that already without any need for new
instances. I think I may be partly responsible for the confusion by
defining separate mzero' and mplus' which are fully equivalent to
those in MonadPlus. Anyway, because of this equivalence,
you can simply write
instance Member Choose r => MonadPlus (Eff r) where
mzero = mzero'
mplus = mplus'
The instance says: A computation that has a Choose effect, among
others, is an instance of the MonadPlus computation. Let me stress
the part ``among others''. The computation may have other effects,
for example, throw exceptions. The MonadPlus instance above covers
that case, as well as all others.
Thus, to use non-determinism and exceptions, you just use mplus, mzero
(or mplus', mzero') along with throwExc. There is no need to define
any new instances - in stark contrast with Monad Transformers.
Of course you have to decide how you want your exceptions to interact
with non-determinism: should an exception discard all choices or only
remaining choices? This depends on how you order your handlers, which
effect gets handled first. Moreover, you can write a handler for both
Choose and Exc effects (to keep the already made choices upon an
exception and discard the remaining -- thus modeling Prolog's cut).
The code of the library (and the code accompanying the paper) has examples of that.
Edit in reply to the amended question:
If all you need is <|>, it can be implemented simply, without MonadPlus or cut.
This operator is merely a form of exception handling, and is implementable as the
composition of two catchError. Here is the full code
alttry :: forall e r a. (Typeable e, Monoid e, MemberU2 Exc (Exc e) r) =>
Eff r a -> Eff r a -> Eff r a
alttry ma mb =
catchError ma $ \ea ->
catchError mb $ \eb -> throwError (mappend (ea::e) eb)
If the computation ma finishes successfully, its result is returned. Otherwise,
mb is tried; it it finishes successfully, its result is returned. If both fail,
the mappend-ed exception is raised. The code directly matches the English specification.
We use MemberU2 in the signature rather than Member to
ensure that the computation throws only one type of exceptions.
Otherwise, this construction is not very useful. I used the original implementation
Eff.hs. That file also contains the test case.
BTW, with extensible effects there is no
need to define or use type classes like MonadPlus, MonadState, etc. These type classes
were intended to hide the concrete layout of the MonadTransformer stack. With extensible effects, there is nothing to hide. The crutches are no longer needed.

Transformation under Transformers

I'm having a bit of difficulty with monad transformers at the moment. I'm defining a few different non-deterministic relations which make use of transformers. Unfortunately, I'm having trouble understanding how to translate cleanly from one effectful model to another.
Suppose these relations are "foo" and "bar". Suppose that "foo" relates As and Bs to Cs; suppose "bar" relates Bs and Cs to Ds. We will define "bar" in terms of "foo". To make matters more interesting, the computation of these relations will fail in different ways. (Since the bar relation depends on the foo relation, its failure cases are a superset.) I therefore give the following type definitions:
data FooFailure = FooFailure String
data BarFailure = BarSpecificFailure | BarFooFailure FooFailure
type FooM = ListT (EitherT FooFailure (Reader Context))
type BarM = ListT (EitherT BarFailure (Reader Context))
I would then expect to be able to write the relations with the following function signatures:
foo :: A -> B -> FooM C
bar :: B -> C -> BarM D
My problem is that, when writing the definition for "bar", I need to be able to receive errors from the "foo" relation and properly represent them in "bar" space. So I'd be fine with a function of the form
convert :: (e -> e') -> ListT (EitherT e (Reader Context) a
-> ListT (EitherT e' (Reader Context) a
I can even write that little beast by running the ListT, mapping on EitherT, and then reassembling the ListT (because it happens that m [a] can be converted to ListT m a). But this seems... messy.
There's a good reason I can't just run a transformer, do some stuff under it, and generically "put it back"; the transformer I ran might have effects and I can't magically undo them. But is there some way in which I can lift a function just far enough into a transformer stack to do some work for me so I don't have to write the convert function shown above?
I think convert is a good answer, and using Control.Monad.Morph and Control.Monad.Trans.Either it's (almost) really simple to write:
convert :: (Monad m, Functor m, MFunctor t)
=> (e -> e')
-> t (EitherT e m) b -> t (EitherT e' m) b
convert f = hoist (bimapEitherT f id)
the slight problem is that ListT isn't an instance of MFunctor. I think this is the author boycotting ListT because it doesn't follow the monad transformer laws though because it's easy to write a type-checking instance
instance MFunctor ListT where hoist nat (ListT mas) = ListT (nat mas)
Anyway, generally take a look at Control.Monad.Morph for dealing with natural transformations on (parts of) transformer stacks. I'd say that fits the definition of lifting a function "just enough" into a stack.

Resources