| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.IdempotentLowering
Synopsis
- (.@!) :: (Monad base, Monad m) => base (forall x. Sem r x -> m x) -> ((forall x. Sem r x -> m x) -> base (forall y. Sem (e ': r) y -> Sem r y)) -> base (forall z. Sem (e ': r) z -> m z)
- nat :: Applicative base => (forall x. m x -> n x) -> base (forall x. m x -> n x)
- liftNat :: Applicative base => (forall x. (forall y. f y -> g y) -> m x -> n x) -> (forall y. f y -> g y) -> base (forall x. m x -> n x)
- fixedNat :: forall m n base. Applicative base => ((forall x. m x -> n x) -> forall x. m x -> n x) -> base (forall x. m x -> n x)
- (.@@!) :: (Monad base, Monad m) => base (forall x. Sem r x -> m x) -> ((forall x. Sem r x -> m x) -> base (forall y. Sem (e ': r) y -> Sem r (f y))) -> base (forall z. Sem (e ': r) z -> m (f z))
- nat' :: Applicative base => (forall x. m x -> n (f x)) -> base (forall x. m x -> n (f x))
- liftNat' :: Applicative base => (forall x. (forall y. f y -> g y) -> m x -> n (f x)) -> (forall y. f y -> g y) -> base (forall x. m x -> n (f x))
- fixedNat' :: forall m n f base. Applicative base => ((forall x. m x -> n (f x)) -> forall x. m x -> n (f x)) -> base (forall x. m x -> n (f x))
Documentation
Arguments
| :: (Monad base, Monad m) | |
| => base (forall x. Sem r x -> m x) | The lowering function, likely  | 
| -> ((forall x. Sem r x -> m x) -> base (forall y. Sem (e ': r) y -> Sem r y)) | |
| -> base (forall z. Sem (e ': r) z -> m z) | 
Like .@, but useful for interpreters that wish to perform some
 initialization before being run. Most of the time, you don't want to
 duplicate this initialization every time your effect is lowered.
Consider an interpreter which wants to use an IORef to store
 intermediary state. It might begin like this:
myIntepreter
    :: Member (Lift IO) r
    => (∀ x. Sem r x -> IO x)
    -> Sem (MyEff ': r) a
    -> Sem r a
myInterpreter lower sem = do
    ref <- sendM $ newIORef 0
    go ref sem
  where
    go ref = interpretH $ e -> ...
This interpreter will do the wrong thing when composed via .@. It
 would have been correct if we didn't attempt to hide the creation of the
 IORef, but that's an unfortunate side-effect of wanting to hide
 implementation details.
Instead, we can write myInterpreter thusly:
myIntepreter
    :: (∀ x. Sem r x -> IO x)
    -> IO (∀ a. Sem (MyEff ': r) a -> Sem r a)
myInterpreter lower = do
    ref <- newIORef 0
    nat $ interpretH $ e -> ...
and use .@! (rather than .@) to compose these things together.
Note: you must enable -XImpredicativeTypes to give the correct type to
 myInterpreter here. Don't worry, it's (probably) not as scary as it
 sounds.
Since: 0.1.1.0
nat :: Applicative base => (forall x. m x -> n x) -> base (forall x. m x -> n x) Source #
This is just pure but with a type specialised for lifting interpreters.
Since: 0.1.1.0
liftNat :: Applicative base => (forall x. (forall y. f y -> g y) -> m x -> n x) -> (forall y. f y -> g y) -> base (forall x. m x -> n x) Source #
fixedNat :: forall m n base. Applicative base => ((forall x. m x -> n x) -> forall x. m x -> n x) -> base (forall x. m x -> n x) Source #
Like nat, but for higher-order interpreters that need access to
 themselves.
For example:
fixedNat$ me ->interpretH$ case SomeEffect -> ...
Arguments
| :: (Monad base, Monad m) | |
| => base (forall x. Sem r x -> m x) | The lowering function, likely  | 
| -> ((forall x. Sem r x -> m x) -> base (forall y. Sem (e ': r) y -> Sem r (f y))) | |
| -> base (forall z. Sem (e ': r) z -> m (f z)) | 
Like .@!, but for interpreters which change the resulting type --- eg.
 'Polysemy.Error.lowerError.
Since: 0.1.1.0
nat' :: Applicative base => (forall x. m x -> n (f x)) -> base (forall x. m x -> n (f x)) Source #
liftNat' :: Applicative base => (forall x. (forall y. f y -> g y) -> m x -> n (f x)) -> (forall y. f y -> g y) -> base (forall x. m x -> n (f x)) Source #