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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Conc.Class

Contents

Description

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

Deviations: An instance of MonadCoonc 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.

Synopsis

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.

Associated Types

type STM m :: * -> * Source

The associated MonadSTM for this class.

type MVar m :: * -> * Source

The mutable reference type, like MVars. 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.

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.

type Ticket m :: * -> * Source

When performing compare-and-swap operations on CRefs, a Ticket is a proof that a thread observed a specific previous value.

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 MVars.

fork ma = forkWithUnmask (\_ -> ma)

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 ""

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

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)

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 ""

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

getNumCapabilities :: m Int Source

Get the number of Haskell threads that can run simultaneously.

setNumCapabilities :: Int -> m () Source

Set the number of Haskell threads that can run simultaneously.

myThreadId :: m (ThreadId m) Source

Get the ThreadId of the current thread.

yield :: m () Source

Allows a context-switch to any other currently runnable thread (if any).

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

newEmptyMVar :: m (MVar m a) Source

Create a new empty MVar.

newEmptyMVar = newEmptyMVarN ""

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 MVars with the same name are given a numeric suffix, counting up from 1.

newEmptyMVarN _ = newEmptyMVar

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.

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.

readMVar :: MVar m a -> m a Source

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

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.

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.

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

Create a new reference.

newCRef = newCRefN ""

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 CRefs with the same name are given a numeric suffix, counting up from 1.

newCRefN _ = newCRef

readCRef :: CRef m a -> m a Source

Read the current value stored in a reference.

readCRef cref = readForCAS cref >>= peekTicket

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

Atomically modify the value stored in a reference. This imposes a full memory barrier.

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.

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

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.

peekTicket :: Ticket m a -> m a Source

Extract the actual Haskell value from a Ticket.

This shouldn't need to do any monadic computation, the m appears in the result type because of the need for injectivity in the Ticket type family, which can't be expressed currently.

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.

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.

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

atomically :: STM m a -> m a Source

Perform an STM transaction atomically.

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

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.

_concKnowsAbout :: Either (MVar m a) (TVar (STM m) a) -> m () Source

Does nothing.

This function is purely for testing purposes, and indicates that the thread has a reference to the provided MVar or TVar. This function may be called multiple times, to add new knowledge to the system. It does not need to be called when MVars or TVars 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 _ = pure ()

_concForgets :: Either (MVar m a) (TVar (STM 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 _ = pure ()

_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 MVars or TVars 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 = pure ()

_concMessage :: Typeable a => a -> m () Source

Does nothing.

During testing, records a message which shows up in the trace.

_concMessage _ = pure ()

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.

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.

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.

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.

lineNum :: Q Exp Source

Get the current line number as a String. Useful for automatically naming threads, MVars, and CRefs.

Example usage:

forkN $lineNum ...

Unfortunately this can't be packaged up into a forkLforkOnLetc set of functions, because this imposes a Lift constraint on the monad, which IO does not have.

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.

isCurrentThreadBound :: MonadConc m => m Bool Source

Provided for compatibility, always returns False.

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.

catch :: (MonadConc m, 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.

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.

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.

Mutable State

newMVar :: MonadConc m => a -> m (MVar m a) Source

Create a new MVar containing a value.

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 MVars with the same name are given a numeric suffix, counting up from 1.

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.

Utilities for instance writers

makeTransConc :: Name -> DecsQ Source

Make an instance MonadConc m => MonadConc (t m) for a given transformer, t. The parameter should be the name of a function :: forall a. StT t a -> a.

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.

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.