polysemy-conc-0.10.0.0: Polysemy effects for concurrency
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Conc.Interpreter.Scoped

Description

 
Synopsis

Documentation

interpretScopedH Source #

Arguments

:: forall resource param effect r. (forall x. param -> (resource -> Sem r x) -> Sem r x)

A callback function that allows the user to acquire a resource for each computation wrapped by scoped using other effects, with an additional argument that contains the call site parameter passed to scoped.

-> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) r x)

A handler like the one expected by interpretH with an additional parameter that contains the resource allocated by the first argument.

-> InterpreterFor (Scoped param effect) r 

Construct an interpreter for a higher-order effect wrapped in a Scoped, given a resource allocation function and a parameterized handler for the plain effect.

This combinator is analogous to interpretH in that it allows the handler to use the Tactical environment and transforms the effect into other effects on the stack.

interpretScopedH' :: forall resource param effect r. (forall e r0 x. param -> (resource -> Tactical e (Sem r0) r x) -> Tactical e (Sem r0) r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical (Scoped param effect) (Sem r0) r x) -> InterpreterFor (Scoped param effect) r Source #

Variant of interpretScopedH that allows the resource acquisition function to use Tactical.

interpretScoped :: forall resource param effect r. (forall x. param -> (resource -> Sem r x) -> Sem r x) -> (forall m x. resource -> effect m x -> Sem r x) -> InterpreterFor (Scoped param effect) r Source #

First-order variant of interpretScopedH.

interpretScopedAs :: forall resource param effect r. (param -> Sem r resource) -> (forall m x. resource -> effect m x -> Sem r x) -> InterpreterFor (Scoped param effect) r Source #

Variant of interpretScoped in which the resource allocator is a plain action.

interpretScopedWithH :: forall extra resource param effect r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> (resource -> Sem r1 x) -> Sem r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) r1 x) -> InterpreterFor (Scoped param effect) r Source #

Higher-order interpreter for Scoped that allows the handler to use additional effects that are interpreted by the resource allocator.

Note: It is necessary to specify the list of local interpreters with a type application; GHC won't be able to figure them out from the type of withResource.

As an example for a higher order effect, consider a mutexed concurrent state effect, where an effectful function may lock write access to the state while making it still possible to read it:

data MState s :: Effect where
  MState :: (s -> m (s, a)) -> MState s m a
  MRead :: MState s m s

makeSem ''MState

We can now use an AtomicState to store the current value and lock write access with an MVar. Since the state callback is effectful, we need a higher order interpreter:

withResource ::
  Member (Embed IO) r =>
  s ->
  (MVar () -> Sem (AtomicState s : r) a) ->
  Sem r a
withResource initial use = do
  tv <- embed (newTVarIO initial)
  lock <- embed (newMVar ())
  runAtomicStateTVar tv $ use lock

interpretMState ::
  ∀ s r .
  Members [Resource, Embed IO] r =>
  InterpreterFor (Scoped s (MState s)) r
interpretMState =
  interpretScopedWithH @'[AtomicState s] withResource \ lock -> \case
    MState f ->
      bracket_ (embed (takeMVar lock)) (embed (tryPutMVar lock ())) do
        s0 <- atomicGet
        res <- runTSimple (f s0)
        Inspector ins <- getInspectorT
        for_ (ins res) \ (s, _) -> atomicPut s
        pure (snd <$> res)
    MRead ->
      liftT atomicGet

interpretScopedWith :: forall extra param resource effect r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> (resource -> Sem r1 x) -> Sem r x) -> (forall m x. resource -> effect m x -> Sem r1 x) -> InterpreterFor (Scoped param effect) r Source #

First-order variant of interpretScopedWithH.

Note: It is necessary to specify the list of local interpreters with a type application; GHC won't be able to figure them out from the type of withResource:

data SomeAction :: Effect where
  SomeAction :: SomeAction m ()

foo :: InterpreterFor (Scoped () SomeAction) r
foo =
  interpretScopedWith @[Reader Int, State Bool] localEffects \ () -> \case
    SomeAction -> put . (> 0) =<< ask @Int
  where
    localEffects () use = evalState False (runReader 5 (use ()))

interpretScopedWith_ :: forall extra param effect r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> Sem r1 x -> Sem r x) -> (forall m x. effect m x -> Sem r1 x) -> InterpreterFor (Scoped param effect) r Source #

Variant of interpretScopedWith in which no resource is used and the resource allocator is a plain interpreter. This is useful for scopes that only need local effects, but no resources in the handler.

See the Note on interpretScopedWithH.

runScoped :: forall resource param effect r. (forall x. param -> (resource -> Sem r x) -> Sem r x) -> (resource -> InterpreterFor effect r) -> InterpreterFor (Scoped param effect) r Source #

Variant of interpretScoped that uses another interpreter instead of a handler.

This is mostly useful if you want to reuse an interpreter that you cannot easily rewrite (like from another library). If you have full control over the implementation, interpretScoped should be preferred.

Note: The wrapped interpreter will be executed fully, including the initializing code surrounding its handler, for each action in the program, so if the interpreter allocates any resources, they will be scoped to a single action. Move them to withResource instead.

For example, consider the following interpreter for AtomicState:

atomicTVar :: Member (Embed IO) r => a -> InterpreterFor (AtomicState a) r
atomicTVar initial sem = do
  tv <- embed (newTVarIO initial)
  runAtomicStateTVar tv sem

If this interpreter were used for a scoped version of AtomicState like this:

runScoped (\ initial use -> use initial) \ initial -> atomicTVar initial

Then the TVar would be created every time an AtomicState action is run, not just when entering the scope.

The proper way to implement this would be to rewrite the resource allocation:

runScoped (\ initial use -> use =<< embed (newTVarIO initial)) runAtomicStateTVar

runScopedAs :: forall resource param effect r. (param -> Sem r resource) -> (resource -> InterpreterFor effect r) -> InterpreterFor (Scoped param effect) r Source #

Variant of runScoped in which the resource allocator returns the resource rather tnen calling a continuation.

interpretScopedResumableH :: forall param resource effect err r. (forall x. param -> (resource -> Sem (Stop err ': r) x) -> Sem (Stop err ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop err ': r) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined higher-order interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumable :: forall param resource effect err r. (forall x. param -> (resource -> Sem (Stop err ': r) x) -> Sem (Stop err ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err ': r) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumable_ :: forall param resource effect err r. (param -> Sem (Stop err ': r) resource) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err ': r) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope. In this variant, the resource allocator is a plain action.

interpretScopedResumableWithH :: forall extra param resource effect err r r1. r1 ~ (extra ++ (Stop err ': r)) => r1 ~ ((extra ++ '[Stop err]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop err]) => (forall x. param -> (resource -> Sem r1 x) -> Sem (Stop err ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) r1 x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined higher-order interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumableWith :: forall extra param resource effect err r r1. r1 ~ (extra ++ (Stop err ': r)) => r1 ~ ((extra ++ '[Stop err]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop err]) => (forall x. param -> (resource -> Sem r1 x) -> Sem (Stop err ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem r1 x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumableWith_ :: forall extra param effect err r r1. r1 ~ (extra ++ (Stop err ': r)) => r1 ~ ((extra ++ '[Stop err]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop err]) => (forall x. param -> Sem r1 x -> Sem (Stop err ': r) x) -> (forall r0 x. effect (Sem r0) x -> Sem r1 x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope. In this variant, no resource is used and the allocator is a plain interpreter.

interpretResumableScopedH :: forall param resource effect err r. (forall x. param -> (resource -> Sem r x) -> Sem r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop err ': r) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined higher-order interpreter for Resumable and Scoped. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScoped :: forall param resource effect err r. (forall x. param -> (resource -> Sem r x) -> Sem r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err ': r) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScoped_ :: forall param resource effect err r. (param -> Sem r resource) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err ': r) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped. In this variant: - Only the handler may send Stop, but this allows resumption to happen on each action inside of the scope. - The resource allocator is a plain action.

interpretResumableScopedWithH :: forall extra param resource effect err r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> (resource -> Sem r1 x) -> Sem r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop err ': r1) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined higher-order interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScopedWith :: forall extra param resource effect err r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> (resource -> Sem r1 x) -> Sem r x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err ': r1) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScopedWith_ :: forall extra param effect err r r1. r1 ~ (extra ++ r) => KnownList extra => (forall x. param -> Sem r1 x -> Sem r x) -> (forall r0 x. effect (Sem r0) x -> Sem (Stop err ': r1) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant: - Only the handler may send Stop, but this allows resumption to happen on each action inside of the scope. - No resource is used and the allocator is a plain interpreter.

interpretScopedRH :: forall param resource effect eo ei r. (forall x. param -> (resource -> Sem (Stop eo ': r) x) -> Sem (Stop eo ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop ei ': r) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined higher-order interpreter for Resumable and Scoped. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedR :: forall param resource effect eo ei r. (forall x. param -> (resource -> Sem (Stop eo ': r) x) -> Sem (Stop eo ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei ': r) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedR_ :: forall param resource effect eo ei r. (param -> Sem (Stop eo ': r) resource) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei ': r) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable. In this variant: - Both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption. - The resource allocator is a plain action.

interpretScopedRWithH :: forall extra param resource effect eo ei r r1. r1 ~ (extra ++ (Stop eo ': r)) => r1 ~ ((extra ++ '[Stop eo]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop eo]) => (forall x. param -> (resource -> Sem r1 x) -> Sem (Stop eo ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop ei ': r1) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined higher-order interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedRWith :: forall extra param resource effect eo ei r r1. r1 ~ (extra ++ (Stop eo ': r)) => r1 ~ ((extra ++ '[Stop eo]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop eo]) => (forall x. param -> (resource -> Sem r1 x) -> Sem (Stop eo ': r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei ': r1) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedRWith_ :: forall extra param effect eo ei r r1. r1 ~ (extra ++ (Stop eo ': r)) => r1 ~ ((extra ++ '[Stop eo]) ++ r) => KnownList extra => KnownList (extra ++ '[Stop eo]) => (forall x. param -> Sem r1 x -> Sem (Stop eo ': r) x) -> (forall r0 x. effect (Sem r0) x -> Sem (Stop ei ': r1) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. - Both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption. - The resource allocator is a plain action.