base-4.2.0.1: Basic librariesSource codeContentsIndex
GHC.Conc
Portabilitynon-portable (GHC extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Contents
Forking and suchlike
Waiting
TVars
Miscellaneous
Description
Basic concurrency stuff.
Synopsis
data ThreadId = ThreadId ThreadId#
forkIO :: IO () -> IO ThreadId
forkOnIO :: Int -> IO () -> IO ThreadId
numCapabilities :: Int
childHandler :: SomeException -> IO ()
myThreadId :: IO ThreadId
killThread :: ThreadId -> IO ()
throwTo :: Exception e => ThreadId -> e -> IO ()
par :: a -> b -> b
pseq :: a -> b -> b
runSparks :: IO ()
yield :: IO ()
labelThread :: ThreadId -> String -> IO ()
data ThreadStatus
= ThreadRunning
| ThreadFinished
| ThreadBlocked BlockReason
| ThreadDied
data BlockReason
= BlockedOnMVar
| BlockedOnBlackHole
| BlockedOnException
| BlockedOnSTM
| BlockedOnForeignCall
| BlockedOnOther
threadStatus :: ThreadId -> IO ThreadStatus
threadDelay :: Int -> IO ()
registerDelay :: Int -> IO (TVar Bool)
threadWaitRead :: Fd -> IO ()
threadWaitWrite :: Fd -> IO ()
newtype STM a = STM (State# RealWorld -> (#State# RealWorld, a#))
atomically :: STM a -> IO a
retry :: STM a
orElse :: STM a -> STM a -> STM a
catchSTM :: STM a -> (SomeException -> STM a) -> STM a
alwaysSucceeds :: STM a -> STM ()
always :: STM Bool -> STM ()
data TVar a = TVar (TVar# RealWorld a)
newTVar :: a -> STM (TVar a)
newTVarIO :: a -> IO (TVar a)
readTVar :: TVar a -> STM a
readTVarIO :: TVar a -> IO a
writeTVar :: TVar a -> a -> STM ()
unsafeIOToSTM :: IO a -> STM a
withMVar :: MVar a -> (a -> IO b) -> IO b
type Signal = CInt
type HandlerFun = ForeignPtr Word8 -> IO ()
setHandler :: Signal -> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic))
runHandlers :: Ptr Word8 -> Int -> IO ()
ensureIOManagerIsRunning :: IO ()
syncIOManager :: IO ()
setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO ()
getUncaughtExceptionHandler :: IO (SomeException -> IO ())
reportError :: SomeException -> IO ()
reportStackOverflow :: IO ()
Documentation
data ThreadId 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 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#
show/hide Instances
Forking and suchlike
forkIO :: IO () -> IO ThreadIdSource

Sparks off a new thread to run the IO computation passed as the first argument, and returns the ThreadId of the newly created thread.

The new thread will be a lightweight thread; if you want to use a foreign library that uses thread-local storage, use Control.Concurrent.forkOS instead.

GHC note: the new thread inherits the blocked state of the parent (see Control.Exception.block).

The newly created thread has an exception handler that discards the exceptions BlockedIndefinitelyOnMVar, BlockedIndefinitelyOnSTM, and ThreadKilled, and passes all other exceptions to the uncaught exception handler (see setUncaughtExceptionHandler).

forkOnIO :: Int -> IO () -> IO ThreadIdSource

Like forkIO, but lets you specify on which CPU the thread is created. Unlike a forkIO thread, a thread created by forkOnIO will stay on the same CPU for its entire lifetime (forkIO threads can migrate between CPUs according to the scheduling policy). forkOnIO is useful for overriding the scheduling policy when you know in advance how best to distribute the threads.

The Int argument specifies the CPU number; it is interpreted modulo numCapabilities (note that it actually specifies a capability number rather than a CPU number, but to a first approximation the two are equivalent).

numCapabilities :: IntSource
the value passed to the +RTS -N flag. This is the number of Haskell threads that can run truly simultaneously at any given time, and is typically set to the number of physical CPU cores on the machine.
childHandler :: SomeException -> IO ()Source
myThreadId :: IO ThreadIdSource
Returns the ThreadId of the calling thread (GHC only).
killThread :: ThreadId -> IO ()Source

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 ThreadKilled

Killthread is a no-op if the target thread has already completed.

throwTo :: Exception e => ThreadId -> e -> IO ()Source

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.

If the target thread is currently making a foreign call, then the exception will not be raised (and hence throwTo will not return) until the call has completed. This is the case regardless of whether the call is inside a block or not.

Important note: the behaviour of throwTo differs from that described in the paper "Asynchronous exceptions in Haskell" (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). In the paper, throwTo is non-blocking; but the library implementation adopts a more synchronous design in which throwTo does not return until the exception is received by the target thread. The trade-off is discussed in Section 9 of the paper. Like any blocking operation, throwTo is therefore interruptible (see Section 5.3 of the paper).

There is currently no guarantee that the exception delivered by throwTo will be delivered at the first possible opportunity. In particular, a thread may unblock and then re-block exceptions (using unblock and block) without receiving a pending throwTo. This is arguably undesirable behaviour.

par :: a -> b -> bSource
pseq :: a -> b -> bSource
runSparks :: IO ()Source
Internal function used by the RTS to run sparks.
yield :: IO ()Source
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 ()Source

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.

data ThreadStatus Source
The current status of a thread
Constructors
ThreadRunningthe thread is currently runnable or running
ThreadFinishedthe thread has finished
ThreadBlocked BlockReasonthe thread is blocked on some resource
ThreadDiedthe thread received an uncaught exception
show/hide Instances
data BlockReason Source
Constructors
BlockedOnMVarblocked on on MVar
BlockedOnBlackHoleblocked on a computation in progress by another thread
BlockedOnExceptionblocked in throwTo
BlockedOnSTMblocked in retry in an STM transaction
BlockedOnForeignCallcurrently in a foreign call
BlockedOnOtherblocked on some other resource. Without -threaded, I/O and threadDelay show up as BlockedOnOther, with -threaded they show up as BlockedOnMVar.
show/hide Instances
threadStatus :: ThreadId -> IO ThreadStatusSource
Waiting
threadDelay :: Int -> IO ()Source

Suspends the current thread for a given number of microseconds (GHC only).

There is no guarantee that the thread will be rescheduled promptly when the delay has expired, but the thread will never continue to run earlier than specified.

registerDelay :: Int -> IO (TVar Bool)Source
Set the value of returned TVar to True after a given number of microseconds. The caveats associated with threadDelay also apply.
threadWaitRead :: Fd -> IO ()Source
Block the current thread until data is available to read on the given file descriptor (GHC only).
threadWaitWrite :: Fd -> IO ()Source
Block the current thread until data can be written to the given file descriptor (GHC only).
TVars
newtype STM a Source
A monad supporting atomic memory transactions.
Constructors
STM (State# RealWorld -> (#State# RealWorld, a#))
show/hide Instances
atomically :: STM a -> IO aSource

Perform a series of STM actions atomically.

You cannot use atomically inside an unsafePerformIO or unsafeInterleaveIO. Any attempt to do so will result in a runtime error. (Reason: allowing this would effectively allow a transaction inside a transaction, depending on exactly when the thunk is evaluated.)

However, see newTVarIO, which can be called inside unsafePerformIO, and which allows top-level TVars to be allocated.

retry :: STM aSource
Retry execution of the current memory transaction because it has seen values in TVars which mean that it should not continue (e.g. the TVars represent a shared buffer that is now empty). The implementation may block the thread until one of the TVars that it has read from has been udpated. (GHC only)
orElse :: STM a -> STM a -> STM aSource
Compose two alternative STM actions (GHC only). If the first action completes without retrying then it forms the result of the orElse. Otherwise, if the first action retries, then the second action is tried in its place. If both actions retry then the orElse as a whole retries.
catchSTM :: STM a -> (SomeException -> STM a) -> STM aSource
Exception handling within STM actions.
alwaysSucceeds :: STM a -> STM ()Source
alwaysSucceeds adds a new invariant that must be true when passed to alwaysSucceeds, at the end of the current transaction, and at the end of every subsequent transaction. If it fails at any of those points then the transaction violating it is aborted and the exception raised by the invariant is propagated.
always :: STM Bool -> STM ()Source
always is a variant of alwaysSucceeds in which the invariant is expressed as an STM Bool action that must return True. Returning False or raising an exception are both treated as invariant failures.
data TVar a Source
Shared memory locations that support atomic memory transactions.
Constructors
TVar (TVar# RealWorld a)
show/hide Instances
newTVar :: a -> STM (TVar a)Source
Create a new TVar holding a value supplied
newTVarIO :: a -> IO (TVar a)Source
IO version of newTVar. This is useful for creating top-level TVars using System.IO.Unsafe.unsafePerformIO, because using atomically inside System.IO.Unsafe.unsafePerformIO isn't possible.
readTVar :: TVar a -> STM aSource
Return the current value stored in a TVar
readTVarIO :: TVar a -> IO aSource

Return the current value stored in a TVar. This is equivalent to

  readTVarIO = atomically . readTVar

but works much faster, because it doesn't perform a complete transaction, it just reads the current value of the TVar.

writeTVar :: TVar a -> a -> STM ()Source
Write the supplied value into a TVar
unsafeIOToSTM :: IO a -> STM aSource

Unsafely performs IO in the STM monad. Beware: this is a highly dangerous thing to do.

  • The STM implementation will often run transactions multiple times, so you need to be prepared for this if your IO has any side effects.
  • The STM implementation will abort transactions that are known to be invalid and need to be restarted. This may happen in the middle of unsafeIOToSTM, so make sure you don't acquire any resources that need releasing (exception handlers are ignored when aborting the transaction). That includes doing any IO using Handles, for example. Getting this wrong will probably lead to random deadlocks.
  • The transaction may have seen an inconsistent view of memory when the IO runs. Invariants that you expect to be true throughout your program may not be true inside a transaction, due to the way transactions are implemented. Normally this wouldn't be visible to the programmer, but using unsafeIOToSTM can expose it.
Miscellaneous
withMVar :: MVar a -> (a -> IO b) -> IO bSource
type Signal = CIntSource
type HandlerFun = ForeignPtr Word8 -> IO ()Source
setHandler :: Signal -> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic))Source
runHandlers :: Ptr Word8 -> Int -> IO ()Source
ensureIOManagerIsRunning :: IO ()Source
syncIOManager :: IO ()Source
setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO ()Source
getUncaughtExceptionHandler :: IO (SomeException -> IO ())Source
reportError :: SomeException -> IO ()Source
reportStackOverflow :: IO ()Source
Produced by Haddock version 2.6.1