dejafu-0.1.0.0: Overloadable primitives for testable, potentially non-deterministic, concurrency.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Conc.Class

Contents

Description

This module captures in a typeclass the interface of concurrency monads.

Synopsis

Documentation

class (Applicative m, Monad m, MonadCatch m, MonadThrow m, MonadMask m, MonadSTM (STMLike m), Eq (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.

There are a few notable differences between this and the Par monad approach: firstly, Par imposes NFData constraints on everything, as it achieves its speed-up by forcing evaluation in separate threads. MonadConc doesn't do that, and so you need to be careful about where evaluation occurs, just like with MVars. Secondly, this builds on Par's futures by allowing CVars which threads can read from and write to, possibly multiple times, whereas with the Par monads it is illegal to write multiple times to the same IVar (or to non-blockingly read from it) which, when there are no exceptions, removes the possibility of data races.

Every MonadConc has an associated MonadSTM, transactions of which can be run atomically.

Associated Types

type STMLike m :: * -> * Source

The associated MonadSTM for this class.

type CVar m :: * -> * Source

The mutable reference type, like MVars. This may contain one value at a time, attempting to read or take from an "empty" CVar will block until it is full, and attempting to put to a "full" CVar will block until it is empty.

type CRef m :: * -> * Source

The mutable non-blocking reference type. These are like IORefs, but don't have the potential re-ordering problem mentioned in Data.IORef.

type ThreadId m :: * Source

An abstract handle to a thread.

Methods

fork :: m () -> m (ThreadId m) Source

Fork a computation to happen concurrently. Communication may happen over CVars.

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.

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.

getNumCapabilities :: m Int Source

Get the number of Haskell threads that can run simultaneously.

myThreadId :: m (ThreadId m) Source

Get the ThreadId of the current thread.

newEmptyCVar :: m (CVar m a) Source

Create a new empty CVar.

putCVar :: CVar m a -> a -> m () Source

Put a value into a CVar. If there is already a value there, this will block until that value has been taken, at which point the value will be stored.

tryPutCVar :: CVar m a -> a -> m Bool Source

Attempt to put a value in a CVar non-blockingly, returning True (and filling the CVar) if there was nothing there, otherwise returning False.

readCVar :: CVar m a -> m a Source

Block until a value is present in the CVar, and then return it. As with readMVar, this does not "remove" the value, multiple reads are possible.

takeCVar :: CVar m a -> m a Source

Take a value from a CVar. This "empties" the CVar, allowing a new value to be put in. This will block if there is no value in the CVar already, until one has been put.

tryTakeCVar :: CVar m a -> m (Maybe a) Source

Attempt to take a value from a CVar non-blockingly, returning a Just (and emptying the CVar) if there was something there, otherwise returning Nothing.

newCRef :: a -> m (CRef m a) Source

Create a new reference.

readCRef :: CRef m a -> m a Source

Read the current value stored in a reference.

modifyCRef :: CRef m a -> (a -> (a, b)) -> m b Source

Atomically modify the value stored in a reference.

writeCRef :: CRef m a -> a -> m () Source

Replace the value stored in a reference.

writeCRef r a = modifyCRef r $ const (a, ())

atomically :: STMLike m a -> m a Source

Perform an STM transaction atomically.

throw :: 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.

throw = Control.Monad.Catch.throwM

catch :: Exception e => m a -> (e -> m a) -> m a Source

Catch an exception. This is only required to be able to catch exceptions raised by throw, unlike the more general Control.Exception.catch function. If you need to be able to catch all errors, you will have to use IO.

catch = Control.Monad.Catch.catch

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.

mask :: ((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.

mask = Control.Monad.Catch.mask

uninterruptibleMask :: ((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.

uninterruptibleMask = Control.Monad.Catch.uninterruptibleMask

_concNoTest :: m a -> m a Source

Runs its argument, just as if the _concNoTest weren't there.

This function is purely for testing purposes, and indicates that it's not worth considering more than one schedule here. This is useful if you have some larger computation built up out of subcomputations which you have already got tests for: you only want to consider what's unique to the large component.

The test runner will report a failure if the argument fails.

Note that inappropriate use of _concNoTest can actually suppress bugs! For this reason it is recommended to use it only for things which don't make use of any state from a larger scope. As a rule-of-thumb: if you can't define it as a top-level function taking no CVRef, CVar, or CTVar arguments, you probably shouldn't _concNoTest it.

_concNoTest x = x

_concKnowsAbout :: Either (CVar m a) (CTVar (STMLike m) a) -> m () Source

Does nothing.

This function is purely for testing purposes, and indicates that the thread has a reference to the provided CVar or CTVar. This function may be called multiple times, to add new knowledge to the system. It does not need to be called when CVars or CTVars are created, these get recorded automatically.

Gathering this information allows detection of cases where the main thread is blocked on a variable no runnable thread has a reference to, which is a deadlock situation.

_concKnowsAbout _ = return ()

_concForgets :: Either (CVar m a) (CTVar (STMLike m) a) -> m () Source

Does nothing.

The counterpart to _concKnowsAbout. Indicates that the referenced variable will never be touched again by the current thread.

Note that inappropriate use of _concForgets can result in false positives! Be very sure that the current thread will never refer to the variable again, for instance when leaving its scope.

_concForgets _ = return ()

_concAllKnown :: m () Source

Does nothing.

Indicates to the test runner that all variables which have been passed in to this thread have been recorded by calls to _concKnowsAbout. If every thread has called _concAllKnown, then detection of nonglobal deadlock is turned on.

If a thread receives references to CVars or CTVars in the future (for instance, if one was sent over a channel), then _concKnowsAbout should be called immediately, otherwise there is a risk of identifying false positives.

_concAllKnown = return ()

Instances

MonadConc IO 
MonadConc (Conc t) 
MonadConc (ConcIO t) 
MonadConc m => MonadConc (ReaderT r m) 
MonadConc m => MonadConc (StateT s m) 
MonadConc m => MonadConc (StateT s m) 
(MonadConc m, Monoid w) => MonadConc (WriterT w m) 
(MonadConc m, Monoid w) => MonadConc (WriterT w m) 
(MonadConc m, Monoid w) => MonadConc (RWST r w s m) 
(MonadConc m, Monoid w) => MonadConc (RWST r w s m) 

Utilities

spawn :: MonadConc m => m a -> m (CVar m a) Source

Create a concurrent computation for the provided action, and return a CVar which can be used to query the result.

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.

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.