Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Effectful.Dispatch.Dynamic
Description
Dynamically dispatched effects.
Synopsis
- send :: (HasCallStack, DispatchOf e ~ Dynamic, e :> es) => e (Eff es) a -> Eff es a
- type EffectHandler e es = forall a localEs. HasCallStack => LocalEnv localEs es -> e (Eff localEs) a -> Eff es a
- interpret :: DispatchOf e ~ Dynamic => EffectHandler e es -> Eff (e ': es) a -> Eff es a
- reinterpret :: DispatchOf e ~ Dynamic => (Eff handlerEs a -> Eff es b) -> EffectHandler e handlerEs -> Eff (e ': es) a -> Eff es b
- interpose :: forall e es a. (DispatchOf e ~ Dynamic, e :> es) => EffectHandler e es -> Eff es a -> Eff es a
- impose :: forall e es handlerEs a b. (DispatchOf e ~ Dynamic, e :> es) => (Eff handlerEs a -> Eff es b) -> EffectHandler e handlerEs -> Eff es a -> Eff es b
- data LocalEnv (localEs :: [Effect]) (handlerEs :: [Effect])
- localSeqUnlift :: (HasCallStack, SuffixOf es handlerEs) => LocalEnv localEs handlerEs -> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
- localSeqUnliftIO :: (HasCallStack, SuffixOf es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> ((forall r. Eff localEs r -> IO r) -> IO a) -> Eff es a
- localUnlift :: (HasCallStack, SuffixOf es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
- localUnliftIO :: (HasCallStack, SuffixOf es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff localEs r -> IO r) -> IO a) -> Eff es a
- withLiftMap :: (HasCallStack, SuffixOf es handlerEs) => LocalEnv localEs handlerEs -> ((forall a b. (Eff es a -> Eff es b) -> Eff localEs a -> Eff localEs b) -> Eff es r) -> Eff es r
- withLiftMapIO :: (HasCallStack, SuffixOf es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> ((forall a b. (IO a -> IO b) -> Eff localEs a -> Eff localEs b) -> Eff es r) -> Eff es r
- localLiftUnlift :: (HasCallStack, SuffixOf es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff es r -> Eff localEs r) -> (forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
- localLiftUnliftIO :: (HasCallStack, SuffixOf es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. IO r -> Eff localEs r) -> (forall r. Eff localEs r -> IO r) -> IO a) -> Eff es a
- type family SuffixOf (es :: [Effect]) (baseEs :: [Effect]) :: Constraint where ...
- type HasCallStack = ?callStack :: CallStack
Introduction
A dynamically dispatched effect is a collection of operations that can be interpreted in different ways at runtime, depending on the handler that is used to run the effect.
This allows a programmer to separate the what from the how, i.e. define effects that model what the code should do, while providing handlers that determine how it should do it later. Moreover, different environments can use different handlers to change the behavior of specific parts of the application if appropriate.
An example
Let's create an effect for basic file access, i.e. writing and reading files.
First, we need to define a generalized algebraic data type of kind Effect
,
where each constructor corresponds to a specific operation of the effect in
question.
>>>
:{
data FileSystem :: Effect where ReadFile :: FilePath -> FileSystem m String WriteFile :: FilePath -> String -> FileSystem m () :}
>>>
type instance DispatchOf FileSystem = Dynamic
The FileSystem
effect has two operations:
ReadFile
, which takes aFilePath
and returns aString
in the monadic context.WriteFile
, which takes aFilePath
, aString
and returns a()
in the monadic context.
For people familiar with the mtl
style effects, note that the syntax looks
very similar to defining an appropriate type class:
class FileSystem m where readFile :: FilePath -> m String writeFile :: FilePath -> String -> m ()
The biggest difference between these two is that the definition of a type
class gives us operations as functions, while the definition of an effect
gives us operations as data constructors. They can be turned into functions
with the help of send
:
>>>
:{
readFile :: (HasCallStack, FileSystem :> es) => FilePath -> Eff es String readFile path = send (ReadFile path) :}
>>>
:{
writeFile :: (HasCallStack, FileSystem :> es) => FilePath -> String -> Eff es () writeFile path content = send (WriteFile path content) :}
Note: the above functions and the DispatchOf
instance can also be
automatically generated by the makeEffect
function from the effectful-th
library.
The following defines an EffectHandler
that reads and writes files from the
drive:
>>>
import Control.Exception (IOException)
>>>
import Control.Monad.Catch (catch)
>>>
import qualified System.IO as IO
>>>
import Effectful.Error.Static
>>>
newtype FsError = FsError String deriving Show
>>>
:{
runFileSystemIO :: (IOE :> es, Error FsError :> es) => Eff (FileSystem : es) a -> Eff es a runFileSystemIO = interpret $ \_ -> \case ReadFile path -> adapt $ IO.readFile path WriteFile path contents -> adapt $ IO.writeFile path contents where adapt m = liftIO m `catch` \(e::IOException) -> throwError . FsError $ show e :}
Here, we use interpret
and simply execute corresponding IO
actions for
each operation, additionally doing a bit of error management.
On the other hand, maybe there is a situation in which instead of interacting with the outside world, a pure, in-memory storage is preferred:
>>>
import qualified Data.Map.Strict as M
>>>
import Effectful.State.Static.Local
>>>
:{
runFileSystemPure :: Error FsError :> es => M.Map FilePath String -> Eff (FileSystem : es) a -> Eff es a runFileSystemPure fs0 = reinterpret (evalState fs0) $ \_ -> \case ReadFile path -> gets (M.lookup path) >>= \case Just contents -> pure contents Nothing -> throwError . FsError $ "File not found: " ++ show path WriteFile path contents -> modify $ M.insert path contents :}
Here, we use reinterpret
and introduce a
State
effect for the storage that is private
to the effect handler and cannot be accessed outside of it.
Let's compare how these differ.
>>>
:{
action = do file <- readFile "effectful-core.cabal" pure $ length file > 0 :}
>>>
:t action
action :: (FileSystem :> es) => Eff es Bool
>>>
runEff . runError @FsError . runFileSystemIO $ action
Right True
>>>
runPureEff . runErrorNoCallStack @FsError . runFileSystemPure M.empty $ action
Left (FsError "File not found: \"effectful-core.cabal\"")
First order and higher order effects
Note that the definition of the FileSystem
effect from the previous section
doesn't use the m
type parameter. What is more, when the effect is
interpreted, the LocalEnv
argument of the EffectHandler
is also not
used. Such effects are first order.
If an effect makes use of the m
parameter, it is a higher order effect.
Interpretation of higher order effects is slightly more involved. To see why,
let's consider the Profiling
effect for logging how much time a specific
action took to run:
>>>
:{
data Profiling :: Effect where Profile :: String -> m a -> Profiling m a :}
>>>
type instance DispatchOf Profiling = Dynamic
>>>
:{
profile :: (HasCallStack, Profiling :> es) => String -> Eff es a -> Eff es a profile label action = send (Profile label action) :}
If we naively try to interpret it, we will run into trouble:
>>>
import GHC.Clock (getMonotonicTime)
>>>
:{
runProfiling :: IOE :> es => Eff (Profiling : es) a -> Eff es a runProfiling = interpret $ \_ -> \case Profile label action -> do t1 <- liftIO getMonotonicTime r <- action t2 <- liftIO getMonotonicTime liftIO . putStrLn $ "Action '" ++ label ++ "' took " ++ show (t2 - t1) ++ " seconds." pure r :} ... ... Couldn't match type ‘localEs’ with ‘es’ ...
The problem is that action
has a type Eff localEs a
, while the monad of
the effect handler is Eff es
. localEs
represents the local environment
in which the Profile
operation was called, which is opaque as the effect
handler cannot possibly know how it looks like.
The solution is to use the LocalEnv
that an EffectHandler
is given to run
the action using one of the functions from the localUnlift
family:
>>>
:{
runProfiling :: IOE :> es => Eff (Profiling : es) a -> Eff es a runProfiling = interpret $ \env -> \case Profile label action -> localSeqUnliftIO env $ \unlift -> do t1 <- getMonotonicTime r <- unlift action t2 <- getMonotonicTime putStrLn $ "Action '" ++ label ++ "' took " ++ show (t2 - t1) ++ " seconds." pure r :}
In a similar way we can define a dummy interpreter that does no profiling:
>>>
:{
runNoProfiling :: Eff (Profiling : es) a -> Eff es a runNoProfiling = interpret $ \env -> \case Profile label action -> localSeqUnlift env $ \unlift -> unlift action :}
...and it's done.
>>>
action = profile "greet" . liftIO $ putStrLn "Hello!"
>>>
:t action
action :: (Profiling :> es, IOE :> es) => Eff es ()
>>>
runEff . runProfiling $ action
Hello! Action 'greet' took ... seconds.
>>>
runEff . runNoProfiling $ action
Hello!
Sending operations to the handler
Arguments
:: (HasCallStack, DispatchOf e ~ Dynamic, e :> es) | |
=> e (Eff es) a | The effect. |
-> Eff es a |
Send an operation of the given effect to its handler for execution.
Handling effects
type EffectHandler e es Source #
Arguments
= forall a localEs. HasCallStack | |
=> LocalEnv localEs es | Capture of the local environment for handling local |
-> e (Eff localEs) a | The effect performed in the local environment. |
-> Eff es a |
Type signature of the effect handler.
Arguments
:: DispatchOf e ~ Dynamic | |
=> EffectHandler e es | The effect handler. |
-> Eff (e ': es) a | |
-> Eff es a |
Interpret an effect.
Arguments
:: DispatchOf e ~ Dynamic | |
=> (Eff handlerEs a -> Eff es b) | Introduction of effects encapsulated within the handler. |
-> EffectHandler e handlerEs | The effect handler. |
-> Eff (e ': es) a | |
-> Eff es b |
Interpret an effect using other, private effects.
interpret
≡reinterpret
id
Arguments
:: forall e es a. (DispatchOf e ~ Dynamic, e :> es) | |
=> EffectHandler e es | The effect handler. |
-> Eff es a | |
-> Eff es a |
Replace the handler of an existing effect with a new one.
Note: this function allows for augmenting handlers with a new functionality as the new handler can send operations to the old one.
>>>
:{
data E :: Effect where Op :: E m () type instance DispatchOf E = Dynamic :}
>>>
:{
runE :: IOE :> es => Eff (E : es) a -> Eff es a runE = interpret $ \_ Op -> liftIO (putStrLn "op") :}
>>>
runEff . runE $ send Op
op
>>>
:{
augmentE :: (E :> es, IOE :> es) => Eff es a -> Eff es a augmentE = interpose $ \_ Op -> liftIO (putStrLn "augmented op") >> send Op :}
>>>
runEff . runE . augmentE $ send Op
augmented op op
Arguments
:: forall e es handlerEs a b. (DispatchOf e ~ Dynamic, e :> es) | |
=> (Eff handlerEs a -> Eff es b) | Introduction of effects encapsulated within the handler. |
-> EffectHandler e handlerEs | The effect handler. |
-> Eff es a | |
-> Eff es b |
Handling local Eff
computations
Unlifts
Arguments
:: (HasCallStack, SuffixOf es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create a local unlifting function with the SeqUnlift
strategy. For the
general version see localUnlift
.
Arguments
:: (HasCallStack, SuffixOf es handlerEs, IOE :> es) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> ((forall r. Eff localEs r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create a local unlifting function with the SeqUnlift
strategy. For the
general version see localUnliftIO
.
Arguments
:: (HasCallStack, SuffixOf es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> UnliftStrategy | |
-> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create a local unlifting function with the given strategy.
Arguments
:: (HasCallStack, SuffixOf es handlerEs, IOE :> es) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> UnliftStrategy | |
-> ((forall r. Eff localEs r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create a local unlifting function with the given strategy.
Lifts
Arguments
:: (HasCallStack, SuffixOf es handlerEs, IOE :> es) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> ((forall a b. (IO a -> IO b) -> Eff localEs a -> Eff localEs b) -> Eff es r) | Continuation with the lifting function in scope. |
-> Eff es r |
Utility for lifting IO
computations of type
IO
a ->IO
b
to
Eff
localEs a ->Eff
localEs b
Note: the computation must not run its argument in a different thread, attempting to do so will result in a runtime error.
Useful e.g. for lifting the unmasking function in
mask
-like computations:
>>>
:{
data Fork :: Effect where ForkWithUnmask :: ((forall a. m a -> m a) -> m ()) -> Fork m ThreadId type instance DispatchOf Fork = Dynamic :}
>>>
:{
runFork :: IOE :> es => Eff (Fork : es) a -> Eff es a runFork = interpret $ \env (ForkWithUnmask m) -> withLiftMapIO env $ \liftMap -> do localUnliftIO env (ConcUnlift Ephemeral $ Limited 1) $ \unlift -> do forkIOWithUnmask $ \unmask -> unlift $ m $ liftMap unmask :}
Bidirectional lifts
Arguments
:: (HasCallStack, SuffixOf es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> UnliftStrategy | |
-> ((forall r. Eff es r -> Eff localEs r) -> (forall r. Eff localEs r -> Eff es r) -> Eff es a) | Continuation with the lifting and unlifting function in scope. |
-> Eff es a |
Create a local lifting and unlifting function with the given strategy.
Useful for lifting complicated Eff
computations where the monadic action
shows in both positive (as a result) and negative (as an argument) position.
Note: depending on the computation you're lifting localUnlift
along with
withLiftMap
might be enough and is more efficient.
Arguments
:: (HasCallStack, SuffixOf es handlerEs, IOE :> es) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> UnliftStrategy | |
-> ((forall r. IO r -> Eff localEs r) -> (forall r. Eff localEs r -> IO r) -> IO a) | Continuation with the lifting and unlifting function in scope. |
-> Eff es a |
Create a local unlifting function with the given strategy along with an unrestricted lifting function.
Useful for lifting complicated IO
computations where the monadic action
shows in both positive (as a result) and negative (as an argument) position.
Note: depending on the computation you're lifting localUnliftIO
along
with withLiftMapIO
might be enough and is more efficient.
Utils
type family SuffixOf (es :: [Effect]) (baseEs :: [Effect]) :: Constraint where ... Source #
Require that the second list of effects is a suffix of the first one.
In other words, SuffixOf
es
baseEs
means "a suffix of es
is
baseEs
".
Re-exports
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0