Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Lifting primitive Monad types to effectful computations. We only allow a single Lifted Monad because Monads aren't commutative (e.g. Maybe (IO a) is functionally distinct from IO (Maybe a)).
Synopsis
- newtype Lift m a = Lift (m a)
- type Lifted m r = SetMember Lift (Lift m) r
- type LiftedBase m r = (SetMember Lift (Lift m) r, MonadBaseControl m (Eff r))
- lift :: SetMember Lift (Lift m) r => m a -> Eff r a
- runLift :: Monad m => Eff '[Lift m] w -> m w
- catchDynE :: forall e a r. (Lifted IO r, Exception e) => Eff r a -> (e -> Eff r a) -> Eff r a
Documentation
Lifting: emulating monad transformers
Lift (m a) |
type Lifted m r = SetMember Lift (Lift m) r Source #
A convenient alias to 'SetMember Lift (Lift m) r'
type LiftedBase m r = (SetMember Lift (Lift m) r, MonadBaseControl m (Eff r)) Source #
Same as Lifted
but with additional MonadBaseControl
constraint
lift :: SetMember Lift (Lift m) r => m a -> Eff r a Source #
embed an operation of type `m a` into the Eff
monad when Lift m
is in
a part of the effect-list.
By using SetMember, it is possible to assert that the lifted type occurs only once in the effect list