pandora-0.2.8: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Paradigm.Primary.Transformer.Construction

Documentation

data Construction t a Source #

Constructors

Construct a ((t :. Construction t) := a) 
Instances
Lowerable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Focusable Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Focus Stack a :: Type Source #

Focusable Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Focus Rose a :: Type Source #

(forall a. Chain a) => Focusable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focus Binary a :: Type Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

Alternative t => Bindable (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

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

Applicative t => Applicative (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

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

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

Covariant t => Extendable (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

extend :: (Construction t a -> b) -> Construction t a -> Construction t b Source #

duplicate :: Construction t a -> (Construction t :. Construction t) := a Source #

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

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

Avoidable t => Pointable (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

point :: a |-> Construction t Source #

(Avoidable t, Alternative t) => Monad (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

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

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

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

Semigroup (Stack a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

(+) :: Stack a -> Stack a -> Stack a Source #

Monoid (Stack a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

zero :: Stack a Source #

Covariant t => Extractable (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Covariant t => Comonad (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Setoid a => Setoid (Stack a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

(==) :: Stack a -> Stack a -> Boolean Source #

(/=) :: Stack a -> Stack a -> Boolean Source #

Focusable (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focus (Construction Wye) a :: Type Source #

Focusable (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Focus (Construction Maybe) a :: Type Source #

Focusable (Construction Stack) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Focus (Construction Stack) a :: Type Source #

Hoistable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

hoist :: Covariant u => (u ~> v) -> Construction u ~> Construction v Source #

Substructure (Left :: Type -> Wye Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Left Binary a :: Type Source #

Substructure (Right :: Type -> Wye Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Right Binary a :: Type Source #

Substructure (Just :: Type -> Maybe Type) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural Just Rose a :: Type Source #

Substructure (Left :: Type -> Wye Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Left (Construction Wye) a :: Type Source #

Substructure (Right :: Type -> Wye Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Right (Construction Wye) a :: Type Source #

Substructure (Just :: Type -> Maybe Type) (Construction Stack) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural Just (Construction Stack) a :: Type Source #

(Semigroup a, forall b. Semigroup b => Semigroup (t b)) => Semigroup (Construction t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(+) :: Construction t a -> Construction t a -> Construction t a Source #

(Monoid a, forall b. Semigroup b => Monoid (t b)) => Monoid (Construction t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

zero :: Construction t a Source #

(Setoid a, forall b. Setoid b => Setoid (t b)) => Setoid (Construction t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

(Covariant t, Covariant u) => Covariant (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(<$>) :: (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

comap :: (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

(<$) :: a -> TU Covariant Covariant u (Construction t) b -> TU Covariant Covariant u (Construction t) a Source #

($>) :: TU Covariant Covariant u (Construction t) a -> b -> TU Covariant Covariant u (Construction t) b Source #

void :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) () Source #

loeb :: TU Covariant Covariant u (Construction t) (a <-| TU Covariant Covariant u (Construction t)) -> TU Covariant Covariant u (Construction t) a Source #

(<&>) :: TU Covariant Covariant u (Construction t) a -> (a -> b) -> TU Covariant Covariant u (Construction t) b Source #

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

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

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

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

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

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

(Applicative t, Applicative u) => Applicative (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(<*>) :: TU Covariant Covariant u (Construction t) (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

apply :: TU Covariant Covariant u (Construction t) (a -> b) -> TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

(*>) :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b -> TU Covariant Covariant u (Construction t) b Source #

(<*) :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b -> TU Covariant Covariant u (Construction t) a Source #

forever :: TU Covariant Covariant u (Construction t) a -> TU Covariant Covariant u (Construction t) b Source #

(<**>) :: Applicative u0 => ((TU Covariant Covariant u (Construction t) :. u0) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. u0) := a) -> (TU Covariant Covariant u (Construction t) :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((TU Covariant Covariant u (Construction t) :. (u0 :. v)) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. (u0 :. v)) := a) -> (TU Covariant Covariant u (Construction t) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := (a -> b)) -> ((TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := a) -> (TU Covariant Covariant u (Construction t) :. (u0 :. (v :. w))) := b Source #

(Covariant t, Alternative u) => Alternative (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

(Covariant t, Avoidable u) => Avoidable (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

(Avoidable t, Pointable u) => Pointable (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

(Traversable t, Traversable u) => Traversable (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(->>) :: (Pointable u0, Applicative u0) => TU Covariant Covariant u (Construction t) a -> (a -> u0 b) -> (u0 :. TU Covariant Covariant u (Construction t)) := b Source #

traverse :: (Pointable u0, Applicative u0) => (a -> u0 b) -> TU Covariant Covariant u (Construction t) a -> (u0 :. TU Covariant Covariant u (Construction t)) := b Source #

sequence :: (Pointable u0, Applicative u0) => ((TU Covariant Covariant u (Construction t) :. u0) := a) -> (u0 :. TU Covariant Covariant u (Construction t)) := a Source #

(->>>) :: (Pointable u0, Applicative u0, Traversable v) => ((v :. TU Covariant Covariant u (Construction t)) := a) -> (a -> u0 b) -> (u0 :. (v :. TU Covariant Covariant u (Construction t))) := b Source #

(->>>>) :: (Pointable u0, Applicative u0, Traversable v, Traversable w) => ((w :. (v :. TU Covariant Covariant u (Construction t))) := a) -> (a -> u0 b) -> (u0 :. (w :. (v :. TU Covariant Covariant u (Construction t)))) := b Source #

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

type Nonempty Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Nonempty Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focus Stack a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Focus Stack a = Maybe a
type Focus Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focus Rose a = Maybe a
type Focus Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focus Binary a = Maybe a
type Focus (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focus (Construction Wye) a = a
type Focus (Construction Maybe) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Focus (Construction Maybe) a = a
type Focus (Construction Stack) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focus (Construction Stack) a = a
type Substructural (Left :: Type -> Wye Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Left :: Type -> Wye Type) Binary a = Binary a
type Substructural (Right :: Type -> Wye Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Right :: Type -> Wye Type) Binary a = Binary a
type Substructural (Just :: Type -> Maybe Type) Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Substructural (Just :: Type -> Maybe Type) Rose a = (Stack :. Construction Stack) := a
type Substructural (Left :: Type -> Wye Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Left :: Type -> Wye Type) (Construction Wye) a = (Maybe :. Construction Wye) := a
type Substructural (Right :: Type -> Wye Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Right :: Type -> Wye Type) (Construction Wye) a = (Maybe :. Construction Wye) := a
type Substructural (Just :: Type -> Maybe Type) (Construction Stack) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose