base-4.6.0.0: Basic libraries

Portabilitynon-portable (GHC extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Safe HaskellUnsafe

GHC.Conc

Contents

Description

Basic concurrency stuff.

Synopsis

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# 

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 forkOS instead.

GHC note: the new thread inherits the masked state of the parent (see mask).

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.

forkIOUnmasked :: IO () -> IO ThreadIdSource

This function is deprecated; use forkIOWithUnmask instead

forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadIdSource

Like forkIO, but the child thread is passed a function that can be used to unmask asynchronous exceptions. This function is typically used in the following way

  ... mask_ $ forkIOWithUnmask $ \unmask ->
                 catch (unmask ...) handler

so that the exception handler in the child thread is established with asynchronous exceptions masked, meanwhile the main body of the child thread is executed in the unmasked state.

Note that the unmask function passed to the child thread should only be used in that thread; the behaviour is undefined if it is invoked in a different thread.

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

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

The Int argument specifies a capability number (see getNumCapabilities). Typically capabilities correspond to physical processors, but the exact behaviour is implementation-dependent. The value passed to forkOn is interpreted modulo the total number of capabilities as returned by getNumCapabilities.

GHC note: the number of capabilities is specified by the +RTS -N option when the program is started. Capabilities can be fixed to actual processor cores with +RTS -qa if the underlying operating system supports that, although in practice this is usually unnecessary (and may actually degrade perforamnce in some cases - experimentation is recommended).

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

This function is deprecated; use forkOn instead

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

This function is deprecated; use forkOnWIthUnmask instead

forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadIdSource

Like forkIOWithUnmask, but the child thread is pinned to the given CPU, as with forkOn.

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 processor cores on the machine.

Strictly speaking it is better to use getNumCapabilities, because the number of capabilities might vary at runtime.

getNumCapabilities :: IO IntSource

Returns the number of Haskell threads that can run truly simultaneously (on separate physical processors) at any given time. To change this value, use setNumCapabilities.

setNumCapabilities :: Int -> IO ()Source

Set the number of Haskell threads that can run truly simultaneously (on separate physical processors) at any given time. The number passed to forkOn is interpreted modulo this value. The initial value is given by the +RTS -N runtime flag.

This is also the number of threads that will participate in parallel garbage collection. It is strongly recommended that the number of capabilities is not set larger than the number of physical processor cores, and it may often be beneficial to leave one or more cores free to avoid contention with other processes in the machine.

numSparks :: IO IntSource

Returns the number of sparks currently in the local spark pool

myThreadId :: IO ThreadIdSource

Returns the ThreadId of the calling thread (GHC only).

killThread :: ThreadId -> IO ()Source

killThread raises the ThreadKilled exception in the given thread (GHC only).

 killThread tid = throwTo tid ThreadKilled

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.

Whatever work the target thread was doing when the exception was raised is not lost: the computation is suspended until required by another thread.

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 mask or not. However, in GHC a foreign call can be annotated as interruptible, in which case a throwTo will cause the RTS to attempt to cause the call to return; see the GHC documentation for more details.

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). Unlike other interruptible operations, however, throwTo is always interruptible, even if it does not actually block.

There is no guarantee that the exception will be delivered promptly, although the runtime will endeavour to ensure that arbitrary delays don't occur. In GHC, an exception can only be raised when a thread reaches a safe point, where a safe point is where memory allocation occurs. Some loops do not perform any memory allocation inside the loop and therefore cannot be interrupted by a throwTo.

If the target of throwTo is the calling thread, then the behaviour is the same as throwIO, except that the exception is thrown as an asynchronous exception. This means that if there is an enclosing pure computation, which would be the case if the current IO operation is inside unsafePerformIO or unsafeInterleaveIO, that computation is not permanently replaced by the exception, but is suspended as if it had received an asynchronous exception.

Note that if throwTo is called with the current thread as the target, the exception will be thrown even if the thread is currently inside mask or uninterruptibleMask.

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.

mkWeakThreadId :: ThreadId -> IO (Weak ThreadId)Source

make a weak pointer to a ThreadId. It can be important to do this if you want to hold a reference to a ThreadId while still allowing the thread to receive the BlockedIndefinitely family of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a normal ThreadId reference will prevent the delivery of BlockedIndefinitely exceptions because the reference could be used as the target of throwTo at any time, which would unblock the thread.

Holding a Weak ThreadId, on the other hand, will not prevent the thread from receiving BlockedIndefinitely exceptions. It is still possible to throw an exception to a Weak ThreadId, but the caller must use deRefWeak first to determine whether the thread still exists.

data ThreadStatus Source

The current status of a thread

Constructors

ThreadRunning

the thread is currently runnable or running

ThreadFinished

the thread has finished

ThreadBlocked BlockReason

the thread is blocked on some resource

ThreadDied

the thread received an uncaught exception

data BlockReason Source

Constructors

BlockedOnMVar

blocked on on MVar

BlockedOnBlackHole

blocked on a computation in progress by another thread

BlockedOnException

blocked in throwTo

BlockedOnSTM

blocked in retry in an STM transaction

BlockedOnForeignCall

currently in a foreign call

BlockedOnOther

blocked on some other resource. Without -threaded, I/O and threadDelay show up as BlockedOnOther, with -threaded they show up as BlockedOnMVar.

threadCapability :: ThreadId -> IO (Int, Bool)Source

returns the number of the capability on which the thread is currently running, and a boolean indicating whether the thread is locked to that capability or not. A thread is locked to a capability if it was created with forkOn.

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

This will throw an IOError if the file descriptor was closed while this thread was blocked. To safely close a file descriptor that has been used with threadWaitRead, use closeFdWith.

threadWaitWrite :: Fd -> IO ()Source

Block the current thread until data can be written to the given file descriptor (GHC only).

This will throw an IOError if the file descriptor was closed while this thread was blocked. To safely close a file descriptor that has been used with threadWaitWrite, use closeFdWith.

closeFdWithSource

Arguments

:: (Fd -> IO ())

Low-level action that performs the real close.

-> Fd

File descriptor to close.

-> IO () 

Close a file descriptor in a concurrency-safe way (GHC only). If you are using threadWaitRead or threadWaitWrite to perform blocking I/O, you must use this function to close file descriptors, or blocked threads may not be woken.

Any threads that are blocked on the file descriptor via threadWaitRead or threadWaitWrite will be unblocked by having IO exceptions thrown.

TVars

newtype STM a Source

A monad supporting atomic memory transactions.

Constructors

STM (State# RealWorld -> (#State# RealWorld, a#)) 

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.

throwSTM :: Exception e => e -> STM aSource

A variant of throw that can only be used within the STM monad.

Throwing an exception in STM aborts the transaction and propagates the exception.

Although throwSTM has a type that is an instance of the type of throw, the two functions are subtly different:

 throw e    `seq` x  ===> throw e
 throwSTM e `seq` x  ===> x

The first example will cause the exception e to be raised, whereas the second one won't. In fact, throwSTM will only cause an exception to be raised when it is used within the STM monad. The throwSTM variant should be used in preference to throw to raise an exception within the STM monad because it guarantees ordering with respect to other STM operations, whereas throw does not.

catchSTM :: Exception e => STM a -> (e -> 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) 

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 unsafePerformIO, because using atomically inside 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