Copyright | (c) 2016--2020 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | CPP, FlexibleContexts, PolyKinds, RankNTypes, ScopedTypeVariables, StandaloneDeriving, 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 IORef
, 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. The BlockedIndefinitelyOnMVar
(and
similar) exceptions are not thrown during testing, so do not rely
on them at all.
Synopsis
- class (Monad m, MonadCatch m, MonadThrow m, MonadMask m, MonadSTM (STM m), Ord (ThreadId m), Show (ThreadId m)) => MonadConc m where
- type STM m :: * -> *
- type MVar m :: * -> *
- type IORef m :: * -> *
- type Ticket m :: * -> *
- type ThreadId m :: *
- forkWithUnmask :: ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- forkWithUnmaskN :: String -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- forkOnWithUnmask :: Int -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- forkOnWithUnmaskN :: String -> Int -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- forkOSWithUnmask :: ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- forkOSWithUnmaskN :: String -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m)
- supportsBoundThreads :: m Bool
- isCurrentThreadBound :: m Bool
- getNumCapabilities :: m Int
- setNumCapabilities :: Int -> m ()
- myThreadId :: m (ThreadId m)
- yield :: m ()
- threadDelay :: Int -> m ()
- newEmptyMVar :: m (MVar m a)
- newEmptyMVarN :: String -> m (MVar m a)
- putMVar :: MVar m a -> a -> m ()
- tryPutMVar :: MVar m a -> a -> m Bool
- readMVar :: MVar m a -> m a
- tryReadMVar :: MVar m a -> m (Maybe a)
- takeMVar :: MVar m a -> m a
- tryTakeMVar :: MVar m a -> m (Maybe a)
- newIORef :: a -> m (IORef m a)
- newIORefN :: String -> a -> m (IORef m a)
- readIORef :: IORef m a -> m a
- atomicModifyIORef :: IORef m a -> (a -> (a, b)) -> m b
- writeIORef :: IORef m a -> a -> m ()
- atomicWriteIORef :: IORef m a -> a -> m ()
- readForCAS :: IORef m a -> m (Ticket m a)
- peekTicket' :: Proxy m -> Ticket m a -> a
- casIORef :: IORef m a -> Ticket m a -> a -> m (Bool, Ticket m a)
- modifyIORefCAS :: IORef m a -> (a -> (a, b)) -> m b
- modifyIORefCAS_ :: IORef m a -> (a -> a) -> m ()
- atomically :: STM m a -> m a
- newTVarConc :: a -> m (TVar (STM m) a)
- readTVarConc :: TVar (STM m) a -> m a
- throwTo :: Exception e => ThreadId m -> e -> m ()
- getMaskingState :: m MaskingState
- unsafeUnmask :: m a -> m a
- fork :: MonadConc m => m () -> m (ThreadId m)
- forkOn :: MonadConc m => Int -> m () -> m (ThreadId m)
- forkOS :: MonadConc m => m () -> m (ThreadId m)
- forkFinally :: MonadConc m => m a -> (Either SomeException a -> m ()) -> m (ThreadId m)
- spawn :: MonadConc m => m a -> m (MVar m a)
- killThread :: MonadConc m => ThreadId m -> m ()
- rtsSupportsBoundThreads :: Bool
- runInBoundThread :: MonadConc m => m a -> m a
- runInUnboundThread :: MonadConc m => m a -> m a
- forkN :: MonadConc m => String -> m () -> m (ThreadId m)
- forkOnN :: MonadConc m => String -> Int -> m () -> m (ThreadId m)
- forkOSN :: MonadConc m => String -> m () -> m (ThreadId m)
- 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
- interruptible :: MonadConc 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 => IORef m a -> a -> m (Bool, a)
- peekTicket :: forall m a. MonadConc m => Ticket m a -> m a
- data IsConc m a
- toIsConc :: MonadConc m => m a -> IsConc m a
- fromIsConc :: MonadConc m => IsConc 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 (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.
Deriving instances: If you have a newtype wrapper around a type
with an existing MonadConc
instance, you should be able to derive
an instance for your type automatically, in simple cases.
For example:
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} data Env = Env newtype MyMonad m a = MyMonad { runMyMonad :: ReaderT Env m a } deriving (Functor, Applicative, Monad) deriving instance MonadThrow m => MonadThrow (MyMonad m) deriving instance MonadCatch m => MonadCatch (MyMonad m) deriving instance MonadMask m => MonadMask (MyMonad m) deriving instance MonadConc m => MonadConc (MyMonad m)
Do not be put off by the use of UndecidableInstances
, it is safe
here.
Since: 1.11.0.0
(forkWithUnmask | forkWithUnmaskN), (forkOnWithUnmask | forkOnWithUnmaskN), (forkOSWithUnmask | forkOSWithUnmaskN), supportsBoundThreads, isCurrentThreadBound, getNumCapabilities, setNumCapabilities, myThreadId, yield, (newEmptyMVar | newEmptyMVarN), putMVar, tryPutMVar, readMVar, tryReadMVar, takeMVar, tryTakeMVar, (newIORef | newIORefN), atomicModifyIORef, writeIORef, readForCAS, peekTicket', casIORef, modifyIORefCAS, atomically, throwTo, getMaskingState, unsafeUnmask
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 IORef m :: * -> * Source #
The mutable non-blocking reference type. These may suffer from
relaxed memory effects if functions outside the set newIORef
,
readIORef
, atomicModifyIORef
, and atomicWriteIORef
are used.
Since: 1.6.0.0
type Ticket m :: * -> * Source #
When performing compare-and-swap operations on IORef
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
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.
forkWithUnmaskN _ = forkWithUnmask
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
forkOSWithUnmask :: ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like forkOS
, 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
.
forkOSWithUnmask = forkOSWithUnmaskN ""
Since: 1.5.0.0
forkOSWithUnmaskN :: String -> ((forall a. m a -> m a) -> m ()) -> m (ThreadId m) Source #
Like forkOSWithUnmask
, but the thread is given a name which
may be used to present more useful debugging information.
forkOSWithUnmaskN _ = forkOSWithUnmask
Since: 1.5.0.0
supportsBoundThreads :: m Bool Source #
Returns True
if bound threads can be forked. If False
,
isCurrentThreadBound
will always return False
and both
forkOS
and runInBoundThread
will fail.
Since: 1.7.0.0
isCurrentThreadBound :: m Bool Source #
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.
This will always be false if your program is not compiled with the threaded runtime.
Since: 1.3.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 unblocked 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.
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
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
newIORef :: a -> m (IORef m a) Source #
Create a new reference.
newIORef = newIORefN ""
Since: 1.6.0.0
newIORefN :: String -> a -> m (IORef m a) Source #
Create a new reference, but it is given a name which may be used to present more useful debugging information.
newIORefN _ = newIORef
Since: 1.6.0.0
readIORef :: IORef m a -> m a Source #
Read the current value stored in a reference.
readIORef ioref = readForCAS ioref >>= peekTicket
Since: 1.6.0.0
atomicModifyIORef :: IORef m a -> (a -> (a, b)) -> m b Source #
Atomically modify the value stored in a reference. This imposes a full memory barrier.
Since: 1.6.0.0
writeIORef :: IORef m a -> a -> m () Source #
Write a new value into an IORef
, without imposing a memory
barrier. This means that relaxed memory effects can be observed.
Since: 1.6.0.0
atomicWriteIORef :: IORef m a -> a -> m () Source #
Replace the value stored in a reference, with the
barrier-to-reordering property that atomicModifyIORef
has.
atomicWriteIORef r a = atomicModifyIORef r $ const (a, ())
Since: 1.6.0.0
readForCAS :: IORef 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.6.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.4.0.0
casIORef :: IORef m a -> Ticket m a -> a -> m (Bool, Ticket m a) Source #
Perform a machine-level compare-and-swap (CAS) operation on a
IORef
. Returns an indication of success and a Ticket
for the
most current value in the IORef
.
This is strict in the "new" value argument.
Since: 1.6.0.0
modifyIORefCAS :: IORef m a -> (a -> (a, b)) -> m b Source #
A replacement for atomicModifyIORef
using a compare-and-swap.
This is strict in the "new" value argument.
Since: 1.6.0.0
modifyIORefCAS_ :: IORef m a -> (a -> a) -> m () Source #
A variant of modifyIORefCAS
which doesn't return a result.
modifyIORefCAS_ ioref f = modifyIORefCAS ioref (\a -> (f a, ()))
Since: 1.6.0.0
atomically :: STM m a -> m a Source #
Perform an STM transaction atomically.
Since: 1.0.0.0
newTVarConc :: a -> m (TVar (STM m) a) Source #
Create a TVar
. This may be implemented differently for speed.
newTVarConc = atomically . newTVar
Since: 1.8.1.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
getMaskingState :: m MaskingState Source #
Return the MaskingState
for the current thread.
Since: 1.10.0.0
unsafeUnmask :: m a -> m a Source #
Set the MaskingState
for the current thread to MaskedUninterruptible
.
Since: 1.11.0.0
Instances
Threads
fork :: MonadConc m => m () -> m (ThreadId m) Source #
Fork a computation to happen concurrently. Communication may
happen over MVar
s.
Since: 1.5.0.0
forkOn :: MonadConc m => 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
.
Since: 1.5.0.0
forkOS :: MonadConc m => m () -> m (ThreadId m) Source #
Fork a computation to happen in a bound thread, which is necessary if you need to call foreign (non-Haskell) libraries that make use of thread-local state, such as OpenGL.
Since: 1.5.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
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
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
Bound threads
Support for multiple operating system threads and bound threads as described below is currently only available in the GHC runtime system if you use the -threaded option when linking.
Other Haskell systems do not currently support multiple operating system threads.
A bound thread is a haskell thread that is bound to an operating system thread. While the bound thread is still scheduled by the Haskell run-time system, the operating system thread takes care of all the foreign calls made by the bound thread.
To a foreign library, the bound thread will look exactly like an ordinary operating system thread created using OS functions like pthread_create or CreateThread.
rtsSupportsBoundThreads :: Bool Source #
Deprecated: Use supportsBoundThreads
instead
True
if bound threads are supported. If
rtsSupportsBoundThreads
is False
, isCurrentThreadBound
will
always return False
and both forkOS
and runInBoundThread
will
fail.
Use supportsBoundThreads
in MonadConc
instead.
Since: 1.3.0.0
runInBoundThread :: MonadConc m => m a -> m a Source #
Run the computation passed as the first argument. If the calling
thread is not bound, a bound thread is created temporarily.
runInBoundThread
doesn't finish until the inner computation
finishes.
You can wrap a series of foreign function calls that rely on
thread-local state with runInBoundThread
so that you can use them
without knowing whether the current thread is bound.
Since: 1.3.0.0
runInUnboundThread :: MonadConc m => m a -> m a Source #
Run the computation passed as the first argument. If the calling
thread is bound, an unbound thread is created temporarily using
fork
. runInBoundThread
doesn't finish until the inner
computation finishes.
Use this function only in the rare case that you have actually
observed a performance loss due to the use of bound threads. A
program that doesn't need its main thread to be bound and makes
heavy use of concurrency (e.g. a web server), might want to wrap
its main
action in runInUnboundThread
.
Note that exceptions which are thrown to the current thread are thrown in turn to the thread that is executing the given computation. This ensures there's always a way of killing the forked thread.
Since: 1.3.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.
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.
Since: 1.0.0.0
forkOSN :: MonadConc m => String -> m () -> m (ThreadId m) Source #
Like forkOS
, but the thread is given a name which may be used
to present more useful debugging information.
Since: 1.5.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.
interruptible :: MonadConc m => m a -> m a Source #
Allow asynchronous exceptions to be raised even inside mask
,
making the operation interruptible.
When called outside mask
, or inside uninterruptibleMask
, this
function has no effect.
Since: 1.11.0.0
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.
Since: 1.0.0.0
cas :: MonadConc m => IORef m a -> a -> m (Bool, a) Source #
Compare-and-swap a value in a IORef
, returning an indication of
success and the new value.
Since: 1.6.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 type shenanigans
A value of type IsConc m a
can only be constructed if m
has a
MonadConc
instance.
Since: 1.2.2.0
Instances
toIsConc :: MonadConc m => m a -> IsConc m a Source #
Wrap an m a
value inside an IsConc
if m
has a MonadConc
instance.
Since: 1.2.2.0
fromIsConc :: MonadConc m => IsConc m a -> m a Source #
Unwrap an IsConc
value.
Since: 1.2.2.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