Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 /|\)
(/|\) :: Covariant m m u => (forall a. m (u a) (v a)) -> forall a. m (t u a) (t v a) infixr 5 Source #
Instances
Hoistable ((->) :: Type -> Type -> Type) Outline Source # | |
Hoistable ((->) :: Type -> Type -> Type) Jack Source # | |
Hoistable ((->) :: Type -> Type -> Type) Tap Source # | |
(forall (v :: Type -> Type). Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v) => Hoistable ((->) :: Type -> Type -> Type) Instruction Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction (/|\) :: 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 # | |
Defined in Pandora.Paradigm.Primary.Transformer.Construction (/|\) :: 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 # | |
Hoistable ((->) :: Type -> Type -> Type) (Schematic Monad t) => Hoistable ((->) :: Type -> Type -> Type) ((:>) t :: (Type -> Type) -> Type -> Type) Source # | |
Hoistable ((->) :: Type -> Type -> Type) (Backwards :: (Type -> Type) -> Type -> Type) Source # | |
Hoistable ((->) :: Type -> Type -> Type) (Reverse :: (Type -> Type) -> Type -> Type) Source # | |
Hoistable ((->) :: Type -> Type -> Type) (Schematic Comonad t) => Hoistable ((->) :: Type -> Type -> Type) ((:<) t :: (Type -> Type) -> Type -> Type) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable ((->) :: Type -> Type -> Type) (TU Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Hoistable ((->) :: Type -> Type -> Type) (TT Covariant Covariant t :: (Type -> Type) -> Type -> Type) Source # | |