pandora-0.3.4: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Pattern.Transformer.Liftable

Synopsis

Documentation

class Liftable t where Source #

When providing a new instance, you should ensure it satisfies one law:
* Interchange: lift . point ≡ point

Methods

lift :: Covariant u => u ~> t u Source #

Instances

Instances details
Liftable Yoneda Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Yoneda u Source #

Liftable Jack Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Jack u Source #

Liftable Instruction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Instruction u Source #

Liftable Outline Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Outline u Source #

Liftable (Schematic Monad t) => Liftable ((:>) t) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> (t :> u) Source #

Liftable (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Backwards u Source #

Liftable (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Reverse u Source #

(forall (u :: Type -> Type). Bindable u) => Liftable (Continuation r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Continuation r u Source #

(Adjoint t' t, Distributive t) => Liftable (t <:<.>:> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> (t <:<.>:> t') u Source #

Avoidable t => Liftable (U_T Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.U_T

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> U_T Covariant Covariant t u Source #

Avoidable t => Liftable (T_U Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> T_U Covariant Covariant t u Source #

Pointable t => Liftable (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> UT Covariant Covariant t u Source #

Pointable t => Liftable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> TU Covariant Covariant t u Source #