pandora-0.3.1: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Paradigm.Primary.Transformer.Instruction

Documentation

data Instruction t a Source #

Constructors

Enter a 
Instruct ((t :. Instruction t) := a) 
Instances
Liftable Instruction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

lift :: Covariant u => u ~> Instruction u Source #

Covariant t => Covariant (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

comap :: (a -> b) -> Instruction t a -> Instruction t b Source #

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

($>) :: Instruction t a -> b -> Instruction t b Source #

void :: Instruction t a -> Instruction t () Source #

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

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

(<$$>) :: Covariant u => (a -> b) -> ((Instruction t :. u) := a) -> (Instruction t :. u) := b Source #

(<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((Instruction t :. (u :. v)) := a) -> (Instruction t :. (u :. v)) := b Source #

(<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Instruction t :. (u :. (v :. w))) := a) -> (Instruction t :. (u :. (v :. w))) := b Source #

(<&&>) :: Covariant u => ((Instruction t :. u) := a) -> (a -> b) -> (Instruction t :. u) := b Source #

(<&&&>) :: (Covariant u, Covariant v) => ((Instruction t :. (u :. v)) := a) -> (a -> b) -> (Instruction t :. (u :. v)) := b Source #

(<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Instruction t :. (u :. (v :. w))) := a) -> (a -> b) -> (Instruction t :. (u :. (v :. w))) := b Source #

Covariant t => Bindable (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

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

bind :: (a -> Instruction t b) -> Instruction t a -> Instruction t b Source #

join :: ((Instruction t :. Instruction t) := a) -> Instruction t a Source #

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

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

($>>=) :: Covariant u => (a -> Instruction t b) -> ((u :. Instruction t) := a) -> (u :. Instruction t) := b Source #

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

Covariant t => Applicative (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

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

apply :: Instruction t (a -> b) -> Instruction t a -> Instruction t b Source #

(*>) :: Instruction t a -> Instruction t b -> Instruction t b Source #

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

forever :: Instruction t a -> Instruction t b Source #

(<**>) :: Applicative u => ((Instruction t :. u) := (a -> b)) -> ((Instruction t :. u) := a) -> (Instruction t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Instruction t :. (u :. v)) := (a -> b)) -> ((Instruction t :. (u :. v)) := a) -> (Instruction t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Instruction t :. (u :. (v :. w))) := (a -> b)) -> ((Instruction t :. (u :. (v :. w))) := a) -> (Instruction t :. (u :. (v :. w))) := b Source #

Alternative t => Alternative (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Avoidable t => Avoidable (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

empty :: Instruction t a Source #

Covariant t => Pointable (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

point :: a |-> Instruction t Source #

Traversable t => Traversable (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

(->>) :: (Pointable u, Applicative u) => Instruction t a -> (a -> u b) -> (u :. Instruction t) := b Source #

traverse :: (Pointable u, Applicative u) => (a -> u b) -> Instruction t a -> (u :. Instruction t) := b Source #

sequence :: (Pointable u, Applicative u) => ((Instruction t :. u) := a) -> (u :. Instruction t) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Instruction t) := a) -> (a -> u b) -> (u :. (v :. Instruction t)) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Instruction t)) := a) -> (a -> u b) -> (u :. (w :. (v :. Instruction t))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Instruction t))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Instruction t)))) := b Source #