MonadFail proposal (MFP): Moving fail out of Monad
Herbert Valerio Riedel
hvr at gnu.org
Wed Jun 10 06:46:56 UTC 2015
On 2015-06-09 at 23:56:59 +0200, Henning Thielemann wrote:
[...]
> You think about making MonadFail a subclass of Applicative where the
> name MonadFail becomes misleading - how about naming it Fail instead?
'Fail' would be a good name, if it became an independent class (w/o a
superclass to either 'Applicative' or 'Monad'). But the cost for that is
having to use `(Fail m, Monad m) =>`
Or rely on e.g. constraint synonyms, via e.g.
{-# LANGUAGE ConstraintKinds #-}
type MonadFail m = (Fail m, Monad m)
type ApplicativeFail m = (Fail m, Applicative m)
for convenience.
I've also heard the suggestion 'FailDo', which could make sense if it
became a superclass of Applicative (but then we'd still have to use
'(FailDo m, Monad m)' or a constraint-synonym for the majority of cases,
where 'fail' is used in a 'Monad' context)
Otoh, the reason I suggested to just go w/ 'MonadFail' to keep it simple
was that I doubted that that 'fail' in a '-XApplicativeDo' made much
sense. But maybe it does make sense?
I.e. while 'fail' has laws w/ 'Monad', what would be the respective laws
for 'fail' in an 'Applicative' context?
Cheers,
hvr
More information about the Libraries
mailing list