data-category-0.4: Restricted categories

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.Category.Discrete

Contents

Description

Discrete n, the category with n objects, and as the only arrows their identities.

Synopsis

Discrete Categories

data Discrete whereSource

The arrows in Discrete n, a finite set of identity arrows.

Constructors

Z :: Discrete (S n) Z Z 
S :: Discrete n a a -> Discrete (S n) (S a) (S a) 

Instances

Category (Discrete Z)

Discrete Z is the discrete category with no objects.

Category (Discrete n) => Category (Discrete (S n))

Discrete (S n) is the discrete category with one object more than Discrete n.

(HasLimits (Discrete n) ~>, HasBinaryProducts ~>) => HasLimits (Discrete (S n)) ~> 
(HasColimits (Discrete n) ~>, HasBinaryCoproducts ~>) => HasColimits (Discrete (S n)) ~> 

data Z Source

Instances

Category (Discrete Z)

Discrete Z is the discrete category with no objects.

Category ~> => Functor (DiscreteDiagram ~> Z ()) 

data S n Source

Instances

Category (Discrete n) => Category (Discrete (S n))

Discrete (S n) is the discrete category with one object more than Discrete n.

(HasLimits (Discrete n) ~>, HasBinaryProducts ~>) => HasLimits (Discrete (S n)) ~> 
(HasColimits (Discrete n) ~>, HasBinaryCoproducts ~>) => HasColimits (Discrete (S n)) ~> 
(Category ~>, Category (Discrete n), Functor (DiscreteDiagram ~> n xs)) => Functor (DiscreteDiagram ~> (S n) (x, xs)) 

type Void = Discrete ZSource

Void is the empty category.

type Unit = Discrete (S Z)Source

Unit is the discrete category with one object.

type Pair = Discrete (S (S Z))Source

Pair is the discrete category with two objects.

magicZ :: Discrete Z a b -> xSource

Functors

data Succ n Source

Constructors

Succ 

Instances

data DiscreteDiagram whereSource

The functor from Discrete n to (~>), a diagram of n objects in (~>).

Constructors

Nil :: DiscreteDiagram ~> Z () 
::: :: Obj ~> x -> DiscreteDiagram ~> n xs -> DiscreteDiagram ~> (S n) (x, xs) 

Instances

(Category ~>, Category (Discrete n), Functor (DiscreteDiagram ~> n xs)) => Functor (DiscreteDiagram ~> (S n) (x, xs)) 
Category ~> => Functor (DiscreteDiagram ~> Z ()) 

Natural Transformations

voidNat :: (Functor f, Functor g, Category d, Dom f ~ Void, Dom g ~ Void, Cod f ~ d, Cod g ~ d) => f -> g -> Nat Void d f gSource