[Haskell-cafe] Implementing tryReadMVar

Einar Karttunen ekarttun at cs.helsinki.fi
Wed Sep 1 05:46:13 EDT 2004


Hello

Is it possible to implement an operation like 
tryReadMVar :: MVar a -> IO (Maybe a)
in a good fashion? The semantics should be 
"Read the value of the MVar without taking
it if it is filled, otherwise return Nothing".

There are several easy and flawed implementations:

tryReadMvar mv = do e <- isEmptyMVar mv
                    case e of
                     True -> return Nothing
                     False-> readMVar mv >>= return . Just

This does not work because there can be a thread switch 
between the isEmpty and readMVar.

tryReadMVar mv = do mc <- tryTakeMVar mv
                    case mc of
                     Nothing -> return mc
                     Just v  -> putMVar mv v >> return mc

Now this can block on the putMVar if there was a thread switch 
and someone filled the MVar behind our back. 

Using tryPutMVar does not help much as it just creates another 
race condition:

tryReadMVar mv = do mc <- tryTakeMVar mv
                    case mc of
                     Nothing -> return mc
                     Just c  -> tryPutMVar mv v >> return mc

Consider what happens if the tryPutMVar fails:

-- read till we get the value with foobar in the middle
loopTill mv = do foobar 
                 mc <- tryReadMVar mv
                 case mc of
				  Nothing -> loopTill mv
				  Just v  -> return v

maybe (loopTill mv) process (tryReadMVar mv)

error = do mv <- newEmptyMVar
           forkIO (mapM_ (\i -> putMVar mv i) [1..10])
           mapM_ (\_ -> loopTill mv >>= print >> takeMVar mv >>= print) [1..10]

If a tryPutMVar fails, then there will be less than ten values to 
read which will make the process block in takeMVar.

This seems quite straightforward in C with GHC (might be wrong
in the SMP case with locking?):

tryReadMVarzh_fast
{
    W_ mvar, info;

    /* args: R1 = MVar closure */
    mvar = R1;
    info = GET_INFO(mvar);

    if (info == stg_EMPTY_MVAR_info) 
	  RET_NP(0, stg_NO_FINALIZER_closure);

    RET_NP(1, vStgMVar_value(mvar);
}

What is the best way to do this?

- Einar Karttunen


More information about the Haskell-Cafe mailing list