[Haskell-cafe] Re: Asynchronous exception wormholes kill modularity

Simon Marlow marlowsd at gmail.com
Mon Apr 19 11:48:17 EDT 2010


On 10/04/2010 20:07, Iavor Diatchki wrote:
> Hello,
> I wonder if it might be possible to use just one primitive which
> atomically changes the interrupt mask for a thread?  Here is an example
> of what I'm thinking:
>
> data MaskingState   = Unmasked
>                     | MaskedInterruptible
>                     | MaskedNonInterruptible
>
> -- Atomically changes the interrupt mask for a thread, and returns the
> old mask.
> setMask            :: MaskingState -> IO MaskingState
> setMask             = error "primitive?"
>
> -- Change the mask for the duration of an IO action.
> -- The action is passed the old mask.
> scopedSetMask      :: MaskingState -> (MaskingState -> IO a) -> IO a
> scopedSetMask m io  = do m1 <- setMask m
>                          a <- io m1
>                          setMask m1
>                          return a
>
> -- Change the mask for the duration of an IO action.
> scopedSetMask_     :: MaskingState -> IO a -> IO a
> scopedSetMask_ m io = scopedSetMask m $ \_ ->
>                         io
> -- Simon's mask:
> mask               :: ((IO a -> IO a) -> IO b) -> IO b
> mask f              = scopedSetMask MaskedInterruptible $ \m ->
>                         f (scopedSetMask_ m)

I could replace 3 of the primitives I have (block, unblock, and 
uninterruptibleBlock) with just one as you suggest, yes.  And we could 
replace the scoping behaviour of the primitives with scopedSetMask, 
although some care would be needed to make sure it wasn't any less 
efficient, we would probably have to explicitly expand the code for 
scopedSetMask into the three possible cases.

However, the current block and unblock primitives have a bit of clever 
logic to keep the stack at a constant size when called recursively (see 
the async exceptions paper for details), we would lose that if we used 
the above formulation.

Note that this isn't the only place that changes the masking state: when 
an exception is raised, we have to temporarily mask exeptions for the 
handler, and then restore them to the prevailing state if the handler 
returns.  The way the primitives are currently defined makes this quite 
easy, because I have ready-made stack frames to use.  We could lift this 
into Haskell by redefining catch:

catch :: IO a -> (Exception -> IO a) -> IO a
catch io handler = mask $ \restore -> restore io `realCatch` handler

but this adds more overhead to catch, and the implementation of throw 
still has to restore the masking state from the stack frame for catch.

BTW, you also need a way to check what the current masking state is, 
otherwise the "wormhole" that was the original problem being discussed 
here reappears. For example, mask should only change the masking state 
to MaskedInterruptible if it is currently Unmasked, otherwise it will 
(a) make the state interruptible if it was uninterruptible, and (b) 
introduce an unnecessary stack frame.

Cheers,
	Simon


>
> -Iavor
>
>
> On Sat, Apr 10, 2010 at 11:42 AM, Iavor Diatchki
> <iavor.diatchki at gmail.com <mailto:iavor.diatchki at gmail.com>> wrote:
>  > Hello,
>  > It seems that rank-2 types are sufficient to make the more
> polymorphic types:
>  >
>  > ----------------------------------------------------
>  > {-# LANGUAGE Rank2Types #-}
>  > import Control.Exception
>  >
>  > data Mask = Mask (forall a. IO a -> IO a)
>  >
>  > mask :: (Mask -> IO a) -> IO a
>  > mask io = do
>  >  b <- blocked
>  >  if b
>  >    then io (Mask id)
>  >    else block $ io (Mask unblock)
>  >
>  > restore :: Mask -> IO a -> IO a
>  > restore (Mask f) a = f a
>  > ----------------------------------------------------------
>  >
>  > This is useful in an example like this:
>  >
>  > forkThen :: IO () -> IO a -> IO a
>  > forkThen io k = mask $ \m ->
>  >  do tid <- forkIO (restore m io)
>  >     restore m k `catch` \e ->
>  >       do when (e == ThreadKilled) (killThread tid)
>  >          throwIO e
>  >
>  > -Iavor
>  >
>  >
>  > On Thu, Apr 8, 2010 at 1:23 AM, Simon Marlow <marlowsd at gmail.com
> <mailto:marlowsd at gmail.com>> wrote:
>  >> On 07/04/2010 18:54, Isaac Dupree wrote:
>  >>>
>  >>> On 04/07/10 11:12, Simon Marlow wrote:
>  >>>>
>  >>>> It's possible to mis-use the API, e.g.
>  >>>>
>  >>>> getUnmask = mask return
>  >>>
>  >>> ...incidentally,
>  >>> unmask a = mask (\restore -> return restore) >>= (\restore ->
> restore a)
>  >>
>  >> That doesn't work, as in it can't be used to unmask exceptions when
> they are
>  >> masked.  The 'restore' you get just restores the state to its
> current, i.e.
>  >> masked, state.
>  >>
>  >>>> mask :: ((IO a -> IO a) -> IO b) -> IO b
>  >>>
>  >>> It needs to be :: ((forall a. IO a -> IO a) -> IO b) -> IO b
>  >>> so that you can use 'restore' on two different pieces of IO if you need
>  >>> to. (alas, this requires not just Rank2Types but RankNTypes. Also, it
>  >>> doesn't cure the loophole. But I think it's still essential.)
>  >>
>  >> Sigh, yes I suppose that's true, but I've never encountered a case
> where I
>  >> needed to call unmask more than once, let alone at different types,
> within
>  >> the scope of a mask.  Anyone else?
>  >>
>  >> Cheers,
>  >>        Simon
>  >> _______________________________________________
>  >> Haskell-Cafe mailing list
>  >> Haskell-Cafe at haskell.org <mailto:Haskell-Cafe at haskell.org>
>  >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>  >>
>  >
>



More information about the Libraries mailing list