Lowerable Construction Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Stack List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Measurable 'Length List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Measurable 'Heighth Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Measurable 'Length (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Measurable 'Heighth (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Monotonic a (Construction Maybe a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Monotonic a ((Maybe <:.> Construction Maybe) := a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Covariant t => Covariant (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Alternative t => Bindable (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Applicative t => Applicative (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Extendable (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
Extendable (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Covariant t => Extendable (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Covariant t => Extractable (Construction t) Source # | |
|
Covariant t => Comonad (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Avoidable t => Pointable (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
(Avoidable t, Alternative t) => Monad (Construction t) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Traversable (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List Methods (->>) :: (Pointable u, Applicative u) => Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> (a -> u b) -> (u :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) := b Source # traverse :: (Pointable u, Applicative u) => (a -> u b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> (u :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) := b Source # sequence :: (Pointable u, Applicative u) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := a) -> (u :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) := a Source # (->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) := a) -> (a -> u b) -> (u :. (v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) := b Source # (->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) := a) -> (a -> u b) -> (u :. (w :. (v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))))) := b Source # (->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))))) := b Source # |
Traversable (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List Methods (->>) :: (Pointable u, Applicative u) => Tap ((List <:.:> List) := (:*:)) a -> (a -> u b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source # traverse :: (Pointable u, Applicative u) => (a -> u b) -> Tap ((List <:.:> List) := (:*:)) a -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source # sequence :: (Pointable u, Applicative u) => ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (u :. Tap ((List <:.:> List) := (:*:))) := a Source # (->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Tap ((List <:.:> List) := (:*:))) := a) -> (a -> u b) -> (u :. (v :. Tap ((List <:.:> List) := (:*:)))) := b Source # (->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Tap ((List <:.:> List) := (:*:)))) := a) -> (a -> u b) -> (u :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := b Source # (->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Tap ((List <:.:> List) := (:*:)))))) := b Source # |
Traversable t => Traversable (Construction t) Source # | |
Instance detailsDefined 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 (List a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Monoid (List a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Setoid a => Setoid (List a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Hoistable Construction Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Nullable List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Nullable Rose Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
Nullable Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Focusable ('Root :: Type -> Location Type) Rose Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
(forall a. Chain a) => Focusable ('Root :: Type -> Location Type) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Focusable ('Head :: Type -> Location Type) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Focusable ('Root :: Type -> Location Type) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Focusable ('Root :: Type -> Location Type) (Construction List) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
Focusable ('Head :: Type -> Location Type) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Focusable ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Focusable ('Head :: Type -> Location Type) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
Morphable ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into (Construction Maybe)) (Vector r) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
Morphable ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into List) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Into List) (Vector r) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
Morphable ('Into Binary) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
Setoid k => Morphable ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
(Semigroup a, forall b. Semigroup b => Semigroup (t b), Covariant t) => Semigroup (Construction t a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Semigroup (Construction Maybe a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
(Monoid a, forall b. Semigroup b => Monoid (t b), Covariant t) => Monoid (Construction t a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
(Setoid a, forall b. Setoid b => Setoid (t b), Covariant t) => Setoid (Construction t a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Construction |
Morphable ('Pop :: a -> Morph a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Push :: a -> Morph a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Insert :: a -> Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Substructure ('Tail :: a -> Segment a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Substructure ('Just :: a -> Maybe a) Rose Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
Substructure ('Right :: a -> Wye a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Substructure ('Left :: a -> Wye a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Morphable ('Push :: a -> Morph a) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Morphable ('Insert :: a -> Morph a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Substructure ('Tail :: a -> Segment a) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
Substructure ('Just :: a -> Maybe a) (Construction List) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
Substructure ('Right :: a -> Wye a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
Substructure ('Left :: a -> Wye a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Nonempty List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Nonempty Rose Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Nonempty Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Zipper Stream Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
type Zipper List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Measural 'Length List a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Measural 'Heighth Binary a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Measural 'Length (Construction Maybe) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Measural 'Heighth (Construction Wye) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Zipper (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Zipper (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Focusing ('Root :: Type -> Location Type) Rose a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Focusing ('Root :: Type -> Location Type) Binary a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Focusing ('Head :: Type -> Location Type) List a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Focusing ('Root :: Type -> Location Type) (Construction Wye) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Focusing ('Root :: Type -> Location Type) (Construction List) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Focusing ('Head :: Type -> Location Type) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Focusing ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Focusing ('Head :: Type -> Location Type) (Construction Maybe) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (o ds) :: Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
type Morphing ('Into (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into (Construction Maybe)) (Vector r) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
type Morphing ('Into List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into List) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Into List) (Vector r) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
type Morphing ('Into Binary) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Stream <:.:> Stream) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Splay |
type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
type Morphing ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # | |
Instance detailsDefined 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 detailsDefined 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 detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Morphing ('Pop :: a -> Morph a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Push :: a -> Morph a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Insert :: a -> Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Substructural ('Tail :: a -> Segment a) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Substructural ('Just :: a -> Maybe a) Rose Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Substructural ('Right :: a -> Wye a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Substructural ('Left :: a -> Wye a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Morphing ('Push :: a -> Morph a) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Morphing ('Insert :: a -> Morph a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Substructural ('Tail :: a -> Segment a) (Construction Maybe) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
type Substructural ('Just :: a -> Maybe a) (Construction List) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Rose |
type Substructural ('Right :: a -> Wye a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
type Substructural ('Left :: a -> Wye a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |