Copyright | (c) 2016 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | CPP, FlexibleContexts, PolyKinds, RankNTypes, ScopedTypeVariables, TypeFamilies |
Safe Haskell | None |
Language | Haskell2010 |
This module captures in a typeclass the interface of concurrency monads.
Deviations: An instance of MonadConc
is not required to be
an instance of MonadFix
, unlike IO
. The CRef
, MVar
, and
Ticket
types are not required to be instances of Show
or Eq
,
unlike their normal counterparts. The threadCapability
,
threadWaitRead
, threadWaitWrite
, threadWaitReadSTM
,
threadWaitWriteSTM
, and mkWeakThreadId
functions are not
provided. The threadDelay
function is not required to delay the
thread, merely to yield it. Bound threads are not supported. The
BlockedIndefinitelyOnMVar
(and similar) exceptions are not
thrown during testing, so do not rely on them at all.
- class (Applicative m, Monad m, MonadCatch m, MonadThrow m, MonadMask m, MonadSTM (STM m), Ord (ThreadId m), Show (ThreadId m)) => MonadConc m where
- spawn :: MonadConc m => m a -> m (MVar m a)
- forkFinally :: MonadConc m => m a -> (Either SomeException a -> m ()) -> m (ThreadId m)
- killThread :: MonadConc m => ThreadId m -> m ()
- forkN :: MonadConc m => String -> m () -> m (ThreadId m)
- forkOnN :: MonadConc m => String -> Int -> m () -> m (ThreadId m)
- rtsSupportsBoundThreads :: Bool
- isCurrentThreadBound :: MonadConc m => m Bool
- throw :: (MonadConc m, Exception e) => e -> m a
- catch :: (MonadConc m, Exception e) => m a -> (e -> m a) -> m a
- mask :: MonadConc m => ((forall a. m a -> m a) -> m b) -> m b
- mask_ :: MonadMask m => m a -> m a
- uninterruptibleMask :: MonadConc m => ((forall a. m a -> m a) -> m b) -> m b
- uninterruptibleMask_ :: MonadMask m => m a -> m a
- newMVar :: MonadConc m => a -> m (MVar m a)
- newMVarN :: MonadConc m => String -> a -> m (MVar m a)
- cas :: MonadConc m => CRef m a -> a -> m (Bool, a)
- peekTicket :: forall m a. MonadConc m => Ticket m a -> m a
- liftedF :: (MonadTransControl t, MonadConc m) => (forall x. StT t x -> x) -> (m a -> m b) -> t m a -> t m b
- liftedFork :: (MonadTransControl t, MonadConc m) => (forall x. StT t x -> x) -> (((forall x. m x -> m x) -> m a) -> m b) -> ((forall x. t m x -> t m x) -> t m a) -> t m b
Documentation
class (Applicative m, Monad m, MonadCatch m, MonadThrow m, MonadMask m, MonadSTM (STM m), Ord (ThreadId m), Show (ThreadId m)) => MonadConc m where Source #
MonadConc
is an abstraction over GHC's typical concurrency
abstraction. It captures the interface of concurrency monads in
terms of how they can operate on shared state and in the presence
of exceptions.
Every MonadConc
has an associated MonadSTM
, transactions of
which can be run atomically.
Since: 1.0.0.0
The associated MonadSTM
for this class.
Since: 1.0.0.0
type MVar m :: * -> * Source #
The mutable reference type, like MVar
s. This may contain one
value at a time, attempting to read or take from an "empty"
MVar
will block until it is full, and attempting to put to a
"full" MVar
will block until it is empty.
Since: 1.0.0.0
type CRef m :: * -> * Source #
The mutable non-blocking reference type. These may suffer from
relaxed memory effects if functions outside the set newCRef
,
readCRef
, atomicModifyCRef
, and atomicWriteCRef
are used.
Since: 1.0.0.0
type Ticket m :: * -> * Source #
When performing compare-and-swap operations on CRef
s, a
Ticket
is a proof that a thread observed a specific previous
value.
Since: 1.0.0.0
An abstract handle to a thread.
Since: 1.0.0.0
fork :: m () -> m (ThreadId m) Source #
Fork a computation to happen concurrently. Communication may
happen over MVar
s.
fork ma = forkWithUnmask (\_ -> ma)
Since: 1.0.0.0
forkWithUnmask :: ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like fork
, but the child thread is passed a function that can
be used to unmask asynchronous exceptions. This function should
not be used within a mask
or uninterruptibleMask
.
forkWithUnmask = forkWithUnmaskN ""
Since: 1.0.0.0
forkWithUnmaskN :: String -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like forkWithUnmask
, but the thread is given a name which may
be used to present more useful debugging information.
If an empty name is given, the ThreadId
is used. If names
conflict, successive threads with the same name are given a
numeric suffix, counting up from 1.
forkWithUnmaskN _ = forkWithUnmask
Since: 1.0.0.0
forkOn :: Int -> m () -> m (ThreadId m) Source #
Fork a computation to happen on a specific processor. The
specified int is the capability number, typically capabilities
correspond to physical processors or cores but this is
implementation dependent. The int is interpreted modulo to the
total number of capabilities as returned by getNumCapabilities
.
forkOn c ma = forkOnWithUnmask c (\_ -> ma)
Since: 1.0.0.0
forkOnWithUnmask :: Int -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like forkWithUnmask
, but the child thread is pinned to the
given CPU, as with forkOn
.
forkOnWithUnmask = forkOnWithUnmaskN ""
Since: 1.0.0.0
forkOnWithUnmaskN :: String -> Int -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like forkWithUnmaskN
, but the child thread is pinned to the
given CPU, as with forkOn
.
forkOnWithUnmaskN _ = forkOnWithUnmask
Since: 1.0.0.0
getNumCapabilities :: m Int Source #
Get the number of Haskell threads that can run simultaneously.
Since: 1.0.0.0
setNumCapabilities :: Int -> m () Source #
Set the number of Haskell threads that can run simultaneously.
Since: 1.0.0.0
myThreadId :: m (ThreadId m) Source #
Get the ThreadId
of the current thread.
Since: 1.0.0.0
Allows a context-switch to any other currently runnable thread (if any).
Since: 1.0.0.0
threadDelay :: Int -> m () Source #
Yields the current thread, and optionally suspends the current thread for a given number of microseconds.
If suspended, 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.
threadDelay _ = yield
Since: 1.0.0.0
newEmptyMVar :: m (MVar m a) Source #
Create a new empty MVar
.
newEmptyMVar = newEmptyMVarN ""
Since: 1.0.0.0
newEmptyMVarN :: String -> m (MVar m a) Source #
Create a new empty MVar
, but it is given a name which may be
used to present more useful debugging information.
If an empty name is given, a counter starting from 0 is used. If
names conflict, successive MVar
s with the same name are given a
numeric suffix, counting up from 1.
newEmptyMVarN _ = newEmptyMVar
Since: 1.0.0.0
putMVar :: MVar m a -> a -> m () Source #
Put a value into a MVar
. If there is already a value there,
this will block until that value has been taken, at which point
the value will be stored.
Since: 1.0.0.0
tryPutMVar :: MVar m a -> a -> m Bool Source #
Attempt to put a value in a MVar
non-blockingly, returning
True
(and filling the MVar
) if there was nothing there,
otherwise returning False
.
Since: 1.0.0.0
readMVar :: MVar m a -> m a Source #
Block until a value is present in the MVar
, and then return
it. This does not "remove" the value, multiple reads are
possible.
Since: 1.0.0.0
tryReadMVar :: MVar m a -> m (Maybe a) Source #
Attempt to read a value from a MVar
non-blockingly, returning
a Just
(and emptying the MVar
) if there is something there,
otherwise returning Nothing
. As with readMVar
, this does not
"remove" the value.
Since: 1.1.0.0
takeMVar :: MVar m a -> m a Source #
Take a value from a MVar
. This "empties" the MVar
,
allowing a new value to be put in. This will block if there is no
value in the MVar
already, until one has been put.
Since: 1.0.0.0
tryTakeMVar :: MVar m a -> m (Maybe a) Source #
Attempt to take a value from a MVar
non-blockingly, returning
a Just
(and emptying the MVar
) if there was something there,
otherwise returning Nothing
.
Since: 1.0.0.0
newCRef :: a -> m (CRef m a) Source #
Create a new reference.
newCRef = newCRefN ""
Since: 1.0.0.0
newCRefN :: String -> a -> m (CRef m a) Source #
Create a new reference, but it is given a name which may be used to present more useful debugging information.
If an empty name is given, a counter starting from 0 is used. If
names conflict, successive CRef
s with the same name are given a
numeric suffix, counting up from 1.
newCRefN _ = newCRef
Since: 1.0.0.0
readCRef :: CRef m a -> m a Source #
Read the current value stored in a reference.
readCRef cref = readForCAS cref >>= peekTicket
Since: 1.0.0.0
atomicModifyCRef :: CRef m a -> (a -> (a, b)) -> m b Source #
Atomically modify the value stored in a reference. This imposes a full memory barrier.
Since: 1.0.0.0
writeCRef :: CRef m a -> a -> m () Source #
Write a new value into an CRef
, without imposing a memory
barrier. This means that relaxed memory effects can be observed.
Since: 1.0.0.0
atomicWriteCRef :: CRef m a -> a -> m () Source #
Replace the value stored in a reference, with the
barrier-to-reordering property that atomicModifyCRef
has.
atomicWriteCRef r a = atomicModifyCRef r $ const (a, ())
Since: 1.0.0.0
readForCAS :: CRef m a -> m (Ticket m a) Source #
Read the current value stored in a reference, returning a
Ticket
, for use in future compare-and-swap operations.
Since: 1.0.0.0
peekTicket' :: proxy m -> Ticket m a -> a Source #
Extract the actual Haskell value from a Ticket
.
The proxy m
is to determine the m
in the Ticket
type.
Since: 1.0.0.0
casCRef :: CRef m a -> Ticket m a -> a -> m (Bool, Ticket m a) Source #
Perform a machine-level compare-and-swap (CAS) operation on a
CRef
. Returns an indication of success and a Ticket
for the
most current value in the CRef
.
This is strict in the "new" value argument.
Since: 1.0.0.0
modifyCRefCAS :: CRef m a -> (a -> (a, b)) -> m b Source #
A replacement for atomicModifyCRef
using a compare-and-swap.
This is strict in the "new" value argument.
Since: 1.0.0.0
modifyCRefCAS_ :: CRef m a -> (a -> a) -> m () Source #
A variant of modifyCRefCAS
which doesn't return a result.
modifyCRefCAS_ cref f = modifyCRefCAS cref (\a -> (f a, ()))
Since: 1.0.0.0
atomically :: STM m a -> m a Source #
Perform an STM transaction atomically.
Since: 1.0.0.0
readTVarConc :: TVar (STM m) a -> m a Source #
Read the current value stored in a TVar
. This may be
implemented differently for speed.
readTVarConc = atomically . readTVar
Since: 1.0.0.0
throwTo :: Exception e => ThreadId m -> e -> m () Source #
Throw an exception to the target thread. This blocks until the
exception is delivered, and it is just as if the target thread
had raised it with throw
. This can interrupt a blocked action.
Since: 1.0.0.0
MonadConc IO Source # | Since: 1.0.0.0 |
MonadConc m => MonadConc (StateT s m) Source # | New threads inherit the state of their parent, but do not communicate results back. Since: 1.0.0.0 |
MonadConc m => MonadConc (StateT s m) Source # | New threads inherit the state of their parent, but do not communicate results back. Since: 1.0.0.0 |
(MonadConc m, Monoid w) => MonadConc (WriterT w m) Source # | New threads inherit the writer state of their parent, but do not communicate results back. Since: 1.0.0.0 |
(MonadConc m, Monoid w) => MonadConc (WriterT w m) Source # | New threads inherit the writer state of their parent, but do not communicate results back. Since: 1.0.0.0 |
MonadConc m => MonadConc (IdentityT * m) Source # | Since: 1.0.0.0 |
MonadConc m => MonadConc (ReaderT * r m) Source # | New threads inherit the reader state of their parent, but do not communicate results back. Since: 1.0.0.0 |
(MonadConc m, Monoid w) => MonadConc (RWST r w s m) Source # | New threads inherit the states of their parent, but do not communicate results back. Since: 1.0.0.0 |
(MonadConc m, Monoid w) => MonadConc (RWST r w s m) Source # | New threads inherit the states of their parent, but do not communicate results back. Since: 1.0.0.0 |
Threads
spawn :: MonadConc m => m a -> m (MVar m a) Source #
Create a concurrent computation for the provided action, and
return a MVar
which can be used to query the result.
Since: 1.0.0.0
forkFinally :: MonadConc m => m a -> (Either SomeException a -> m ()) -> m (ThreadId m) Source #
Fork a thread and call the supplied function when the thread is about to terminate, with an exception or a returned value. The function is called with asynchronous exceptions masked.
This function is useful for informing the parent when a child terminates, for example.
Since: 1.0.0.0
killThread :: MonadConc m => ThreadId m -> m () Source #
Raise the ThreadKilled
exception in the target thread. Note
that if the thread is prepared to catch this exception, it won't
actually kill it.
Since: 1.0.0.0
Named Threads
forkN :: MonadConc m => String -> m () -> m (ThreadId m) Source #
Like fork
, but the thread is given a name which may be used to
present more useful debugging information.
If no name is given, the ThreadId
is used. If names conflict,
successive threads with the same name are given a numeric suffix,
counting up from 1.
Since: 1.0.0.0
forkOnN :: MonadConc m => String -> Int -> m () -> m (ThreadId m) Source #
Like forkOn
, but the thread is given a name which may be used
to present more useful debugging information.
If no name is given, the ThreadId
is used. If names conflict,
successive threads with the same name are given a numeric suffix,
counting up from 1.
Since: 1.0.0.0
Bound Threads
MonadConc
does not support bound threads, if you need that
sort of thing you will have to use regular IO
.
rtsSupportsBoundThreads :: Bool Source #
Provided for compatibility, always returns False
.
Since: 1.0.0.0
isCurrentThreadBound :: MonadConc m => m Bool Source #
Provided for compatibility, always returns False
.
Since: 1.0.0.0
Exceptions
throw :: (MonadConc m, Exception e) => e -> m a Source #
Throw an exception. This will "bubble up" looking for an exception handler capable of dealing with it and, if one is not found, the thread is killed.
Since: 1.0.0.0
mask :: MonadConc m => ((forall a. m a -> m a) -> m b) -> m b Source #
Executes a computation with asynchronous exceptions
masked. That is, any thread which attempts to raise an exception
in the current thread with throwTo
will be blocked until
asynchronous exceptions are unmasked again.
The argument passed to mask is a function that takes as its
argument another function, which can be used to restore the
prevailing masking state within the context of the masked
computation. This function should not be used within an
uninterruptibleMask
.
Since: 1.0.0.0
uninterruptibleMask :: MonadConc m => ((forall a. m a -> m a) -> m b) -> m b Source #
Like mask
, but the masked computation is not
interruptible. THIS SHOULD BE USED WITH GREAT CARE, because if a
thread executing in uninterruptibleMask
blocks for any reason,
then the thread (and possibly the program, if this is the main
thread) will be unresponsive and unkillable. This function should
only be necessary if you need to mask exceptions around an
interruptible operation, and you can guarantee that the
interruptible operation will only block for a short period of
time. The supplied unmasking function should not be used within a
mask
.
Since: 1.0.0.0
uninterruptibleMask_ :: MonadMask m => m a -> m a #
Like uninterruptibleMask
, but does not pass a restore
action to the
argument.
Mutable State
newMVar :: MonadConc m => a -> m (MVar m a) Source #
Create a new MVar
containing a value.
Since: 1.0.0.0
newMVarN :: MonadConc m => String -> a -> m (MVar m a) Source #
Create a new MVar
containing a value, but it is given a name
which may be used to present more useful debugging information.
If no name is given, a counter starting from 0 is used. If names
conflict, successive MVar
s with the same name are given a numeric
suffix, counting up from 1.
Since: 1.0.0.0
cas :: MonadConc m => CRef m a -> a -> m (Bool, a) Source #
Compare-and-swap a value in a CRef
, returning an indication of
success and the new value.
Since: 1.0.0.0
peekTicket :: forall m a. MonadConc m => Ticket m a -> m a Source #
Extract the actual Haskell value from a Ticket
.
This doesn't do do any monadic computation, the m
appears in the
result type to determine the m
in the Ticket
type.
Since: 1.0.0.0
Utilities for instance writers
liftedF :: (MonadTransControl t, MonadConc m) => (forall x. StT t x -> x) -> (m a -> m b) -> t m a -> t m b Source #
Given a function to remove the transformer-specific state, lift a function invocation.
Since: 1.0.0.0
liftedFork :: (MonadTransControl t, MonadConc m) => (forall x. StT t x -> x) -> (((forall x. m x -> m x) -> m a) -> m b) -> ((forall x. t m x -> t m x) -> t m a) -> t m b Source #
Given a function to remove the transformer-specific state, lift
a fork(on)WithUnmask
invocation.
Since: 1.0.0.0