Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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, e :> localEs) => 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, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
- localSeqUnliftIO :: (HasCallStack, SharedSuffix es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> ((forall r. Eff localEs r -> IO r) -> IO a) -> Eff es a
- localUnlift :: (HasCallStack, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
- localUnliftIO :: (HasCallStack, SharedSuffix es handlerEs, IOE :> es) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff localEs r -> IO r) -> IO a) -> Eff es a
- localSeqLift :: (HasCallStack, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> ((forall r. Eff es r -> Eff localEs r) -> Eff es a) -> Eff es a
- localLift :: (HasCallStack, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff es r -> Eff localEs r) -> Eff es a) -> Eff es a
- withLiftMap :: (HasCallStack, SharedSuffix 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, SharedSuffix 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, SharedSuffix 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, SharedSuffix 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
- localSeqLend :: (e :> es, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> ((forall r. Eff (e : localEs) r -> Eff localEs r) -> Eff es a) -> Eff es a
- localLend :: (e :> es, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff (e : localEs) r -> Eff localEs r) -> Eff es a) -> Eff es a
- localSeqBorrow :: (e :> localEs, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> ((forall r. Eff (e : es) r -> Eff es r) -> Eff es a) -> Eff es a
- localBorrow :: (e :> localEs, SharedSuffix es handlerEs) => LocalEnv localEs handlerEs -> UnliftStrategy -> ((forall r. Eff (e : es) r -> Eff es r) -> Eff es a) -> Eff es a
- class SharedSuffix (es1 :: [Effect]) (es2 :: [Effect])
- 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 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 package.
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 involving. 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!
Integration with mtl
style effects
There exists a lot of libraries that provide their functionality as an mtl
style effect, which generally speaking is a type class that contains core
operations of the library in question.
Such effects are quite easy to use with the Eff
monad. As an example,
consider the mtl
style effect for generation of random numbers:
>>>
:{
class Monad m => MonadRNG m where randomInt :: m Int :}
Let's say the library also defines a helper function for generation of random strings:
>>>
import Control.Monad
>>>
import Data.Char
>>>
:{
randomString :: MonadRNG m => Int -> m String randomString n = map chr <$> replicateM n randomInt :}
To make it possible to use it with the Eff
monad, the first step is to
create an effect with operations that mirror the ones of a type class:
>>>
:{
data RNG :: Effect where RandomInt :: RNG m Int :}
>>>
type instance DispatchOf RNG = Dynamic
If we continued as in the example above, we'd now create top level helper
functions that execute effect operations using send
, in this case
randomInt
tied to RandomInt
. But this function is already declared by the
MonadRNG
type class! Therefore, what we do instead is provide an
orphan, canonical instance of MonadRNG
for Eff
that delegates to
the RNG
effect:
>>>
:set -XUndecidableInstances
>>>
:{
instance RNG :> es => MonadRNG (Eff es) where randomInt = send RandomInt :}
Now we only need an interpreter:
>>>
:{
runDummyRNG :: Eff (RNG : es) a -> Eff es a runDummyRNG = interpret $ \_ -> \case RandomInt -> pure 55 :}
and we can use any function that requires a MonadRNG
constraint with the
Eff
monad as long as the RNG
effect is in place:
>>>
runEff . runDummyRNG $ randomString 3
"777"
Functional dependencies
For dealing with classes that employ functional dependencies an additional trick is needed.
Consider the following:
>>>
:set -XFunctionalDependencies
>>>
:{
class Monad m => MonadInput i m | m -> i where input :: m i :}
An attempt to define the instance as in the example above leads to violation of the liberal coverage condition:
>>>
:{
instance Reader i :> es => MonadInput i (Eff es) where input = ask :} ... ...Illegal instance declaration for ‘MonadInput i (Eff es)’... ... The liberal coverage condition fails in class ‘MonadInput’... ... for functional dependency: ‘m -> i’... ...
However, there exists a dirty trick for bypassing the coverage condition, i.e. including the instance head in the context:
>>>
:{
instance (MonadInput i (Eff es), Reader i :> es) => MonadInput i (Eff es) where input = ask :}
Now the MonadInput
class can be used with the Eff
monad:
>>>
:{
double :: MonadInput Int m => m Int double = (+) <$> input <*> input :}
>>>
runPureEff . runReader @Int 3 $ double
6
Sending operations to the handler
:: (HasCallStack, DispatchOf e ~ Dynamic, e :> es) | |
=> e (Eff es) a | The operation. |
-> Eff es a |
Send an operation of the given effect to its handler for execution.
Handling effects
type EffectHandler e es Source #
= forall a localEs. (HasCallStack, e :> localEs) | |
=> 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.
:: DispatchOf e ~ Dynamic | |
=> EffectHandler e es | The effect handler. |
-> Eff (e : es) a | |
-> Eff es a |
Interpret an effect.
Note: interpret
can be turned into a reinterpret
with the use of
inject
.
:: 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
:: 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
:: 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
data LocalEnv (localEs :: [Effect]) (handlerEs :: [Effect]) Source #
Opaque representation of the Eff
environment at the point of calling the
send
function, i.e. right before the control is passed to the effect
handler.
The second type variable represents effects of a handler and is needed for
technical reasons to guarantee soundness (see
SharedSuffix
for more information).
Unlifts
:: (HasCallStack, SharedSuffix 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
.
:: (HasCallStack, SharedSuffix 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
.
:: (HasCallStack, SharedSuffix 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.
:: (HasCallStack, SharedSuffix 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
:: (HasCallStack, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> ((forall r. Eff es r -> Eff localEs r) -> Eff es a) | Continuation with the lifting function in scope. |
-> Eff es a |
:: (HasCallStack, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> UnliftStrategy | |
-> ((forall r. Eff es r -> Eff localEs r) -> Eff es a) | Continuation with the lifting function in scope. |
-> Eff es a |
Create a local lifting function with the given strategy.
Since: 2.2.1.0
:: (HasCallStack, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | Local environment. |
-> ((forall a b. (Eff es a -> Eff es b) -> Eff localEs a -> Eff localEs b) -> Eff es r) | Continuation with the lifting function in scope. |
-> Eff es r |
:: (HasCallStack, SharedSuffix 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
:: (HasCallStack, SharedSuffix 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.
:: (HasCallStack, SharedSuffix 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.
Misc
:: (e :> es, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | |
-> ((forall r. Eff (e : localEs) r -> Eff localEs r) -> Eff es a) | Continuation with the lent handler in scope. |
-> Eff es a |
Lend an effect to the local environment.
Consider the following effect:
>>>
:{
data D :: Effect where D :: D m () type instance DispatchOf D = Dynamic :}
and an auxiliary effect that requires both IOE
and D
to run:
>>>
:{
data E :: Effect runE :: (IOE :> es, D :> es) => Eff (E : es) a -> Eff es a runE = error "runE" :}
Trying to use runE
inside the handler of D
doesn't work out of the box:
>>>
:{
runD :: IOE :> es => Eff (D : es) a -> Eff es a runD = interpret $ \env -> \case D -> localSeqUnlift env $ \unlift -> do unlift . runE $ pure () :} ... ...Could not deduce ...IOE :> localEs... arising from a use of ‘runE’ ...from the context: IOE :> es ...
The problem is that runE
needs IOE :> localEs
, but only IOE :> es
is
available. This function allows us to bridge the gap:
>>>
:{
runD :: IOE :> es => Eff (D : es) a -> Eff es a runD = interpret $ \env -> \case D -> localSeqUnlift env $ \unlift -> do localSeqLend @IOE env $ \useIOE -> do unlift . useIOE . runE $ pure () :}
Since: 2.3.1.0
:: (e :> es, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | |
-> UnliftStrategy | |
-> ((forall r. Eff (e : localEs) r -> Eff localEs r) -> Eff es a) | Continuation with the lent handler in scope. |
-> Eff es a |
Lend an effect to the local environment with a given unlifting strategy.
Generalizes localSeqLend
.
Since: 2.3.1.0
:: (e :> localEs, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | |
-> ((forall r. Eff (e : es) r -> Eff es r) -> Eff es a) | Continuation with the borrowed handler in scope. |
-> Eff es a |
Borrow an effect from the local environment.
Since: 2.3.1.0
:: (e :> localEs, SharedSuffix es handlerEs) | |
=> LocalEnv localEs handlerEs | |
-> UnliftStrategy | |
-> ((forall r. Eff (e : es) r -> Eff es r) -> Eff es a) | Continuation with the borrowed handler in scope. |
-> Eff es a |
Borrow an effect from the local environment with a given unlifting strategy.
Generalizes localSeqBorrow
.
Since: 2.3.1.0
class SharedSuffix (es1 :: [Effect]) (es2 :: [Effect]) Source #
Require that both effect stacks share an opaque suffix.
Functions from the localUnlift
family utilize this constraint to guarantee
sensible usage of unlifting functions.
As an example, consider the following higher order effect:
>>>
:{
data E :: Effect where E :: m a -> E m a type instance DispatchOf E = Dynamic :}
Running local actions in a more specific environment is fine:
>>>
:{
runE1 :: Eff (E : es) a -> Eff es a runE1 = interpret $ \env -> \case E m -> runReader () $ do localSeqUnlift env $ \unlift -> unlift m :}
Running local actions in a more general environment is fine:
>>>
:{
runE2 :: Eff (E : es) a -> Eff es a runE2 = reinterpret (runReader ()) $ \env -> \case E m -> raise $ do localSeqUnlift env $ \unlift -> unlift m :}
However, running local actions in an unrelated environment is not fine as
this would make it possible to run anything within runPureEff
:
>>>
:{
runE3 :: Eff (E : es) a -> Eff es a runE3 = reinterpret (runReader ()) $ \env -> \case E m -> pure . runPureEff $ do localSeqUnlift env $ \unlift -> unlift m :} ... ...Could not deduce ...SharedSuffix '[] es... ...
Running local actions in a monomorphic effect stack is also not fine as this makes a special case of the above possible:
>>>
:{
runE4 :: Eff [E, IOE] a -> Eff '[IOE] a runE4 = interpret $ \env -> \case E m -> pure . runPureEff $ do localSeqUnlift env $ \unlift -> unlift m :} ... ...Running local actions in monomorphic effect stacks is not supported... ...
Since: 1.2.0.0
Instances
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