unliftio-0.2.24.0: The MonadUnliftIO typeclass for unlifting monads to IO (batteries included)
Safe HaskellSafe-Inferred
LanguageHaskell2010

UnliftIO.Concurrent

Description

Unlifted Control.Concurrent.

This module is not reexported by UnliftIO, use it only if UnliftIO.Async is not enough.

Since: 0.1.1.0

Synopsis

Concurrent Haskell

data ThreadId #

A ThreadId is an abstract type representing a handle to a thread. ThreadId is an instance of Eq, Ord and Show, where the Ord instance implements an arbitrary total ordering over ThreadIds. The Show instance lets you convert an arbitrary-valued ThreadId to string form; showing a ThreadId value is occasionally useful when debugging or diagnosing the behaviour of a concurrent program.

Note: in GHC, if you have a ThreadId, you essentially have a pointer to the thread itself. This means the thread itself can't be garbage collected until you drop the ThreadId. This misfeature will hopefully be corrected at a later date.

Instances

Instances details
Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

NFData ThreadId

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ThreadId -> () #

Eq ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Hashable ThreadId 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

Basic concurrency operations

myThreadId :: MonadIO m => m ThreadId Source #

Lifted version of myThreadId.

Since: 0.1.1.0

forkIO :: MonadUnliftIO m => m () -> m ThreadId Source #

Unlifted version of forkIO.

Since: 0.1.1.0

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

Deprecated: forkWithUnmask has been renamed to forkIOWithUnmask

Please use forkIOWithUnmask instead. This function has been deprecated in release 0.2.11 and will be removed in the next major release.

Since: 0.1.1.0

forkIOWithUnmask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m ()) -> m ThreadId Source #

Unlifted version of forkIOWithUnmask.

Since: 0.2.11

forkFinally :: MonadUnliftIO m => m a -> (Either SomeException a -> m ()) -> m ThreadId Source #

Unlifted version of forkFinally.

Since: 0.1.1.0

killThread :: MonadIO m => ThreadId -> m () Source #

Lifted version of killThread.

Since: 0.1.1.0

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

Throw an asynchronous exception to another thread.

Synchronously typed exceptions will be wrapped into an AsyncExceptionWrapper, see https://github.com/fpco/safe-exceptions#determining-sync-vs-async.

It's usually a better idea to use the UnliftIO.Async module, see https://github.com/fpco/safe-exceptions#quickstart.

Since: 0.1.0.0

Threads with affinity

forkOn :: MonadUnliftIO m => Int -> m () -> m ThreadId Source #

Unlifted version of forkOn.

Since: 0.1.1.0

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

Unlifted version of forkOnWithUnmask.

Since: 0.1.1.0

getNumCapabilities :: MonadIO m => m Int Source #

Lifted version of getNumCapabilities.

Since: 0.1.1.0

setNumCapabilities :: MonadIO m => Int -> m () Source #

Lifted version of setNumCapabilities.

Since: 0.1.1.0

threadCapability :: MonadIO m => ThreadId -> m (Int, Bool) Source #

Lifted version of threadCapability.

Since: 0.1.1.0

Scheduling

yield :: MonadIO m => m () Source #

Lifted version of yield.

Since: 0.1.1.0

Waiting

threadDelay :: MonadIO m => Int -> m () Source #

Lifted version of threadDelay.

Since: 0.1.1.0

threadWaitRead :: MonadIO m => Fd -> m () Source #

Lifted version of threadWaitRead.

Since: 0.1.1.0

threadWaitWrite :: MonadIO m => Fd -> m () Source #

Lifted version of threadWaitWrite.

Since: 0.1.1.0

Communication abstractions

Bound Threads

rtsSupportsBoundThreads :: Bool #

True if bound threads are supported. If rtsSupportsBoundThreads is False, isCurrentThreadBound will always return False and both forkOS and runInBoundThread will fail.

forkOS :: MonadUnliftIO m => m () -> m ThreadId Source #

Unflifted version of forkOS.

Since: 0.1.1.0

isCurrentThreadBound :: MonadIO m => m Bool Source #

Lifted version of isCurrentThreadBound.

Since: 0.1.1.0

runInBoundThread :: MonadUnliftIO m => m a -> m a Source #

Unlifted version of runInBoundThread.

Since: 0.1.1.0

runInUnboundThread :: MonadUnliftIO m => m a -> m a Source #

Unlifted version of runInUnboundThread.

Since: 0.1.1.0

Weak references to ThreadIds

mkWeakThreadId :: MonadIO m => ThreadId -> m (Weak ThreadId) Source #

Lifted version of mkWeakThreadId.

Since: 0.1.1.0