Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Primary.Transformer.Instruction
Documentation
data Instruction t a Source #
Constructors
Enter a | |
Instruct ((t :. Instruction t) := a) |
Instances
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Monoidal (-->) (-->) (:*:) (:*:) (Instruction t) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Semimonoidal (-->) (:*:) (:*:) (Instruction t :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods mult :: forall (a :: k) (b :: k). (Instruction t a :*: Instruction t b) --> Instruction t (a :*: b) 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 Methods (/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). Instruction u a -> Instruction v a Source # | |
Liftable ((->) :: Type -> Type -> Type) Instruction Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods lift :: Covariant (->) (->) u => u a -> Instruction u a Source # | |
(forall (t :: Type -> Type). Bindable ((->) :: Type -> Type -> Type) t, forall (t :: Type -> Type). Monoidal (-->) (-->) (:*:) (:*:) t) => Lowerable ((->) :: Type -> Type -> Type) Instruction Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods lower :: Covariant (->) (->) u => Instruction u a -> u a Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Bindable ((->) :: Type -> Type -> Type) (Instruction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods (=<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source # | |
Monad ((->) :: Type -> Type -> Type) t => Monad ((->) :: Type -> Type -> Type) (Instruction t) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Instruction t) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Instruction Methods (<-|-) :: (a -> b) -> Instruction t a -> Instruction t b Source # | |
Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Instruction t) Source # | |