Copyright | (c) 2010 Galois Inc. |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | John Launchbury, john@galois.com |
Stability | experimental |
Portability | concurrency |
Safe Haskell | Safe |
Language | Haskell98 |
Overloads the standard operations on MVars, Chans, and threads,
as defined in Control.Concurrent. This module is name-for-name
swappable with Control.Concurrent unless ghc-specific
operations like mergeIO
or threadWaitRead
are used.
The standard operations on MVar
and Chan
(such as
newEmptyMVar
, or putChan
) are overloaded over the
MonadIO
class. A monad m
is declared an instance of
MonadIO
by defining a function
liftIO :: IO a -> m a
The explicit concurrency operations over threads are
available if a monad m
is declared an instance of the
HasFork
class, by defining a function
fork :: m () -> m ThreadId
- Example use.
Suppose you define a new monad (EIO say) which is like
IO
except that it provides an environment too.
You will need to declare EIO and instance of the Monad
class. In
addition, you can declare it in the MonadIO
class. For example:
newtype EIO a = EIO {useEnv :: Env -> IO a} instance MonadIO EIO where liftIO m = EIO $ (\_ -> m)
Now the standard operations on MVar
and Chan
(such as
newEmptyMVar
, or putChan
are immediately available as
EIO operations. To enable EIO to fork explicit threads, and to
access operations such as killThread
and threadDelay
, use
the declaration
instance HasFork EIO where fork em = EIO $ \e -> forkIO (em `useEnv` e)
- Notes.
The MVar
operations do not include: withMVar, modifyMVar, or
addMVarFinalizer. Consider using TMVars for these instead. In particular,
modifyMVar seems to promise atomicity, but it is NOT atomic. In
contrast TMVars can be used just like MVars, and they
will behave the way you expect (module Control.Concurrent.STM.MonadIO).
Synopsis
- class Monad m => MonadIO (m :: * -> *) where
- data MVar a
- newEmptyMVar :: MonadIO io => io (MVar a)
- newMVar :: MonadIO io => a -> io (MVar a)
- takeMVar :: MonadIO io => MVar a -> io a
- putMVar :: MonadIO io => MVar a -> a -> io ()
- readMVar :: MonadIO io => MVar a -> io a
- swapMVar :: MonadIO io => MVar a -> a -> io a
- tryTakeMVar :: MonadIO io => MVar a -> io (Maybe a)
- tryPutMVar :: MonadIO io => MVar a -> a -> io Bool
- isEmptyMVar :: MonadIO io => MVar a -> io Bool
- data Chan a
- newChan :: MonadIO io => io (Chan a)
- writeChan :: MonadIO io => Chan a -> a -> io ()
- readChan :: MonadIO io => Chan a -> io a
- dupChan :: MonadIO io => Chan a -> io (Chan a)
- unGetChan :: MonadIO io => Chan a -> a -> io ()
- getChanContents :: MonadIO io => Chan a -> io [a]
- writeList2Chan :: MonadIO io => Chan a -> [a] -> io ()
- class MonadIO io => HasFork io where
- data ThreadId
- forkIO :: IO () -> IO ThreadId
- myThreadId :: HasFork io => io ThreadId
- killThread :: HasFork io => ThreadId -> io ()
- throwTo :: (Exception e, HasFork io) => ThreadId -> e -> io ()
- yield :: HasFork io => io ()
- threadDelay :: HasFork io => Int -> io ()
Documentation
An MVar
(pronounced "em-var") is a synchronising variable, used
for communication between concurrent threads. It can be thought of
as a a box, which may be empty or full.
newEmptyMVar :: MonadIO io => io (MVar a) Source #
Chan
is an abstract type representing an unbounded FIFO channel.
getChanContents :: MonadIO io => Chan a -> io [a] Source #
writeList2Chan :: MonadIO io => Chan a -> [a] -> io () Source #
A ThreadId
is an abstract type representing a handle to a thread.
ThreadId
is an instance of Eq
, Ord
and Show
, where
the Ord
instance implements an arbitrary total ordering over
ThreadId
s. The Show
instance lets you convert an arbitrary-valued
ThreadId
to string form; showing a ThreadId
value is occasionally
useful when debugging or diagnosing the behaviour of a concurrent
program.
Note: in GHC, if you have a ThreadId
, you essentially have
a pointer to the thread itself. This means the thread itself can't be
garbage collected until you drop the ThreadId
.
This misfeature will hopefully be corrected at a later date.
forkIO :: IO () -> IO ThreadId Source #
Included to maintain name-for-name compatibility with Control.Concurrent
myThreadId :: HasFork io => io ThreadId Source #
killThread :: HasFork io => ThreadId -> io () Source #
threadDelay :: HasFork io => Int -> io () Source #