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

Pandora.Paradigm.Primary.Transformer.Construction

Documentation

data Construction t a Source #

Constructors

Construct a ((t :. Construction t) := a) 

Instances

Instances details
Insertable Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

insert :: a -> Stack a -> Stack a Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Methods

insert :: a -> Binary a -> Binary a Source #

Lowerable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

lower :: forall (u :: Type -> Type). Covariant u => Construction u ~> u Source #

Measurable 'Length Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Measural 'Length Stack a Source #

Measurable 'Heighth Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Measural 'Heighth Binary a Source #

Measurable 'Length (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Measural 'Length (Construction Maybe) a Source #

Measurable 'Heighth (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Measural 'Heighth (Construction Wye) a Source #

Monotonic a (Construction Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

reduce :: (a -> r -> r) -> r -> Construction Maybe a -> r Source #

resolve :: (a -> r) -> r -> Construction Maybe a -> r Source #

Monotonic a ((Maybe <:.> Construction Maybe) := a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

reduce :: (a -> r -> r) -> r -> ((Maybe <:.> Construction Maybe) := a) -> r Source #

resolve :: (a -> r) -> r -> ((Maybe <:.> Construction Maybe) := a) -> r Source #

(forall a. Chain a) => Insertable (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Insertable (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

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 => ((u :. Construction t) := a) -> (a -> Construction t b) -> (u :. Construction t) := b 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 #

Extendable (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Methods

(=>>) :: Tap (Delta <:.> Stream) a -> (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) b Source #

(<<=) :: (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> Tap (Delta <:.> Stream) b Source #

extend :: (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> Tap (Delta <:.> Stream) b Source #

duplicate :: Tap (Delta <:.> Stream) a -> (Tap (Delta <:.> Stream) :. Tap (Delta <:.> Stream)) := a Source #

(=<=) :: (Tap (Delta <:.> Stream) b -> c) -> (Tap (Delta <:.> Stream) a -> b) -> Tap (Delta <:.> Stream) a -> c Source #

(=>=) :: (Tap (Delta <:.> Stream) a -> b) -> (Tap (Delta <:.> Stream) b -> c) -> Tap (Delta <:.> Stream) a -> c Source #

($=>>) :: Covariant u => ((u :. Tap (Delta <:.> Stream)) := a) -> (Tap (Delta <:.> Stream) a -> b) -> (u :. Tap (Delta <:.> Stream)) := b Source #

(<<=$) :: Covariant u => ((u :. Tap (Delta <:.> Stream)) := a) -> (Tap (Delta <:.> Stream) a -> b) -> (u :. Tap (Delta <:.> Stream)) := b Source #

Extendable (Tap (Delta <:.> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

(=>>) :: Tap (Delta <:.> Stack) a -> (Tap (Delta <:.> Stack) a -> b) -> Tap (Delta <:.> Stack) b Source #

(<<=) :: (Tap (Delta <:.> Stack) a -> b) -> Tap (Delta <:.> Stack) a -> Tap (Delta <:.> Stack) b Source #

extend :: (Tap (Delta <:.> Stack) a -> b) -> Tap (Delta <:.> Stack) a -> Tap (Delta <:.> Stack) b Source #

duplicate :: Tap (Delta <:.> Stack) a -> (Tap (Delta <:.> Stack) :. Tap (Delta <:.> Stack)) := a Source #

(=<=) :: (Tap (Delta <:.> Stack) b -> c) -> (Tap (Delta <:.> Stack) a -> b) -> Tap (Delta <:.> Stack) a -> c Source #

(=>=) :: (Tap (Delta <:.> Stack) a -> b) -> (Tap (Delta <:.> Stack) b -> c) -> Tap (Delta <:.> Stack) a -> c Source #

($=>>) :: Covariant u => ((u :. Tap (Delta <:.> Stack)) := a) -> (Tap (Delta <:.> Stack) a -> b) -> (u :. Tap (Delta <:.> Stack)) := b Source #

(<<=$) :: Covariant u => ((u :. Tap (Delta <:.> Stack)) := a) -> (Tap (Delta <:.> Stack) a -> b) -> (u :. Tap (Delta <:.> Stack)) := 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 #

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

(<<=$) :: Covariant u => ((u :. Construction t) := a) -> (Construction t a -> b) -> (u :. Construction t) := b 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

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 #

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 #

Nullable Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Methods

null :: forall (a :: k). (Predicate :. Stack) := a Source #

Nullable Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Methods

null :: forall (a :: k). (Predicate :. Rose) := a Source #

Nullable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Methods

null :: forall (a :: k). (Predicate :. Binary) := a Source #

Hoistable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Focusable ('Root :: Type -> Location Type) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Focusing 'Root Rose a Source #

(forall a. Chain a) => Focusable ('Root :: Type -> Location Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focusing 'Root Binary a Source #

Focusable ('Head :: Type -> Location Type) Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Focusing 'Head Stack a Source #

Focusable ('Root :: Type -> Location Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focusing 'Root (Construction Wye) a Source #

Focusable ('Root :: Type -> Location Type) (Construction Stack) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Focusing 'Root (Construction Stack) a Source #

Focusable ('Head :: Type -> Location Type) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Focusing 'Head (Construction Maybe) a Source #

Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) Stack a2 Source #

Rotatable ('Right ('Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Right 'Zig) (Construction Wye) a Source #

Rotatable ('Left ('Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Left 'Zig) (Construction Wye) a Source #

Rotatable ('Right ('Zig ('Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Right ('Zig 'Zag)) (Construction Wye) a Source #

Rotatable ('Left ('Zig ('Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Left ('Zig 'Zag)) (Construction Wye) a Source #

Rotatable ('Right ('Zig ('Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Right ('Zig 'Zig)) (Construction Wye) a Source #

Rotatable ('Left ('Zig ('Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Rotational ('Left ('Zig 'Zig)) (Construction Wye) a Source #

Setoid a2 => Substructure ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'All) (Construction Maybe) a2 Source #

Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) (Construction Maybe) a2 Source #

Rotatable ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

(Semigroup a, forall b. Semigroup b => Semigroup (t b), Covariant t) => 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), Covariant t) => 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), Covariant t) => Setoid (Construction t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Substructure ('Tail :: a1 -> Segment a1) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail Stack a2 Source #

Substructure ('Just :: a1 -> Maybe a1) Rose a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just Rose a2 Source #

Substructure ('Right :: a1 -> Wye a1) Binary a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Right Binary a2 Source #

Substructure ('Left :: a1 -> Wye a1) Binary a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Left Binary a2 Source #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Rotational 'Right (Tap (Delta <:.> Stream)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Rotational 'Left (Tap (Delta <:.> Stream)) a Source #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Right (Tap (Delta <:.> Construction Maybe)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Left (Tap (Delta <:.> Construction Maybe)) a Source #

Rotatable ('Right :: a -> Wye a) (Tap (Delta <:.> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Right (Tap (Delta <:.> Stack)) a Source #

Rotatable ('Left :: a -> Wye a) (Tap (Delta <:.> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Rotational 'Left (Tap (Delta <:.> Stack)) a Source #

Substructure ('Tail :: a1 -> Segment a1) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail (Construction Maybe) a2 Source #

Substructure ('Just :: a1 -> Maybe a1) (Construction Stack) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just (Construction Stack) a2 Source #

Substructure ('Right :: a1 -> Wye a1) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Right (Construction Wye) a2 Source #

Substructure ('Left :: a1 -> Wye a1) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Left (Construction Wye) a2 Source #

Rotatable ('Up :: a -> Vertical a) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

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 Zipper Stream Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Zipper Stack Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Measural 'Length Stack a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Measural 'Heighth Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Measural 'Length (Construction Maybe) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Measural 'Heighth (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Zipper (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Zipper (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Focusing ('Root :: Type -> Location Type) Rose a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focusing ('Root :: Type -> Location Type) Rose a = Maybe a
type Focusing ('Root :: Type -> Location Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focusing ('Root :: Type -> Location Type) Binary a = Maybe a
type Focusing ('Head :: Type -> Location Type) Stack a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Focusing ('Head :: Type -> Location Type) Stack a = Maybe a
type Focusing ('Root :: Type -> Location Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focusing ('Root :: Type -> Location Type) (Construction Wye) a = a
type Focusing ('Root :: Type -> Location Type) (Construction Stack) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Focusing ('Root :: Type -> Location Type) (Construction Stack) a = a
type Focusing ('Head :: Type -> Location Type) (Construction Maybe) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Focusing ('Head :: Type -> Location Type) (Construction Maybe) a = a
type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 = a2 |-> Stack
type Rotational ('Right ('Zig :: a1 -> Splay a1) :: Wye (a1 -> Splay a1)) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Right ('Zig :: a1 -> Splay a1) :: Wye (a1 -> Splay a1)) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Rotational ('Left ('Zig :: a1 -> Splay a1) :: Wye (a1 -> Splay a1)) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Left ('Zig :: a1 -> Splay a1) :: Wye (a1 -> Splay a1)) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Rotational ('Right ('Zig ('Zag :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Right ('Zig ('Zag :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Rotational ('Left ('Zig ('Zag :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Left ('Zig ('Zag :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Rotational ('Right ('Zig ('Zig :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Right ('Zig ('Zig :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Rotational ('Left ('Zig ('Zig :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

type Rotational ('Left ('Zig ('Zig :: a1 -> Splay a1)) :: Wye (Splay (a1 -> Splay a1))) (Construction Wye) a2 = Maybe (Construction Wye a2)
type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack
type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack
type Rotational ('Down ('Right :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Left :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Tail :: a1 -> Segment a1) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Tail :: a1 -> Segment a1) Stack a2 = Stack a2
type Substructural ('Just :: a1 -> Maybe a1) Rose a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Substructural ('Just :: a1 -> Maybe a1) Rose a2 = (Stack :. Construction Stack) := a2
type Substructural ('Right :: a1 -> Wye a1) Binary a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Right :: a1 -> Wye a1) Binary a2 = Binary a2
type Substructural ('Left :: a1 -> Wye a1) Binary a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Left :: a1 -> Wye a1) Binary a2 = Binary a2
type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 = Tap (Delta <:.> Stream) a2
type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stream)) a2 = Tap (Delta <:.> Stream) a2
type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Construction Maybe)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Construction Maybe)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Right :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 = (Maybe :. Zipper Stack) := a2
type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Rotational ('Left :: a1 -> Wye a1) (Tap (Delta <:.> Stack)) a2 = (Maybe :. Zipper Stack) := a2
type Substructural ('Tail :: a1 -> Segment a1) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Tail :: a1 -> Segment a1) (Construction Maybe) a2 = Stack a2
type Substructural ('Just :: a1 -> Maybe a1) (Construction Stack) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

type Substructural ('Right :: a1 -> Wye a1) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Right :: a1 -> Wye a1) (Construction Wye) a2 = (Maybe :. Construction Wye) := a2
type Substructural ('Left :: a1 -> Wye a1) (Construction Wye) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural ('Left :: a1 -> Wye a1) (Construction Wye) a2 = (Maybe :. Construction Wye) := a2
type Rotational ('Up :: a1 -> Vertical a1) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

(.-+) :: Covariant t => (a |-> t) -> a |-> Construction t infixr 7 Source #