Haskell Hierarchical Libraries (base package)ContentsIndex
GHC.Conc
Portability non-portable (GHC extensions)
Stability internal
Maintainer cvs-ghc@haskell.org
Description
Basic concurrency stuff.
Synopsis
data ThreadId = ThreadId ThreadId#
myThreadId :: IO ThreadId
killThread :: ThreadId -> IO ()
throwTo :: ThreadId -> Exception -> IO ()
par :: a -> b -> b
pseq :: a -> b -> b
yield :: IO ()
labelThread :: ThreadId -> String -> IO ()
threadDelay :: Int -> IO ()
threadWaitRead :: Int -> IO ()
threadWaitWrite :: Int -> IO ()
data MVar a
newMVar :: a -> IO (MVar a)
newEmptyMVar :: IO (MVar a)
takeMVar :: MVar a -> IO a
putMVar :: MVar a -> a -> IO ()
tryTakeMVar :: MVar a -> IO (Maybe a)
tryPutMVar :: MVar a -> a -> IO Bool
isEmptyMVar :: MVar a -> IO Bool
addMVarFinalizer :: MVar a -> IO () -> IO ()
Documentation
data ThreadId

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 ThreadIds. 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.

Note: Hugs does not provide any operations on other threads; it defines ThreadId as a synonym for ().

Constructors
ThreadId ThreadId#
Instances
Eq ThreadId
Ord ThreadId
Show ThreadId
myThreadId :: IO ThreadId
Returns the ThreadId of the calling thread (GHC only).
killThread :: ThreadId -> IO ()

killThread terminates the given thread (GHC only). Any work already done by the thread isn't lost: the computation is suspended until required by another thread. The memory used by the thread will be garbage collected if it isn't referenced from anywhere. The killThread function is defined in terms of throwTo:

 killThread tid = throwTo tid (AsyncException ThreadKilled)
throwTo :: ThreadId -> Exception -> IO ()

throwTo raises an arbitrary exception in the target thread (GHC only).

throwTo does not return until the exception has been raised in the target thread. The calling thread can thus be certain that the target thread has received the exception. This is a useful property to know when dealing with race conditions: eg. if there are two threads that can kill each other, it is guaranteed that only one of the threads will get to kill the other.

par :: a -> b -> b
pseq :: a -> b -> b
yield :: IO ()
The yield action allows (forces, in a co-operative multitasking implementation) a context-switch to any other currently runnable threads (if any), and is occasionally useful when implementing concurrency abstractions.
labelThread :: ThreadId -> String -> IO ()

labelThread stores a string as identifier for this thread if you built a RTS with debugging support. This identifier will be used in the debugging output to make distinction of different threads easier (otherwise you only have the thread state object's address in the heap).

Other applications like the graphical Concurrent Haskell Debugger (http://www.informatik.uni-kiel.de/~fhu/chd/) may choose to overload labelThread for their purposes as well.

threadDelay :: Int -> IO ()

The threadDelay operation will cause the current thread to suspend for a given number of microseconds (GHC only).

Note that the resolution used by the Haskell runtime system's internal timer together with the fact that the thread may take some time to be rescheduled after the time has expired, means that the accuracy is more like 1/50 second.

threadWaitRead :: Int -> IO ()
Block the current thread until data is available to read on the given file descriptor (GHC only).
threadWaitWrite :: Int -> IO ()
Block the current thread until data can be written to the given file descriptor (GHC only).
data MVar a
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.
Instances
Eq (MVar a)
newMVar :: a -> IO (MVar a)
Create an MVar which contains the supplied value.
newEmptyMVar :: IO (MVar a)
Create an MVar which is initially empty.
takeMVar :: MVar a -> IO a

Return the contents of the MVar. If the MVar is currently empty, takeMVar will wait until it is full. After a takeMVar, the MVar is left empty.

If several threads are competing to take the same MVar, one is chosen to continue at random when the MVar becomes full.

putMVar :: MVar a -> a -> IO ()

Put a value into an MVar. If the MVar is currently full, putMVar will wait until it becomes empty.

If several threads are competing to fill the same MVar, one is chosen to continue at random with the MVar becomes empty.

tryTakeMVar :: MVar a -> IO (Maybe a)
A non-blocking version of takeMVar. The tryTakeMVar function returns immediately, with Nothing if the MVar was empty, or Just a if the MVar was full with contents a. After tryTakeMVar, the MVar is left empty.
tryPutMVar :: MVar a -> a -> IO Bool
A non-blocking version of putMVar. The tryPutMVar function attempts to put the value a into the MVar, returning True if it was successful, or False otherwise.
isEmptyMVar :: MVar a -> IO Bool

Check whether a given MVar is empty.

Notice that the boolean value returned is just a snapshot of the state of the MVar. By the time you get to react on its result, the MVar may have been filled (or emptied) - so be extremely careful when using this operation. Use tryTakeMVar instead if possible.

addMVarFinalizer :: MVar a -> IO () -> IO ()
Add a finalizer to an MVar (GHC only). See Foreign.ForeignPtr and System.Mem.Weak for more about finalizers.
Produced by Haddock version 0.6