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

Pandora.Pattern.Transformer.Hoistable

Synopsis

Documentation

class Hoistable m t where Source #

When providing a new instance, you should ensure it satisfies one law:
* Exactly morphism: (identity /|\) ≡ identity
* Interpreted of morphisms: (f . g /|\) ≡ (f /|\) . (g /|\)

Methods

(/|\) :: Covariant m m u => (forall a. m (u a) (v a)) -> forall a. m (t u a) (t v a) infixr 5 Source #

Instances

Instances details
Hoistable ((->) :: Type -> Type -> Type) Outline Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Outline u a -> Outline v a Source #

Hoistable ((->) :: Type -> Type -> Type) Jack Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Jack u a -> Jack v a Source #

Hoistable ((->) :: Type -> Type -> Type) Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Tap u a -> Tap v a Source #

(forall (v :: Type -> Type). Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v) => Hoistable ((->) :: Type -> Type -> Type) Instruction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Instruction u a -> Instruction v a Source #

(forall (u :: Type -> Type). Semimonoidal (<--) (:*:) (:*:) u, forall (u :: Type -> Type). Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Hoistable ((->) :: Type -> Type -> Type) Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Construction u a -> Construction v a Source #

Hoistable ((->) :: Type -> Type -> Type) (Day t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Day t u a -> Day t v a Source #

Hoistable ((->) :: Type -> Type -> Type) (Schematic Monad t) => Hoistable ((->) :: Type -> Type -> Type) ((:>) t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

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

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). (t :> u) a -> (t :> v) a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Backwards u a -> Backwards v a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Reverse u a -> Reverse v a Source #

Hoistable ((->) :: Type -> Type -> Type) (Schematic Comonad t) => Hoistable ((->) :: Type -> Type -> Type) ((:<) t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

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

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). (t :< u) a -> (t :< v) a Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). TU Covariant Covariant t u a -> TU Covariant Covariant t v a Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable ((->) :: Type -> Type -> Type) (TT Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TT

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). TT Covariant Covariant t u a -> TT Covariant Covariant t v a Source #