> --- blocking versions
> takeMVar :: MVar a -> IO a
> putMVar  :: MVar a -> a -> IO ()
> 
> --- non-blocking versions
> tryTakeMVar :: MVar a -> IO (Maybe a)
> tryPutMVar  :: MVar a -> a -> IO Bool
> 
> --- current putMVar:
> putMVarMayFail :: MVar a -> a -> IO ()
> putMVarMayFail m a
> = b <- tryPutMVar m a
+>   if b then return () else throw PutFullMVar

One minor point: whereas it is not possible to ignore a failed 
tryTakeMVar unless the result is never used anyway, do-notation
makes it all to easy to ignore a failed tryPutMVar - I'm not sure
whether that's a good thing or  not. However, the name and the 
type should be clear enough hints.

So: yes, your proposal looks good to me. 


You mentioned the timeout operation defined in your asynchronous
exception paper, so I had a look at it. It might indeed allow me to do
what I wanted. However, the programming style in version 3 takes 
some getting used to, and although trying to define my own version
of timeout helped me to notice some of the issues involved, I've 
probably missed something. 

Would the following (which started out much simpler..) work as well? 

-- idea: timeout is a race between a worker and a clock;
-- the new tryPutMVar captures the race condition nicely;
-- keeping all the administration in the parent and the work
-- in the child also seems to simplify things (well, apart 
-- from the forwarding of exceptions..); 

timeout secs action = block $ do
    result <- newEmptyMVar
    parent <- myThreadId
    worker <- forkIO $ catch (action) (badNews parent) 
                                    >>= (tryPutMVar result).Just    
    catch (sleep (secs * 1e6)) (badNews worker)
    tryPutMVar result Nothing
    killThread worker
    takeMVar result

badNews who exception = do
    throwTo who exception
    throw exception

The problem with forwarding exceptions here makes me wonder
whether asynchronous exceptions should always come with a
sender-ThreadId (reserved id for system-generated exceptions).

Claus

PS. Given the subtleties of programming with asynchronous
    exceptions and the acknowledgements in your paper,
    wasn't it Hoare who said the following?-)

    "..there are two ways of constructing a software design:
    One way is to make it so simple that there are obviously
    no deficiencies and the other way is to make it so 
    complicated that there are no obvious deficiencies."



Reply via email to