| Copyright | (c) 2021 Xy Ren |
|---|---|
| License | BSD3 |
| Maintainer | xy.r@outlook.com |
| Stability | unstable |
| Portability | non-portable (GHC only) |
| Safe Haskell | None |
| Language | Haskell2010 |
Cleff.Internal.Base
Description
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 capable of 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 =>Effes () log =liftIO(putStrLn"Test logging")
It is not recommended to use this effect directly in application code, as it is too liberal and allows arbitrary IO, therefore making it harder to do proper effect management. Ideally, this is only used in interpreting more fine-grained effects.
Technical details
Note that this is not a real effect and cannot be interpreted in any way besides thisIsPureTrustMe and
runIOE. 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
withToIO :: (Handling esSend e es, IOE :> es) => ((Eff esSend ~> IO) -> IO a) -> Eff es a Source #
Temporarily gain the ability to unlift an computation into Eff esSendIO. This is analogous to
withRunInIO, and is useful in dealing with higher-order effects that involves IO. For example, the Resource
effect that supports brecketing:
data Resource m a where Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b
can be interpreted into bracket actions in IO, by converting all effect computations into
IO compucations via withToIO:
runResource ::IOE:>es =>Eff(Resource ': es) a ->Effes a runResource =interpret\case Bracket alloc dealloc use ->withToIO$ \toIO ->bracket(toIO alloc) (toIO . dealloc) (toIO . use)
fromIO :: (Handling esSend e es, IOE :> es) => IO ~> Eff esSend Source #
Lift an IO computation into . This is analogous to Eff esSendliftIO, and is only useful in dealing with
effect operations with the monad type in the negative position, for example masking:
data Mask ::Effectwhere Mask :: ((m~>m) -> m a) -> Mask m a ^ this "m" is in negative position
See how the restore :: IO a -> IO a from mask is "wrapped" into
:Eff esSend a -> Eff esSend a
runMask ::IOE:>es =>Eff(Mask ': es) a ->Effes a runMask =interpret\case Mask f ->withToIO$ \toIO ->mask$ \restore -> f (fromIO. restore . toIO)
Here, toIO from withToIO takes an to Eff esSendIO, where it can be passed into the restore function,
and the returned IO computation is recovered into Eff with fromIO.
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 # | |