| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Effectful.Internal.Unlift
Description
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
- ephemeralConcUnlift :: HasCallStack => Int -> ((forall r. m r -> IO r) -> IO a) -> Env es -> (forall r. m r -> Env es -> IO r) -> IO a
- persistentConcUnlift :: HasCallStack => Bool -> Int -> ((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, withRunInIO or the
localUnlift family.
Warning: unlifting functions should not be used outside of continuations that brought them into scope. While this currently works just fine, there are no guarantees it will continue doing so in the future.
Constructors
| SeqUnlift | The fastest strategy and a default setting for |
| ConcUnlift !Persistence !Limit | A strategy that 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
pooledMapConcurrentlyNfrom theunliftiolibrary requires theEphemeralstrategy as we don't want jobs to share environment changes made by previous jobs run in the same worker thread. - Lifting
forkIOWithUnmaskrequires thePersistentstrategy, otherwise the unmasking function would start with a fresh environment each time it's called.
Constructors
| 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
| Eq Persistence Source # | |
Defined in Effectful.Internal.Unlift | |
| Ord Persistence Source # | |
Defined in Effectful.Internal.Unlift Methods compare :: Persistence -> Persistence -> Ordering # (<) :: Persistence -> Persistence -> Bool # (<=) :: Persistence -> Persistence -> Bool # (>) :: Persistence -> Persistence -> Bool # (>=) :: Persistence -> Persistence -> Bool # max :: Persistence -> Persistence -> Persistence # min :: Persistence -> Persistence -> Persistence # | |
| Show Persistence Source # | |
Defined in Effectful.Internal.Unlift Methods showsPrec :: Int -> Persistence -> ShowS # show :: Persistence -> String # showList :: [Persistence] -> ShowS # | |
| Generic Persistence Source # | |
Defined in Effectful.Internal.Unlift Associated Types type Rep Persistence :: Type -> Type # | |
| type Rep Persistence Source # | |
Defined in Effectful.Internal.Unlift | |
Limit setting for the ConcUnlift strategy.
Constructors
| Limited !Int | Behavior dependent on the For For |
| Unlimited | Unlimited use of the unlifting function. |
Instances
| Eq Limit Source # | |
| Ord Limit Source # | |
| Show Limit Source # | |
| Generic Limit Source # | |
| type Rep Limit Source # | |
Defined in Effectful.Internal.Unlift type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "effectful-core-1.2.0.0-Ag0kJ5PsTC1BiOpulhLp2m" '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 for various strategies and limits.
Arguments
| :: HasCallStack | |
| => Int | Number of permitted uses of the unlift function. |
| -> ((forall r. m r -> IO r) -> IO a) | |
| -> Env es | |
| -> (forall r. m r -> Env es -> IO r) | |
| -> IO a |
Concurrent unlift that doesn't preserve the environment between calls to the unlifting function in threads other than its creator.
Arguments
| :: HasCallStack | |
| => Bool | |
| -> Int | Number of threads that are allowed to use the unlift function. |
| -> ((forall r. m r -> IO r) -> IO a) | |
| -> Env es | |
| -> (forall r. m r -> Env es -> IO r) | |
| -> IO a |
Concurrent unlift that preserves the environment between calls to the unlifting function within a particular thread.