data-category-0.6.2: Category theory

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

Data.Category.Fix

Description

 

Synopsis

Documentation

newtype Fix f a b Source #

Constructors

Fix (f (Fix f) a b) 

Instances

Category (f (Fix f)) => Category (Fix f) Source #

Fix f is the fixed point category for a category combinator f.

Methods

src :: Fix f a b -> Obj (Fix f) a Source #

tgt :: Fix f a b -> Obj (Fix f) b Source #

(.) :: Fix f b c -> Fix f a b -> Fix f a c Source #

HasBinaryCoproducts (f (Fix f)) => HasBinaryCoproducts (Fix f) Source #

Fix f inherits its (co)limits from f (Fix f).

Associated Types

type BinaryCoproduct (Fix f :: * -> * -> *) x y :: * Source #

Methods

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

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

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

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

HasBinaryProducts (f (Fix f)) => HasBinaryProducts (Fix f) Source #

Fix f inherits its (co)limits from f (Fix f).

Associated Types

type BinaryProduct (Fix f :: * -> * -> *) x y :: * Source #

Methods

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

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

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

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

HasInitialObject (f (Fix f)) => HasInitialObject (Fix f) Source #

Fix f inherits its (co)limits from f (Fix f).

Associated Types

type InitialObject (Fix f :: * -> * -> *) :: * Source #

HasTerminalObject (f (Fix f)) => HasTerminalObject (Fix f) Source #

Fix f inherits its (co)limits from f (Fix f).

Associated Types

type TerminalObject (Fix f :: * -> * -> *) :: * Source #

CartesianClosed (f (Fix f)) => CartesianClosed (Fix f) Source #

Fix f inherits its exponentials from f (Fix f).

Associated Types

type Exponential (Fix f :: * -> * -> *) y z :: * Source #

Methods

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

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

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

type InitialObject (Fix f) Source # 
type InitialObject (Fix f) = InitialObject (f (Fix f))
type TerminalObject (Fix f) Source # 
type BinaryCoproduct (Fix f) a b Source # 
type BinaryCoproduct (Fix f) a b = BinaryCoproduct (f (Fix f)) a b
type BinaryProduct (Fix f) a b Source # 
type BinaryProduct (Fix f) a b = BinaryProduct (f (Fix f)) a b
type Exponential (Fix f) a b Source # 
type Exponential (Fix f) a b = Exponential (f (Fix f)) a b

data Wrap f Source #

Constructors

Wrap 

Instances

Category (f (Fix f)) => Functor (Wrap f) Source #

The Wrap functor wraps Fix around f (Fix f).

Associated Types

type Dom (Wrap f) :: * -> * -> * Source #

type Cod (Wrap f) :: * -> * -> * Source #

type (Wrap f) :% a :: * Source #

Methods

(%) :: Wrap f -> Dom (Wrap f) a b -> Cod (Wrap f) (Wrap f :% a) (Wrap f :% b) Source #

type Dom (Wrap f) Source # 
type Dom (Wrap f) = f (Fix f)
type Cod (Wrap f) Source # 
type Cod (Wrap f) = Fix f
type (Wrap f) :% a Source # 
type (Wrap f) :% a = a

type Omega = Fix ((:>>:) Unit) Source #

Take the Omega category, add a new disctinct object, and an arrow from that object to every object in Omega, and you get Omega again.