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

Pandora.Paradigm.Primary.Transformer.Instruction

Documentation

data Instruction t a Source #

Constructors

Enter a 
Instruct ((t :. Instruction t) := a) 

Instances

Instances details
Monad t => Monad (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

(forall (v :: Type -> Type). Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Instruction t :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

multiply :: forall (a :: k) (b :: k). (Instruction t a :*: Instruction t b) -> Instruction t (a :*: b) Source #

Liftable ((->) :: Type -> Type -> Type) Instruction Source # 
Instance details

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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t) => Lowerable ((->) :: Type -> Type -> Type) Instruction Source # 
Instance details

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 # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

(=<<) :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) -> Instruction t a Source #

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

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 # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (->) (->) (:*:) (:*:) u) => (a -> u b) -> Instruction t a -> u (Instruction t b) Source #