data-category-0.4: Restricted categories

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.Category.CartesianClosed

Description

 

Documentation

type family Exponential (~>) y z :: *Source

class (HasTerminalObject ~>, HasBinaryProducts ~>) => CartesianClosed (~>) whereSource

Methods

apply :: Obj ~> y -> Obj ~> z -> BinaryProduct ~> (Exponential ~> y z) y ~> zSource

tuple :: Obj ~> y -> Obj ~> z -> z ~> Exponential ~> y (BinaryProduct ~> z y)Source

(^^^) :: (z1 ~> z2) -> (y2 ~> y1) -> Exponential ~> y1 z1 ~> Exponential ~> y2 z2Source

data ExpFunctor (~>) Source

Constructors

ExpFunctor 

Instances

data CatApply y z Source

Constructors

CatApply 

Instances

(Category y, Category z) => Functor (CatApply y z) 

data CatTuple y z Source

Constructors

CatTuple 

Instances

(Category y, Category z) => Functor (CatTuple y z) 

type Presheaves (~>) = Nat (Op ~>) (->)Source

data PShExponential (~>) p q Source

Constructors

PShExponential 

Instances

(Dom p ~ Op ~>, Dom q ~ Op ~>, Cod p ~ (->), Cod q ~ (->), Category ~>, Functor p, Functor q) => Functor (PShExponential ~> p q) 

data ProductWith (~>) y Source

Constructors

ProductWith (Obj ~> y) 

Instances

data ExponentialWith (~>) y Source

Constructors

ExponentialWith (Obj ~> y) 

Instances

curry :: CartesianClosed ~> => Obj ~> x -> Obj ~> y -> Obj ~> z -> ((ProductWith ~> y :% x) ~> z) -> x ~> (ExponentialWith ~> y :% z)Source

uncurry :: CartesianClosed ~> => Obj ~> x -> Obj ~> y -> Obj ~> z -> (x ~> (ExponentialWith ~> y :% z)) -> (ProductWith ~> y :% x) ~> zSource

type State (~>) s a = ExponentialWith ~> s :% (ProductWith ~> s :% a)Source

stateMonadReturn :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> a ~> State ~> s aSource

stateMonadJoin :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> State ~> s (State ~> s a) ~> State ~> s aSource

type Context (~>) s a = ProductWith ~> s :% (ExponentialWith ~> s :% a)Source

contextComonadExtract :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> Context ~> s a ~> aSource

contextComonadDuplicate :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> Context ~> s a ~> Context ~> s (Context ~> s a)Source