| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ki.Implicit
Synopsis
- type Context = ?context :: Context
- withGlobalContext :: (Context => IO a) -> IO a
- data Scope
- scoped :: Context => (Context => Scope -> IO a) -> IO a
- wait :: Scope -> IO ()
- waitSTM :: Scope -> STM ()
- waitFor :: Scope -> Duration -> IO ()
- data Thread a
- fork :: Scope -> (Context => IO a) -> IO (Thread a)
- fork_ :: Scope -> (Context => IO ()) -> IO ()
- forkWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread a)
- forkWithUnmask_ :: Scope -> (Context => (forall x. IO x -> IO x) -> IO ()) -> IO ()
- async :: Scope -> (Context => IO a) -> IO (Thread (Either ThreadFailed a))
- asyncWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either ThreadFailed a))
- await :: Thread a -> IO a
- awaitSTM :: Thread a -> STM a
- awaitFor :: Thread a -> Duration -> IO (Maybe a)
- cancelScope :: Scope -> IO ()
- cancelled :: Context => IO (Maybe CancelToken)
- cancelledSTM :: Context => STM CancelToken
- data CancelToken
- data Duration
- microseconds :: Duration
- milliseconds :: Duration
- seconds :: Duration
- timeoutSTM :: Duration -> STM (IO a) -> IO a -> IO a
- sleep :: Context => Duration -> IO ()
- data ThreadFailed = ThreadFailed {}
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
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
scopeditself, if any. ThreadFailedcontaining the first exception a thread created withforkthrows, if any.
Examples
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.
A running thread.
Instances
| Functor Thread Source # | |
| Eq (Thread a) Source # | |
| Ord (Thread a) Source # | |
Defined in Ki.Thread | |
| Generic (Thread a) Source # | |
| type Rep (Thread a) Source # | |
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
errorif 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
errorif 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
errorif the scope is closed.
asyncWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either ThreadFailed a)) Source #
Await
await :: Thread a -> IO a Source #
Wait for a thread to finish.
Throws:
ThreadFailedif the thread threw an exception and was created withfork.
awaitSTM :: Thread a -> STM a Source #
STM variant of await.
Throws:
ThreadFailedif the thread threw an exception and was created withfork.
awaitFor :: Thread a -> Duration -> IO (Maybe a) Source #
Variant of await that waits for up to the given duration.
Throws:
ThreadFailedif the thread threw an exception and was created withfork.
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.
Instances
| Eq CancelToken Source # | |
Defined in Ki.CancelToken | |
| Show CancelToken Source # | |
Defined in Ki.CancelToken Methods showsPrec :: Int -> CancelToken -> ShowS # show :: CancelToken -> String # showList :: [CancelToken] -> ShowS # | |
| Exception CancelToken Source # | |
Defined in Ki.CancelToken Methods toException :: CancelToken -> SomeException # fromException :: SomeException -> Maybe CancelToken # displayException :: CancelToken -> String # | |
Miscellaneous
A length of time with microsecond precision. Numeric literals are treated as seconds.
Instances
| Enum Duration Source # | |
| Eq Duration Source # | |
| Fractional Duration Source # | |
| Data Duration Source # | |
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 # | |
| Ord Duration Source # | |
Defined in Ki.Duration | |
| Read Duration Source # | |
| Real Duration Source # | |
Defined in Ki.Duration Methods toRational :: Duration -> Rational # | |
| RealFrac Duration Source # | |
| Show Duration Source # | |
| Generic Duration Source # | |
| type Rep Duration Source # | |
microseconds :: Duration Source #
One microsecond.
milliseconds :: Duration Source #
One millisecond.
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
CancelTokenif the current context is cancelled.
Exceptions
data ThreadFailed Source #
A thread failed, either by throwing or being thrown an exception.
Constructors
| ThreadFailed | |
Fields | |
Instances
| Show ThreadFailed Source # | |
Defined in Ki.ThreadFailed Methods showsPrec :: Int -> ThreadFailed -> ShowS # show :: ThreadFailed -> String # showList :: [ThreadFailed] -> ShowS # | |
| Exception ThreadFailed Source # | |
Defined in Ki.ThreadFailed Methods toException :: ThreadFailed -> SomeException # fromException :: SomeException -> Maybe ThreadFailed # displayException :: ThreadFailed -> String # | |