| Semimonoidal Maybe (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Maybe |
| Divisible_ Predicate (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Predicate |
| Monotonic a (Vector r a) => Monotonic a (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| Monotonic s a => Monotonic s (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Accessible b a => Accessible b (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Accessible a (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Accessible s (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Vectorize a r => Vectorize a (a :*: r) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| Bivariant (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| Covariant ((:*:) s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product Methods (<$>) :: (a -> b) -> (s :*: a) -> s :*: b Source # comap :: (a -> b) -> (s :*: a) -> s :*: b Source # (<$) :: a -> (s :*: b) -> s :*: a Source # ($>) :: (s :*: a) -> b -> s :*: b Source # void :: (s :*: a) -> s :*: () Source # loeb :: (s :*: (a <:= (:*:) s)) -> s :*: a Source # (<&>) :: (s :*: a) -> (a -> b) -> s :*: b Source # (<$$>) :: Covariant u => (a -> b) -> (((:*:) s :. u) := a) -> ((:*:) s :. u) := b Source # (<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> (((:*:) s :. (u :. v)) := a) -> ((:*:) s :. (u :. v)) := b Source # (<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> (((:*:) s :. (u :. (v :. w))) := a) -> ((:*:) s :. (u :. (v :. w))) := b Source # (<&&>) :: Covariant u => (((:*:) s :. u) := a) -> (a -> b) -> ((:*:) s :. u) := b Source # (<&&&>) :: (Covariant u, Covariant v) => (((:*:) s :. (u :. v)) := a) -> (a -> b) -> ((:*:) s :. (u :. v)) := b Source # (<&&&&>) :: (Covariant u, Covariant v, Covariant w) => (((:*:) s :. (u :. (v :. w))) := a) -> (a -> b) -> ((:*:) s :. (u :. (v :. w))) := b Source # (.#..) :: ((:*:) s ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source # (.#...) :: ((:*:) s ~ v a, (:*:) s ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source # (.#....) :: ((:*:) s ~ v a, (:*:) s ~ v b, (:*:) s ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source # (<$$) :: Covariant u => b -> (((:*:) s :. u) := a) -> ((:*:) s :. u) := b Source # (<$$$) :: (Covariant u, Covariant v) => b -> (((:*:) s :. (u :. v)) := a) -> ((:*:) s :. (u :. v)) := b Source # (<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> (((:*:) s :. (u :. (v :. w))) := a) -> ((:*:) s :. (u :. (v :. w))) := b Source # ($$>) :: Covariant u => (((:*:) s :. u) := a) -> b -> ((:*:) s :. u) := b Source # ($$$>) :: (Covariant u, Covariant v) => (((:*:) s :. (u :. v)) := a) -> b -> ((:*:) s :. (u :. v)) := b Source # ($$$$>) :: (Covariant u, Covariant v, Covariant w) => (((:*:) s :. (u :. (v :. w))) := a) -> b -> ((:*:) s :. (u :. (v :. w))) := b Source # |
| Applicative t => Applicative (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| Applicative (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| Semigroup e => Semimonoidal (Validation e) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Validation |
| Semimonoidal (Conclusion e) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Conclusion |
| Semimonoidal (State s) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.State |
| Extendable ((:*:) s) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| Extendable (Tap ((Stream <:.:> Stream) := (:*:))) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.Stream |
| Extendable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| Extractable ((:*:) a) ((->) :: Type -> Type -> Type) Source # | |
|
| Comonad ((:*:) s) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List 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 (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) 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 (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| 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 ('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 |
| Covariant_ ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| Traversable ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic |
| Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Tap ((t <:.:> t) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| Traversable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| 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 |
| Adjoint ((:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic |
| Covariant (Flip (:*:) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary Methods (<$>) :: (a0 -> b) -> Flip (:*:) a a0 -> Flip (:*:) a b Source # comap :: (a0 -> b) -> Flip (:*:) a a0 -> Flip (:*:) a b Source # (<$) :: a0 -> Flip (:*:) a b -> Flip (:*:) a a0 Source # ($>) :: Flip (:*:) a a0 -> b -> Flip (:*:) a b Source # void :: Flip (:*:) a a0 -> Flip (:*:) a () Source # loeb :: Flip (:*:) a (a0 <:= Flip (:*:) a) -> Flip (:*:) a a0 Source # (<&>) :: Flip (:*:) a a0 -> (a0 -> b) -> Flip (:*:) a b Source # (<$$>) :: Covariant u => (a0 -> b) -> ((Flip (:*:) a :. u) := a0) -> (Flip (:*:) a :. u) := b Source # (<$$$>) :: (Covariant u, Covariant v) => (a0 -> b) -> ((Flip (:*:) a :. (u :. v)) := a0) -> (Flip (:*:) a :. (u :. v)) := b Source # (<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a0 -> b) -> ((Flip (:*:) a :. (u :. (v :. w))) := a0) -> (Flip (:*:) a :. (u :. (v :. w))) := b Source # (<&&>) :: Covariant u => ((Flip (:*:) a :. u) := a0) -> (a0 -> b) -> (Flip (:*:) a :. u) := b Source # (<&&&>) :: (Covariant u, Covariant v) => ((Flip (:*:) a :. (u :. v)) := a0) -> (a0 -> b) -> (Flip (:*:) a :. (u :. v)) := b Source # (<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Flip (:*:) a :. (u :. (v :. w))) := a0) -> (a0 -> b) -> (Flip (:*:) a :. (u :. (v :. w))) := b Source # (.#..) :: (Flip (:*:) a ~ v a0, Category v) => v c d -> ((v a0 :. v b) := c) -> (v a0 :. v b) := d Source # (.#...) :: (Flip (:*:) a ~ v a0, Flip (:*:) a ~ v b, Category v, Covariant (v a0), Covariant (v b)) => v d e -> ((v a0 :. (v b :. v c)) := d) -> (v a0 :. (v b :. v c)) := e Source # (.#....) :: (Flip (:*:) a ~ v a0, Flip (:*:) a ~ v b, Flip (:*:) a ~ v c, Category v, Covariant (v a0), Covariant (v b), Covariant (v c)) => v e f -> ((v a0 :. (v b :. (v c :. v d))) := e) -> (v a0 :. (v b :. (v c :. v d))) := f Source # (<$$) :: Covariant u => b -> ((Flip (:*:) a :. u) := a0) -> (Flip (:*:) a :. u) := b Source # (<$$$) :: (Covariant u, Covariant v) => b -> ((Flip (:*:) a :. (u :. v)) := a0) -> (Flip (:*:) a :. (u :. v)) := b Source # (<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Flip (:*:) a :. (u :. (v :. w))) := a0) -> (Flip (:*:) a :. (u :. (v :. w))) := b Source # ($$>) :: Covariant u => ((Flip (:*:) a :. u) := a0) -> b -> (Flip (:*:) a :. u) := b Source # ($$$>) :: (Covariant u, Covariant v) => ((Flip (:*:) a :. (u :. v)) := a0) -> b -> (Flip (:*:) a :. (u :. v)) := b Source # ($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Flip (:*:) a :. (u :. (v :. w))) := a0) -> b -> (Flip (:*:) a :. (u :. (v :. w))) := b Source # |
| (Semigroup s, Semigroup a) => Semigroup (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Semigroup a, Semigroup r, Semigroup (a :*: r), Semigroup (Vector r a)) => Semigroup (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| (Ringoid s, Ringoid a) => Ringoid (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Ringoid a, Ringoid r, Ringoid (a :*: r), Ringoid (Vector r a)) => Ringoid (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| (Monoid s, Monoid a) => Monoid (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Monoid a, Monoid r, Monoid (a :*: r), Monoid (Vector r a)) => Monoid (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| (Quasiring s, Quasiring a) => Quasiring (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Quasiring a, Quasiring r, Quasiring (a :*: r), Quasiring (Vector r a)) => Quasiring (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| (Group s, Group a) => Group (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Group a, Group r, Group (a :*: r), Group (Vector r a)) => Group (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| (Supremum s, Supremum a) => Supremum (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Infimum s, Infimum a) => Infimum (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Lattice s, Lattice a) => Lattice (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Setoid s, Setoid a) => Setoid (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Setoid a, Setoid (Vector r a)) => Setoid (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| Semimonoidal t (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Semimonoidal (Backwards t) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Backwards |
| Semimonoidal t (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Semimonoidal (Reverse t) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Reverse |
| (Covariant t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Substructure ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| (Covariant t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| (Covariant t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Substructure ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| Substructure ('Right :: a -> Wye a) ((:*:) s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Substructure ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| (Covariant t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Substructure ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| (Covariant t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Substructure ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| Extractable (Flip (:*:) a) ((->) :: Type -> Type -> Type) Source # | |
|
| Covariant_ (Flip (:*:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| Adjoint (Flip (:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| Semimonoidal ((->) e :: Type -> Type) (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic |
| Applicative t => Applicative ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Algebraic.Product |
| (Semigroup e, Applicative u) => Applicative ((:*:) e <.:> u) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| (Semigroup e, Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| Extendable u ((->) :: Type -> Type -> Type) => Extendable ((:*:) e <:.> u) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Equipment |
| (Pointable u ((->) :: Type -> Type -> Type), Monoid e) => Pointable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List 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 (Comprehension Maybe)) (Tap ((List <:.:> List) := (:*:))) 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 (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| 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 ('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 ('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 Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Available ('Right :: a -> Wye a) ((:*:) s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Transformer.Tap |
| type Substance ('Right :: a -> Wye a) ((:*:) s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Available ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Substance ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |