concurrency-1.11.0.0: Typeclasses, functions, and data types for concurrency and STM.

Copyright(c) 2016--2020 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityCPP, FlexibleContexts, PolyKinds, RankNTypes, ScopedTypeVariables, StandaloneDeriving, TypeFamilies
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Conc.Class

Contents

Description

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

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

Associated Types

type STM m :: * -> * Source #

The associated MonadSTM for this class.

Since: 1.0.0.0

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.

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 IORefs, a Ticket is a proof that a thread observed a specific previous value.

Since: 1.0.0.0

type ThreadId m :: * Source #

An abstract handle to a thread.

Since: 1.0.0.0

Methods

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

yield :: m () Source #

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
MonadConc IO Source #

Since: 1.0.0.0

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM IO :: Type -> Type Source #

type MVar IO :: Type -> Type Source #

type IORef IO :: Type -> Type Source #

type Ticket IO :: Type -> Type Source #

type ThreadId IO :: Type Source #

Methods

forkWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

forkWithUnmaskN :: String -> ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

forkOSWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

forkOSWithUnmaskN :: String -> ((forall a. IO a -> IO a) -> IO ()) -> IO (ThreadId IO) Source #

supportsBoundThreads :: IO Bool Source #

isCurrentThreadBound :: IO Bool Source #

getNumCapabilities :: IO Int Source #

setNumCapabilities :: Int -> IO () Source #

myThreadId :: IO (ThreadId IO) Source #

yield :: IO () Source #

threadDelay :: Int -> IO () Source #

newEmptyMVar :: IO (MVar IO a) Source #

newEmptyMVarN :: String -> IO (MVar IO a) Source #

putMVar :: MVar IO a -> a -> IO () Source #

tryPutMVar :: MVar IO a -> a -> IO Bool Source #

readMVar :: MVar IO a -> IO a Source #

tryReadMVar :: MVar IO a -> IO (Maybe a) Source #

takeMVar :: MVar IO a -> IO a Source #

tryTakeMVar :: MVar IO a -> IO (Maybe a) Source #

newIORef :: a -> IO (IORef IO a) Source #

newIORefN :: String -> a -> IO (IORef IO a) Source #

readIORef :: IORef IO a -> IO a Source #

atomicModifyIORef :: IORef IO a -> (a -> (a, b)) -> IO b Source #

writeIORef :: IORef IO a -> a -> IO () Source #

atomicWriteIORef :: IORef IO a -> a -> IO () Source #

readForCAS :: IORef IO a -> IO (Ticket IO a) Source #

peekTicket' :: Proxy IO -> Ticket IO a -> a Source #

casIORef :: IORef IO a -> Ticket IO a -> a -> IO (Bool, Ticket IO a) Source #

modifyIORefCAS :: IORef IO a -> (a -> (a, b)) -> IO b Source #

modifyIORefCAS_ :: IORef IO a -> (a -> a) -> IO () Source #

atomically :: STM IO a -> IO a Source #

newTVarConc :: a -> IO (TVar (STM IO) a) Source #

readTVarConc :: TVar (STM IO) a -> IO a Source #

throwTo :: Exception e => ThreadId IO -> e -> IO () Source #

getMaskingState :: IO MaskingState Source #

unsafeUnmask :: IO a -> IO a Source #

(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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (WriterT w m) :: Type -> Type Source #

type MVar (WriterT w m) :: Type -> Type Source #

type IORef (WriterT w m) :: Type -> Type Source #

type Ticket (WriterT w m) :: Type -> Type Source #

type ThreadId (WriterT w m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkWithUnmaskN :: String -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOnWithUnmask :: Int -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOSWithUnmask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

supportsBoundThreads :: WriterT w m Bool Source #

isCurrentThreadBound :: WriterT w m Bool Source #

getNumCapabilities :: WriterT w m Int Source #

setNumCapabilities :: Int -> WriterT w m () Source #

myThreadId :: WriterT w m (ThreadId (WriterT w m)) Source #

yield :: WriterT w m () Source #

threadDelay :: Int -> WriterT w m () Source #

newEmptyMVar :: WriterT w m (MVar (WriterT w m) a) Source #

newEmptyMVarN :: String -> WriterT w m (MVar (WriterT w m) a) Source #

putMVar :: MVar (WriterT w m) a -> a -> WriterT w m () Source #

tryPutMVar :: MVar (WriterT w m) a -> a -> WriterT w m Bool Source #

readMVar :: MVar (WriterT w m) a -> WriterT w m a Source #

tryReadMVar :: MVar (WriterT w m) a -> WriterT w m (Maybe a) Source #

takeMVar :: MVar (WriterT w m) a -> WriterT w m a Source #

tryTakeMVar :: MVar (WriterT w m) a -> WriterT w m (Maybe a) Source #

newIORef :: a -> WriterT w m (IORef (WriterT w m) a) Source #

newIORefN :: String -> a -> WriterT w m (IORef (WriterT w m) a) Source #

readIORef :: IORef (WriterT w m) a -> WriterT w m a Source #

atomicModifyIORef :: IORef (WriterT w m) a -> (a -> (a, b)) -> WriterT w m b Source #

writeIORef :: IORef (WriterT w m) a -> a -> WriterT w m () Source #

atomicWriteIORef :: IORef (WriterT w m) a -> a -> WriterT w m () Source #

readForCAS :: IORef (WriterT w m) a -> WriterT w m (Ticket (WriterT w m) a) Source #

peekTicket' :: Proxy (WriterT w m) -> Ticket (WriterT w m) a -> a Source #

casIORef :: IORef (WriterT w m) a -> Ticket (WriterT w m) a -> a -> WriterT w m (Bool, Ticket (WriterT w m) a) Source #

modifyIORefCAS :: IORef (WriterT w m) a -> (a -> (a, b)) -> WriterT w m b Source #

modifyIORefCAS_ :: IORef (WriterT w m) a -> (a -> a) -> WriterT w m () Source #

atomically :: STM (WriterT w m) a -> WriterT w m a Source #

newTVarConc :: a -> WriterT w m (TVar (STM (WriterT w m)) a) Source #

readTVarConc :: TVar (STM (WriterT w m)) a -> WriterT w m a Source #

throwTo :: Exception e => ThreadId (WriterT w m) -> e -> WriterT w m () Source #

getMaskingState :: WriterT w m MaskingState Source #

unsafeUnmask :: WriterT w m a -> WriterT w m a Source #

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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (StateT s m) :: Type -> Type Source #

type MVar (StateT s m) :: Type -> Type Source #

type IORef (StateT s m) :: Type -> Type Source #

type Ticket (StateT s m) :: Type -> Type Source #

type ThreadId (StateT s m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkWithUnmaskN :: String -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOnWithUnmask :: Int -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOSWithUnmask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

supportsBoundThreads :: StateT s m Bool Source #

isCurrentThreadBound :: StateT s m Bool Source #

getNumCapabilities :: StateT s m Int Source #

setNumCapabilities :: Int -> StateT s m () Source #

myThreadId :: StateT s m (ThreadId (StateT s m)) Source #

yield :: StateT s m () Source #

threadDelay :: Int -> StateT s m () Source #

newEmptyMVar :: StateT s m (MVar (StateT s m) a) Source #

newEmptyMVarN :: String -> StateT s m (MVar (StateT s m) a) Source #

putMVar :: MVar (StateT s m) a -> a -> StateT s m () Source #

tryPutMVar :: MVar (StateT s m) a -> a -> StateT s m Bool Source #

readMVar :: MVar (StateT s m) a -> StateT s m a Source #

tryReadMVar :: MVar (StateT s m) a -> StateT s m (Maybe a) Source #

takeMVar :: MVar (StateT s m) a -> StateT s m a Source #

tryTakeMVar :: MVar (StateT s m) a -> StateT s m (Maybe a) Source #

newIORef :: a -> StateT s m (IORef (StateT s m) a) Source #

newIORefN :: String -> a -> StateT s m (IORef (StateT s m) a) Source #

readIORef :: IORef (StateT s m) a -> StateT s m a Source #

atomicModifyIORef :: IORef (StateT s m) a -> (a -> (a, b)) -> StateT s m b Source #

writeIORef :: IORef (StateT s m) a -> a -> StateT s m () Source #

atomicWriteIORef :: IORef (StateT s m) a -> a -> StateT s m () Source #

readForCAS :: IORef (StateT s m) a -> StateT s m (Ticket (StateT s m) a) Source #

peekTicket' :: Proxy (StateT s m) -> Ticket (StateT s m) a -> a Source #

casIORef :: IORef (StateT s m) a -> Ticket (StateT s m) a -> a -> StateT s m (Bool, Ticket (StateT s m) a) Source #

modifyIORefCAS :: IORef (StateT s m) a -> (a -> (a, b)) -> StateT s m b Source #

modifyIORefCAS_ :: IORef (StateT s m) a -> (a -> a) -> StateT s m () Source #

atomically :: STM (StateT s m) a -> StateT s m a Source #

newTVarConc :: a -> StateT s m (TVar (STM (StateT s m)) a) Source #

readTVarConc :: TVar (STM (StateT s m)) a -> StateT s m a Source #

throwTo :: Exception e => ThreadId (StateT s m) -> e -> StateT s m () Source #

getMaskingState :: StateT s m MaskingState Source #

unsafeUnmask :: StateT s m a -> StateT s m a Source #

MonadConc m => MonadConc (IdentityT m) Source #

Since: 1.0.0.0

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (IdentityT m) :: Type -> Type Source #

type MVar (IdentityT m) :: Type -> Type Source #

type IORef (IdentityT m) :: Type -> Type Source #

type Ticket (IdentityT m) :: Type -> Type Source #

type ThreadId (IdentityT m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

forkWithUnmaskN :: String -> ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

forkOnWithUnmask :: Int -> ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

forkOSWithUnmask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m ()) -> IdentityT m (ThreadId (IdentityT m)) Source #

supportsBoundThreads :: IdentityT m Bool Source #

isCurrentThreadBound :: IdentityT m Bool Source #

getNumCapabilities :: IdentityT m Int Source #

setNumCapabilities :: Int -> IdentityT m () Source #

myThreadId :: IdentityT m (ThreadId (IdentityT m)) Source #

yield :: IdentityT m () Source #

threadDelay :: Int -> IdentityT m () Source #

newEmptyMVar :: IdentityT m (MVar (IdentityT m) a) Source #

newEmptyMVarN :: String -> IdentityT m (MVar (IdentityT m) a) Source #

putMVar :: MVar (IdentityT m) a -> a -> IdentityT m () Source #

tryPutMVar :: MVar (IdentityT m) a -> a -> IdentityT m Bool Source #

readMVar :: MVar (IdentityT m) a -> IdentityT m a Source #

tryReadMVar :: MVar (IdentityT m) a -> IdentityT m (Maybe a) Source #

takeMVar :: MVar (IdentityT m) a -> IdentityT m a Source #

tryTakeMVar :: MVar (IdentityT m) a -> IdentityT m (Maybe a) Source #

newIORef :: a -> IdentityT m (IORef (IdentityT m) a) Source #

newIORefN :: String -> a -> IdentityT m (IORef (IdentityT m) a) Source #

readIORef :: IORef (IdentityT m) a -> IdentityT m a Source #

atomicModifyIORef :: IORef (IdentityT m) a -> (a -> (a, b)) -> IdentityT m b Source #

writeIORef :: IORef (IdentityT m) a -> a -> IdentityT m () Source #

atomicWriteIORef :: IORef (IdentityT m) a -> a -> IdentityT m () Source #

readForCAS :: IORef (IdentityT m) a -> IdentityT m (Ticket (IdentityT m) a) Source #

peekTicket' :: Proxy (IdentityT m) -> Ticket (IdentityT m) a -> a Source #

casIORef :: IORef (IdentityT m) a -> Ticket (IdentityT m) a -> a -> IdentityT m (Bool, Ticket (IdentityT m) a) Source #

modifyIORefCAS :: IORef (IdentityT m) a -> (a -> (a, b)) -> IdentityT m b Source #

modifyIORefCAS_ :: IORef (IdentityT m) a -> (a -> a) -> IdentityT m () Source #

atomically :: STM (IdentityT m) a -> IdentityT m a Source #

newTVarConc :: a -> IdentityT m (TVar (STM (IdentityT m)) a) Source #

readTVarConc :: TVar (STM (IdentityT m)) a -> IdentityT m a Source #

throwTo :: Exception e => ThreadId (IdentityT m) -> e -> IdentityT m () Source #

getMaskingState :: IdentityT m MaskingState Source #

unsafeUnmask :: IdentityT m a -> IdentityT m a Source #

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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (StateT s m) :: Type -> Type Source #

type MVar (StateT s m) :: Type -> Type Source #

type IORef (StateT s m) :: Type -> Type Source #

type Ticket (StateT s m) :: Type -> Type Source #

type ThreadId (StateT s m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkWithUnmaskN :: String -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOnWithUnmask :: Int -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOSWithUnmask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. StateT s m a -> StateT s m a) -> StateT s m ()) -> StateT s m (ThreadId (StateT s m)) Source #

supportsBoundThreads :: StateT s m Bool Source #

isCurrentThreadBound :: StateT s m Bool Source #

getNumCapabilities :: StateT s m Int Source #

setNumCapabilities :: Int -> StateT s m () Source #

myThreadId :: StateT s m (ThreadId (StateT s m)) Source #

yield :: StateT s m () Source #

threadDelay :: Int -> StateT s m () Source #

newEmptyMVar :: StateT s m (MVar (StateT s m) a) Source #

newEmptyMVarN :: String -> StateT s m (MVar (StateT s m) a) Source #

putMVar :: MVar (StateT s m) a -> a -> StateT s m () Source #

tryPutMVar :: MVar (StateT s m) a -> a -> StateT s m Bool Source #

readMVar :: MVar (StateT s m) a -> StateT s m a Source #

tryReadMVar :: MVar (StateT s m) a -> StateT s m (Maybe a) Source #

takeMVar :: MVar (StateT s m) a -> StateT s m a Source #

tryTakeMVar :: MVar (StateT s m) a -> StateT s m (Maybe a) Source #

newIORef :: a -> StateT s m (IORef (StateT s m) a) Source #

newIORefN :: String -> a -> StateT s m (IORef (StateT s m) a) Source #

readIORef :: IORef (StateT s m) a -> StateT s m a Source #

atomicModifyIORef :: IORef (StateT s m) a -> (a -> (a, b)) -> StateT s m b Source #

writeIORef :: IORef (StateT s m) a -> a -> StateT s m () Source #

atomicWriteIORef :: IORef (StateT s m) a -> a -> StateT s m () Source #

readForCAS :: IORef (StateT s m) a -> StateT s m (Ticket (StateT s m) a) Source #

peekTicket' :: Proxy (StateT s m) -> Ticket (StateT s m) a -> a Source #

casIORef :: IORef (StateT s m) a -> Ticket (StateT s m) a -> a -> StateT s m (Bool, Ticket (StateT s m) a) Source #

modifyIORefCAS :: IORef (StateT s m) a -> (a -> (a, b)) -> StateT s m b Source #

modifyIORefCAS_ :: IORef (StateT s m) a -> (a -> a) -> StateT s m () Source #

atomically :: STM (StateT s m) a -> StateT s m a Source #

newTVarConc :: a -> StateT s m (TVar (STM (StateT s m)) a) Source #

readTVarConc :: TVar (STM (StateT s m)) a -> StateT s m a Source #

throwTo :: Exception e => ThreadId (StateT s m) -> e -> StateT s m () Source #

getMaskingState :: StateT s m MaskingState Source #

unsafeUnmask :: StateT s m a -> StateT s m a Source #

(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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (WriterT w m) :: Type -> Type Source #

type MVar (WriterT w m) :: Type -> Type Source #

type IORef (WriterT w m) :: Type -> Type Source #

type Ticket (WriterT w m) :: Type -> Type Source #

type ThreadId (WriterT w m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkWithUnmaskN :: String -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOnWithUnmask :: Int -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOSWithUnmask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m ()) -> WriterT w m (ThreadId (WriterT w m)) Source #

supportsBoundThreads :: WriterT w m Bool Source #

isCurrentThreadBound :: WriterT w m Bool Source #

getNumCapabilities :: WriterT w m Int Source #

setNumCapabilities :: Int -> WriterT w m () Source #

myThreadId :: WriterT w m (ThreadId (WriterT w m)) Source #

yield :: WriterT w m () Source #

threadDelay :: Int -> WriterT w m () Source #

newEmptyMVar :: WriterT w m (MVar (WriterT w m) a) Source #

newEmptyMVarN :: String -> WriterT w m (MVar (WriterT w m) a) Source #

putMVar :: MVar (WriterT w m) a -> a -> WriterT w m () Source #

tryPutMVar :: MVar (WriterT w m) a -> a -> WriterT w m Bool Source #

readMVar :: MVar (WriterT w m) a -> WriterT w m a Source #

tryReadMVar :: MVar (WriterT w m) a -> WriterT w m (Maybe a) Source #

takeMVar :: MVar (WriterT w m) a -> WriterT w m a Source #

tryTakeMVar :: MVar (WriterT w m) a -> WriterT w m (Maybe a) Source #

newIORef :: a -> WriterT w m (IORef (WriterT w m) a) Source #

newIORefN :: String -> a -> WriterT w m (IORef (WriterT w m) a) Source #

readIORef :: IORef (WriterT w m) a -> WriterT w m a Source #

atomicModifyIORef :: IORef (WriterT w m) a -> (a -> (a, b)) -> WriterT w m b Source #

writeIORef :: IORef (WriterT w m) a -> a -> WriterT w m () Source #

atomicWriteIORef :: IORef (WriterT w m) a -> a -> WriterT w m () Source #

readForCAS :: IORef (WriterT w m) a -> WriterT w m (Ticket (WriterT w m) a) Source #

peekTicket' :: Proxy (WriterT w m) -> Ticket (WriterT w m) a -> a Source #

casIORef :: IORef (WriterT w m) a -> Ticket (WriterT w m) a -> a -> WriterT w m (Bool, Ticket (WriterT w m) a) Source #

modifyIORefCAS :: IORef (WriterT w m) a -> (a -> (a, b)) -> WriterT w m b Source #

modifyIORefCAS_ :: IORef (WriterT w m) a -> (a -> a) -> WriterT w m () Source #

atomically :: STM (WriterT w m) a -> WriterT w m a Source #

newTVarConc :: a -> WriterT w m (TVar (STM (WriterT w m)) a) Source #

readTVarConc :: TVar (STM (WriterT w m)) a -> WriterT w m a Source #

throwTo :: Exception e => ThreadId (WriterT w m) -> e -> WriterT w m () Source #

getMaskingState :: WriterT w m MaskingState Source #

unsafeUnmask :: WriterT w m a -> WriterT w m a Source #

MonadConc m => MonadConc (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (IsConc m) :: Type -> Type Source #

type MVar (IsConc m) :: Type -> Type Source #

type IORef (IsConc m) :: Type -> Type Source #

type Ticket (IsConc m) :: Type -> Type Source #

type ThreadId (IsConc m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkWithUnmaskN :: String -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOnWithUnmask :: Int -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOSWithUnmask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

supportsBoundThreads :: IsConc m Bool Source #

isCurrentThreadBound :: IsConc m Bool Source #

getNumCapabilities :: IsConc m Int Source #

setNumCapabilities :: Int -> IsConc m () Source #

myThreadId :: IsConc m (ThreadId (IsConc m)) Source #

yield :: IsConc m () Source #

threadDelay :: Int -> IsConc m () Source #

newEmptyMVar :: IsConc m (MVar (IsConc m) a) Source #

newEmptyMVarN :: String -> IsConc m (MVar (IsConc m) a) Source #

putMVar :: MVar (IsConc m) a -> a -> IsConc m () Source #

tryPutMVar :: MVar (IsConc m) a -> a -> IsConc m Bool Source #

readMVar :: MVar (IsConc m) a -> IsConc m a Source #

tryReadMVar :: MVar (IsConc m) a -> IsConc m (Maybe a) Source #

takeMVar :: MVar (IsConc m) a -> IsConc m a Source #

tryTakeMVar :: MVar (IsConc m) a -> IsConc m (Maybe a) Source #

newIORef :: a -> IsConc m (IORef (IsConc m) a) Source #

newIORefN :: String -> a -> IsConc m (IORef (IsConc m) a) Source #

readIORef :: IORef (IsConc m) a -> IsConc m a Source #

atomicModifyIORef :: IORef (IsConc m) a -> (a -> (a, b)) -> IsConc m b Source #

writeIORef :: IORef (IsConc m) a -> a -> IsConc m () Source #

atomicWriteIORef :: IORef (IsConc m) a -> a -> IsConc m () Source #

readForCAS :: IORef (IsConc m) a -> IsConc m (Ticket (IsConc m) a) Source #

peekTicket' :: Proxy (IsConc m) -> Ticket (IsConc m) a -> a Source #

casIORef :: IORef (IsConc m) a -> Ticket (IsConc m) a -> a -> IsConc m (Bool, Ticket (IsConc m) a) Source #

modifyIORefCAS :: IORef (IsConc m) a -> (a -> (a, b)) -> IsConc m b Source #

modifyIORefCAS_ :: IORef (IsConc m) a -> (a -> a) -> IsConc m () Source #

atomically :: STM (IsConc m) a -> IsConc m a Source #

newTVarConc :: a -> IsConc m (TVar (STM (IsConc m)) a) Source #

readTVarConc :: TVar (STM (IsConc m)) a -> IsConc m a Source #

throwTo :: Exception e => ThreadId (IsConc m) -> e -> IsConc m () Source #

getMaskingState :: IsConc m MaskingState Source #

unsafeUnmask :: IsConc m a -> IsConc m a Source #

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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (ReaderT r m) :: Type -> Type Source #

type MVar (ReaderT r m) :: Type -> Type Source #

type IORef (ReaderT r m) :: Type -> Type Source #

type Ticket (ReaderT r m) :: Type -> Type Source #

type ThreadId (ReaderT r m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

forkWithUnmaskN :: String -> ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

forkOnWithUnmask :: Int -> ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

forkOSWithUnmask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m ()) -> ReaderT r m (ThreadId (ReaderT r m)) Source #

supportsBoundThreads :: ReaderT r m Bool Source #

isCurrentThreadBound :: ReaderT r m Bool Source #

getNumCapabilities :: ReaderT r m Int Source #

setNumCapabilities :: Int -> ReaderT r m () Source #

myThreadId :: ReaderT r m (ThreadId (ReaderT r m)) Source #

yield :: ReaderT r m () Source #

threadDelay :: Int -> ReaderT r m () Source #

newEmptyMVar :: ReaderT r m (MVar (ReaderT r m) a) Source #

newEmptyMVarN :: String -> ReaderT r m (MVar (ReaderT r m) a) Source #

putMVar :: MVar (ReaderT r m) a -> a -> ReaderT r m () Source #

tryPutMVar :: MVar (ReaderT r m) a -> a -> ReaderT r m Bool Source #

readMVar :: MVar (ReaderT r m) a -> ReaderT r m a Source #

tryReadMVar :: MVar (ReaderT r m) a -> ReaderT r m (Maybe a) Source #

takeMVar :: MVar (ReaderT r m) a -> ReaderT r m a Source #

tryTakeMVar :: MVar (ReaderT r m) a -> ReaderT r m (Maybe a) Source #

newIORef :: a -> ReaderT r m (IORef (ReaderT r m) a) Source #

newIORefN :: String -> a -> ReaderT r m (IORef (ReaderT r m) a) Source #

readIORef :: IORef (ReaderT r m) a -> ReaderT r m a Source #

atomicModifyIORef :: IORef (ReaderT r m) a -> (a -> (a, b)) -> ReaderT r m b Source #

writeIORef :: IORef (ReaderT r m) a -> a -> ReaderT r m () Source #

atomicWriteIORef :: IORef (ReaderT r m) a -> a -> ReaderT r m () Source #

readForCAS :: IORef (ReaderT r m) a -> ReaderT r m (Ticket (ReaderT r m) a) Source #

peekTicket' :: Proxy (ReaderT r m) -> Ticket (ReaderT r m) a -> a Source #

casIORef :: IORef (ReaderT r m) a -> Ticket (ReaderT r m) a -> a -> ReaderT r m (Bool, Ticket (ReaderT r m) a) Source #

modifyIORefCAS :: IORef (ReaderT r m) a -> (a -> (a, b)) -> ReaderT r m b Source #

modifyIORefCAS_ :: IORef (ReaderT r m) a -> (a -> a) -> ReaderT r m () Source #

atomically :: STM (ReaderT r m) a -> ReaderT r m a Source #

newTVarConc :: a -> ReaderT r m (TVar (STM (ReaderT r m)) a) Source #

readTVarConc :: TVar (STM (ReaderT r m)) a -> ReaderT r m a Source #

throwTo :: Exception e => ThreadId (ReaderT r m) -> e -> ReaderT r m () Source #

getMaskingState :: ReaderT r m MaskingState Source #

unsafeUnmask :: ReaderT r m a -> ReaderT r m a Source #

(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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (RWST r w s m) :: Type -> Type Source #

type MVar (RWST r w s m) :: Type -> Type Source #

type IORef (RWST r w s m) :: Type -> Type Source #

type Ticket (RWST r w s m) :: Type -> Type Source #

type ThreadId (RWST r w s m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkWithUnmaskN :: String -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOnWithUnmask :: Int -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOSWithUnmask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

supportsBoundThreads :: RWST r w s m Bool Source #

isCurrentThreadBound :: RWST r w s m Bool Source #

getNumCapabilities :: RWST r w s m Int Source #

setNumCapabilities :: Int -> RWST r w s m () Source #

myThreadId :: RWST r w s m (ThreadId (RWST r w s m)) Source #

yield :: RWST r w s m () Source #

threadDelay :: Int -> RWST r w s m () Source #

newEmptyMVar :: RWST r w s m (MVar (RWST r w s m) a) Source #

newEmptyMVarN :: String -> RWST r w s m (MVar (RWST r w s m) a) Source #

putMVar :: MVar (RWST r w s m) a -> a -> RWST r w s m () Source #

tryPutMVar :: MVar (RWST r w s m) a -> a -> RWST r w s m Bool Source #

readMVar :: MVar (RWST r w s m) a -> RWST r w s m a Source #

tryReadMVar :: MVar (RWST r w s m) a -> RWST r w s m (Maybe a) Source #

takeMVar :: MVar (RWST r w s m) a -> RWST r w s m a Source #

tryTakeMVar :: MVar (RWST r w s m) a -> RWST r w s m (Maybe a) Source #

newIORef :: a -> RWST r w s m (IORef (RWST r w s m) a) Source #

newIORefN :: String -> a -> RWST r w s m (IORef (RWST r w s m) a) Source #

readIORef :: IORef (RWST r w s m) a -> RWST r w s m a Source #

atomicModifyIORef :: IORef (RWST r w s m) a -> (a -> (a, b)) -> RWST r w s m b Source #

writeIORef :: IORef (RWST r w s m) a -> a -> RWST r w s m () Source #

atomicWriteIORef :: IORef (RWST r w s m) a -> a -> RWST r w s m () Source #

readForCAS :: IORef (RWST r w s m) a -> RWST r w s m (Ticket (RWST r w s m) a) Source #

peekTicket' :: Proxy (RWST r w s m) -> Ticket (RWST r w s m) a -> a Source #

casIORef :: IORef (RWST r w s m) a -> Ticket (RWST r w s m) a -> a -> RWST r w s m (Bool, Ticket (RWST r w s m) a) Source #

modifyIORefCAS :: IORef (RWST r w s m) a -> (a -> (a, b)) -> RWST r w s m b Source #

modifyIORefCAS_ :: IORef (RWST r w s m) a -> (a -> a) -> RWST r w s m () Source #

atomically :: STM (RWST r w s m) a -> RWST r w s m a Source #

newTVarConc :: a -> RWST r w s m (TVar (STM (RWST r w s m)) a) Source #

readTVarConc :: TVar (STM (RWST r w s m)) a -> RWST r w s m a Source #

throwTo :: Exception e => ThreadId (RWST r w s m) -> e -> RWST r w s m () Source #

getMaskingState :: RWST r w s m MaskingState Source #

unsafeUnmask :: RWST r w s m a -> RWST r w s m a Source #

(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

Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (RWST r w s m) :: Type -> Type Source #

type MVar (RWST r w s m) :: Type -> Type Source #

type IORef (RWST r w s m) :: Type -> Type Source #

type Ticket (RWST r w s m) :: Type -> Type Source #

type ThreadId (RWST r w s m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkWithUnmaskN :: String -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOnWithUnmask :: Int -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOSWithUnmask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m ()) -> RWST r w s m (ThreadId (RWST r w s m)) Source #

supportsBoundThreads :: RWST r w s m Bool Source #

isCurrentThreadBound :: RWST r w s m Bool Source #

getNumCapabilities :: RWST r w s m Int Source #

setNumCapabilities :: Int -> RWST r w s m () Source #

myThreadId :: RWST r w s m (ThreadId (RWST r w s m)) Source #

yield :: RWST r w s m () Source #

threadDelay :: Int -> RWST r w s m () Source #

newEmptyMVar :: RWST r w s m (MVar (RWST r w s m) a) Source #

newEmptyMVarN :: String -> RWST r w s m (MVar (RWST r w s m) a) Source #

putMVar :: MVar (RWST r w s m) a -> a -> RWST r w s m () Source #

tryPutMVar :: MVar (RWST r w s m) a -> a -> RWST r w s m Bool Source #

readMVar :: MVar (RWST r w s m) a -> RWST r w s m a Source #

tryReadMVar :: MVar (RWST r w s m) a -> RWST r w s m (Maybe a) Source #

takeMVar :: MVar (RWST r w s m) a -> RWST r w s m a Source #

tryTakeMVar :: MVar (RWST r w s m) a -> RWST r w s m (Maybe a) Source #

newIORef :: a -> RWST r w s m (IORef (RWST r w s m) a) Source #

newIORefN :: String -> a -> RWST r w s m (IORef (RWST r w s m) a) Source #

readIORef :: IORef (RWST r w s m) a -> RWST r w s m a Source #

atomicModifyIORef :: IORef (RWST r w s m) a -> (a -> (a, b)) -> RWST r w s m b Source #

writeIORef :: IORef (RWST r w s m) a -> a -> RWST r w s m () Source #

atomicWriteIORef :: IORef (RWST r w s m) a -> a -> RWST r w s m () Source #

readForCAS :: IORef (RWST r w s m) a -> RWST r w s m (Ticket (RWST r w s m) a) Source #

peekTicket' :: Proxy (RWST r w s m) -> Ticket (RWST r w s m) a -> a Source #

casIORef :: IORef (RWST r w s m) a -> Ticket (RWST r w s m) a -> a -> RWST r w s m (Bool, Ticket (RWST r w s m) a) Source #

modifyIORefCAS :: IORef (RWST r w s m) a -> (a -> (a, b)) -> RWST r w s m b Source #

modifyIORefCAS_ :: IORef (RWST r w s m) a -> (a -> a) -> RWST r w s m () Source #

atomically :: STM (RWST r w s m) a -> RWST r w s m a Source #

newTVarConc :: a -> RWST r w s m (TVar (STM (RWST r w s m)) a) Source #

readTVarConc :: TVar (STM (RWST r w s m)) a -> RWST r w s m a Source #

throwTo :: Exception e => ThreadId (RWST r w s m) -> e -> RWST r w s m () Source #

getMaskingState :: RWST r w s m MaskingState Source #

unsafeUnmask :: RWST r w s m a -> RWST r w s m a Source #

Threads

fork :: MonadConc m => m () -> m (ThreadId m) Source #

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

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

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.

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

mask_ :: MonadMask m => m a -> m a #

Like mask, but does not pass a restore action to the argument.

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

data IsConc m a Source #

A value of type IsConc m a can only be constructed if m has a MonadConc instance.

Since: 1.2.2.0

Instances
Monad m => Monad (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

(>>=) :: IsConc m a -> (a -> IsConc m b) -> IsConc m b #

(>>) :: IsConc m a -> IsConc m b -> IsConc m b #

return :: a -> IsConc m a #

fail :: String -> IsConc m a #

Functor m => Functor (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

fmap :: (a -> b) -> IsConc m a -> IsConc m b #

(<$) :: a -> IsConc m b -> IsConc m a #

MonadFail m => MonadFail (IsConc m) Source #

Since: 1.8.0.0

Instance details

Defined in Control.Monad.Conc.Class

Methods

fail :: String -> IsConc m a #

Applicative m => Applicative (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

pure :: a -> IsConc m a #

(<*>) :: IsConc m (a -> b) -> IsConc m a -> IsConc m b #

liftA2 :: (a -> b -> c) -> IsConc m a -> IsConc m b -> IsConc m c #

(*>) :: IsConc m a -> IsConc m b -> IsConc m b #

(<*) :: IsConc m a -> IsConc m b -> IsConc m a #

MonadThrow m => MonadThrow (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

throwM :: Exception e => e -> IsConc m a #

MonadCatch m => MonadCatch (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

catch :: Exception e => IsConc m a -> (e -> IsConc m a) -> IsConc m a #

MonadMask m => MonadMask (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Methods

mask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m b) -> IsConc m b #

uninterruptibleMask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m b) -> IsConc m b #

generalBracket :: IsConc m a -> (a -> ExitCase b -> IsConc m c) -> (a -> IsConc m b) -> IsConc m (b, c) #

MonadConc m => MonadConc (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

Associated Types

type STM (IsConc m) :: Type -> Type Source #

type MVar (IsConc m) :: Type -> Type Source #

type IORef (IsConc m) :: Type -> Type Source #

type Ticket (IsConc m) :: Type -> Type Source #

type ThreadId (IsConc m) :: Type Source #

Methods

forkWithUnmask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkWithUnmaskN :: String -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOnWithUnmask :: Int -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOnWithUnmaskN :: String -> Int -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOSWithUnmask :: ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

forkOSWithUnmaskN :: String -> ((forall a. IsConc m a -> IsConc m a) -> IsConc m ()) -> IsConc m (ThreadId (IsConc m)) Source #

supportsBoundThreads :: IsConc m Bool Source #

isCurrentThreadBound :: IsConc m Bool Source #

getNumCapabilities :: IsConc m Int Source #

setNumCapabilities :: Int -> IsConc m () Source #

myThreadId :: IsConc m (ThreadId (IsConc m)) Source #

yield :: IsConc m () Source #

threadDelay :: Int -> IsConc m () Source #

newEmptyMVar :: IsConc m (MVar (IsConc m) a) Source #

newEmptyMVarN :: String -> IsConc m (MVar (IsConc m) a) Source #

putMVar :: MVar (IsConc m) a -> a -> IsConc m () Source #

tryPutMVar :: MVar (IsConc m) a -> a -> IsConc m Bool Source #

readMVar :: MVar (IsConc m) a -> IsConc m a Source #

tryReadMVar :: MVar (IsConc m) a -> IsConc m (Maybe a) Source #

takeMVar :: MVar (IsConc m) a -> IsConc m a Source #

tryTakeMVar :: MVar (IsConc m) a -> IsConc m (Maybe a) Source #

newIORef :: a -> IsConc m (IORef (IsConc m) a) Source #

newIORefN :: String -> a -> IsConc m (IORef (IsConc m) a) Source #

readIORef :: IORef (IsConc m) a -> IsConc m a Source #

atomicModifyIORef :: IORef (IsConc m) a -> (a -> (a, b)) -> IsConc m b Source #

writeIORef :: IORef (IsConc m) a -> a -> IsConc m () Source #

atomicWriteIORef :: IORef (IsConc m) a -> a -> IsConc m () Source #

readForCAS :: IORef (IsConc m) a -> IsConc m (Ticket (IsConc m) a) Source #

peekTicket' :: Proxy (IsConc m) -> Ticket (IsConc m) a -> a Source #

casIORef :: IORef (IsConc m) a -> Ticket (IsConc m) a -> a -> IsConc m (Bool, Ticket (IsConc m) a) Source #

modifyIORefCAS :: IORef (IsConc m) a -> (a -> (a, b)) -> IsConc m b Source #

modifyIORefCAS_ :: IORef (IsConc m) a -> (a -> a) -> IsConc m () Source #

atomically :: STM (IsConc m) a -> IsConc m a Source #

newTVarConc :: a -> IsConc m (TVar (STM (IsConc m)) a) Source #

readTVarConc :: TVar (STM (IsConc m)) a -> IsConc m a Source #

throwTo :: Exception e => ThreadId (IsConc m) -> e -> IsConc m () Source #

getMaskingState :: IsConc m MaskingState Source #

unsafeUnmask :: IsConc m a -> IsConc m a Source #

type STM (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

type STM (IsConc m) = IsSTM (STM m)
type MVar (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

type MVar (IsConc m) = MVar m
type IORef (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

type IORef (IsConc m) = IORef m
type Ticket (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

type Ticket (IsConc m) = Ticket m
type ThreadId (IsConc m) Source # 
Instance details

Defined in Control.Monad.Conc.Class

type ThreadId (IsConc m) = ThreadId m

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