Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 SomeException a))
- asyncWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either SomeException a))
- await :: Thread a -> IO a
- awaitSTM :: Thread a -> STM a
- awaitFor :: Thread a -> Duration -> IO (Maybe a)
- data CancelToken
- cancel :: Scope -> IO ()
- cancelled :: Context => IO (Maybe CancelToken)
- cancelledSTM :: Context => STM CancelToken
- data Duration
- microseconds :: Duration
- milliseconds :: Duration
- seconds :: Duration
- timeoutSTM :: Duration -> STM (IO a) -> IO a -> IO a
- sleep :: Context => Duration -> IO ()
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 #
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 # | |
Generic (Thread a) Source # | |
type Rep (Thread a) Source # | |
Defined in Ki.Thread type Rep (Thread a) = D1 ('MetaData "Thread" "Ki.Thread" "ki-0.2.0-inplace" 'False) (C1 ('MetaCons "Thread" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ThreadId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (STM a)))) |
Fork
fork :: Scope -> (Context => IO a) -> IO (Thread a) Source #
Create a thread within a scope.
If the thread throws an exception, the exception is 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.
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
asyncWithUnmask :: Scope -> (Context => (forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either SomeException a)) Source #
Await
awaitFor :: Thread a -> Duration -> IO (Maybe a) Source #
Variant of await
that gives up after the given duration.
Soft-cancellation
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 (==) :: CancelToken -> CancelToken -> Bool # (/=) :: CancelToken -> CancelToken -> Bool # | |
Show CancelToken Source # | |
Defined in Ki.CancelToken showsPrec :: Int -> CancelToken -> ShowS # show :: CancelToken -> String # showList :: [CancelToken] -> ShowS # | |
Exception CancelToken Source # | |
Defined in Ki.CancelToken |
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.
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 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 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.