transformers: remove instance MonadFix ExceptT and ErrorT

I propose to remove the MonadFix instance for the ExceptT transformer, because it gives the illusion that it can handle exceptions, which it cannot. The current implementation is: instance (MonadFix m) => MonadFix (ExceptT e m) where mfix f = ExceptT $ mfix $ \ a -> runExceptT $ f $ case a of Right x -> x Left _ -> error "mfix ExceptT: Left" You see, that it cannot handle the exception case. Whenever someone needs an mfix on ExceptT I strongly suggest that he first handles the exception, thus turning (ExceptT e m a) into plain (m a) and then calls 'mfix' only on (m a). I further propose to declare the MonadFix instance as non-implementable in a way suggested in [1]: class NoMonadFix m where instance (NoMonadFix m) => MonadFix (ExceptT e m) where mfix = error "unimplementable" where no instance of NoMonadFix exist and NoMonadFix is not exported. Whenever someone tries to call 'mfix' on 'ExceptT e m' he will get the type error, that a NoMonadFix instance on 'm' is missing and he will not be able to add it. [1] http://ghc.haskell.org/trac/ghc/ticket/9334#comment:9

Henning Thielemann wrote:
I propose to remove the MonadFix instance for the ExceptT transformer, because it gives the illusion that it can handle exceptions, which it cannot.
I think this analysis is not quite correct. The exception is not handled but propagated outside the mfix, which is what I would expect: ghci> runExcept (mfix (\_ -> throwE ())) Left () The only case where one gets to see the artificial bottom introduced in the exception case, is when one incorporates the fixpoint value into an exception: ghci> runExcept (mfix (\v -> throwE v)) Left *** Exception: mfix ExceptT: Left That looks reasonable to me, because indeed no value is being produced by the inner monad action. Note that 'mfix' is a partial function to begin with; one always has to be careful about using the produced value inside the argument of 'mfix'. -1 from me on the proposal. Cheers, Bertram

On 12-08-2014 12:10, Bertram Felgenhauer wrote:
ghci> runExcept (mfix (\v -> throwE v)) Left *** Exception: mfix ExceptT: Left
Perhaps the error message should be changed to something more descriptive, then. For example: "mfix ExceptT: Fixpoint computation depends on an exception". -- Felipe.

Note: This follows how MonadFix works for *every* Monad involving a sum type currently. instance MonadFix Maybe where mfix f = let a = f (unJust a) in a where unJust (Just x) = x unJust Nothing = error "mfix Maybe: Nothing" instance MonadFix (Either e) where mfix f = let a = f (unRight a) in a where unRight (Right x) = x unRight (Left _) = error "mfix Either: Left" so it seems the logical extension of your request would be to strip all such instances, which seems to me to speak to you having a different interpretation of the purpose of mfix than its original authors. -Edward On Tue, Aug 12, 2014 at 5:13 AM, Henning Thielemann < schlepptop@henning-thielemann.de> wrote:
I propose to remove the MonadFix instance for the ExceptT transformer, because it gives the illusion that it can handle exceptions, which it cannot.
The current implementation is:
instance (MonadFix m) => MonadFix (ExceptT e m) where mfix f = ExceptT $ mfix $ \ a -> runExceptT $ f $ case a of Right x -> x Left _ -> error "mfix ExceptT: Left"
You see, that it cannot handle the exception case. Whenever someone needs an mfix on ExceptT I strongly suggest that he first handles the exception, thus turning (ExceptT e m a) into plain (m a) and then calls 'mfix' only on (m a).
I further propose to declare the MonadFix instance as non-implementable in a way suggested in [1]:
class NoMonadFix m where
instance (NoMonadFix m) => MonadFix (ExceptT e m) where mfix = error "unimplementable"
where no instance of NoMonadFix exist and NoMonadFix is not exported. Whenever someone tries to call 'mfix' on 'ExceptT e m' he will get the type error, that a NoMonadFix instance on 'm' is missing and he will not be able to add it.
[1] http://ghc.haskell.org/trac/ghc/ticket/9334#comment:9 _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Am 12.08.2014 um 21:17 schrieb Edward Kmett:
so it seems the logical extension of your request would be to strip all such instances,
one by one, please :-) Can someone provide me examples of useful applications of mfix on Maybe, ExceptT etc.? I mean, all those mfix instances contain an "error" - wouldn't it be better if the user would do such dirty things and insert a more specific error message? Admittedly, I have used mfix only once so far, at all, namely on an RWS monad, as far as I remember. Eventually I chose another design, because the mfix way was too fragile.

