effectful-core-2.2.1.0: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Unlifting strategies

data UnliftStrategy Source #

The strategy to use when unlifting Eff computations via withEffToIO, withRunInIO or the localUnlift family.

Constructors

SeqUnlift

The fastest strategy and a default setting for IOE. An attempt to call the unlifting function in threads distinct from its creator will result in a runtime error.

ConcUnlift !Persistence !Limit

A strategy that makes it possible for the unlifting function to be called in threads distinct from its creator. See Persistence and Limit settings for more information.

Instances

Instances details
Generic UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep UnliftStrategy :: Type -> Type #

Show UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Eq UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Ord UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep UnliftStrategy = D1 ('MetaData "UnliftStrategy" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" 'False) (C1 ('MetaCons "SeqUnlift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConcUnlift" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Persistence) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Limit)))

data Persistence Source #

Persistence setting for the ConcUnlift strategy.

Different functions require different persistence strategies. Examples:

  • Lifting pooledMapConcurrentlyN from the unliftio library requires the Ephemeral strategy as we don't want jobs to share environment changes made by previous jobs run in the same worker thread.
  • Lifting forkIOWithUnmask requires the Persistent strategy, 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

Instances details
Generic Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Persistence :: Type -> Type #

Show Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Eq Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Ord Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Persistence = D1 ('MetaData "Persistence" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" 'False) (C1 ('MetaCons "Ephemeral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Persistent" 'PrefixI 'False) (U1 :: Type -> Type))

data Limit Source #

Limit setting for the ConcUnlift strategy.

Constructors

Limited !Int

Behavior dependent on the Persistence setting.

For Ephemeral, it limits the amount of uses of the unlifting function in threads distinct from its creator to N. The unlifting function will create N copies of the environment when called N times and K+1 copies when called K < N times.

For Persistent, it limits the amount of threads, distinct from the creator of the unlifting function, it can be called in to N. The amount of calls to the unlifting function within a particular threads is unlimited. The unlifting function will create N copies of the environment when called in N threads and K+1 copies when called in K < N threads.

Unlimited

Unlimited use of the unlifting function.

Instances

Instances details
Generic Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Limit :: Type -> Type #

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Show Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

Eq Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

(==) :: Limit -> Limit -> Bool #

(/=) :: Limit -> Limit -> Bool #

Ord Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

(>=) :: Limit -> Limit -> Bool #

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

type Rep Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" '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.

ephemeralConcUnlift Source #

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.

persistentConcUnlift Source #

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.