[Haskell-cafe] ErrorT vs Either
Daniel Fischer
daniel.is.fischer at googlemail.com
Tue May 17 12:12:54 CEST 2011
On Tuesday 17 May 2011 01:40:41, Gracjan Polak wrote:
> Daniel Fischer <daniel.is.fischer <at> googlemail.com> writes:
> > On Monday 16 May 2011 23:41:44, Gracjan Polak wrote:
> > > Thanks Daniel, Yves and Edward for explanation. Two things come to
> > > my mind now.
> > >
> > > 1. It should be unified.
> >
> > The (Either e) Monad instance was recently changed after people have
> > long complained that there shouldn't be an (Error e) constraint.
> > It's unlikely that that will be reverted soon.
>
> I did not request a revert, I asked about consistent behavior.
>
Not directly, but for
ghci> fail "msg" :: Either String Int
and
ghci> runIdentity (runErrorT (fail "msg")) :: Either String Int
to have the same behaviour, there are three possibilities
a) change ErrorT's behaviour, so that the latter matches the former.
b) change (Either e)'s Monad instance so that the former matches the
latter.
c) change both.
b) is the most reasonable, IMO, and that's reverting the change of the
Monad instance of (Either e).
> > It's the (Error e) Monad which adds the structure [nowadays, Error e =
> > ErrorT e Identity].
Misremembered, there never was a newtype doing for ErrorT what State does
[did] for StateT etc.
>
> I do not understand this part. Can you elaborate?
>
You wrote:
"... Should be the same as Identity monad should not add structure."
Now, the Identity Monad doesn't add the structure that makes the former
result in (Left "msg"),
Prelude Control.Monad.Identity> runIdentity (fail "msg") :: Either String
Int
*** Exception: msg
The Monad instance that makes fail not be error is
instance (Monad m, Error e) => Monad (ErrorT e m) where ...
> > > 2. I need a Failure monad that works well with pattern match
> > > failures
> > >
> > > (that call fail). I'd like to use it like this:
> > > runErrorT $ do
> > >
> > > Active <- getStatus -- ensure proper status
> > > Just elm <- lookup stuff there -- lookup element
> > > when (condition) $ fail "wrong!" -- check condition
> > > return 1234 -- return useful value
> > >
> > > sort of...
> >
> > That does work, doesn't it?
>
> Indeed this does work, but it is fragile wrt refactorings.
>
> Suppose we have the code:
>
> result <- runErrorT $ do
> lift $ print "was here"
> fail "msg"
>
> (result = Left "msg")
>
> after a while the print statement may be removed:
>
> result <- runErrorT $ do
> fail "msg"
>
> (result = Left "msg")
>
> and then somebody will see that inner 'do' does not depend on outer
> monad
But the transformation
result <- runWhatEver stuff
to
let result = stuff
generally doesn't typecheck, so it can't be generally correct, hence if it
typechecks, one has to examine each case to decide where it's valid and
where not. One big point of ErrorT is the working around the inner Monad's
fail, so it should be a big warning sign if a `fail' appears.
> so next refactoring will be:
>
> let result = do
> fail "msg"
>
> (result = error "msg")
>
> And here code breaks...
>
> > Roll your own,
>
> That is a good idea. I looked also at Attempt.
>
> Thanks for responses.
More information about the Haskell-Cafe
mailing list