Stability | experimental |
---|---|
Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
Safe Haskell | Safe-Infered |
This is a wrapped version of Concurrent
with types generalized
from IO
to all monads in either MonadBase
or MonadBaseControl
.
- data ThreadId
- myThreadId :: MonadBase IO m => m ThreadId
- fork :: MonadBaseControl IO m => m () -> m ThreadId
- forkWithUnmask :: MonadBaseControl IO m => ((forall α. m α -> m α) -> m ()) -> m ThreadId
- killThread :: MonadBase IO m => ThreadId -> m ()
- throwTo :: (MonadBase IO m, Exception e) => ThreadId -> e -> m ()
- forkOn :: MonadBaseControl IO m => Int -> m () -> m ThreadId
- forkOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall α. m α -> m α) -> m ()) -> m ThreadId
- getNumCapabilities :: MonadBase IO m => m Int
- threadCapability :: MonadBase IO m => ThreadId -> m (Int, Bool)
- yield :: MonadBase IO m => m ()
- threadDelay :: MonadBase IO m => Int -> m ()
- threadWaitRead :: MonadBase IO m => Fd -> m ()
- threadWaitWrite :: MonadBase IO m => Fd -> m ()
- module Control.Concurrent.MVar.Lifted
- merge :: MonadBase IO m => [α] -> [α] -> m [α]
- nmerge :: MonadBase IO m => [[α]] -> m [α]
- forkOS :: MonadBaseControl IO m => m () -> m ThreadId
- isCurrentThreadBound :: MonadBase IO m => m Bool
- runInBoundThread :: MonadBaseControl IO m => m α -> m α
- runInUnboundThread :: MonadBaseControl IO m => m α -> m α
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
ThreadId
s. 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
.
forkWithUnmask :: MonadBaseControl IO m => ((forall α. m α -> m α) -> 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
.
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
forkOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall α. m α -> m α) -> 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
.
threadCapability :: MonadBase IO m => ThreadId -> m (Int, Bool)Source
Generalized version of threadCapability
.
Scheduling
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
Merging of streams
Bound Threads
isCurrentThreadBound :: MonadBase IO m => m BoolSource
Generalized version of isCurrentThreadBound
.
runInBoundThread :: MonadBaseControl IO m => m α -> m αSource
Generalized version of runInBoundThread
.
runInUnboundThread :: MonadBaseControl IO m => m α -> m αSource
Generalized version of runInUnboundThread
.