Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data BaseControl b m a
- withLowerToBase :: forall b m a. Eff (BaseControl b) m => (forall f. (forall x. m x -> b (f x)) -> b (f a)) -> m a
- gainBaseControl :: forall b m a. Eff (BaseControl b) m => (forall z. (MonadBaseControl b z, Coercible z m) => GainBaseControlC b z m a) -> m a
- runBaseControl :: Carrier m => BaseControlC m a -> m a
- baseControlToFinal :: (MonadBaseControl b m, Carrier m) => BaseControlToFinalC b m a -> m a
- class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b where
- control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a
- threadBaseControlViaClass :: forall b t m a. (MonadTrans t, Monad m, forall z. MonadBaseControl b z => MonadBaseControl b (t z), forall z. Coercible z m => Coercible (t z) (t m)) => (forall x. BaseControl b m x -> m x) -> BaseControl b (t m) a -> t m a
- powerAlgBaseControl :: forall m p a. Monad m => Algebra' p m a -> Algebra' (BaseControl m ': p) m a
- powerAlgBaseControlFinal :: forall b m p a. MonadBaseControl b m => Algebra' p m a -> Algebra' (BaseControl b ': p) m a
- newtype GainBaseControlC b z m a = GainBaseControlC {
- unGainBaseControlC :: m a
- data BaseControlC m a
- type BaseControlToFinalC b = InterpretPrimC BaseControlToFinalH (BaseControl b)
Effects
data BaseControl b m a Source #
A helper primitive effect that allows for lowering computations to a base monad.
Helper primitive effects are effects that allow you to avoid interpreting one
of your own effects as a primitive if the power needed from direct access to
the underlying monad can instead be provided by the relevant helper primitive
effect. The reason why you'd want to do this is that helper primitive effects
already have ThreadsEff
instances defined for them; so you don't have to
define any for your own effect.
The helper primitive effects offered in this library are -- in order of
ascending power -- Regional
,
Optional
, BaseControl
and Unlift
.
BaseControl
is typically used as a primitive effect.
If you define a Carrier
that relies on a novel
non-trivial monad transformer t
, then you need to make a
a
instance (if possible).
ThreadsEff
t (BaseControl
b)threadBaseControlViaClass
can help you with that.
The following threading constraints accept BaseControl
:
Instances
Actions
withLowerToBase :: forall b m a. Eff (BaseControl b) m => (forall f. (forall x. m x -> b (f x)) -> b (f a)) -> m a Source #
Gain access to a function that allows for lowering m
to the
base monad b
.
This is less versatile, but easier to use than gainBaseControl
.
gainBaseControl :: forall b m a. Eff (BaseControl b) m => (forall z. (MonadBaseControl b z, Coercible z m) => GainBaseControlC b z m a) -> m a Source #
Locally gain access to a
instance
within a region.MonadBaseControl
b
You'll need to use lift
if you want to use the MonadBaseControl
instance
with computations outside of the region.
This is common with effect handlers. For example:
import System.IO (FilePath, IOMode, Handle) import qualified System.IO as SysIO data WithFile m a where WithFile :: FilePath -> IOMode -> (Handle -> m a) -> WithFile m a runWithFile ::Eff
(BaseControl
IO) m =>SimpleInterpreterFor
WithFile m runWithFile =interpretSimple
$ case WithFile fp mode c ->gainBaseControl
$control
$ lower -> SysIO.withFile fp mode (hdl -> lower (lift (c hdl)))
Interpretations
runBaseControl :: Carrier m => BaseControlC m a -> m a Source #
Run a
effect, where the base BaseControl
mm
is the current monad.
Derivs
(BaseControlC
m) =BaseControl
m ':Derivs
m
Prims
(BaseControlC
m) =BaseControl
m ':Prims
m
baseControlToFinal :: (MonadBaseControl b m, Carrier m) => BaseControlToFinalC b m a -> m a Source #
Run a
effect, where the base BaseControl
bb
is the final base monad.
Derivs
(BaseControlToFinalC
b m) =BaseControl
b ':Derivs
m
Prims
(BaseControlToFinalC
b m) =BaseControl
b ':Prims
m
MonadBaseControl
class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b where #
Writing instances
The usual way to write a
instance for a transformer
stack over a base monad MonadBaseControl
B
is to write an instance MonadBaseControl B B
for the base monad, and MonadTransControl T
instances for every transformer
T
. Instances for
are then simply implemented using
MonadBaseControl
, ComposeSt
, defaultLiftBaseWith
.defaultRestoreM
type StM (m :: Type -> Type) a #
Monadic state that m
adds to the base monad b
.
For all base (non-transformed) monads, StM m a ~ a
:
StMIO
a ~ a StMMaybe
a ~ a StM (Either
e) a ~ a StM [] a ~ a StM ((->) r) a ~ a StMIdentity
a ~ a StMSTM
a ~ a StM (ST
s) a ~ a
If m
is a transformed monad, m ~ t b
,
is the monadic state of
the transformer StM
t
(given by its StT
from MonadTransControl
). For a
transformer stack,
is defined recursively:StM
StM (IdentityT
m) a ~ComposeSt
IdentityT
m a ~ StM m a StM (MaybeT
m) a ~ComposeSt
MaybeT
m a ~ StM m (Maybe
a) StM (ErrorT
e m) a ~ComposeSt
ErrorT
m a ~Error
e => StM m (Either
e a) StM (ExceptT
e m) a ~ComposeSt
ExceptT
m a ~ StM m (Either
e a) StM (ListT
m) a ~ComposeSt
ListT
m a ~ StM m [a] StM (ReaderT
r m) a ~ComposeSt
ReaderT
m a ~ StM m a StM (StateT
s m) a ~ComposeSt
StateT
m a ~ StM m (a, s) StM (WriterT
w m) a ~ComposeSt
WriterT
m a ~Monoid
w => StM m (a, w) StM (RWST
r w s m) a ~ComposeSt
RWST
m a ~Monoid
w => StM m (a, s, w)
liftBaseWith :: (RunInBase m b -> b a) -> m a #
liftBaseWith
is similar to liftIO
and liftBase
in that it
lifts a base computation to the constructed monad.
Instances should satisfy similar laws as the MonadIO
and MonadBase
laws:
liftBaseWith . const . return = return
liftBaseWith (const (m >>= f)) = liftBaseWith (const m) >>= liftBaseWith . const . f
The difference with liftBase
is that before lifting the base computation
liftBaseWith
captures the state of m
. It then provides the base
computation with a RunInBase
function that allows running m
computations in the base monad on the captured state:
withFileLifted :: MonadBaseControl IO m => FilePath -> IOMode -> (Handle -> m a) -> m a withFileLifted file mode action = liftBaseWith (\runInBase -> withFile file mode (runInBase . action)) >>= restoreM -- = control $ \runInBase -> withFile file mode (runInBase . action) -- = liftBaseOp (withFile file mode) action
is usually not implemented directly, but using
liftBaseWith
.defaultLiftBaseWith
Construct a m
computation from the monadic state of m
that is
returned from a RunInBase
function.
Instances should satisfy:
liftBaseWith (\runInBase -> runInBase m) >>= restoreM = m
is usually not implemented directly, but using
restoreM
.defaultRestoreM
Instances
control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a #
An often used composition: control f =
liftBaseWith
f >>= restoreM
Example:
liftedBracket :: MonadBaseControl IO m => m a -> (a -> m b) -> (a -> m c) -> m c liftedBracket acquire release action = control $ \runInBase -> bracket (runInBase acquire) (\saved -> runInBase (restoreM saved >>= release)) (\saved -> runInBase (restoreM saved >>= action))
Threading utilities
threadBaseControlViaClass :: forall b t m a. (MonadTrans t, Monad m, forall z. MonadBaseControl b z => MonadBaseControl b (t z), forall z. Coercible z m => Coercible (t z) (t m)) => (forall x. BaseControl b m x -> m x) -> BaseControl b (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance, given that ThreadsEff
t (BaseControl
b)t
lifts
for any MonadBaseControl
bb
.
Combinators for Algebra
s
powerAlgBaseControl :: forall m p a. Monad m => Algebra' p m a -> Algebra' (BaseControl m ': p) m a Source #
Strengthen an
by adding a Algebra
p m
handlerBaseControl
m
powerAlgBaseControlFinal :: forall b m p a. MonadBaseControl b m => Algebra' p m a -> Algebra' (BaseControl b ': p) m a Source #
Strengthen an
by adding a Algebra
p m
handler,
where BaseControl
bb
is the final base monad.
Carriers
newtype GainBaseControlC b z m a Source #
Instances
data BaseControlC m a Source #
Instances
type BaseControlToFinalC b = InterpretPrimC BaseControlToFinalH (BaseControl b) Source #