Difference between revisions of "MonadFail Proposal"
EdwardKmett (talk | contribs) (Reflect the current timeline under consideration by the CLC) |
(Add note that article was moved to Haskell' Wiki) |
||
Line 1: | Line 1: | ||
+ | '''Note:''' this proposal page has been moved to [https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail the Haskell Prime Wiki]; the article below is unmaintained. | ||
+ | |||
+ | |||
== <code>MonadFail</code> proposal (MFP) == | == <code>MonadFail</code> proposal (MFP) == | ||
Revision as of 18:00, 25 November 2015
Note: this proposal page has been moved to the Haskell Prime Wiki; the article below is unmaintained.
Contents
MonadFail
proposal (MFP)
A couple of years ago, we proposed to make Applicative
a superclass of Monad
which successfully killed the single most ugly thing in Haskell as of GHC 7.10.
Now, it's time to tackle the other major issue with Monad
fail
being a part of it.
You can contact me as usual via IRC/Freenode as quchen, or by email to dluposchainsky at the email service of Google. This file was posted on the ghc-devs@ and libraries@ mailing lists, as well as on Reddit.
This proposal was first posted on quchen's articles Github repo.
Overview
- The problem - reason for the proposal
- MonadFail class - the solution
- Discussion - explaining our design choices
- Adapting old code - how to prepare current code to transition smoothly
- Estimating the breakage - how much stuff we will break
- Transitional strategy - how to break as little as possible while transitioning
- Current status
The problem
Currently, the <-
symbol is unconditionally desugared as follows:
do pat <- computation >>> let f pat = more
more >>> f _ = fail "..."
>>> in computation >>= f
The problem with this is that fail
cannot (!) be sensibly implemented for many monads, for example Either
, State
, IO
, and Reader
. In those cases it defaults to error
As a consequence, in current Haskell, you can not use Monad
polymorphic code safely, because although it claims to work for all Monad
, it might just crash on you. This kind of implicit non-totality baked into the class is terrible.
The goal of this proposal is adding the fail
only when necessary and reflecting that in the type signature of the do
block, so that it can be used safely, and more importantly, is guaranteed not to be used if the type signature does not say so.
MonadFail
class
To fix this, introduce a new typeclass:
class Monad m => MonadFail m where
fail :: String -> m a
Desugaring can now be changed to produce this constraint when necessary. For this, we have to decide when a pattern match can not fail; if this is the case, we can omit inserting the fail
call.
The most trivial examples of unfailable patterns are of course those that match anywhere unconditionally,
do x <- action >>> let f x = more
more >>> in action >>= f
In particular, the programmer can assert any pattern be unfailable by making it irrefutable using a prefix tilde:
do ~pat <- action >>> let f ~pat = more
more >>> in action >>= f
A class of patterns that are conditionally failable are newtype
, and single constructor data
types, which are unfailable by themselves, but may fail if matching on their fields is done with failable patterns.
data Newtype a = Newtype a
-- "x" cannot fail
do Newtype x <- action >>> let f (Newtype x) = more
more >>> in action >>= f
-- "Just x" can fail
do Newtype (Just x) <- action >>> let f (Newtype (Just x)) = more
more >>> f _ = fail "..."
>>> in action >>= f
ViewPatterns
are as failable as the pattern the view is matched against. Patterns like (Just -> Just x)
should generate a MonadFail
constraint even when it's "obvious" from the view's implementation that the pattern will always match. From an implementor's perspective, this means that only types (and their constructors) have to be looked at, not arbitrary values (like functions), which is impossible to do statically in general.
do (view -> pat) <- action >>> let f (view -> pat) = more
more >>> f _ = fail "..."
>>> in action >>= f
do (view -> ~pat) <- action >>> let f (view -> ~pat) = more
more >>> in action >>= f
[Edward Kmett: `(view -> pat)` should be unfailing iff pat is unfailing.]
A similar issue arises for PatternSynonyms
which we cannot inspect during compilation sufficiently. A pattern synonym will therefore always be considered failable.
do PatternSynonym x <- action >>> let f PatternSynonym x = more
more >>> f _ = fail "..."
>>> in action >>= f
[Edward Kmett: We have the contents of the pattern synonym available to us at the definition site. With some work we should be able to expose it enough that the compiler can see through it:
pattern Foo a b = Bar a 0 b
pattern Baz a b c <- Quux a b c
Both of those tell us the "real" desugaring as just another pattern we could recurse into.]
Discussion
- What laws should
fail
follow?- Left zero:
∀ s f. fail s >>= f ≡ fail s
. - Right zero:
∀ v s. v >> fail s ≡ fail s
.
- Left zero:
- What is the relationship to
MonadPlus
?- As the laws above indicate,
fail
is a close relative ofmzero
. We could suggest a default definition offail _ = mzero
, which shows the intended usage and effect of theMonadFail
class. - However, we should not remove
fail
and use onlymzero
instead.- Not all types with
Monad
instances haveMonadPlus
instances. - Some types do use the
String
argument tofail
. For example, a parser might fail with a message involving positional information.Binary
usesfail
as their only interface to fail a decoding step. - Some types have different definitions for
mzero
andfail
. AlthoughSTM
isMonadPlus
it uses the defaultfail = error
. It should therefore not get aMonadFail
instance.
- Not all types with
- As the laws above indicate,
- Rename
fail
?- No. Old code might use
fail
explicitly and we should avoid breaking it. The Report talks aboutfail
and we have a solid migration strategy that does not require a renaming.
- No. Old code might use
- Remove the
String
argument?- No. The
String
might help error reporting and debugging.String
may be ugly, but it's the de facto standard for simple text in GHC. No high performance string operations are to be expected withfail
so this breaking change would in no way be justified. Also note that explicitfail
calls would break if we removed the argument.
- No. The
- How sensitive would existing code be to subtle changes in the strictness behaviour of
do
notation pattern matching?- It doesn't. The implementation does not affect strictness at all, only the desugaring step. Care must be taken when fixing warnings by making patterns irrefutable using
~
as that does affect strictness. (Cf. difference between lazy/strict State)
- It doesn't. The implementation does not affect strictness at all, only the desugaring step. Care must be taken when fixing warnings by making patterns irrefutable using
- Do we need a class constraint (e.g.
Monad
) onMonadFail
?- Yes. The intended use of
fail
is for desugaringdo
-notation, not generally for anyString -> m a
function. Given that goal, we would rather keep the constraints simple asMonadFail m =>
rather than the somewhat redundant(Monad m, MonadFail m) =>
.
- Yes. The intended use of
- Can we relax the class constraint from
Monad
toApplicative
?- We don't necessarily have to choose now. Since
Applicative
is a superclass ofMonad
, it is possible to change the superclass forMonadFail
toApplicative
later. This will naturally require a migration period, and the name will, of course, become misleading. - For the sake of discussion, let's use the following definition:
class Applicative f => ApplicativeFail f where fail :: String -> f a
- Pros
ApplicativeDo
is coming, andfail
may be useful to combine pattern matching andApplicative
code.- If the
Monad
constraint is kept, that would forceApplicative
code with pattern matching to beMonad
code.
- Cons
- The constraints for
Monad
code usingfail
become(Monad m, ApplicativeFail m) =>
instead of the simplerMonadFail m =>
. If we expect the common use offail
to be inMonad
— notApplicative
—do
-notation, this leaves us with more verbose constraints.
- The constraints for
- Here are alternative definitions (with names open to debate) that would allow us to keep the constraints simple:
class Applicative f => ApplicativeFail f where failA :: String -> f a
class ApplicativeFail m => MonadFail m where fail :: String -> m a; fail = failA
- Since we do not have much experience using
ApplicativeDo
, it is not yet clear that this large of a change is useful.
- We don't necessarily have to choose now. Since
- Which types with
Monad
instances will not haveMonadFail
instances?base
:Either
transformers
:stm
:STM
- What
MonadFail
instances will be created?base
:IO
transformers
:- Proposal for an
Either
instance usingMonad
instance inControl.Monad.Trans.Error
:instance MonadFail (Either String) where fail = Left
- Proposal for an
Adapting old code
- Help! My code is broken because of a missing
MonadFail
instance! Here are your options:- Write a
MonadFail
instance (and bring it into scope)#if !MIN_VERSION_base(4,11,0) -- Control.Monad.Fail import will become redundant in GHC 7.16+ import qualified Control.Monad.Fail as Fail #endif import Control.Monad instance Monad Foo where (>>=) = <...bind impl...> -- NB: <code>return</code> defaults to <code>pure</code> #if !MIN_VERSION_base(4,11,0) -- Monad(fail) will be removed in GHC 7.16+ fail = Fail.fail #endif instance MonadFail Foo where fail = <...fail implementation...>
- Change your pattern to be irrefutable
- Emulate the old behaviour by desugaring the pattern match by hand:
becomes
do Left e <- foobar stuff
The point is you'll have to do your dirty laundry yourself now if you have a value that you know will always match, and if you don't handle the other patterns you'll get incompleteness warnings, and the compiler won't silently eat those for you.do x <- foobar e <- case x of Left e' -> e' Right r -> error "Pattern match failed" -- Boooo stuff
- Write a
- Help! My code is broken because you removed
fail
fromMonad
but my class defines it! Delete that part of the instance definition.
Esimating the breakage
Using our initial implementation, I compiled stackage-nightly, and grepped the logs for the warnings. Assuming my implementation is correct, the number of "missing MonadFail
warnings generated is 487. Note that I filtered out []
Maybe
and ReadPrec
since those can be given a MonadFail
instance from within GHC, and no breakage is expected from them.
The build logs can be found here. Search for "failable pattern" to find your way to the still pretty raw warnings.
Here are some commands you might find interesting for exploring the logs:
# List all packages generating warnings (57 of them)
grep "is used in the context" '' | \
grep -v '(‘\[|Maybe|ReadPrec)' | \
perl -pe 's#^(.'')\.log.''$#\1#' | \
uniq -u
# Histogram of the breaking contexts (mostly IO and parsers)
grep "is used in the context" '' | \
grep -v '(‘\[|Maybe|ReadPrec)' | \
perl -pe 's#^.''in the context ‘([^ ]+).''$#\1#' | \
sort | \
uniq -c | \
sort -rg
Transitional strategy
The roadmap is similar to the AMP, the main difference being that since MonadFail
does not exist yet, we have to introduce new functionality and then switch to it.
- GHC 8.0 / base-4.9
- Add module
Control.Monad.Fail
with new classMonadFail(fail)
so people can start writing instances for it.Control.Monad
only re-exports the classMonadFail
but not itsfail
method. NB: At this point,Control.Monad.Fail.fail
clashes withPrelude.fail
andControl.Monad.fail
. - Add a language extension
-XMonadFailDesugaring
that changes desugaring to useMonadFail(fail)
instead ofMonad(fail)
This has the effect that typechecking will infer aMonadFail
constraint fordo
blocks with failable patterns, just as it is planned to do when the entire thing is done. - Add a warning when a
do
block that contains a failable pattern is desugared, but there is noMonadFail
instance in scope: "Please add the instance or change your pattern matching." Add a flag to control whether this warning appears, but leave it off by default. - Add a warning when an instance implements the
fail
function (or whenfail
is imported as a method ofMonad
, as it will be removed from theMonad
class in the future. (See also GHC #10071). Leave it off by default.
- Add module
- GHC 8.4
- Turn on the warning about missing
MonadFail
instances that we added in 8.0 by default.
- Turn on the warning about missing
- GHC 8.6
- Switch
-XMonadFailDesugaring
on by default. - Warnings are still issued if the desugaring extension has been explicitly disabled.
- Turn on the warning about explicit definition of `fail` in Monad that we added in 8.0 by default.
- Switch
- GHC 8.8
- Remove
-XMonadFail
leaving its effects on at all times. - Remove
fail
fromMonad
- Instead, re-export
Control.Monad.Fail.fail
asPrelude.fail
andControl.Monad.fail
Control.Monad.Fail
is now a redundant module that can be considered deprecated.
- Remove
Current status
- ZuriHac 2015 (29.5. - 31.5.): Franz Thoma (@fmthoma) and me (David Luposchainsky aka @quchen) started implementing the MFP in GHC.
- Desugaring to the new
fail
can be controlled via a new language extension,MonadFailDesugaring
- If the language extension is turned off, a warning will be emitted for code that would break if it was enabled.
- Warnings are emitted for types that have a MonadFail instance. This still needs to be fixed.
- The error messages are readable, but should be more so. We're still on this.
- Desugaring to the new
- 2015-06-09: Estimated breakage by compiling Stackage. Smaller than expected.
- 2015-06-09 (late): Published. People seem to like the idea, with a couple of pain points remaining.
- 2015-06-16: Update 1 posted.
- 2015-09-18: Patch nearly finished. Some nontrivial tests still fail.