> Simon Marlow wrote:
> > There's one implementation issue related to efficiency that
> springs to mind:
> > in GHC, a primitive which blocks or does any allocation must be an
> > out-of-line function. This means that non-blocking put or
> takeMVar can be
> > inline primitives (although putMVar is currently
> out-of-line to avoid code
> > duplication).
> I don't understand this. If out-of-line means giving the
> scheduler/garbage-collector
> a chance to do things, couldn't you just make the blocking
> versions only go out-of-
> line if they have to block?
In principle, yes, but in practice it's quite hard because the test-and-call
has be be atomic. Either that or re-test in the out-of-line code. If
tryTakeMVar is more efficient than takeMVar (entirely possible, but not the
case at the moment), you might like to define takeMVar like this:
fastTakeMVar m = do
e <- tryTakeMVar m
case e of
Just a -> return a
Nothing -> takeMVar m
> In many cases I suspect the
> takeMVar and putMVar
> will work immediately, so this could be a useful saving.
>
> I like the scheme for blocking and non-blocking versions of
> take/putMVar in
> general. If you are working in this area, the function I suggested
>
> takeMVarMulti :: [MVar a] -> IO a
> and in addition
> putMVarMulti :: [MVar a] -> a -> IO ()
> could conceivably be useful to me in the future, so I'd like them too,
> if they're trivial to add.
Let me see if I've got the semantics right: takeMVarMulti makes a
non-deterministic choice between the full MVars to return the value, and if
there are no full MVars it waits for the first one to become full?
Defining this in Haskell is pretty hard. I managed to do it for two MVars
(code at the end of this message). There might be an easier way to do it
using special code in the scheduler, but I need to think about that some
more.
Cheers,
Simon
[ block & unblock are actually blockAsyncExceptions and
unblockAsyncExceptions in the following code. I think this is untested, I
just pulled it out of my scratch directory... ]
takeEither :: MVar a -> MVar a -> IO a
takeEither ma mb = do
m <- newEmptyMVar
mt2 <- newEmptyMVar
t1 <- forkIO (do
block (do a <- takeMVar ma
catch
( unblock (do
t2 <- takeMVar mt2
killThread t2
putMVar m a
)
)
( \e -> putMVar ma a )
)
)
t2 <- forkIO (do
block (do a <- takeMVar mb
catch
( unblock (do
killThread t1
putMVar m a
)
)
( \e -> putMVar mb a )
)
)
putMVar mt2 t2
takeMVar m