Copyright | (c) 2021 Xy Ren |
---|---|
License | BSD3 |
Maintainer | xy.r@outlook.com |
Stability | unstable |
Portability | non-portable (GHC only) |
Safe Haskell | None |
Language | Haskell2010 |
This module contains the IOE
effect together with a few primitives for using it, as well as interpretation
combinators for IO
-related effects. It is not usually needed because safe functionalities are re-exported in the
Cleff module.
This is an internal module and its API may change even between minor versions. Therefore you should be extra careful if you're to depend on this module.
Synopsis
- data IOE :: Effect
- primLiftIO :: IO a -> Eff es a
- primUnliftIO :: ((Eff es ~> IO) -> IO a) -> Eff es a
- thisIsPureTrustMe :: Eff (IOE ': es) ~> Eff es
- runIOE :: Eff '[IOE] ~> IO
- runPure :: Eff '[] a -> a
- type HandlerIO e es = forall esSend. Handling esSend e es => e (Eff esSend) ~> IO
- interpretIO :: IOE :> es => HandlerIO e es -> Eff (e ': es) ~> Eff es
- withToIO :: (Handling esSend e es, IOE :> es) => ((Eff esSend ~> IO) -> IO a) -> Eff es a
- fromIO :: (Handling esSend e es, IOE :> es) => IO ~> Eff esSend
The IOE
Effect
The effect for lifting and unlifting the IO
monad, allowing you to use MonadIO
, MonadUnliftIO
, PrimMonad
,
MonadCatch
, MonadThrow
and MonadMask
functionalities. This is the "final" effect that most effects eventually
are interpreted into. For example, you can do:
log ::IOE
:> es =>Eff
es () log =liftIO
(putStrLn
"Test logging")
It is not recommended to use this effect in application code, as it is too liberal and allows arbitrary IO. Ideally, this is only used in interpreting more fine-grained effects.
Note that this is not a real effect and cannot be interpreted in any way besides thisIsPureTrustMe
and
runIOE
. It is similar to Polysemy's Final
effect which also cannot be interpreted. This is mainly for
performance concern, but also that there doesn't really exist reasonable interpretations other than the current one,
given the underlying implementation of the Eff
monad.
IOE
can be a real effect though, and you can enable the dynamic-ioe
build flag to have that. However it is only
for reference purposes and should not be used in production code.
Primitive IO
functions
primLiftIO :: IO a -> Eff es a Source #
primUnliftIO :: ((Eff es ~> IO) -> IO a) -> Eff es a Source #
Give a runner function a way to run Eff
actions as an IO
computation. This function is highly unsafe and
should not be used directly; use withRunInIO
instead, or if you're interpreting higher-order effects, use
withToIO
.
Unwrapping Eff
thisIsPureTrustMe :: Eff (IOE ': es) ~> Eff es Source #
Unsafely eliminate an IOE
effect from the top of the effect stack. This is mainly for implementing effects that
uses IO
but does not do anything really impure (i.e. can be safely used unsafeDupablePerformIO
on), such as a
State effect.
runPure :: Eff '[] a -> a Source #
Unwrap a pure Eff
computation into a pure value, given that all effects are interpreted.
Effect interpretation
type HandlerIO e es = forall esSend. Handling esSend e es => e (Eff esSend) ~> IO Source #
The type of an IO
effect handler, which is a function that transforms an effect e
into IO
computations.
This is used for interpretIO
.
Combinators for interpreting higher-order effects
Orphan instances
IOE :> es => MonadBase IO (Eff es) Source # | Compatibility instance; use |
IOE :> es => MonadBaseControl IO (Eff es) Source # | Compatibility instance; use |
IOE :> es => MonadIO (Eff es) Source # | |
IOE :> es => MonadThrow (Eff es) Source # | |
IOE :> es => MonadCatch (Eff es) Source # | |
IOE :> es => MonadMask (Eff es) Source # | |
IOE :> es => PrimMonad (Eff es) Source # | |
IOE :> es => MonadUnliftIO (Eff es) Source # | |