Henning: I don't think this is the right forum to discuss examples of mfix. Granted, it's not something everyone needs every day; think about how often you write recursive data-values, and imagine how often you need those to be happening in some monad. Not very often. But the phenomenon has been well studied, and there are a few illustrative "real-world" examples in Chapter 9 of: https://sites.google.com/site/leventerkok/erkok-thesis.pdf -Levent. On Tue, Aug 12, 2014 at 2:34 PM, Henning Thielemann < schlepptop@henning-thielemann.de> wrote:
Am 12.08.2014 um 21:17 schrieb Edward Kmett:
so it seems the logical extension of your request would be to strip all
such instances,
one by one, please :-)
Can someone provide me examples of useful applications of mfix on Maybe, ExceptT etc.?
I mean, all those mfix instances contain an "error" - wouldn't it be better if the user would do such dirty things and insert a more specific error message?
Admittedly, I have used mfix only once so far, at all, namely on an RWS monad, as far as I remember. Eventually I chose another design, because the mfix way was too fragile.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Henning Thielemann wrote:
Am 12.08.2014 um 21:17 schrieb Edward Kmett:
so it seems the logical extension of your request would be to strip all such instances,
one by one, please :-)
Can someone provide me examples of useful applications of mfix on Maybe, ExceptT etc.?
I tend to agree that those MonadFix instances are not immensely useful. As far as I can see, all one can do is a certain amount of knot-tying on the value level on the fly. Going beyond that is prevented because nothing is known about the return value of 'mfix f' until 'f' has run to a successful (non-error) completion; if the success depends in any way on the argument to 'f', the computation will bottom out. For example, a parser for a simple language with gotos could be based on parseProgram :: Labels -> StateT String Maybe (Program, Labels) where 'Labels' stores a map from label names to program locations. Then 'mfix' can be used to feed the resulting labels right back into 'parseProgram'. The use of 'mfix' is not essential though. In principle, one can transform parseProgram into a function parseProgram' :: StateT String Maybe (Labels -> (Program, Labels)) and use an ordinary fixpoint to tie the knot. But 'mfix' buys some convenience. (Note that this convenience comes at a fairly big cost in the case of the list monad's 'mfix' implementation, which reruns the whole list computation for each element of the result list.) I think that this is basically true for all uses of 'mfix' for monads that do not have a linear flow of computation.
I mean, all those mfix instances contain an "error" - wouldn't it be better if the user would do such dirty things and insert a more specific error message?
If those particular error messages turn up then they indicate programming errors: using 'mfix f' in such a way that success depends on the argument of f, or letting the argument of 'f' escape in the case of an unsuccessful evaluation. So I still think that those are the right instances, even though the error messages are not perfect.
Admittedly, I have used mfix only once so far, at all, namely on an RWS monad, as far as I remember. Eventually I chose another design, because the mfix way was too fragile.
I've also found 'mfix' to be of limited use in practice, but there are some cute applications, like spawning a thread, passing it its own thread id: mfix (\tid -> forkIO (f tid)). Cheers, Bertram

On Aug 12, 2014 7:50 PM, "Bertram Felgenhauer" < bertram.felgenhauer@googlemail.com> wrote:
I tend to agree that those MonadFix instances are not immensely useful.
From my perspective as a generally ignorant person, I think these should be kept as long as
1. They satisfy the required laws and 2. No more useful instances can be written. That said, it might make sense to remove them if 1*. You can formulate a new law that distinguishes the instances you consider sensible from the ones you consider insensible. and to change them if 2*. More useful instances can be written. If potential confusion is the only issue, improving the documentation would probably be the way to go. David Feuer

David Feuer wrote:
On Aug 12, 2014 7:50 PM, "Bertram Felgenhauer" < bertram.felgenhauer@googlemail.com> wrote:
I tend to agree that those MonadFix instances are not immensely useful.
From my perspective as a generally ignorant person, I think these should be kept as long as
1. They satisfy the required laws and 2. No more useful instances can be written.
I agree completely, and I never wanted to remove the instances. Cheers, Bertram

