Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data StructuredConcurrency :: Effect
- runStructuredConcurrency :: IOE :> es => Eff (StructuredConcurrency ': es) a -> Eff es a
- data Scope
- data Thread a
- scoped :: StructuredConcurrency :> es => (Scope -> Eff es a) -> Eff es a
- fork :: StructuredConcurrency :> es => Scope -> Eff es a -> Eff es (Thread a)
- forkTry :: Exception e => StructuredConcurrency :> es => Scope -> Eff es a -> Eff es (Thread (Either e a))
- await :: Thread a -> STM a
- awaitAll :: Scope -> STM ()
- fork_ :: StructuredConcurrency :> es => Scope -> Eff es Void -> Eff es ()
- forkWith :: StructuredConcurrency :> es => Scope -> ThreadOptions -> Eff es a -> Eff es (Thread a)
- forkWith_ :: StructuredConcurrency :> es => Scope -> ThreadOptions -> Eff es Void -> Eff es ()
- forkTryWith :: Exception e => Scope -> StructuredConcurrency :> es => ThreadOptions -> Eff es a -> Eff es (Thread (Either e a))
- data ThreadOptions = ThreadOptions {}
- defaultThreadOptions :: ThreadOptions
- data ThreadAffinity
- = Unbound
- | Capability Int
- | OsThread
- data ByteCount
- kilobytes :: Natural -> ByteCount
- megabytes :: Natural -> ByteCount
- atomically :: StructuredConcurrency :> es => STM a -> Eff es a
- newTVarIO :: StructuredConcurrency :> es => a -> Eff es (TVar a)
- newTMVarIO :: StructuredConcurrency :> es => a -> Eff es (TMVar a)
- newEmptyTMVarIO :: StructuredConcurrency :> es => Eff es (TMVar a)
Effect
data StructuredConcurrency :: Effect Source #
Instances
type DispatchOf StructuredConcurrency Source # | |
Defined in Effectful.Ki | |
data StaticRep StructuredConcurrency Source # | |
Defined in Effectful.Ki |
Handlers
runStructuredConcurrency :: IOE :> es => Eff (StructuredConcurrency ': es) a -> Eff es a Source #
Run the StructuredConcurrency
effect.
Core API
A scope.
👉 Details
- A scope delimits the lifetime of all threads created within it.
- A scope is only valid during the callback provided to
scoped
. - The thread that creates a scope is considered the parent of all threads created within it.
- All threads created within a scope can be awaited together (see
awaitAll
). - All threads created within a scope are terminated when the scope closes.
A thread.
👉 Details
- A thread's lifetime is delimited by the scope in which it was created.
- The thread that creates a scope is considered the parent of all threads created within it.
- If an exception is raised in a child thread, the child either propagates the exception to its parent (see
fork
), or returns the exception as a value (seeforkTry
). - All threads created within a scope are terminated when the scope closes.
forkTry :: Exception e => StructuredConcurrency :> es => Scope -> Eff es a -> Eff es (Thread (Either e a)) Source #
Extended API
forkWith :: StructuredConcurrency :> es => Scope -> ThreadOptions -> Eff es a -> Eff es (Thread a) Source #
forkWith_ :: StructuredConcurrency :> es => Scope -> ThreadOptions -> Eff es Void -> Eff es () Source #
forkTryWith :: Exception e => Scope -> StructuredConcurrency :> es => ThreadOptions -> Eff es a -> Eff es (Thread (Either e a)) Source #
Thread options
data ThreadOptions #
affinity
The affinity of a thread. A thread can be unbound, bound to a specific capability, or bound to a specific OS thread.
Default:
Unbound
allocationLimit
The maximum number of bytes a thread may allocate before it is delivered an
AllocationLimitExceeded
exception. If caught, the thread is allowed to allocate an additional 100kb (tunable with+RTS -xq
) to perform any necessary cleanup actions; if exceeded, the thread is delivered another.Default:
Nothing
(no limit)label
The label of a thread, visible in the event log (
+RTS -l
).Default:
""
(no label)maskingState
The masking state a thread is created in. To unmask, use
unsafeUnmask
.Default:
Unmasked
Instances
Show ThreadOptions | |
Defined in Ki.Internal.Thread showsPrec :: Int -> ThreadOptions -> ShowS # show :: ThreadOptions -> String # showList :: [ThreadOptions] -> ShowS # | |
Eq ThreadOptions | |
Defined in Ki.Internal.Thread (==) :: ThreadOptions -> ThreadOptions -> Bool # (/=) :: ThreadOptions -> ThreadOptions -> Bool # |
defaultThreadOptions :: ThreadOptions #
Default thread options.
ThreadOptions
{affinity
=Unbound
,allocationLimit
= Nothing ,label
= "" ,maskingState
=Unmasked
}
data ThreadAffinity #
What, if anything, a thread is bound to.
Unbound | Unbound. |
Capability Int | Bound to a capability. |
OsThread | Bound to an OS thread. |
Instances
Show ThreadAffinity | |
Defined in Ki.Internal.Thread showsPrec :: Int -> ThreadAffinity -> ShowS # show :: ThreadAffinity -> String # showList :: [ThreadAffinity] -> ShowS # | |
Eq ThreadAffinity | |
Defined in Ki.Internal.Thread (==) :: ThreadAffinity -> ThreadAffinity -> Bool # (/=) :: ThreadAffinity -> ThreadAffinity -> Bool # |
Byte count
A number of bytes.
STM re-export
atomically :: StructuredConcurrency :> es => STM a -> Eff es a Source #
newTMVarIO :: StructuredConcurrency :> es => a -> Eff es (TMVar a) Source #
newEmptyTMVarIO :: StructuredConcurrency :> es => Eff es (TMVar a) Source #