pandora-0.5.4: 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
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Monoidal (-->) (-->) (:*:) (:*:) (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

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

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

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 # 
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 (-->) (-->) (:*:) (:*:) 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 #

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) (Instruction t)) => (a -> b) -> Instruction t (u (v a)) -> Instruction t (u (v 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 (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Instruction t a -> u (Instruction t b) Source #

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

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

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

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

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

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