data-category-0.9: Category theory

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

Data.Category.Void

Description

 

Documentation

data Void a b Source #

Instances
(Category k, HasInitialObject k) => HasColimits Void k Source #

An initial object is the colimit of the functor from 0 to k.

Instance details

Defined in Data.Category.Limit

Methods

colimit :: Obj (Nat Void k) f -> Cocone Void k f (ColimitFam Void k f) Source #

colimitFactorizer :: Cocone Void k f n -> k (ColimitFam Void k f) n Source #

(Category k, HasTerminalObject k) => HasLimits Void k Source #

A terminal object is the limit of the functor from 0 to k.

Instance details

Defined in Data.Category.Limit

Methods

limit :: Obj (Nat Void k) f -> Cone Void k f (LimitFam Void k f) Source #

limitFactorizer :: Cone Void k f n -> k n (LimitFam Void k f) Source #

Category Void Source #

Void is the category with no objects.

Instance details

Defined in Data.Category.Void

Methods

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

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

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

type ColimitFam Void k f Source # 
Instance details

Defined in Data.Category.Limit

type LimitFam Void k f Source # 
Instance details

Defined in Data.Category.Limit

magic :: Void a b -> x Source #

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

data Magic (k :: * -> * -> *) Source #

Constructors

Magic 
Instances
Category k => Functor (Magic k) Source #

Since there is nothing to map in Void, there's a functor from it to any other category.

Instance details

Defined in Data.Category.Void

Associated Types

type Dom (Magic k) :: Type -> Type -> Type Source #

type Cod (Magic k) :: Type -> Type -> Type Source #

type (Magic k) :% a :: Type Source #

Methods

(%) :: Magic k -> Dom (Magic k) a b -> Cod (Magic k) (Magic k :% a) (Magic k :% b) Source #

type Dom (Magic k) Source # 
Instance details

Defined in Data.Category.Void

type Dom (Magic k) = Void
type Cod (Magic k) Source # 
Instance details

Defined in Data.Category.Void

type Cod (Magic k) = k