Am 13.08.2014 um 02:02 schrieb David Feuer:
On Aug 12, 2014 7:50 PM, "Bertram Felgenhauer"
I tend to agree that those MonadFix instances are not immensely useful.
From my perspective as a generally ignorant person, I think these should be kept as long as
1. They satisfy the required laws and 2. No more useful instances can be written.
That said, it might make sense to remove them if
1*. You can formulate a new law that distinguishes the instances you consider sensible from the ones you consider insensible.
and to change them if 2*. More useful instances can be written.
I was not argueing from a mathematical point of view but from a safety point of view. It's the same reason why I object to, say (Ord (Complex a)) and (Num (a -> b)). Incidentally, I had the ThreadId problem last week, but fortunately I could solve it with myThreadId instead of mfix.
If potential confusion is the only issue, improving the documentation would probably be the way to go.
Generally I prefer removing dangerous behaviour instead of documenting it. The documentation may easily be missed, a compiler error message cannot.

On Tue, Aug 12, 2014 at 08:02:13PM -0400, David Feuer wrote:
On Aug 12, 2014 7:50 PM, "Bertram Felgenhauer" < bertram.felgenhauer@googlemail.com> wrote:
I tend to agree that those MonadFix instances are not immensely useful.
From my perspective as a generally ignorant person, I think these should be kept as long as
1. They satisfy the required laws and 2. No more useful instances can be written.
That said, it might make sense to remove them if
1*. You can formulate a new law that distinguishes the instances you consider sensible from the ones you consider insensible.
There is a law that discriminates against the instances on strict monads, known as right shrinking or right tightening: mfix (\ (x,_) -> f x >>= rightM g) = mfix f >>= rightM g where rightM :: Monad m => (a -> m b) -> a -> m (a, b) rightM f x = f x >>= \ y -> return (x, y) A special case is mfix (const e) = e In do-notation, these become do {rec {ss; x <- e}; ss'} = do {rec {ss}; x <- e; ss'} (x not free in ss or e) do {rec {x <- e}; ss} = do {x <- e; ss} (x not free in e) This law is pretty handy, but it was deliberately omitted from the axioms for the MonadFix class, to permit the axioms for Maybe, Either, [] and IO. The transformers package is just following those.

Henning: When a computation fails, there's no value to tie the recursive knot over. And in those cases, mfix is supposed to produce bottom. There's actually even a theorem showing that the mfix as defined satisfies all the required axioms of value-recursion if the underlying monad's mfix does (Page 54, Proposition 4.9.1 of https://sites.google.com/site/leventerkok/erkok-thesis.pdf) -Levent. On Tue, Aug 12, 2014 at 2:13 AM, Henning Thielemann < schlepptop@henning-thielemann.de> wrote:
I propose to remove the MonadFix instance for the ExceptT transformer, because it gives the illusion that it can handle exceptions, which it cannot.
The current implementation is:
instance (MonadFix m) => MonadFix (ExceptT e m) where mfix f = ExceptT $ mfix $ \ a -> runExceptT $ f $ case a of Right x -> x Left _ -> error "mfix ExceptT: Left"
You see, that it cannot handle the exception case. Whenever someone needs an mfix on ExceptT I strongly suggest that he first handles the exception, thus turning (ExceptT e m a) into plain (m a) and then calls 'mfix' only on (m a).
I further propose to declare the MonadFix instance as non-implementable in a way suggested in [1]:
class NoMonadFix m where
instance (NoMonadFix m) => MonadFix (ExceptT e m) where mfix = error "unimplementable"
where no instance of NoMonadFix exist and NoMonadFix is not exported. Whenever someone tries to call 'mfix' on 'ExceptT e m' he will get the type error, that a NoMonadFix instance on 'm' is missing and he will not be able to add it.
[1] http://ghc.haskell.org/trac/ghc/ticket/9334#comment:9 _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (7)
-
Bertram Felgenhauer
-
David Feuer
-
Edward Kmett
-
Felipe Lessa
-
Henning Thielemann
-
Levent Erkok
-
Ross Paterson