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

Pandora.Pattern.Transformer.Hoistable

Synopsis

Documentation

class Hoistable t where Source #

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

Minimal complete definition

(/|\)

Methods

(/|\) :: Covariant u => (u ~> v) -> t u ~> t v infixr 5 Source #

hoist :: Covariant u => (u ~> v) -> t u ~> t v Source #

Instances

Instances details
Hoistable Jack Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

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

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

Hoistable Outline Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

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

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

Hoistable Tap Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

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

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> Tap u ~> Tap v Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

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

Hoistable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> Construction u ~> Construction v Source #

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

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

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

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

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u => (u ~> v) -> Day t u ~> Day t v Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

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

Methods

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

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

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