pandora-0.4.5: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Paradigm.Primary.Algebraic.Product

Documentation

data s :*: a infixr 0 Source #

Constructors

s :*: a infixr 0 

Instances

Instances details
Monotonic a (Vector r a) => Monotonic a (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

reduce :: (a -> r0 -> r0) -> r0 -> Vector (a :*: r) a -> r0 Source #

resolve :: (a -> r0) -> r0 -> Vector (a :*: r) a -> r0 Source #

Monotonic s a => Monotonic s (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

reduce :: (s -> r -> r) -> r -> (s :*: a) -> r Source #

resolve :: (s -> r) -> r -> (s :*: a) -> r Source #

Accessible b a => Accessible b (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

access :: Lens Identity (s :*: a) b Source #

Accessible a (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

access :: Lens Identity (s :*: a) a Source #

Accessible s (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

access :: Lens Identity (s :*: a) s Source #

Vectorize a r => Vectorize a (a :*: r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

vectorize :: (a :*: r) -> Vector (a :*: r) a Source #

Bivariant (:*:) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(<->) :: (a -> b) -> (c -> d) -> (a :*: c) -> (b :*: d) Source #

Semimonoidal Maybe ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

multiply_ :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) -> Maybe (a :+: b) Source #

Semimonoidal Maybe ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

multiply_ :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) -> Maybe (a :*: b) Source #

Semimonoidal ((:+:) e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

multiply_ :: forall (a :: k) (b :: k). ((e :+: a) :*: (e :+: b)) -> (e :+: (a :+: b)) Source #

Semigroup e => Semimonoidal (Validation e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

multiply_ :: forall (a :: k) (b :: k). (Validation e a :*: Validation e b) -> Validation e (a :+: b) Source #

Semigroup e => Semimonoidal (Validation e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

multiply_ :: forall (a :: k) (b :: k). (Validation e a :*: Validation e b) -> Validation e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

multiply_ :: forall (a :: k) (b :: k). (Instruction t a :*: Instruction t b) -> Instruction t (a :*: b) Source #

(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (Construction t :: Type -> Type) ((->) :: Type -> 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 #

Semigroup e => Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

multiply_ :: forall (a :: k) (b :: k). (Conclusion e a :*: Conclusion e b) -> Conclusion e (a :+: b) Source #

Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

multiply_ :: forall (a :: k) (b :: k). (Conclusion e a :*: Conclusion e b) -> Conclusion e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

multiply_ :: forall (a :: k) (b :: k). (Comprehension t a :*: Comprehension t b) -> Comprehension t (a :*: b) Source #

Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (Tap t :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

multiply_ :: forall (a :: k) (b :: k). (Tap t a :*: Tap t b) -> Tap t (a :*: b) Source #

Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (Tap ((t <:.:> t) := (:*:)) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

multiply_ :: forall (a :: k) (b :: k). (Tap ((t <:.:> t) := (:*:)) a :*: Tap ((t <:.:> t) := (:*:)) b) -> Tap ((t <:.:> t) := (:*:)) (a :*: b) Source #

Semimonoidal (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Semimonoidal (State s :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

multiply_ :: forall (a :: k) (b :: k). (State s a :*: State s b) -> State s (a :*: b) Source #

Semimonoidal (Environment e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

multiply_ :: forall (a :: k) (b :: k). (Environment e a :*: Environment e b) -> Environment e (a :*: b) Source #

Semigroup e => Semimonoidal (Accumulator e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

multiply_ :: forall (a :: k) (b :: k). (Accumulator e a :*: Accumulator e b) -> Accumulator e (a :*: b) Source #

Extractable ((:*:) a) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

extract :: (a :*: a0) -> a0 Source #

Extendable ((:*:) s) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(<<=) :: ((s :*: a) -> b) -> (s :*: a) -> (s :*: b) Source #

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable (Tap ((List <:.:> List) := (:*:))) ((->) :: Type -> Type -> Type) 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 #

Comonad ((:*:) s) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

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 ('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 (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) (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 ('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 #

Covariant ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(-<$>-) :: (a -> b) -> (s :*: a) -> (s :*: b) Source #

Traversable ((:*:) s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> (s :*: a) -> u (s :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Tap ((t <:.:> t) := (:*:)) a -> u (Tap ((t <:.:> t) := (:*:)) b) Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Methods

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

Semimonoidal (Schematic Monad t u) ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (t :> u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

multiply_ :: forall (a :: k) (b :: k). ((t :> u) a :*: (t :> u) b) -> (t :> u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

multiply_ :: forall (a :: k) (b :: k). (Backwards t a :*: Backwards t b) -> Backwards t (a :*: b) Source #

Semimonoidal (Schematic Comonad t u) ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal (t :< u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Methods

multiply_ :: forall (a :: k) (b :: k). ((t :< u) a :*: (t :< u) b) -> (t :< u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) :: 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 #

Semimonoidal ((->) e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

multiply_ :: forall (a :: k) (b :: k). ((e -> a) :*: (e -> b)) -> (e -> (a :*: b)) Source #

Adjoint ((:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

(-|) :: ((s :*: a) -> b) -> a -> (s -> b) Source #

(|-) :: (a -> (s -> b)) -> (s :*: a) -> b Source #

Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:) => Semimonoidal ((t <:.:> t) := (:*:) :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

multiply_ :: forall (a :: k) (b :: k). (((t <:.:> t) := (:*:)) a :*: ((t <:.:> t) := (:*:)) b) -> ((t <:.:> t) := (:*:)) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

multiply_ :: forall (a :: k) (b :: k). (((t <:<.>:> t') := u) a :*: ((t <:<.>:> t') := u) b) -> ((t <:<.>:> t') := u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

multiply_ :: forall (a :: k) (b :: k). ((t <.:> u) a :*: (t <.:> u) b) -> (t <.:> u) (a :*: b) Source #

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

multiply_ :: forall (a :: k) (b :: k). ((t <:.> u) a :*: (t <:.> u) b) -> (t <:.> u) (a :*: b) Source #

(Semigroup s, Semigroup a) => Semigroup (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(+) :: (s :*: a) -> (s :*: a) -> s :*: a Source #

(Semigroup a, Semigroup r, Semigroup (a :*: r), Semigroup (Vector r a)) => Semigroup (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

(+) :: Vector (a :*: r) a -> Vector (a :*: r) a -> Vector (a :*: r) a Source #

(Ringoid s, Ringoid a) => Ringoid (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(*) :: (s :*: a) -> (s :*: a) -> s :*: a Source #

(Ringoid a, Ringoid r, Ringoid (a :*: r), Ringoid (Vector r a)) => Ringoid (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

(*) :: Vector (a :*: r) a -> Vector (a :*: r) a -> Vector (a :*: r) a Source #

(Monoid s, Monoid a) => Monoid (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

zero :: s :*: a Source #

(Monoid a, Monoid r, Monoid (a :*: r), Monoid (Vector r a)) => Monoid (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

zero :: Vector (a :*: r) a Source #

(Quasiring s, Quasiring a) => Quasiring (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

one :: s :*: a Source #

(Quasiring a, Quasiring r, Quasiring (a :*: r), Quasiring (Vector r a)) => Quasiring (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

one :: Vector (a :*: r) a Source #

(Group s, Group a) => Group (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

invert :: (s :*: a) -> s :*: a Source #

(-) :: (s :*: a) -> (s :*: a) -> s :*: a Source #

(Group a, Group r, Group (a :*: r), Group (Vector r a)) => Group (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

invert :: Vector (a :*: r) a -> Vector (a :*: r) a Source #

(-) :: Vector (a :*: r) a -> Vector (a :*: r) a -> Vector (a :*: r) a Source #

(Supremum s, Supremum a) => Supremum (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(\/) :: (s :*: a) -> (s :*: a) -> s :*: a Source #

(Infimum s, Infimum a) => Infimum (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(/\) :: (s :*: a) -> (s :*: a) -> s :*: a Source #

(Lattice s, Lattice a) => Lattice (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

(Setoid s, Setoid a) => Setoid (s :*: a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(==) :: (s :*: a) -> (s :*: a) -> Boolean Source #

(!=) :: (s :*: a) -> (s :*: a) -> Boolean Source #

(Setoid a, Setoid (Vector r a)) => Setoid (Vector (a :*: r) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Methods

(==) :: Vector (a :*: r) a -> Vector (a :*: r) a -> Boolean Source #

(!=) :: Vector (a :*: r) a -> Vector (a :*: r) a -> Boolean Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

type Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

type Substance 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Right ((:*:) s) :: Type -> Type Source #

type Substance 'Right ((:*:) s) :: Type -> Type Source #

Substructure ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Left (Flip (:*:) a2) :: Type -> Type Source #

type Substance 'Left (Flip (:*:) a2) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Right ((t <:.:> t) := (:*:)) :: Type -> Type Source #

type Substance 'Right ((t <:.:> t) := (:*:)) :: Type -> Type Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Substructure ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Left ((t <:.:> t) := (:*:)) :: Type -> Type Source #

type Substance 'Left ((t <:.:> t) := (:*:)) :: Type -> Type Source #

Extractable (Flip (:*:) a) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Methods

extract :: Flip (:*:) a a0 -> a0 Source #

Covariant (Flip (:*:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(-<$>-) :: (a0 -> b) -> Flip (:*:) a a0 -> Flip (:*:) a b Source #

Adjoint (Flip (:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Methods

(-|) :: (Flip (:*:) s a -> b) -> a -> (s -> b) Source #

(|-) :: (a -> (s -> b)) -> Flip (:*:) s a -> b Source #

(Pointable u ((->) :: Type -> Type -> Type), Monoid e) => Pointable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

point :: a -> ((:*:) e <.:> u) a Source #

Extendable u ((->) :: Type -> Type -> Type) => Extendable ((:*:) e <:.> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

(<<=) :: (((:*:) e <:.> u) a -> b) -> ((:*:) e <:.> u) a -> ((:*:) e <:.> u) b Source #

(Semigroup e, Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

(=<<) :: (a -> ((:*:) e <.:> u) b) -> ((:*:) e <.:> u) a -> ((:*:) e <.:> u) b Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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) (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 ('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 ('Into Wye) ((Maybe <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

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 Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Right :: a -> Wye a) ((:*:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Right :: a -> Wye a) ((:*:) s) = Identity
type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Right :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = t
type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Left :: a -> Wye a) (Tap ((t <:.:> t) := (:*:))) = t
type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Substance ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Substance ('Right :: a -> Wye a) ((:*:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right :: a -> Wye a) ((:*:) s) = Identity
type Available ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Left :: a1 -> Wye a1) (Flip (:*:) a2) = Identity
type Substance ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Left :: a1 -> Wye a1) (Flip (:*:) a2) = Identity
type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) = Identity
type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Available ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) = Identity
type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right :: a -> Wye a) ((t <:.:> t) := (:*:)) = t
type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Left :: a -> Wye a) ((t <:.:> t) := (:*:)) = t

delta :: a -> a :*: a Source #

swap :: (a :*: b) -> b :*: a Source #

attached :: (a :*: b) -> a Source #

twosome :: t a -> u a -> (<:.:>) t u (:*:) a Source #