Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Implementation of sequential and concurrent unlifts.
This module is intended for internal use only, and may change without warning in subsequent releases.
Synopsis
- data UnliftStrategy
- data Persistence
- data Limit
- seqUnlift :: HasCallStack => ((forall r. m r -> IO r) -> IO a) -> Env es -> (forall r. m r -> Env es -> IO r) -> IO a
- concUnlift :: HasCallStack => Persistence -> Limit -> ((forall r. m r -> IO r) -> IO a) -> Env es -> (forall r. m r -> Env es -> IO r) -> IO a
Unlifting strategies
data UnliftStrategy Source #
The strategy to use when unlifting Eff
computations via
withEffToIO
or the localUnlift
family.
SeqUnlift | The sequential strategy is the fastest and a default setting for
|
ConcUnlift !Persistence !Limit | The concurrent strategy makes it possible for the unlifting function to
be called in threads distinct from its creator. See |
Instances
data Persistence Source #
Persistence setting for the ConcUnlift
strategy.
Different functions require different persistence strategies. Examples:
- Lifting
pooledMapConcurrentlyN
from theunliftio
library requires theEphemeral
strategy as we don't want jobs to share environment changes made by previous jobs run in the same worker thread. - Lifting
forkIOWithUnmask
requires thePersistent
strategy, otherwise the unmasking function would start with a fresh environment each time it's called.
Ephemeral | Don't persist the environment between calls to the unlifting function in threads distinct from its creator. |
Persistent | Persist the environment between calls to the unlifting function within a particular thread. |
Instances
Generic Persistence Source # | |
Defined in Effectful.Internal.Unlift type Rep Persistence :: Type -> Type # from :: Persistence -> Rep Persistence x # to :: Rep Persistence x -> Persistence # | |
Show Persistence Source # | |
Defined in Effectful.Internal.Unlift showsPrec :: Int -> Persistence -> ShowS # show :: Persistence -> String # showList :: [Persistence] -> ShowS # | |
Eq Persistence Source # | |
Defined in Effectful.Internal.Unlift (==) :: Persistence -> Persistence -> Bool # (/=) :: Persistence -> Persistence -> Bool # | |
Ord Persistence Source # | |
Defined in Effectful.Internal.Unlift compare :: Persistence -> Persistence -> Ordering # (<) :: Persistence -> Persistence -> Bool # (<=) :: Persistence -> Persistence -> Bool # (>) :: Persistence -> Persistence -> Bool # (>=) :: Persistence -> Persistence -> Bool # max :: Persistence -> Persistence -> Persistence # min :: Persistence -> Persistence -> Persistence # | |
type Rep Persistence Source # | |
Defined in Effectful.Internal.Unlift |
Limit setting for the ConcUnlift
strategy.
Limited !Int | Behavior dependent on the For For |
Unlimited | Unlimited use of the unlifting function. |
Instances
Generic Limit Source # | |
Show Limit Source # | |
Eq Limit Source # | |
Ord Limit Source # | |
type Rep Limit Source # | |
Defined in Effectful.Internal.Unlift type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "effectful-core-2.3.0.1-1VFncKAQtvu2DINlTY1Lvd" 'False) (C1 ('MetaCons "Limited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type)) |
Unlifting functions
seqUnlift :: HasCallStack => ((forall r. m r -> IO r) -> IO a) -> Env es -> (forall r. m r -> Env es -> IO r) -> IO a Source #
Sequential unlift.
concUnlift :: HasCallStack => Persistence -> Limit -> ((forall r. m r -> IO r) -> IO a) -> Env es -> (forall r. m r -> Env es -> IO r) -> IO a Source #
Concurrent unlift.