| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Pandora.Pattern.Transformer.Hoistable
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
| Hoistable Outline Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Outline | |
| Hoistable Jack Source # | |
| (forall (v :: Type -> Type). Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v) => Hoistable Instruction Source # | |
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 # | |
| (forall (u :: Type -> Type). Semimonoidal (<--) (:*:) (:*:) u) => Hoistable Construction Source # | |
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 Tap Source # | |
| Hoistable (Day t :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Day | |
| Hoistable (Schematic Monad t) => Hoistable ((:>) t :: (Type -> Type) -> Type -> Type) Source # | |
| Hoistable (Backwards :: (Type -> Type) -> Type -> Type) Source # | |
| Hoistable (Reverse :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Reverse | |
| Hoistable (Schematic Comonad t) => Hoistable ((:<) t :: (Type -> Type) -> Type -> Type) Source # | |
| Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
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 # | |