context-0.2.0.1: Thread-indexed, nested contexts
Safe HaskellNone
LanguageHaskell2010

Context.Concurrent

Synopsis

Introduction

This module provides a Context-compatible interface around Control.Concurrent. Depending on the PropagationStrategy of the Store, the fork* and run* functions in this module can automatically propagate the calling thread's latest registered contexts, if any, over so that they are also available to the thread being created.

This module is designed to be a drop-in replacement for Control.Concurrent so that users only have to import this module instead of both this module and Control.Concurrent. It is also re-exported from Context for convenience.

Control.Concurrent wrappers

forkIO :: IO () -> IO ThreadId Source #

See forkIO.

Since: 0.1.0.0

forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId Source #

See forkFinally.

Since: 0.1.0.0

forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId Source #

See forkIOWithUnmask.

Since: 0.1.0.0

forkOn :: Int -> IO () -> IO ThreadId Source #

See forkOn.

Since: 0.1.0.0

forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId Source #

See forkOnWithUnmask.

Since: 0.1.0.0

forkOS :: IO () -> IO ThreadId Source #

See forkOS.

Since: 0.1.0.0

forkOSWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId Source #

See forkOSWithUnmask.

Since: 0.1.0.0

runInBoundThread :: IO a -> IO a Source #

See runInBoundThread.

Since: 0.1.0.0

runInUnboundThread :: IO a -> IO a Source #

See runInUnboundThread.

Since: 0.1.0.0

Control.Concurrent re-exports

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.

Instances

Instances details
Eq ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

myThreadId :: IO ThreadId #

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

killThread :: ThreadId -> IO () #

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

killThread tid = throwTo tid ThreadKilled

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

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

Exception delivery synchronizes between the source and target thread: 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. Exception delivery is also atomic with respect to other exceptions. Atomicity is a useful property to have when dealing with race conditions: e.g. 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.

getNumCapabilities :: IO Int #

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.

Since: base-4.4.0.0

setNumCapabilities :: Int -> IO () #

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.

Since: base-4.5.0.0

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

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.

Since: base-4.4.0.0

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.

threadDelay :: Int -> IO () #

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.

threadWaitRead :: Fd -> IO () #

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 () #

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.

threadWaitReadSTM :: Fd -> IO (STM (), IO ()) #

Returns an STM action that can be used to wait for data to read from a file descriptor. The second returned value is an IO action that can be used to deregister interest in the file descriptor.

Since: base-4.7.0.0

threadWaitWriteSTM :: Fd -> IO (STM (), IO ()) #

Returns an STM action that can be used to wait until data can be written to a file descriptor. The second returned value is an IO action that can be used to deregister interest in the file descriptor.

Since: base-4.7.0.0

rtsSupportsBoundThreads :: Bool #

True if bound threads are supported. If rtsSupportsBoundThreads is False, isCurrentThreadBound will always return False and both forkOS and runInBoundThread will fail.

isCurrentThreadBound :: IO Bool #

Returns True if the calling thread is bound, that is, if it is safe to use foreign libraries that rely on thread-local state from the calling thread.

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

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.

Since: base-4.6.0.0