Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype CancelToken = CancelToken Int
- newCancelToken :: IO CancelToken
- data Context = Context {}
- dummyContext :: Context
- globalContext :: Context
- data Ctx = Ctx {
- cancelTokenVar :: TVar (Maybe CancelToken)
- childrenVar :: TVar (IntMap Ctx)
- nextIdVar :: TVar Int
- onCancel :: STM ()
- newCtxSTM :: STM Ctx
- deriveCtx :: Ctx -> STM Ctx
- cancelCtx :: Ctx -> IO ()
- cancelCtxSTM :: Ctx -> CancelToken -> STM ()
- ctxCancelToken :: Ctx -> STM CancelToken
- newtype Duration = Duration (Fixed E6)
- toMicroseconds :: Duration -> Int
- microseconds :: Duration
- milliseconds :: Duration
- seconds :: Duration
- data Scope = Scope {}
- cancelScope :: Scope -> IO ()
- scopeCancelledSTM :: Scope -> STM (IO a)
- scopeFork :: Scope -> ((forall x. IO x -> IO x) -> IO a) -> (ThreadId -> Either SomeException a -> IO ()) -> IO ThreadId
- scoped :: Context -> (Scope -> IO a) -> IO a
- wait :: Scope -> IO ()
- waitFor :: Scope -> Duration -> IO ()
- waitSTM :: Scope -> STM ()
- data ScopeClosing = ScopeClosing
- data Thread a
- async :: Scope -> IO a -> IO (Thread (Either ThreadFailed a))
- asyncWithUnmask :: Scope -> ((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)
- fork :: Scope -> IO a -> IO (Thread a)
- fork_ :: Scope -> IO () -> IO ()
- forkWithUnmask :: Scope -> ((forall x. IO x -> IO x) -> IO a) -> IO (Thread a)
- forkWithUnmask_ :: Scope -> ((forall x. IO x -> IO x) -> IO ()) -> IO ()
- data ThreadFailed = ThreadFailed {}
- newtype ThreadFailedAsync = ThreadFailedAsync ThreadFailed
- timeoutSTM :: Duration -> STM (IO a) -> IO a -> IO a
Documentation
newtype 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 |
Context | |
|
globalContext :: Context Source #
The global context. It cannot be cancelled.
Ctx | |
|
cancelCtxSTM :: Ctx -> CancelToken -> STM () Source #
ctxCancelToken :: Ctx -> STM CancelToken Source #
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 # | |
toMicroseconds :: Duration -> Int Source #
microseconds :: Duration Source #
One microsecond.
milliseconds :: Duration Source #
One millisecond.
A scope delimits the lifetime of all threads created within it.
Scope | |
|
cancelScope :: Scope -> IO () Source #
Cancel all contexts derived from a scope.
scopeFork :: Scope -> ((forall x. IO x -> IO x) -> IO a) -> (ThreadId -> Either SomeException a -> IO ()) -> IO ThreadId Source #
waitFor :: Scope -> Duration -> IO () Source #
Variant of wait
that waits for up to the given duration.
data ScopeClosing Source #
Exception thrown by a parent thread to its children when the scope is closing.
Instances
Eq ScopeClosing Source # | |
Defined in Ki.ScopeClosing (==) :: ScopeClosing -> ScopeClosing -> Bool # (/=) :: ScopeClosing -> ScopeClosing -> Bool # | |
Show ScopeClosing Source # | |
Defined in Ki.ScopeClosing showsPrec :: Int -> ScopeClosing -> ShowS # show :: ScopeClosing -> String # showList :: [ScopeClosing] -> ShowS # | |
Exception ScopeClosing Source # | |
Defined in Ki.ScopeClosing |
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.1.0.1-JNrPe1BCZVBCx0CA2xJxNk" '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)))) |
async :: Scope -> 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 -> ((forall x. IO x -> IO x) -> IO a) -> IO (Thread (Either ThreadFailed a)) Source #
fork :: Scope -> 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.
Throws:
- Calls
error
if the scope is closed.
forkWithUnmask_ :: Scope -> ((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.
data ThreadFailed Source #
A thread failed, either by throwing or being thrown an exception.
Instances
Show ThreadFailed Source # | |
Defined in Ki.ThreadFailed showsPrec :: Int -> ThreadFailed -> ShowS # show :: ThreadFailed -> String # showList :: [ThreadFailed] -> ShowS # | |
Exception ThreadFailed Source # | |
Defined in Ki.ThreadFailed |
newtype ThreadFailedAsync Source #
An async wrapper around ThreadFailed
, used when a child thread communicates its failure to its parent. This
is preferred to throwing ThreadFailed
directly, so that client code (outside of this library) can follow
best-practices when encountering a mysterious async exception: clean up resources and re-throw it.
Instances
Show ThreadFailedAsync Source # | |
Defined in Ki.ThreadFailed showsPrec :: Int -> ThreadFailedAsync -> ShowS # show :: ThreadFailedAsync -> String # showList :: [ThreadFailedAsync] -> ShowS # | |
Exception ThreadFailedAsync Source # | |
Defined in Ki.ThreadFailed |