heftia-0.1.0.0: Higher-order version of Freer.
Copyright(c) 2023 Yamada Ryo
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Control.Heftia.Trans

Description

A type class to abstract away the encoding details of the Heftia carrier transformers.

Synopsis

Documentation

class (forall sig f. c f => c (h sig f)) => TransHeftia c h | h -> c where Source #

A type class to abstract away the encoding details of the Heftia carrier transformers.

Minimal complete definition

liftSigT, liftLowerHT, (hoistHeftia, runElaborateH | elaborateHT)

Methods

liftSigT :: HFunctor sig => sig (h sig f) a -> h sig f a Source #

Lift a signature into a Heftia carrier transformer.

transformHT :: (c f, HFunctor sig, HFunctor sig') => (forall g. sig g ~> sig' g) -> h sig f ~> h sig' f Source #

translateT :: (c f, HFunctor sig, HFunctor sig') => (sig (h sig' f) ~> sig' (h sig' f)) -> h sig f ~> h sig' f Source #

Translate signatures embedded in a Heftia carrier transformer.

liftLowerHT :: forall sig f. (c f, HFunctor sig) => f ~> h sig f Source #

hoistHeftia :: (c f, c g, HFunctor sig) => (f ~> g) -> h sig f ~> h sig g Source #

Translate an underlying monad.

interpretLowerHT :: (HFunctor sig, c f, c g) => (f ~> h sig g) -> h sig f ~> h sig g Source #

runElaborateH :: (c f, HFunctor sig) => (sig f ~> f) -> h sig f ~> f Source #

default runElaborateH :: (c f, c (IdentityT f), HFunctor sig) => (sig f ~> f) -> h sig f ~> f Source #

elaborateHT :: (c f, c g, HFunctor sig) => (f ~> g) -> (sig g ~> g) -> h sig f ~> g Source #

reelaborateHT :: (c f, HFunctor sig) => (sig (h sig f) ~> h sig f) -> h sig f ~> h sig f Source #

Instances

Instances details
TransHeftia Monad (HeftiaChurchT :: ((Type -> TYPE LiftedRep) -> Type -> Type) -> (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Trans.Heftia.Church

Methods

liftSigT :: forall sig (f :: Type -> Type) a. HFunctor sig => sig (HeftiaChurchT sig f) a -> HeftiaChurchT sig f a Source #

transformHT :: forall (f :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type) (sig' :: (Type -> Type) -> Type -> Type). (Monad f, HFunctor sig, HFunctor sig') => (forall (g :: Type -> Type). sig g ~> sig' g) -> HeftiaChurchT sig f ~> HeftiaChurchT sig' f Source #

translateT :: forall (f :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type) (sig' :: (Type -> Type) -> Type -> Type). (Monad f, HFunctor sig, HFunctor sig') => (sig (HeftiaChurchT sig' f) ~> sig' (HeftiaChurchT sig' f)) -> HeftiaChurchT sig f ~> HeftiaChurchT sig' f Source #

liftLowerHT :: forall (sig :: (Type -> Type) -> Type -> Type) (f :: Type -> Type). (Monad f, HFunctor sig) => f ~> HeftiaChurchT sig f Source #

hoistHeftia :: forall (f :: Type -> Type) (g :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type). (Monad f, Monad g, HFunctor sig) => (f ~> g) -> HeftiaChurchT sig f ~> HeftiaChurchT sig g Source #

interpretLowerHT :: forall (sig :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (g :: Type -> Type). (HFunctor sig, Monad f, Monad g) => (f ~> HeftiaChurchT sig g) -> HeftiaChurchT sig f ~> HeftiaChurchT sig g Source #

runElaborateH :: forall (f :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type). (Monad f, HFunctor sig) => (sig f ~> f) -> HeftiaChurchT sig f ~> f Source #

elaborateHT :: forall (f :: Type -> Type) (g :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type). (Monad f, Monad g, HFunctor sig) => (f ~> g) -> (sig g ~> g) -> HeftiaChurchT sig f ~> g Source #

reelaborateHT :: forall (f :: Type -> Type) (sig :: (Type -> Type) -> Type -> Type). (Monad f, HFunctor sig) => (sig (HeftiaChurchT sig f) ~> HeftiaChurchT sig f) -> HeftiaChurchT sig f ~> HeftiaChurchT sig f Source #

heftiaToFreer :: (TransHeftia c h, TransFreer c' fr, c f, c (fr ins f), c' f) => h (LiftIns ins) f ~> fr ins f Source #

freerToHeftia :: (TransHeftia c h, TransFreer c' fr, c' f, c' (fr ins f), c' (h (LiftIns ins) f), c f) => fr ins f ~> h (LiftIns ins) f Source #

mergeHeftia :: forall h m sig sig' a c. (HFunctor sig, HFunctor sig', TransHeftia c h, c m) => h sig (h sig' m) a -> h (sig :+: sig') m a Source #