Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Scope
- scoped :: (Scope -> IO a) -> IO a
- wait :: Scope -> IO ()
- waitSTM :: Scope -> STM ()
- waitFor :: Scope -> Duration -> IO ()
- data Thread 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 ()
- 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)
- data Duration
- microseconds :: Duration
- milliseconds :: Duration
- seconds :: Duration
- timeoutSTM :: Duration -> STM (IO a) -> IO a -> IO a
- sleep :: Duration -> IO ()
- data ThreadFailed = ThreadFailed {}
Scope
scoped :: (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 withfork
throws, if any.
Examples
waitFor :: Scope -> Duration -> IO () Source #
Variant of wait
that waits for up to the given duration.
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-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 -> 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.
Async
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 #
Await
await :: Thread a -> IO a Source #
Wait for a thread to finish.
Throws:
ThreadFailed
if the thread threw an exception and was created withfork
.
awaitSTM :: Thread a -> STM a Source #
STM
variant of await
.
Throws:
ThreadFailed
if 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:
ThreadFailed
if the thread threw an exception and was created withfork
.
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.
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.
Exceptions
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 |