data-category-0.7.2: Category theory

LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Category.Unit

Description

 

Documentation

data Unit a b where Source #

Constructors

Unit :: Unit () () 
Instances
Category Unit Source #

Unit is the category with one object.

Instance details

Defined in Data.Category.Unit

Methods

src :: Unit a b -> Obj Unit a Source #

tgt :: Unit a b -> Obj Unit b Source #

(.) :: Unit b c -> Unit a b -> Unit a c Source #

HasBinaryCoproducts Unit Source #

In the category of one object that object is its own coproduct.

Instance details

Defined in Data.Category.Limit

Associated Types

type BinaryCoproduct Unit x y :: Type Source #

Methods

inj1 :: Obj Unit x -> Obj Unit y -> Unit x (BinaryCoproduct Unit x y) Source #

inj2 :: Obj Unit x -> Obj Unit y -> Unit y (BinaryCoproduct Unit x y) Source #

(|||) :: Unit x a -> Unit y a -> Unit (BinaryCoproduct Unit x y) a Source #

(+++) :: Unit a1 b1 -> Unit a2 b2 -> Unit (BinaryCoproduct Unit a1 a2) (BinaryCoproduct Unit b1 b2) Source #

HasBinaryProducts Unit Source #

In the category of one object that object is its own product.

Instance details

Defined in Data.Category.Limit

Associated Types

type BinaryProduct Unit x y :: Type Source #

Methods

proj1 :: Obj Unit x -> Obj Unit y -> Unit (BinaryProduct Unit x y) x Source #

proj2 :: Obj Unit x -> Obj Unit y -> Unit (BinaryProduct Unit x y) y Source #

(&&&) :: Unit a x -> Unit a y -> Unit a (BinaryProduct Unit x y) Source #

(***) :: Unit a1 b1 -> Unit a2 b2 -> Unit (BinaryProduct Unit a1 a2) (BinaryProduct Unit b1 b2) Source #

HasInitialObject Unit Source #

The category of one object has that object as initial object.

Instance details

Defined in Data.Category.Limit

Associated Types

type InitialObject Unit :: Type Source #

HasTerminalObject Unit Source #

The category of one object has that object as terminal object.

Instance details

Defined in Data.Category.Limit

Associated Types

type TerminalObject Unit :: Type Source #

CartesianClosed Unit Source # 
Instance details

Defined in Data.Category.CartesianClosed

Associated Types

type Exponential Unit y z :: Type Source #

Methods

apply :: Obj Unit y -> Obj Unit z -> Unit (BinaryProduct Unit (Exponential Unit y z) y) z Source #

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

(^^^) :: Unit z1 z2 -> Unit y2 y1 -> Unit (Exponential Unit y1 z1) (Exponential Unit y2 z2) Source #

Category k => HasColimits Unit k Source #

The colimit of a single object is that object.

Instance details

Defined in Data.Category.Limit

Methods

colimit :: Obj (Nat Unit k) f -> Cocone f (Colimit f) Source #

colimitFactorizer :: Obj (Nat Unit k) f -> Cocone f n -> k (Colimit f) n Source #

Category k => HasLimits Unit k Source #

The limit of a single object is that object.

Instance details

Defined in Data.Category.Limit

Methods

limit :: Obj (Nat Unit k) f -> Cone f (Limit f) Source #

limitFactorizer :: Obj (Nat Unit k) f -> Cone f n -> k n (Limit f) Source #

type InitialObject Unit Source # 
Instance details

Defined in Data.Category.Limit

type TerminalObject Unit Source # 
Instance details

Defined in Data.Category.Limit

type BinaryCoproduct Unit () () Source # 
Instance details

Defined in Data.Category.Limit

type BinaryCoproduct Unit () () = ()
type BinaryProduct Unit () () Source # 
Instance details

Defined in Data.Category.Limit

type BinaryProduct Unit () () = ()
type ColimitFam Unit k f Source # 
Instance details

Defined in Data.Category.Limit

type ColimitFam Unit k f = f :% ()
type LimitFam Unit k f Source # 
Instance details

Defined in Data.Category.Limit

type LimitFam Unit k f = f :% ()
type Exponential Unit () () Source # 
Instance details

Defined in Data.Category.CartesianClosed

type Exponential Unit () () = ()