[Haskell-cafe] Monad-control rant

Edward Z. Yang ezyang at MIT.EDU
Mon Jan 16 21:00:00 CET 2012


Hello Mikhail,

Thanks for continuing to be willing to participate in a lively discussion. :-)

Excerpts from Mikhail Vorozhtsov's message of Mon Jan 16 08:17:57 -0500 2012:
> On 01/16/2012 02:15 PM, Edward Z. Yang wrote:
> > Anders and I thought a little more about your example, and we first wanted to
> > clarify which instance you thought was impossible to write. [snip]
> I was talking about the latter instance.

Great, that's what I thought.

> And I don't want to lift IO 
> control to AIO, I want an API that works with both IO and AIO.

Yup!  But we're going to have to define what me mean by "API that works with
both IO and AIO".

> The real problem with `MonadBaseControl IO AIO` is that the interpreter 
> cuts actions into smaller pieces (at blocking operations) and then 
> reschedules them in some order. [snip]

I don't what you've said here is inconsistent with me claiming that "AIO needs
to limit IO control flow", but I must admit we've been working with an
approximation of AIO because the full code hasn't been publishing anywhere.

> I don't see why functions like `throwIO`, `catch`, `finally`, `bracket`, 
> etc should be tied to IO or monads that allow lifting of IO actions. The 
> functions make perfect sense in `ErrorT SomeException Identity` and in 
> many other monads that have nothing to do with IO, why restrict 
> ourselves?

I agree. (Later in the message I'll propose a new MonadCatchIO instance that
drops the MonadIO superclass.)

The first section was intended to make sure I understood what you were
talking about.  Based on your response, I *think* I interpreted your problem
correctly.

> > I don't think it makes too much sense have thing pick off a menu of
> > Abort/Recover/Finally from a semantics perspective:
> >
> >> It's easy to imagine monads that have an instance of one of the classes but
> >> not of the others....
> >
> > I'd like to see some examples.  I hypothesize that most of such monads are
> > incoherent, semantically speaking.  For example, what does it mean to have a
> > monad that can recover exceptions, but for which you can't throw exceptions?
> Imagine a monad that disallows lifting of arbitrary IO actions, but can 
> receive asynchronous events (which would probably be /implemented/ on 
> top of asynchronous exceptions, but that's not important here) that 
> behave like runtime-inserted left zeros.
> 
> COMPUTATIONALLY_HEAVY_CODE `recover` \level →
>    GIVE_AN_APPROXIMATION_INSTEAD(level)

The vehicle of implementation here is kind of important.  If they are implemented
as asynchronous exceptions, I can in fact still throw in this universe: I just
attempt to execute the equivalent of 'undefined :: m a'.  Since asynchronous exceptions
can always be thrown from pure code, I can /always/ do this, no matter how you
lock down the types.  Indeed, I think implementing this functionality on asynchronous
exceptions is a good idea, because it lets you handle nonterminating pure code nicely,
and allows you to bail out even when you're not doing monadic execution.

But, for the sake of argument, so let's suppose that they're not done as
asynchronous exceptions; essentially, you define some 'safe points' which have
the possibility to raise exceptions.  In this case, I claim there will never be
a *technical* difficulty against implementing manually thrown exceptions; the
concern here is "you don't want the user to do that."  With some sets of
operations, this isn't a very strong injunction; if there is a deterministic
set of operations that results in an error, the user can make a gadget which is
semantically equivalent to a thrown exception.  I don't think I can argue anything
stronger here, so I concede the rest of the point.

So, to summarize, such an interface (has recovery but not masking or throwing)
always has a trivial throw instance unless you are not implementing it on top
of asynchronous exceptions.

Your example reminds me of what happens in pure code. In this context, we have
the ability to throw errors and map over errors (although I'm not sure how people
feel about that, semantically), but not to catch them or mask them.  But I don't
think we need another typeclass for that.

> > There only a few options:
> >
> >      - You have special primitives which throw exceptions, distinct from
> >        Haskell's IO exceptions.  In that case, you've implemented your own
> >        homebrew exception system, and all you get is a 'Catch MyException'
> >        which is too specific for a client who is expecting to be able
> >        to catch SomeExceptions.
> >
> >      - You execute arbitrary IO and allow those exceptions to be caught.
> >        But then I can implement Throw: I just embed an IO action that
> >        is throwing an exception.
> >
> >      - You only execute a limited subset of IO, but when they throw exceptions
> >        they throw ordinary IO exceptions.  In this case, the client doesn't
> >        have access to any scarce resources except the ones you provided,
> >        so there's no reason for him to even need this functionality, unless
> >        he's specifically coding against your monad.
> As I said, you think of IO too much.

Guilty as charged!

> The purpose of monad-abort-fd is to provide a generic API for handling errors
> that have values attached to them and for guarding actions with finalizers
> (as the notion of failure can include more things besides the errors).

Here's the reason I'm so fixated on IO: There is a very, /very/ bright line
between code that does IO, and pure code.  You can have arbitrary stacks of
monads, but at the end of the day, if IO is not at the end of the line, your
code is pure.

If your code is pure, you don't need finalizers. (Indeed, this is the point
of pure code...)  I can abort computations willy nilly.  I can redo them willy
nilly.  You get a lot of bang for your buck if you're pure.

I don't understand what the "too much IO" objection is about.  If there is no
IO (now, I don't mean a MonadIO instance, but I do mean, in order to interpret
the monad), it seems to me that this API is not so useful.

> No, you can't. MonadFinally instances must (I really should write 
> documentation) handle /all/ possible failures, not just exceptions. The 
> naive
> 
> finally ∷ MonadRecover e μ ⇒ μ α → μ β → μ α
> finally m f = do
>    a ← m `recover` \e → f >> abort e
>    void $ f
>    return a
> 
> wouldn't work in `MaybeT IO`, just consider `finally mzero f`.

I think that's incoherent. To draw out your MaybeT IO example to its logical conclusion,
you've just created two types of zeros, only one of which interacts with 'recover' but
both of which interact with 'finally'. Down this inconsistency lies madness!  Really,
we'd like 'recover' to handle Nothing's: and actually we can: introduce a distinguished
SomeException value that corresponds to nothings, and setup abort to transform that not
into an IO exception but a pure Nothing value. Then 'finally' as written works.

> > What does it mean to have all of the above, but not to have a mask instance?
> > One approach is to pretend asynchronous exceptions do not exist.  As you do in your
> > example, we can simply mask.  I think this is a bit to give up, but I'll concede it.
> > However, I don't think it's acceptable not to provide mask functionality, not mask
> > your interpreter, and allow arbitrary IO.  It's now impossible to properly implement
> > many patterns without having subtle race conditions.
> In my particular case I feel no need for asynchronous exceptions as I 
> have a concurrency primitive that is used for interrupting:
> 
> sh ← newOneShot
> runAIOs s0
>    [ do
>        aioAwait sh
>        info "Service shutdown requested"
>    , ...
>    ]

Sure.  And the point here is conceded, and accounted for later.

> The problem with MonadCatchIO is that it has no proper `finally`, see my 
> `MaybeT IO` example.

Addressed above.

> > To contextualize this whole discussion, recall the insiduous problem that
> > *motivated* the creation of monad-control.  Suppose that we've done all of the
> > hard work and lifted all of the Control.Exception functions to our new formula
> > (maybe we also need uninterruptibleMask in our class, but no big matter.)  Now
> > a user comes along and asks for 'alloca :: Storable a =>  (Ptr a ->  IO b) ->  IO
> > b'.  Crap!  We need to redefine alloca to work for our new monad. So in comes
> > the class Alloca.  But there are a billion, billion of these functions.
> I don't think that's true. There is actually a limited set (induced 
> mainly by primops) of "difficult" functions that require new 
> abstractions. Alloca is a pain only because it implemented as a `IO $ \s 
> → PRIMOP_SPAGHETTI`. I don't know if the spaghetti can be twisted to 
> look something like:
> 
> .. = mask $ \restore → do
>    mbarr ← liftBase $ IO $ newAlignedPinnedByteArray# size align
>    finally (...) $ do
>      ...
>      restore (action ptr)
> 
> It depends on the semantics of the primops involved. Fortunately, most 
> of IO control operations can be easily generalized just by changing the 
> type signature:
> 
> import qualified Control.Concurrent.MVar as MV
> 
> takeMVar ∷ MonadBase IO μ ⇒ MVar α → μ α
> takeMVar = liftBase . MV.takeMVar
> 
> putMVar ∷ MonadBase IO μ ⇒ MVar α → α → μ α
> putMVar v = liftBase . MV.putMVar v
> 
> withMVar ∷ MVar α → (α → IO β) → IO β
> -- withMVar ∷ (MonadBase IO μ, MonadFinally μ, MonadMask m μ)
> --          ⇒ MVar α → (α → μ β) → μ β
> --   works too, /without changing the body/!
> withMVar v f = mask $ \restore → do
>    a ← takeMVar v
>    restore (m a) `finally` putMVar v a
> 
> This `withMVar` would work as expected in IO, AIO, and transformer 
> stacks on top of them.

OK, there are several points involved here.

First, we might wonder, how many operations fundamentally are resistant
to that treatment?  Well, we can look at the primop list:

    catch#
    raiseIO#
    maskAsyncExceptions#
    maskUninterruptible#
    unmaskAsyncExceptions#
    atomically#
    catchRetry#
    catchSTM#
    check#
    fork#
    forkOn#
    finalizeWeak#

So, using the method you describe, we may be able to get away with thirteen
typeclasses.  Ok... (Notice, by the way, that finally# is not on this list!
So if /this/ was what you were thinking, I was probably thrown off by the fact
that you included typeclasses for both primitive functions as well as
derived ones.)

Second, we might wonder, how tractable is this approach?  Certainly, it gives
us another principled way of lifting all of the "hard" functions, assuming that
all of the primops are taken care of.  Of course, there are a lot of
objections:

    - It requires copy pasting code (and if upstream changes their implementation,
      so must we).  I constrast this with the lifted-base method, which, while
      annoying and repetitive, does not involve copypasted code.

    - Un-transforming primop'd code undos important performance optimizations

But I think there is a very important point to concede here, which is that
without language support it may be impossible to implement 'generic' versions
of these derived functions from the specialized ones automatically.
lifted-base achieves the appearance of automatically lifting, but that's only
because directly calling the original implementations is acceptable.

> I hope you see that my approach is entirely different. I'm not 
> interested in lifting IO operations we have in `base` by some clever 
> ad-hoc machinery, I want to generalize (there possible) their types.

And the logical conclusion of this is that, not only do you need to
create a function for every function you want to generalize, you also
need to steal all of the implementations.  Which suggests that actually
you want to be talking to the GHC team about this endeavour, since the
situation is a bit less bad if base is maintaining the generalized versions
as well as the specialized ones: the specialized versions can just be inlined
versions of the generalized ones.

> Summary:
>    1. Exception handling and finalizers are generic concepts that make 
> sense in many monads and therefore should not be tied to IO.

I disagree, and submit the modification: "Exception handling and finalizers
are generic concepts that make sense in many IO-based monads with
alternative control flow or semantics, and therefore should not be tied to
IO-based monads that must precisely implement IO control flow."  Exception
handling is well understood for pure code, and finalizers unnecessary.

>    2. Regular IO functions can be generalized just by prefixing them 
> with `liftBase $`. This will make them work in any `MonadBase IO μ`.

I disagree, and submit the modification: "Regular IO functions can be lifted
without respect to control flow by prefixing them with liftBase.  This will
make them work in any `MonadBase IO mu'."  Just because I can lift a function,
doesn't mean it's been generalized; in particular, any more primitive functions
it calls continue to be the original, and not generalized versions.

>    3. Most IO control operations can be generalized just by changing 
> their type signatures to use MonadAbort/Recover/Finally/Mask (without 
> changing the body; maybe with just a few `liftBase`s here and there). 
> This will make them work at least in IO, AIO, and transformer stacks on 
> top of them.

I agree, but submit that of the MonadAbort/Recover/Finally/Mask quartet
Finally should be dropped and Abort/Recover/Mask unified into one typeclass.

>    4. IO control operations that rely on passing IO actions to a primop 
> (like, presumably, `alloca`) should be generalized the monad-control way 
> (which is OK, I don't see how I can lift it to AIO anyway, even if I try 
> to do it manually). Partial generalizations like `alloca' ∷ (Storable α, 
> MonadBase IO μ) ⇒ (Ptr α → IO β) → μ β` might also be useful.

I (surprisingly) disagree, and submit that they /can/ be generalized the
copy pasting way, and if such a change is coordinated with the base teams,
could be the preferred mechanism.

Summary:

    1. The only known semantics of asynchronous exceptions involves the
    primitives abort, recover and mask, and this semantics can be converted
    into one that is synchronous if we supply a no-op definition for mask and
    require the semantics stay the same.  It seems poor for this semantics to
    grow to include finally or for this semantics to contract to have abort
    without recover, or recover without abort.  But this is not a fundamental
    point, and while there are lots of different exception handling semantics,
    it's possible specialized applications could make sense with limited
    combinators: however, *show me the semantics.*

    2. Finalizer handling is not necessary in pure code.

    3. A way of cleaning up the IO sin bin would be to generalize appropriate
    primitive functions over appropriate type classes, and then copy pasting
    the source for all derived definitions.  I submit that doing so as a third
    party is a bad idea.  I submit that we can do this incrementally, and that
    it's not that bad of an idea if you can convince the GHC team it's a good
    idea.  Exception handling might be a good place to start. (An issue to
    consider: what about the interaction of orthogonal features?)

    4. (3) is the only way of getting an appropriate behavior for models of IO
    with weird control flow.  So, I agree with you, monad-control is no good
    for AIO, and your essential idea is necessary.  (Though, Anders claims that
    at some point he figured out how to fix the ContT problem for monad-peel; I
    should poke him again on this point.)

Cheers,
Edward



More information about the Haskell-Cafe mailing list