pandora-0.1.8: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Paradigm.Basis.Product

Documentation

data Product a b Source #

Constructors

a :*: b infixr 1 
Instances
Covariant (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

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

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

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

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

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

loeb :: Product a (Product a a0 -> a0) -> Product a a0 Source #

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

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

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

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

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

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

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

Extendable (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

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

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

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

duplicate :: Product a a0 -> (Product a :.: Product a) a0 Source #

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

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

Extractable (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

extract :: Product a a0 -> a0 Source #

Comonad (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Traversable (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

(->>) :: (Pointable u, Applicative u) => Product a a0 -> (a0 -> u b) -> (u :.: Product a) b Source #

traverse :: (Pointable u, Applicative u) => (a0 -> u b) -> Product a a0 -> (u :.: Product a) b Source #

sequence :: (Pointable u, Applicative u) => (Product a :.: u) a0 -> (u :.: Product a) a0 Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => (v :.: Product a) a0 -> (a0 -> u b) -> (u :.: (v :.: Product a)) b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => (w :.: (v :.: Product a)) a0 -> (a0 -> u b) -> (u :.: (w :.: (v :.: Product a))) b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => (j :.: (w :.: (v :.: Product a))) a0 -> (a0 -> u b) -> (u :.: (j :.: (w :.: (v :.: Product a)))) b Source #

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

Defined in Pandora.Paradigm.Basis.Product

Methods

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

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

eta :: a0 -> ((->) a :.: Product a) a0 Source #

epsilon :: (Product a :.: (->) a) a0 -> a0 Source #

(Semigroup a, Semigroup b) => Semigroup (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

(+) :: Product a b -> Product a b -> Product a b Source #

(Ringoid a, Ringoid b) => Ringoid (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

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

(Monoid a, Monoid b) => Monoid (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

zero :: Product a b Source #

(Group a, Group b) => Group (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

inverse :: Product a b -> Product a b Source #

(Supremum a, Supremum b) => Supremum (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

(\/) :: Product a b -> Product a b -> Product a b Source #

(Infimum a, Infimum b) => Infimum (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

(/\) :: Product a b -> Product a b -> Product a b Source #

(Lattice a, Lattice b) => Lattice (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

(Setoid a, Setoid b) => Setoid (Product a b) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Product

Methods

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

(/=) :: Product a b -> Product a b -> Boolean Source #

Covariant u => Covariant (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

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

comap :: (a -> b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

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

($>) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

void :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) () Source #

loeb :: TUV Stateful () Stateful ((->) s) u ((:*:) s) (TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> a) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a Source #

(<&>) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> (a -> b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

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

(<$$$>) :: (Covariant u0, Covariant v) => (a -> b) -> ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: v)) >< a) -> (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: v)) >< b Source #

(<$$$$>) :: (Covariant u0, Covariant v, Covariant w) => (a -> b) -> ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: (v :.: w))) >< a) -> (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: (v :.: w))) >< b Source #

(<&&>) :: Covariant u0 => ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: u0) >< a) -> (a -> b) -> (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: u0) >< b Source #

(<&&&>) :: (Covariant u0, Covariant v) => ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: v)) >< a) -> (a -> b) -> (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: v)) >< b Source #

(<&&&&>) :: (Covariant u0, Covariant v, Covariant w) => ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: (v :.: w))) >< a) -> (a -> b) -> (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: (u0 :.: (v :.: w))) >< b Source #

Bindable u => Bindable (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

(>>=) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

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

bind :: (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

join :: (TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: TUV Stateful () Stateful ((->) s) u ((:*:) s)) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a Source #

(>=>) :: (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> (b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c) -> a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c Source #

(<=<) :: (b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c) -> (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c Source #

Bindable u => Applicative (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

(<*>) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) (a -> b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

apply :: TUV Stateful () Stateful ((->) s) u ((:*:) s) (a -> b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

(*>) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

(<*) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a Source #

forever :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

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

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

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

Pointable u => Pointable (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

point :: a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a Source #

Monad u => Monad (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

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

type family Has x xs where ... Source #

Equations

Has x (x :*: xs) = () 
Has x (y :*: xs) = Has x xs 
Has x x = () 

type family Injective xs ys where ... Source #

Equations

Injective (x :*: xs) ys = (Has x ys, Injective xs ys) 
Injective x (x :*: ys) = () 
Injective x (y :*: ys) = Has x ys 
Injective x x = () 

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

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

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

curry :: ((a :*: b) -> c) -> a -> b -> c Source #

uncurry :: (a -> b -> c) -> (a :*: b) -> c Source #