pandora-0.3.7: 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 1 

Instances

Instances details
Bivariant Product Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

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

bimap :: (a -> b) -> (c -> d) -> Product a c -> Product b d 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 #

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 #

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)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Methods

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

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Stack

Methods

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

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

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

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

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

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

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

(<<=$) :: Covariant u => ((u :. Tap ((:*:) <:.:> Stack)) := a) -> (Tap ((:*:) <:.:> Stack) a -> b) -> (u :. Tap ((:*:) <:.:> Stack)) := 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 #

Focusable ('Left :: Type -> Wye Type) (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Focusing 'Left (Product s) a Source #

Focusable ('Right :: Type -> Wye Type) (Product s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Focusing 'Right (Product s) a Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Wye) ((:*:) <:.:> Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 #

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

zero :: s :*: a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

one :: s :*: 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 #

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

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 #

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

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

type Focusing ('Left :: Type -> Wye Type) (Product s) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Focusing ('Left :: Type -> Wye Type) (Product s) a = s
type Focusing ('Right :: Type -> Wye Type) (Product s) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Focusing ('Right :: Type -> Wye Type) (Product s) a = a
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) = Tap ((:*:) <:.:> Stream)
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) = Tap ((:*:) <:.:> Stream)
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.Stack

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack
type Morphing ('Into Wye) ((:*:) <:.:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 (:*:) = Product infixr 1 Source #

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

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

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