cleff-0.1.0.0: Fast and concise extensible effects
Safe HaskellNone
LanguageHaskell2010

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

The IOE effect

data IOE :: Effect Source #

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 #

Lift an IO computation into Eff. This function is highly unsafe and should not be used directly; use liftIO instead, or if you're interpreting higher-order effects, use fromIO.

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.

runEff :: Eff '[] a -> IO a Source #

Extract the IO computation out of an Eff given no effect remains on the stack.

runIOE :: Eff '[IOE] ~> IO Source #

Unwrap an Eff computation with side effects into an IO computation, given that all effects other than IOE are interpreted.

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 e es esSend => 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.

interpretIO :: IOE :> es => HandlerIO e es -> Eff (e ': es) ~> Eff es Source #

Interpret an effect in terms of IO, by transforming an effect into IO computations.

interpretIO f = interpret (liftIO . f)

Combinators for interpreting higher-order effects

withToIO :: (Handling e es esSend, IOE :> es) => ((Eff esSend ~> IO) -> IO a) -> Eff es a Source #

Temporarily gain the ability to unlift an Eff esSend computation into IO. This is useful for dealing with higher-order effects that involves IO.

fromIO :: (Handling e es esSend, IOE :> es) => IO ~> Eff esSend Source #

Lift an IO computation into Eff esSend. This is useful for dealing with effect operations with the monad type in the negative position within IOE, like masking.

Orphan instances

IOE :> es => MonadBase IO (Eff es) Source #

Compatibility instance; use MonadIO if possible.

Instance details

Methods

liftBase :: IO α -> Eff es α #

IOE :> es => MonadBaseControl IO (Eff es) Source #

Compatibility instance; use MonadUnliftIO if possible.

Instance details

Associated Types

type StM (Eff es) a #

Methods

liftBaseWith :: (RunInBase (Eff es) IO -> IO a) -> Eff es a #

restoreM :: StM (Eff es) a -> Eff es a #

IOE :> es => MonadIO (Eff es) Source # 
Instance details

Methods

liftIO :: IO a -> Eff es a #

IOE :> es => MonadThrow (Eff es) Source # 
Instance details

Methods

throwM :: Exception e => e -> Eff es a #

IOE :> es => MonadCatch (Eff es) Source # 
Instance details

Methods

catch :: Exception e => Eff es a -> (e -> Eff es a) -> Eff es a #

IOE :> es => MonadMask (Eff es) Source # 
Instance details

Methods

mask :: ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b #

uninterruptibleMask :: ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b #

generalBracket :: Eff es a -> (a -> ExitCase b -> Eff es c) -> (a -> Eff es b) -> Eff es (b, c) #

IOE :> es => PrimMonad (Eff es) Source # 
Instance details

Associated Types

type PrimState (Eff es) #

Methods

primitive :: (State# (PrimState (Eff es)) -> (# State# (PrimState (Eff es)), a #)) -> Eff es a #

IOE :> es => MonadUnliftIO (Eff es) Source # 
Instance details

Methods

withRunInIO :: ((forall a. Eff es a -> IO a) -> IO b) -> Eff es b #