pandora-0.4.6: 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
Stack List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Measurable 'Length List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Measural 'Length List a Source #

Measurable 'Heighth Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth Binary a Source #

Measurable 'Length (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Measural 'Length (Construction Maybe) a Source #

Measurable 'Heighth (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth (Construction Wye) a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

Semigroup (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Monoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

zero :: List a Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

(!=) :: List a -> List a -> Boolean Source #

(forall (u :: Type -> Type). Semimonoidal (<--) (:*:) (:*:) u) => Hoistable Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

Nullable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Nullable Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Methods

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

Nullable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

multiply :: forall (a :: k) (b :: k). (Construction t a :*: Construction t b) <-- Construction t (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List :: Type -> Type Source #

Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'All) List :: Type -> Type Source #

Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'First) List :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) List :: Type -> Type Source #

Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into (o ds)) Binary :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into (o ds)) <:.> Binary) ~> Morphing ('Into (o ds)) Binary Source #

Morphable ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right 'Zig)) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left 'Zig)) Binary :: Type -> Type Source #

Morphable ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zag))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zag))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zig))) Binary :: Type -> Type Source #

Morphable ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zig))) Binary :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Associated Types

type Morphing ('Into (Construction Maybe)) (Vector r) :: Type -> Type Source #

Morphable ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) :: Type -> Type Source #

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Construction Maybe) :: Type -> Type Source #

Morphable ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Associated Types

type Morphing ('Into List) (Vector r) :: Type -> Type Source #

Morphable ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (Construction Wye) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Stream <:.:> Stream) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((List <:.:> List) := (:*:))) :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right 'Zig)) (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left 'Zig)) (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zag))) (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zag))) (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Right ('Zig 'Zig))) (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Morphing ('Rotate ('Left ('Zig 'Zig))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed (Construction Maybe) key) :: Type -> Type Source #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed List key) :: Type -> Type Source #

Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Rose k) :: Type -> Type Source #

Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed (Construction Wye) key) :: Type -> Type Source #

Chain k => Morphable ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Vary 'Element) (Prefixed Binary k) :: Type -> Type Source #

Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Binary k) :: Type -> Type Source #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

(Semigroup a, forall b. Semigroup b => Semigroup (t b), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (<--) (:*:) (:*:) 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 #

Semigroup (Construction Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

(forall (u :: Type -> Type). Semimonoidal (<--) (:*:) (:*:) u) => Lowerable ((->) :: Type -> Type -> Type) Construction Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

lower :: Covariant (->) (->) u => Construction u a -> u a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Extendable ((->) :: Type -> Type -> Type) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

Morphable ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Pop List :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Push List :: Type -> Type Source #

Morphable ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert Binary :: Type -> Type Source #

Substructure ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Tail List :: Type -> Type Source #

type Substance 'Tail List :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Root List :: Type -> Type Source #

type Substance 'Root List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Right Binary :: Type -> Type Source #

type Substance 'Right Binary :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Left Binary :: Type -> Type Source #

type Substance 'Left Binary :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Push (Construction Maybe) :: Type -> Type Source #

Morphable ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert (Construction Wye) :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Root (Construction Maybe) :: Type -> Type Source #

type Substance 'Root (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Tail (Construction Maybe) :: Type -> Type Source #

type Substance 'Tail (Construction Maybe) :: Type -> Type Source #

Substructure ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Available 'Tail (Construction List) :: Type -> Type Source #

type Substance 'Tail (Construction List) :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Available 'Root (Construction List) :: Type -> Type Source #

type Substance 'Root (Construction List) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Right (Construction Wye) :: Type -> Type Source #

type Substance 'Right (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Left (Construction Wye) :: Type -> Type Source #

type Substance 'Left (Construction Wye) :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Root (Construction Wye) :: Type -> Type Source #

type Substance 'Root (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (->) (->) (:*:) (:*:) u) => (a -> u b) -> Tap ((List <:.:> List) := (:*:)) a -> u (Tap ((List <:.:> List) := (:*:)) b) Source #

type Nonempty List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Nonempty Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Combinative List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Measural 'Length List a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Measural 'Heighth Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List = (Predicate <:.:> Maybe) := ((->) :: Type -> Type -> Type)
type Morphing ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into (o ds) :: Morph a) Binary = Maybe <:.> Morphing ('Into (o ds)) (Construction Wye)
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) Binary = Binary
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) Binary = Binary
type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

type Morphing ('Into (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

type Morphing ('Into List) (Vector r) = List
type Morphing ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) = Tap ((Stream <:.:> Stream) := (:*:))
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) = Maybe <:.> Tap ((List <:.:> List) := (:*:))
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) = Maybe <:.> Tap ((List <:.:> List) := (:*:))
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) = (Predicate <:.:> Maybe) := ((->) :: Type -> Type -> Type)
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Maybe) key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List k) :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction Wye) key) = ((->) key :: Type -> Type) <:.> Maybe
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = (((:*:) k <:.> Identity) <:.:> Prefixed Binary k) := ((->) :: Type -> Type -> Type)
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((->) k :: Type -> Type) <:.> Maybe
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Zipper List (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper List (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((List <:.:> List) := (:*:))
type Morphing ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Pop :: a -> Morph a) List = List
type Morphing ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Push :: a -> Morph a) List = (Identity <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) Binary = (((Identity <:.:> Comparison) := (:*:)) <:.:> Binary) := ((->) :: Type -> Type -> Type)
type Available ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Tail :: a -> Segment a) List = Identity
type Available ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Root :: a -> Segment a) List = Maybe
type Available ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Right :: a -> Wye a) Binary = Maybe
type Available ('Left :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Left :: a -> Wye a) Binary = Maybe
type Substance ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: a -> Segment a) List = List
type Substance ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Root :: a -> Segment a) List = Identity
type Substance ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left :: a -> Wye a) Binary = Construction Wye
type Morphing ('Push :: a -> Morph a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Push :: a -> Morph a) (Construction Maybe) = (Identity <:.:> Construction Maybe) := ((->) :: Type -> Type -> Type)
type Morphing ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) (Construction Wye) = (((Identity <:.:> Comparison) := (:*:)) <:.:> Construction Wye) := ((->) :: Type -> Type -> Type)
type Available ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Available ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Available ('Right :: a -> Wye a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Right :: a -> Wye a) (Construction Wye) = Maybe
type Available ('Left :: a -> Wye a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Available ('Left :: a -> Wye a) (Construction Wye) = Maybe
type Available ('Root :: a -> Segment a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Right :: a -> Wye a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left :: a -> Wye a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Root :: a -> Segment a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Zipper (Construction Identity) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Zipper (Construction Identity) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((Stream <:.:> Stream) := (:*:))
type Zipper (Construction Maybe) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper (Construction Maybe) (('Left :: a1 -> Wye a1) ::: ('Right :: a2 -> Wye a2) :: k -> k' -> Type) = Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))
type Zipper (Construction Wye) (('Up :: a1 -> Vertical a1) ::: ('Down ('Left :: a2 -> Wye a2) ::: 'Down ('Right :: a3 -> Wye a3) :: k2 -> k'2 -> Type) :: k1 -> k'1 -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Zipper (Construction Wye) (('Up :: a1 -> Vertical a1) ::: ('Down ('Left :: a2 -> Wye a2) ::: 'Down ('Right :: a3 -> Wye a3) :: k2 -> k'2 -> Type) :: k1 -> k'1 -> Type) = (Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)

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