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 <marlo...@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@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe