| Covariant Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Wye |
| Traversable Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Wye Methods (->>) :: (Pointable u, Applicative u) => Wye a -> (a -> u b) -> (u :. Wye) := b Source # traverse :: (Pointable u, Applicative u) => (a -> u b) -> Wye a -> (u :. Wye) := b Source # sequence :: (Pointable u, Applicative u) => ((Wye :. u) := a) -> (u :. Wye) := a Source # (->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Wye) := a) -> (a -> u b) -> (u :. (v :. Wye)) := b Source # (->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Wye)) := a) -> (a -> u b) -> (u :. (w :. (v :. Wye))) := b Source # (->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Wye))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Wye)))) := b Source # |
| Measurable 'Heighth Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| Measurable 'Heighth (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| Monotonic a (Wye a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Wye |
| Semigroup a => Semigroup (Wye a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Wye |
| Semigroup a => Monoid (Wye a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Wye |
| Nullable Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| (forall a. Chain a) => Focusable ('Root :: Type -> Location Type) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| Focusable ('Left :: Type -> Wye Type) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Focusable ('Right :: Type -> Wye Type) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Focusable ('Root :: Type -> Location Type) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Morphable ('Into ('Left Maybe)) Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| Morphable ('Into ('Right Maybe)) Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| 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 |
| Morphable ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| 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 |
| Morphable ('Insert :: a -> Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| 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 ('Insert :: a -> Morph a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| 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 |
| Substructure ('Right :: a -> Wye a) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Contravariant (Kan ('Left :: Type -> Wye Type) t u b) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |
| Covariant (Kan ('Right :: Type -> Wye Type) t u b) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |
| Interpreted (Kan ('Left :: Type -> Wye Type) t u b) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |
| Interpreted (Kan ('Right :: Type -> Wye Type) t u b) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |
| type Nonempty Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| type Measural 'Heighth Binary a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| 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 |
| data Kan ('Left :: Type -> Wye Type) t u b a Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan data Kan (' Left :: Type -> Wye Type) t u b a = Lan ((t b -> a) -> u b) |
| data Kan ('Right :: Type -> Wye Type) t u b a Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan data Kan (' Right :: Type -> Wye Type) t u b a = Ran ((a -> t b) -> u b) |
| type Focusing ('Root :: Type -> Location Type) Binary a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| type Focusing ('Left :: Type -> Wye Type) (Product s) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Focusing ('Right :: Type -> Wye Type) (Product s) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Focusing ('Root :: Type -> Location Type) (Construction Wye) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| type Morphing ('Into (o ds) :: Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Morphing ('Into ('Left Maybe)) Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| type Morphing ('Into ('Right Maybe)) Wye Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| 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 ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| 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 ('Insert :: a -> Morph a) Binary Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| 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 ('Insert :: a -> Morph a) (Construction Wye) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Binary |
| 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 |
| type Substructural ('Right :: a -> Wye a) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Primary (Kan ('Left :: Type -> Wye Type) t u b) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |
| type Primary (Kan ('Right :: Type -> Wye Type) t u b) a Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Kan |