[Haskell-cafe] Monad-control rant

Mikhail Vorozhtsov mikhail.vorozhtsov at gmail.com
Mon Jan 16 14:17:57 CET 2012


On 01/16/2012 02:15 PM, Edward Z. Yang wrote:
> Hello Mikhail,
Hi.
>
> Sorry, long email. tl;dr I think it makes more sense for throw/catch/mask to
> be bundled together, and it is the case that splitting these up doesn't address
> the original issue monad-control was designed to solve.
>
>                                      ~ * ~
>
> Anders and I thought a little more about your example, and we first wanted to
> clarify which instance you thought was impossible to write.
>
> For example, we think it should be possible to write:
>
>      instance MonadBaseControl AIO AIO
>
> Notice that the base monad is AIO: this lets you lift arbitrary AIO
> operations to a transformed AIO monad (e.g. ReaderT r AIO), but no more.
> If this is the instance you claimed was impossible, we'd like to try implementing
> it.  Can you publish the full example code somewhere?
>
> However, we don't think it will be possible to write:
>
>      instance MonadBaseControl IO AIO
>
> Because this lets you leak arbitrary IO control flow into AIO (e.g. forkIO, with
> both threads having the ability to run the current AIO context), and as you stated,
> you only want to allow a limited subset of control flow in.  (I think this was
> the intent of the original message.)
I was talking about the latter instance. And I don't want to lift IO 
control to AIO, I want an 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. For example, consider the following 
piece of code:

(`catch` \e → HANDLER) $ do
   FOO
   -- wait until the state satisfies the condition
   aioCond STATE_CONDITION
   BAR

The interpreter installs HANDLER and executes FOO. Then it restores 
exception handlers of some other program and executes a piece of it. 
Eventually, when the state satisfies STATE_CONDITION, the interpreter 
restores HANDLER and executes BAR. It's impossible to implement `catch` 
by some sort of straightforward delegation to `Control.Exception.catch`, 
you can't inject you logic into IO (at least without some bizarre 
inversion of control).

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? It's like exporting custom named `<|>` and friends for each 
parser combinator library and then reimplementing common Alternative 
idioms again and again.

>
> Maybe client code doesn't want to be attached to AIO base monads, though;
> that's too restrictive for them. So they'd like to generalize a bit.  So let's
> move on to the issue of your typeclass decomposition.
>
>                                      ~ * ~
>
> 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)

> 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. 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).
>
> What does it mean to not have a Finally instance, but a Recover and Throw
> instance?  Well, I can manually reimplement finally in this case (with or
> without support for asynchronous exceptions, depending on whether or not Mask
> is available): this is how the paper does it (finally is not a primitive.)
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`.
>
> What does it mean to have a monad that can throw exceptions, but not catch them?
> This is any of the usual monads that can fail, of which we have many.  And of course,
> you can't allow this in the presence of scarce resources since there is no way to
> properly deallocate them when exceptions are thrown.  So it seems this is just ordinary
> failure which cannot be used in the presence of arbitrary IO.
Again, too much IO, it is not relevant.
>
> 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"
   , ...
   ]

And of course I do not liftBase blocking IO functions. The whole point 
of AIO is to reschedule on blocking operations after all.
>
> So it seems we should collapse these into one class, which conveniently maps straight
> to the semantics defined in "Asynchronous Exceptions in Haskell".
>
> class MonadAsyncExc m where
>      mask :: ((forall a. m a ->  m a) ->  m b) ->  m b
>      throw :: SomeException ->  m ()
>      catch :: m a ->  (SomeException ->  m a) ->  m a
>
> But you get to have your cake and eat it too: if you define a monad which is guaranteed
> to be run with asynchronous exceptions masked, you can define the 'mask' function
> to be a no-op and not violate any laws! Hooray!
>
> But this is in fact what MonadCatchIO was, except that MonadCatchIO was
> formulated when we still had block/unblock and it required MonadIO.  So a
> useful endeavour would be to punt the MonadIO superclass constraint and fix the
> definitions, and we have something that is usable to your case.
The problem with MonadCatchIO is that it has no proper `finally`, see my 
`MaybeT IO` example.
>
>                                    ~ * ~
>
> 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.
>
> This gist of your objection to this typeclass is that there is no principled
> way to tell the difference between:
>
>      forkIO :: IO a ->  IO a
>
> and
>
>      bracketed :: IO a ->  IO a
>
> Thus, it is impossible, with the type system given to us by IO, to write a
> function that will lift bracketed automatically, but not also lift forkIO.
> Long live the IO sin bin.  So the best we can hope for is manually lifting
> every function we think is safe.  You've attempted to work around this by
> defining a typeclass per function, but as I've tried to argue in this email
> that there is no way to reasonably reason about these functions in isolation.
> I also hope that I've convinced you that even with all of these typeclasses,
> we still only have a partial solution.
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.

Summary:
   1. Exception handling and finalizers are generic concepts that make 
sense in many monads and therefore should not be tied to IO.
   2. Regular IO functions can be generalized just by prefixing them 
with `liftBase $`. This will make them work in any `MonadBase IO μ`.
   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.
   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.



More information about the Haskell-Cafe mailing list