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

Effectful.Provider

Description

Turn an effect handler into an effectful operation.

Synopsis

Example

>>> import Control.Monad.IO.Class
>>> import Effectful.Dispatch.Dynamic
>>> import Effectful.State.Static.Local
>>> import qualified Data.Map.Strict as M

Given an effect:

>>> :{
  data Write :: Effect where
    Write :: String -> Write m ()
  type instance DispatchOf Write = Dynamic
:}
>>> :{
  write :: Write :> es => String -> Eff es ()
  write = send . Write
:}

its handler can be turned into an effectful operation with the Provider effect:

>>> :{
  action :: Provider_ Write FilePath :> es => Eff es ()
  action = do
    provideWith_ @Write "in.txt" $ do
      write "hi"
      write "there"
    provideWith_ @Write "out.txt" $ do
      write "good"
      write "bye"
:}

Then, given multiple interpreters:

>>> :{
  runWriteIO
    :: IOE :> es
    => FilePath
    -> Eff (Write : es) a
    -> Eff es a
  runWriteIO fp = interpret $ \_ -> \case
    Write msg -> liftIO . putStrLn $ fp ++ ": " ++ msg
:}
>>> :{
  runWritePure
    :: State (M.Map FilePath [String]) :> es
    => FilePath
    -> Eff (Write : es) a
    -> Eff es a
  runWritePure fp = interpret $ \_ -> \case
    Write msg -> modify $ M.insertWith (++) fp [msg]
:}

action can be supplied with either of them for the appropriate behavior:

>>> :{
  runEff
    . runProvider_ runWriteIO
    $ action
:}
in.txt: hi
in.txt: there
out.txt: good
out.txt: bye
>>> :{
  runPureEff
    . fmap (fmap reverse)
    . execState @(M.Map FilePath [String]) M.empty
    . runProvider_ runWritePure
    $ action
:}
fromList [("in.txt",["hi","there"]),("out.txt",["good","bye"])]

Effect

data Provider (e :: Effect) (input :: Type) (f :: Type -> Type) :: Effect Source #

Provide a way to run a handler of e with a given input.

Note: f can be used to alter the return type of the effect handler. If that's unnecessary, use Provider_.

Instances

Instances details
type DispatchOf (Provider e input f) Source # 
Instance details

Defined in Effectful.Provider

data StaticRep (Provider e input f) Source # 
Instance details

Defined in Effectful.Provider

data StaticRep (Provider e input f) where

type Provider_ e input = Provider e input Identity Source #

A restricted variant of Provider with unchanged return type of the effect handler.

Handlers

runProvider Source #

Arguments

:: (forall r. input -> Eff (e ': es) r -> Eff es (f r))

The effect handler.

-> Eff (Provider e input f ': es) a 
-> Eff es a 

Run the Provider effect with a given effect handler.

runProvider_ Source #

Arguments

:: (forall r. input -> Eff (e ': es) r -> Eff es r)

The effect handler.

-> Eff (Provider_ e input ': es) a 
-> Eff es a 

Run the Provider effect with a given effect handler that doesn't change its return type.

Operations

provide :: Provider e () f :> es => Eff (e ': es) a -> Eff es (f a) Source #

Run the effect handler.

provide_ :: Provider_ e () :> es => Eff (e ': es) a -> Eff es a Source #

Run the effect handler with unchanged return type.

provideWith Source #

Arguments

:: Provider e input f :> es 
=> input

The input to the effect handler.

-> Eff (e ': es) a 
-> Eff es (f a) 

Run the effect handler with a given input.

provideWith_ Source #

Arguments

:: Provider_ e input :> es 
=> input

The input to the effect handler.

-> Eff (e ': es) a 
-> Eff es a 

Run the effect handler that doesn't change its return type with a given input.