ki-0: A lightweight, structured concurrency library
Safe HaskellNone
LanguageHaskell2010

Ki.Implicit

Synopsis

Context

type Context = ?context :: Context Source #

A context models a program's call tree, and is used as a mechanism to propagate cancellation requests to every thread created within a scope.

Every thread is provided its own context, which is derived from its scope.

A thread can query whether its context has been cancelled, which is a suggestion to perform a graceful termination.

withGlobalContext :: (Context => IO a) -> IO a Source #

Perform an IO action in the global context. The global context cannot be cancelled.

Scope

data Scope Source #

A scope delimits the lifetime of all threads created within it.

scoped :: Context => (Context => Scope -> IO a) -> IO a Source #

Open a scope, perform an IO action with it, then close the scope.

When the scope is closed, all remaining threads created within it are killed.

Throws:

  • The exception thrown by the callback to scoped itself, if any.
  • ThreadFailed containing the first exception a thread created with fork throws, if any.

Examples

Expand
scoped \scope -> do
  fork_ scope worker1
  fork_ scope worker2
  wait scope

wait :: Scope -> IO () Source #

Wait until all threads created within a scope finish.

waitSTM :: Scope -> STM () Source #

STM variant of wait.

waitFor :: Scope -> Duration -> IO () Source #

Variant of wait that waits for up to the given duration. This is useful for giving threads some time to fulfill a cancellation request before killing them.

Spawning threads

There are two variants of thread-creating functions with different exception-propagation semantics.

  • If a thread created with fork throws an exception, it is immediately propagated up the call tree to the thread that created its scope.
  • If a thread created with async throws an exception, it is not propagated up the call tree, but can be observed by await.

data Thread a Source #

A running thread.

Instances

Instances details
Functor Thread Source # 
Instance details

Defined in Ki.Thread

Methods

fmap :: (a -> b) -> Thread a -> Thread b #

(<$) :: a -> Thread b -> Thread a #

Eq (Thread a) Source # 
Instance details

Defined in Ki.Thread

Methods

(==) :: Thread a -> Thread a -> Bool #

(/=) :: Thread a -> Thread a -> Bool #

Ord (Thread a) Source # 
Instance details

Defined in Ki.Thread

Methods

compare :: Thread a -> Thread a -> Ordering #

(<) :: Thread a -> Thread a -> Bool #

(<=) :: Thread a -> Thread a -> Bool #

(>) :: Thread a -> Thread a -> Bool #

(>=) :: Thread a -> Thread a -> Bool #

max :: Thread a -> Thread a -> Thread a #

min :: Thread a -> Thread a -> Thread a #

Generic (Thread a) Source # 
Instance details

Defined in Ki.Thread

Associated Types

type Rep (Thread a) :: Type -> Type #

Methods

from :: Thread a -> Rep (Thread a) x #

to :: Rep (Thread a) x -> Thread a #

type Rep (Thread a) Source # 
Instance details

Defined in Ki.Thread

type Rep (Thread a) = D1 ('MetaData "Thread" "Ki.Thread" "ki-0-inplace" 'False) (C1 ('MetaCons "Thread" 'PrefixI 'True) (S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ThreadId) :*: S1 ('MetaSel ('Just "action") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (STM a))))

Fork

fork :: Scope -> (Context => IO a) -> IO (Thread a) Source #

Create a thread within a scope to compute a value concurrently.

If the thread throws an exception, the exception is wrapped in ThreadFailed and immediately propagated up the call tree to the thread that opened its scope, unless that exception is a CancelToken that fulfills a cancellation request.

Throws:

  • Calls error if the scope is closed.

fork_ :: Scope -> (Context => IO ()) -> IO () Source #

Variant of fork that does not return a handle to the created thread.

Throws:

  • Calls error if the scope is closed.

forkWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread a) Source #

Variant of fork that provides the thread a function that unmasks asynchronous exceptions.

Throws:

  • Calls error if the scope is closed.

forkWithUnmask_ :: Scope -> (Context => (forall x. IO x -> IO x) -> IO ()) -> IO () Source #

Variant of forkWithUnmask that does not return a handle to the created thread.

Throws:

  • Calls error if the scope is closed.

Async

async :: Scope -> (Context => IO a) -> IO (Thread (Either ThreadFailed a)) Source #

Create a thread within a scope to compute a value concurrently.

Throws:

  • Calls error if the scope is closed.

asyncWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either ThreadFailed a)) Source #

