lifted-base-0.2.0.2: lifted IO operations from the base library

Stabilityexperimental
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Safe HaskellTrustworthy

Control.Concurrent.Lifted

Contents

Description

This is a wrapped version of Control.Concurrent with types generalized from IO to all monads in either MonadBase or MonadBaseControl.

Synopsis

Concurrent Haskell

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

Basic concurrency operations

myThreadId :: MonadBase IO m => m ThreadIdSource

Generalized version of myThreadId.

fork :: MonadBaseControl IO m => m () -> m ThreadIdSource

Generalized version of forkIO.

Note that, while the forked computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in IO.

forkWithUnmask :: MonadBaseControl IO m => ((forall a. m a -> m a) -> m ()) -> m ThreadIdSource

Generalized version of forkIOWithUnmask.

Note that, while the forked computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in IO.

forkFinally :: MonadBaseControl IO m => m a -> (Either SomeException a -> m ()) -> m ThreadIdSource

Generalized version of forkFinally.

Note that in forkFinally action and_then, while the forked action and the and_then function have access to the captured state, all their side-effects in m are discarded. They're run only for their side-effects in IO.

killThread :: MonadBase IO m => ThreadId -> m ()Source

Generalized version of killThread.

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

Generalized version of throwTo.

Threads with affinity

forkOn :: MonadBaseControl IO m => Int -> m () -> m ThreadIdSource

Generalized version of forkOn.

Note that, while the forked computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in IO.

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

Generalized version of forkOnWithUnmask.

Note that, while the forked computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in IO.

getNumCapabilities :: MonadBase IO m => m IntSource

Generalized version of getNumCapabilities.

setNumCapabilities :: MonadBase IO m => Int -> m ()Source

Generalized version of setNumCapabilities.

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

Generalized version of threadCapability.

Scheduling

yield :: MonadBase IO m => m ()Source

Generalized version of yield.

Blocking

Waiting

threadDelay :: MonadBase IO m => Int -> m ()Source

Generalized version of threadDelay.

threadWaitRead :: MonadBase IO m => Fd -> m ()Source

Generalized version of threadWaitRead.

threadWaitWrite :: MonadBase IO m => Fd -> m ()Source

Generalized version of threadWaitWrite.

Communication abstractions

Bound Threads

rtsSupportsBoundThreads :: Bool

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

forkOS :: MonadBaseControl IO m => m () -> m ThreadIdSource

Generalized version of forkOS.

Note that, while the forked computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in IO.

runInBoundThread :: MonadBaseControl IO m => m a -> m aSource

Generalized version of runInBoundThread.

runInUnboundThread :: MonadBaseControl IO m => m a -> m aSource

Generalized version of runInUnboundThread.

Weak references to ThreadIds

mkWeakThreadId :: MonadBase IO m => ThreadId -> m (Weak ThreadId)Source

Generalized versio of mkWeakThreadId.