core-effect-effectful-0.0.0.4: Interoperability with the effectful effects system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Core.Effect.Effectful

Description

Effect systems are being actively explored as ways to structure Haskell programs. This package provides experimental support for the effectful effect system.

This module introcuces a new effect, ProgramE, which plumbs the current program context into the effect system. By calling runProgramE to add the ProgramE effect to the current list of in-scope effects you can then use withProgram' to run a Program action. The more general withProgram gives you an unlifting function to return back to the effect system so you can continue processing within your effects stack.

Usage

As an example, here's an effect which lifts to Program τ, does some log output, then unlifts back to Eff es to then query something from the Environment effect (which requires the IOE effect to run):

retrieveProgramName
    :: forall τ es
     . (IOE :> es, ProgramE τ :> es)
    => Eff es ()
retrieveProgramName = do
    -- we're in (IOE :> es, ProgramE :> es) => Eff es, right?

    withProgram @τ $ \runEffect -> do
        -- now we're in Program τ

        info "Running in Program"

        path <- runEffect $ do
            -- now back in (IOE :> es, ProgramE τ :> es) => Eff es, and can call
            -- something that requires the IOE effect be present.

            runEnvironment $ do
                -- now in (Environment :> es) => Eff es
                getExecutablePath

        info "Done running effects"
        debugS "path" path

The @τ type application shown here is vital; without it the compiler will not be able to resolve all the ambiguous types when attempting to determine which effect to run. It doesn't have to be polymorphic; if you know the actual top-level application state type you can do @Settings or whatever.

This all assumes you are running with the ProgramE τ effect in-scope. You can achieve that as follows:

main :: IO ()
main = execute program

program :: Program None ()
program = do
    -- in Program τ, where τ is None here
    context <- getContext
    liftIO $ do
        -- in IO
        runEff $ do
            -- in (IOE :> es) => Eff es
            runProgramE context $ do
                -- in (IOE :> es, ProgramE τ :> es) => Eff es
                ...
Synopsis

Effect

data ProgramE (τ :: Type) :: Effect Source #

An effect giving you access to return to the Program τ monad.

Instances

Instances details
type DispatchOf (ProgramE τ) Source # 
Instance details

Defined in Core.Effect.Effectful

newtype StaticRep (ProgramE τ) Source # 
Instance details

Defined in Core.Effect.Effectful

newtype StaticRep (ProgramE τ) = ProgramE (Context τ)

runProgramE :: forall τ es α. IOE :> es => Context τ -> Eff (ProgramE τ ': es) α -> Eff es α Source #

Given you are in the IOE effect, raise the currently in-scope effects to include the ProgramE effect. This will presumably be invoked fairly soon after entering the effect system, and it needs to have been done inside a program that was started with execute or executeWith. Assuming that to be the case, get the Context τ object from the outside edge of your program using getContext and then provide it to this function at the earliest opportunity.

Lifting and unlifting

withProgram :: forall τ es α. (IOE :> es, ProgramE τ :> es) => ((forall β. Eff es β -> Program τ β) -> Program τ α) -> Eff es α Source #

Run a Program τ monad action within the ProgramE τ effect.

This allows you the ability to lift to the Program τ monad, giving you the ability to run actions that do logging, telemetry, input/output, and exception handling, and then unlift back to the Eff es effect to continue work in the effects system.

The order of the existential types in the forall turned out to matter; it allows you to use the TypeApplications language extention to resolve the ambiguous types when invoking this function.

See also Core.Program.Unlift for a general discussion of the unlifting problem and in particular the withContext for a function with a comparable type signature.

withProgram' :: forall τ es α. (IOE :> es, ProgramE τ :> es) => Program τ α -> Eff es α Source #

Simple variant of withProgram which allows you to run a Program τ monad action from within the effect system, provided that the ProgramE τ effect is in scope.