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

Pandora.Paradigm.Primary.Functor.Product

Documentation

data Product s a Source #

Constructors

s :*: a infixr 0 

Instances

Instances details
Bivariant Product Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

(<->) :: (forall i. Covariant (Product i)) => (a -> b) -> (c -> d) -> Product a c -> Product b d Source #

bimap :: (forall i. Covariant (Product i)) => (a -> b) -> (c -> d) -> Product a c -> Product b d Source #

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 :: (s :*: a) :-. b Source #

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

Defined in Pandora.Paradigm.Structure

Methods

access :: (s :*: a) :-. a Source #

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

Defined in Pandora.Paradigm.Structure

Methods

access :: (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 #

Covariant (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

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

comap :: (a -> b) -> Product s a -> Product s b Source #

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

($>) :: Product s a -> b -> Product s b Source #

void :: Product s a -> Product s () Source #

loeb :: Product s (a <:= Product s) -> Product s a Source #

(<&>) :: Product s a -> (a -> b) -> Product s b Source #

(<$$>) :: Covariant u => (a -> b) -> ((Product s :. u) := a) -> (Product s :. u) := b Source #

(<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((Product s :. (u :. v)) := a) -> (Product s :. (u :. v)) := b Source #

(<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Product s :. (u :. (v :. w))) := a) -> (Product s :. (u :. (v :. w))) := b Source #

(<&&>) :: Covariant u => ((Product s :. u) := a) -> (a -> b) -> (Product s :. u) := b Source #

(<&&&>) :: (Covariant u, Covariant v) => ((Product s :. (u :. v)) := a) -> (a -> b) -> (Product s :. (u :. v)) := b Source #

(<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Product s :. (u :. (v :. w))) := a) -> (a -> b) -> (Product s :. (u :. (v :. w))) := b Source #

(.#..) :: (Product s ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Product s ~ v a, Product 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 #

(.#....) :: (Product s ~ v a, Product s ~ v b, Product 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 -> ((Product s :. u) := a) -> (Product s :. u) := b Source #

(<$$$) :: (Covariant u, Covariant v) => b -> ((Product s :. (u :. v)) := a) -> (Product s :. (u :. v)) := b Source #

(<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Product s :. (u :. (v :. w))) := a) -> (Product s :. (u :. (v :. w))) := b Source #

($$>) :: Covariant u => ((Product s :. u) := a) -> b -> (Product s :. u) := b Source #

($$$>) :: (Covariant u, Covariant v) => ((Product s :. (u :. v)) := a) -> b -> (Product s :. (u :. v)) := b Source #

($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Product s :. (u :. (v :. w))) := a) -> b -> (Product s :. (u :. (v :. w))) := b Source #

Applicative (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

apply :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<*) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a Source #

forever :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

Applicative (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

apply :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<*) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a Source #

forever :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

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

apply :: Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(*>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) b Source #

(<*) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) a Source #

forever :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(<%>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((List <:.:> List) := (:*:)) :. u) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (Tap ((List <:.:> List) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := b Source #

Extendable (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

(=>>) :: Product s a -> (Product s a -> b) -> Product s b Source #

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

extend :: (Product s a -> b) -> Product s a -> Product s b Source #

duplicate :: Product s a -> (Product s :. Product s) := a Source #

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

(=>=) :: (Product s a -> b) -> (Product s b -> c) -> Product s a -> c Source #

($=>>) :: Covariant u => ((u :. Product s) := a) -> (Product s a -> b) -> (u :. Product s) := b Source #

(<<=$) :: Covariant u => ((u :. Product s) := a) -> (Product s a -> b) -> (u :. Product s) := b Source #

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(=>>) :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

extend :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

duplicate :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) :. Tap ((List <:.:> List) := (:*:))) := a Source #

(=<=) :: (Tap ((List <:.:> List) := (:*:)) b -> c) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

(=>=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> (Tap ((List <:.:> List) := (:*:)) b -> c) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

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

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

Extractable (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

extract :: a0 <:= Product a Source #

Comonad (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Traversable (Product s) Source # 
Instance details

Defined 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 details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined 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 #

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 (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) := (:*:)))) (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 (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 (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 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 #

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 #

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

Defined in Pandora.Paradigm.Primary.Functor

Methods

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

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

phi :: (Product s a -> b) -> a -> s -> b Source #

psi :: (a -> s -> b) -> Product s a -> b Source #

eta :: a -> ((->) s :. Product s) := a Source #

epsilon :: ((Product s :. (->) s) := a) -> a Source #

(-|$) :: Covariant v => v a -> (Product s a -> b) -> v (s -> b) Source #

($|-) :: Covariant v => v (Product s a) -> (a -> s -> b) -> v b Source #

($$|-) :: (Covariant v, Covariant w) => ((v :. (w :. Product s)) := a) -> (a -> s -> b) -> (v :. w) := b Source #

($$$|-) :: (Covariant v, Covariant w, Covariant x) => ((v :. (w :. (x :. Product s))) := a) -> (a -> s -> b) -> (v :. (w :. x)) := b Source #

($$$$|-) :: (Covariant v, Covariant w, Covariant x, Covariant y) => ((v :. (w :. (x :. (y :. Product s)))) := a) -> (a -> s -> b) -> (v :. (w :. (x :. y))) := b Source #

Covariant (Flip (:*:) a) Source # 
Instance details

Defined 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 #

Extractable (Flip (:*:) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Methods

extract :: a0 <:= Flip (:*:) a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.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.Functor.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.Functor.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.Functor.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.Functor.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.Functor.Product

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Product

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

Defined in Pandora.Paradigm.Primary.Functor.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 #

Substructure ('Right :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Right (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Substructure ('Left :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Left (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Product s) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Left (Flip Product a2) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

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

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

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

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

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

(Semigroup e, Applicative u) => Applicative ((:*:) e <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

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

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

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

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

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

(<***>) :: (Applicative u0, Applicative v) => ((((:*:) e <.:> u) :. (u0 :. v)) := (a -> b)) -> ((((:*:) e <.:> u) :. (u0 :. v)) := a) -> (((:*:) e <.:> u) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((((:*:) e <.:> u) :. (u0 :. (v :. w))) := (a -> b)) -> ((((:*:) e <.:> u) :. (u0 :. (v :. w))) := a) -> (((:*:) e <.:> u) :. (u0 :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

pass :: ((:*:) e <.:> u) () Source #

type Morphing ('Into (Tap ((List <:.:> 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) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) 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 (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 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 <:.> Zipper 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 <:.> Zipper 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 Substructural ('Right :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Left :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Right :: a -> Wye a) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Right :: a -> Wye a) (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

type Substructural ('Left :: a1 -> Wye a1) (Flip Product a2) = Identity

type (:*:) = Product infixr 0 Source #

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 #