Variant of async that provides the thread a function that unmasks asynchronous exceptions.

Throws:

  • Calls error if the scope is closed.

Await

await :: Thread a -> IO a Source #

Wait for a thread to finish.

Throws:

awaitSTM :: Thread a -> STM a Source #

STM variant of await.

Throws:

awaitFor :: Thread a -> Duration -> IO (Maybe a) Source #

Variant of await that waits for up to the given duration.

Throws:

Soft-cancellation

cancelScope :: Scope -> IO () Source #

Cancel all contexts derived from a scope.

cancelled :: Context => IO (Maybe CancelToken) Source #

Return whether the current context is cancelled.

Threads running in a cancelled context should terminate as soon as possible. The cancel token may be thrown to fulfill the cancellation request in case the thread is unable or unwilling to terminate normally with a value.

cancelledSTM :: Context => STM CancelToken Source #

STM variant of cancelled; blocks until the current context is cancelled.

data CancelToken Source #

A cancel token represents a request for cancellation; this request can be fulfilled by throwing the token as an exception.

Miscellaneous

data Duration Source #

A length of time with microsecond precision. Numeric literals are treated as seconds.

Instances

Instances details
Enum Duration Source # 
Instance details

Defined in Ki.Duration

Eq Duration Source # 
Instance details

Defined in Ki.Duration

Fractional Duration Source # 
Instance details

Defined in Ki.Duration

Data Duration Source # 
Instance details

Defined in Ki.Duration

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Duration -> c Duration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Duration #

toConstr :: Duration -> Constr #

dataTypeOf :: Duration -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Duration) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration) #

gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r #

gmapQ :: (forall d. Data d => d -> u) -> Duration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Duration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

Num Duration Source # 
Instance details

Defined in Ki.Duration

Ord Duration Source # 
Instance details

Defined in Ki.Duration

Read Duration Source # 
Instance details

Defined in Ki.Duration

Real Duration Source # 
Instance details

Defined in Ki.Duration

RealFrac Duration Source # 
Instance details

Defined in Ki.Duration

Methods

properFraction :: Integral b => Duration -> (b, Duration) #

truncate :: Integral b => Duration -> b #

round :: Integral b => Duration -> b #

ceiling :: Integral b => Duration -> b #

floor :: Integral b => Duration -> b #

Show Duration Source # 
Instance details

Defined in Ki.Duration

Generic Duration Source # 
Instance details

Defined in Ki.Duration

Associated Types

type Rep Duration :: Type -> Type #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

type Rep Duration Source # 
Instance details

Defined in Ki.Duration

type Rep Duration = D1 ('MetaData "Duration" "Ki.Duration" "ki-0-inplace" 'True) (C1 ('MetaCons "Duration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Fixed E6))))

microseconds :: Duration Source #

One microsecond.

milliseconds :: Duration Source #

One millisecond.

seconds :: Duration Source #

One second.

timeoutSTM :: Duration -> STM (IO a) -> IO a -> IO a Source #

Wait for an STM action to return an IO action, or if the given duration elapses, return the given IO action instead.

sleep :: Context => Duration -> IO () Source #

Context-aware, duration-based threadDelay.

Throws:

  • Throws CancelToken if the current context is cancelled.

Exceptions

data ThreadFailed Source #

A thread failed, either by throwing or being thrown an exception.