| Bivariant Product Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| 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 |
| Covariant (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| Extendable (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| 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 |
| Extractable (Product a) Source # | |
|
| Comonad (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| Traversable (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product Methods (->>) :: (Pointable u, Applicative u) => Product s a -> (a -> u b) -> (u :. Product s) := b Source # traverse :: (Pointable u, Applicative u) => (a -> u b) -> Product s a -> (u :. Product s) := b Source # sequence :: (Pointable u, Applicative u) => ((Product s :. u) := a) -> (u :. Product s) := a Source # (->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Product s) := a) -> (a -> u b) -> (u :. (v :. Product s)) := b Source # (->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Product s)) := a) -> (a -> u b) -> (u :. (w :. (v :. Product s))) := b Source # (->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Product s))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Product s)))) := b Source # |
| 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 # |
| 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 ('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 |
| Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| 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 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 |
| 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 (Product s) ((->) s :: Type -> Type) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor |
| Covariant (Flip (:*:) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary |
| Extractable (Flip (:*:) a) Source # | |
|
| (Semigroup s, Semigroup a) => Semigroup (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.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.Functor.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.Functor.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.Functor.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.Functor.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.Functor.Product |
| (Infimum s, Infimum a) => Infimum (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| (Lattice s, Lattice a) => Lattice (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| (Setoid s, Setoid a) => Setoid (s :*: a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Functor.Product |
| (Setoid a, Setoid (Vector r a)) => Setoid (Vector (a :*: r) a) Source # | |
Instance detailsDefined in Pandora.Paradigm.Primary.Linear.Vector |
| Substructure ('Right :: a -> Wye a) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |
| (Semigroup e, Pointable u, Bindable u) => Bindable ((:*:) e <.:> u) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| (Semigroup e, Applicative u) => Applicative ((:*:) e <.:> u) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| Extendable u => Extendable ((:*:) e <:.> u) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Equipment |
| (Pointable u, Monoid e) => Pointable ((:*:) e <.:> u) Source # | |
Instance detailsDefined in Pandora.Paradigm.Inventory.Accumulator |
| 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 ('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 Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure.Some.List |
| 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 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 Substructural ('Right :: a -> Wye a) (Product s) Source # | |
Instance detailsDefined in Pandora.Paradigm.Structure |