Copyright | (c) 2023 Yamada Ryo |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Control.Monad.Trans.Freer.Church
Description
A Church-encoded Freer transformer.
Synopsis
- newtype FreerChurchT (ins :: Instruction) f a = FreerChurchT {
- unFreerChurchT :: HeftiaChurchT (LiftIns ins) f a
Documentation
newtype FreerChurchT (ins :: Instruction) f a Source #
A Church-encoded Freer transformer.
Constructors
FreerChurchT | |
Fields
|
Instances
TransFreer Monad (FreerChurchT :: Instruction -> (Type -> Type) -> Type -> TYPE LiftedRep) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods liftInsT :: forall (ins :: k -> Type) (f :: k -> Type). ins ~> FreerChurchT ins f Source # liftLowerFT :: forall (ins :: k -> Type) (f :: k -> Type). Monad f => f ~> FreerChurchT ins f Source # transformT :: forall (f :: k -> Type) (ins :: k -> Type) (ins' :: k -> Type). Monad f => (ins ~> ins') -> FreerChurchT ins f ~> FreerChurchT ins' f Source # hoistFreer :: forall (f :: k -> Type) (g :: k -> Type) (ins :: k -> Type). (Monad f, Monad g) => (f ~> g) -> FreerChurchT ins f ~> FreerChurchT ins g Source # interposeLowerT :: forall (f :: k -> Type) (g :: k -> Type) (ins :: k -> Type). (Monad f, Monad g) => (f ~> FreerChurchT ins g) -> FreerChurchT ins f ~> FreerChurchT ins g Source # runInterpretF :: forall f (ins :: k -> Type) (a :: k). Monad f => (ins ~> f) -> FreerChurchT ins f a -> f a Source # interpretFT :: forall (f :: k -> Type) (g :: k -> Type) (ins :: k -> Type). (Monad f, Monad g) => (f ~> g) -> (ins ~> g) -> FreerChurchT ins f ~> g Source # reinterpretFT :: forall (f :: k -> Type) (ins :: k -> Type). Monad f => (ins ~> FreerChurchT ins f) -> FreerChurchT ins f ~> FreerChurchT ins f Source # | |
MonadTransFreer (FreerChurchT :: Instruction -> (Type -> Type) -> Type -> TYPE LiftedRep) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods interpretMK :: forall (m :: Type -> Type) (ins :: Type -> Type) r. Monad m => (ins ~> ContT r m) -> FreerChurchT ins m ~> ContT r m Source # reinterpretMK :: forall (m :: Type -> Type) (ins :: Type -> Type) r. Monad m => (ins ~> ContT r (FreerChurchT ins m)) -> FreerChurchT ins m ~> ContT r (FreerChurchT ins m) Source # interpretMT :: forall (m :: Type -> Type) (t :: (Type -> Type) -> Type -> Type) (ins :: Type -> Type). (Monad m, MonadTrans t, Monad (t m)) => (ins ~> t m) -> FreerChurchT ins m ~> t m Source # reinterpretMT :: forall (m :: Type -> Type) (t :: (Type -> Type) -> Type -> Type) (n :: Type -> Type) (ins :: Type -> Type). (Monad m, MonadTrans t, Coercible n (FreerChurchT ins m), Monad (t n), Monad n) => (ins ~> t n) -> FreerChurchT ins m ~> t n Source # | |
MonadTrans (FreerChurchT ins :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods lift :: Monad m => m a -> FreerChurchT ins m a # | |
Applicative (FreerChurchT ins m) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods pure :: a -> FreerChurchT ins m a # (<*>) :: FreerChurchT ins m (a -> b) -> FreerChurchT ins m a -> FreerChurchT ins m b # liftA2 :: (a -> b -> c) -> FreerChurchT ins m a -> FreerChurchT ins m b -> FreerChurchT ins m c # (*>) :: FreerChurchT ins m a -> FreerChurchT ins m b -> FreerChurchT ins m b # (<*) :: FreerChurchT ins m a -> FreerChurchT ins m b -> FreerChurchT ins m a # | |
Functor (FreerChurchT ins m) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods fmap :: (a -> b) -> FreerChurchT ins m a -> FreerChurchT ins m b # (<$) :: a -> FreerChurchT ins m b -> FreerChurchT ins m a # | |
Monad (FreerChurchT ins m) Source # | |
Defined in Control.Monad.Trans.Freer.Church Methods (>>=) :: FreerChurchT ins m a -> (a -> FreerChurchT ins m b) -> FreerChurchT ins m b # (>>) :: FreerChurchT ins m a -> FreerChurchT ins m b -> FreerChurchT ins m b # return :: a -> FreerChurchT ins m a # |