subhask-0.1.1.0: Type safe interface for programming in subcategories of Hask

Safe HaskellNone
LanguageHaskell2010

SubHask.Category

Contents

Description

SubHask supports two ways to encode categories in Haskell.

  • *Method 1**

Create a data type of kind k -> k -> *, and define an instance of the Category class. Because our version of Category uses the ConstraintKinds extension, we can encode many more categories than the standard Data.Category class.

There are many subclasses of Category for categories with extra features. Most of this module is spent defining these categories and instantiating appropriate instances for Hask.

Unfortunately, many of the terms used in category theory are non-standard. In this module, we try to follow the names used out in John Baez and Mike Stay's Rosetta Stone paper. This is a fairly accessible introduction to category theory for Haskeller's ready to move beyond "monads are monoids in the category of endofunctors."

FIXME: Writing laws for any classes in this file requires at least the Eq class from SubHask.Algebra. Hence, the laws are not explicitly stated anywhere.

  • *Method 2**

For any subcategory of Hask, we can define a type "ProofOf subcat". Then any function of type ProofOf subcat a -> ProofOf subcat b is an arrow within subcat. This is essentially a generalization of automatic differentiation to any category.

TODO: This needs a much better explanation and examples.

  • *Comparison** Method 1 is the primary way to represent a category. It's main advantage is that we have complete control over the representation in memory. With method 2, everything must be wrapped within function calls. Besides this layer of indirection, we also increase the chance for accidental space leaks.

Usually, it is easier to work with functions using method 1, but it is easier to construct functions using method 2.

FIXME: Currently, each category comes with its own mechanism for converting between the two representations. We need something more generic.

Synopsis

Documentation

class Category cat where Source

This Category class modifies the one in the Haskell standard to include the ValidCategory type constraint. This constraint let's us make instances of arbitrary subcategories of Hask.

Subcategories are defined using the subtyping mechanism "(<:)". Intuitively, arrows and objects in a subcategory satisfy additional properties that elements of the larger category do not necessarily satisfy. Elements of a subcategory can always be embeded in the larger category. Going in the other direction, however, requires a proof. These proofs can (usually) not be verified by the type system and are therefore labeled unsafe.

More details available at wikipedia and ncatlab.

Associated Types

type ValidCategory cat a :: Constraint Source

Methods

id :: ValidCategory cat a => cat a a Source

(.) :: cat b c -> cat a b -> cat a c infixr 9 Source

Instances

Category * (->) Source 
Category * DenseFunction Source 
Category * SparseFunctionMonoid Source 
Category * SparseFunction Source 
Category * Polynomial_ Source 
Category * (+>) Source 
Category * cat => Category * (IncreasingT cat) Source 
Category * cat => Category * (MonT cat) Source 
Category * cat => Category * ((/) cat obj) Source 
Category * cat => Category * (ConstrainedT xs cat) Source 
Category k cat => Category k (BijectiveT k k cat) Source 
Category k cat => Category k (SurjectiveT k k cat) Source 
Category k cat => Category k (InjectiveT k k cat) Source 
(Category k cat1, Category k cat2) => Category k ((><) k k cat1 cat2) Source 
Monad cat f => Category * (Kleisli * * * cat f) Source 
(Category k1 cat1, Category k1 cat2, Category k cat3) => Category k (Comma (k -> k -> *) k k cat1 cat2 cat3) Source 

(<<<) :: Category cat => cat b c -> cat a b -> cat a c Source

An alternative form of function composition taken from Control.Arrow

(>>>) :: Category cat => cat a b -> cat b c -> cat a c Source

An alternative form of function composition taken from Control.Arrow

Hask

type Hask = (->) Source

The category with Haskell types as objects, and functions as arrows.

More details available at the Haskell wiki.

($) :: Concrete subcat => subcat a b -> a -> b infixr 0 Source

We generalize the Prelude's definition of "$" so that it applies to any subcategory of Hask (that is, any Concrete Category. This lets us easily use these subcategories as functions. For example, given a polynomial function

f :: Polynomial Double

we can evaluate the polynomial at the number 5 by

f $ 5

NOTE: Base's implementation of $ has special compiler support that let's it work with the RankNTypes extension. This version does not. See this stackoverflow question for more detail.

($!) :: Concrete subcat => subcat a b -> a -> b infixr 0 Source

A strict version of $

embedHask :: Concrete subcat => subcat a b -> a -> b Source

Embeds a unary function into Hask

embedHask2 :: Concrete subcat => subcat a (subcat b c) -> a -> b -> c Source

Embeds a binary function into Hask

withCategory :: Concrete subcat => proxy subcat -> subcat a b -> a -> b Source

This is a special form of the embed function which can make specifying the category we are embedding into easier.

embed2 :: subcat <: cat => subcat a (subcat a b) -> cat a (cat a b) Source

FIXME: This would be a useful function to have, but I'm not sure how to implement it yet!

fst :: (a, b) -> a Source

"fst" specialized to Hask to aid with type inference FIXME: this will not be needed with injective types

snd :: (a, b) -> b Source

"snd" specialized to Hask to aid with type inference FIXME: this will not be needed with injective types

Special types of categories

type Concrete cat = cat <: (->) Source

Technicaly, a concrete category is any category equiped with a faithful functor to the category of sets. This is just a little too platonic to be represented in Haskell, but Hask makes a pretty good approximation. So we call any SubCategory of Hask Concrete. Importantly, not all categories are concrete. See the Slice category for an example.

More details available at wikipedia and ncatlib.

class (Category cat, ValidCategory cat (TUnit cat)) => Monoidal cat where Source

The intuition behind a monoidal category is similar to the intuition behind the Monoid algebraic structure. Unfortunately, there are a number of rather awkward laws to work out the technical details. The associator and unitor functions are provided to demonstrate the required isomorphisms.

More details available at wikipedia

Associated Types

type Tensor cat :: k -> k -> k Source

type TUnit cat :: k Source

Methods

tensor :: (ValidCategory cat a, ValidCategory cat b) => cat a (cat b (Tensor cat a b)) Source

tunit :: proxy cat -> TUnit cat Source

Instances

Monoidal (->) Source 
(AppConstraints xs (TUnit * cat), Monoidal cat) => Monoidal (ConstrainedT xs cat) Source 

class Monoidal cat => Braided cat where Source

Braided categories let us switch the order of tensored objects.

More details available at wikipedia and ncatlab

Methods

braid :: cat (Tensor cat a b) (Tensor cat b a) Source

unbraid :: cat (Tensor cat a b) (Tensor cat b a) Source

Instances

class Braided cat => Symmetric cat Source

In a symmetric braided category, braid and unbraid are inverses of each other.

More details available at wikipedia

Instances

class Symmetric cat => Cartesian cat where Source

In a cartesian monoidal category, the monoid object acts in a particularly nice way where we can compose and decompose it. Intuitively, we can delete information using the fst and snd arrows, as well as duplicate information using the duplicate arrow.

More details available at ncatlab

Methods

fst_ :: (ValidCategory cat a, ValidCategory cat b, ValidCategory cat (Tensor cat a b)) => cat (Tensor cat a b) a Source

snd_ :: (ValidCategory cat a, ValidCategory cat b, ValidCategory cat (Tensor cat a b)) => cat (Tensor cat a b) b Source

terminal :: ValidCategory cat a => a -> cat a (TUnit cat) Source

initial :: ValidCategory cat a => a -> cat (TUnit cat) a Source

Instances

const :: (Cartesian cat, ValidCategory cat a, ValidCategory cat b) => a -> cat b a Source

Creates an arrow that ignores its first parameter.

const2 :: (Cartesian cat, ValidCategory cat a, ValidCategory cat b) => a -> b -> cat b a Source

Based on the type signature, this looks like it should be the inverse of "embed" function. But it's not. This function completely ignores its second argument!

class Braided cat => Closed cat where Source

Closed monoidal categories allow currying, and closed braided categories allow flipping. We combine them into a single Closed class to simplify notation.

In general, closed categories need not be either Monoidal or Braided. All a closed category requires is that all arrows are also objects in the category. For example, `a +> (b +> c)` is a vallid arrow in the category `(+>)`. But I don't know of any uses for this general definition of a closed category. And this restricted definition seems to have a lot of uses.

More details available at wikipedia and ncatlab

Minimal complete definition

curry, uncurry

Methods

curry :: cat (Tensor cat a b) c -> cat a (cat b c) Source

uncurry :: cat a (cat b c) -> cat (Tensor cat a b) c Source

flip :: cat a (cat b c) -> cat b (cat a c) Source

The default definition should be correct for any category, but can be overridden with a more efficient implementation.

FIXME: does this actually need to be in a class? or should it be a stand-alone function like "const"?

Instances

Closed (->) Source 

class Category cat => Groupoid cat where Source

Groupoids are categories where every arrow can be reversed. This generalizes bijective and inverse functions. Notably, Hask is NOT a Groupoid.

More details available at wikipedia ncatlib, and stack overflow.

Methods

inverse :: cat a b -> cat b a Source

Instances

class Symmetric cat => Compact cat where Source

Compact categories are another generalization from linear algebra. In a compact category, we can dualize any object in the same way that we can generate a covector from a vector. Notably, Hask is NOT compact.

More details available at wikipedia and ncatlab.

Associated Types

type Dual cat x Source

Methods

unit :: cat x (Tensor cat x (Dual cat x)) Source

counit :: cat (Tensor cat (Dual cat x) x) x Source

class Category cat => Dagger cat where Source

A dagger (also called an involution) is an arrow that is its own inverse. Daggers generalize the idea of a transpose from linear algebra. Notably, Hask is NOT a dagger category.

More details avalable at wikipedia and ncatlab

Methods

trans :: cat a b -> cat b a Source

Instances

Proofs

class Concrete cat => Provable cat where Source

A provable category gives us the opposite ability as a Concrete category. Instead of embedding a function in the subcategory into Hask, we can embed certain functions from Hask into the subcategory.

Methods

($$) :: cat a b -> ProofOf_ cat a -> ProofOf_ cat b infixr 0 Source

If you want to apply a function inside of a proof, you must use the "($$)" operator instead of the more commonly used "($)".

FIXME: This is rather inelegant. Is there any way to avoid this?

type family ProofOf_ cat a Source

Equations

ProofOf_ Hask a = a 
ProofOf_ cat a = ProofOf cat a 

data family ProofOf cat a Source

This data family can be used to provide proofs that an arrow in Hask (i.e. a function) can be embedded in some subcategory. We're travelling in the opposite direction of the subtyping mechanism. That's valid only in a small number of cases. These proofs give a type safe way to capture some (but not all) of those cases.

Instances

(<:) * a (ProofOf * Hask a) Source 
Sup * a (ProofOf k cat a) (ProofOf k cat a) Source 
(Ord_ a, Ord_ b) => (<:) * (Hask (ProofOf * (IncreasingT Hask) a) (ProofOf * (IncreasingT Hask) b)) (IncreasingT Hask a b) Source 
Sup * (ProofOf k cat a) a (ProofOf k cat a) Source 
IsMutable (ProofOf * Polynomial_ a) Source 
IsMutable (ProofOf * (IncreasingT cat) a) Source 
(ValidLogic a, Ring a) => Ring (ProofOf * Polynomial_ a) Source 
(ValidLogic a, Ring a) => Rig (ProofOf * Polynomial_ a) Source 
(ValidLogic a, Ring a) => Rg (ProofOf * Polynomial_ a) Source 
(Ring a, Abelian a) => Abelian (ProofOf * Polynomial_ a) Source 
Abelian (ProofOf_ cat a) => Abelian (ProofOf * (IncreasingT cat) a) Source 
(ValidLogic a, Ring a) => Group (ProofOf * Polynomial_ a) Source 
(ValidLogic a, Ring a) => Cancellative (ProofOf * Polynomial_ a) Source 
(ValidLogic a, Ring a) => Monoid (ProofOf * Polynomial_ a) Source 
Ring a => Semigroup (ProofOf * Polynomial_ a) Source 
Semigroup (ProofOf_ cat a) => Semigroup (ProofOf * (IncreasingT cat) a) Source 
data ProofOf * Hask = ProofOf {} Source 
data ProofOf * Polynomial_ = ProofOf {} Source 
data ProofOf * (IncreasingT cat) = ProofOf {} Source 
data Mutable m (ProofOf * Polynomial_ a0) = Mutable_AppT__AppT__ConT_SubHask_Category_ProofOf___ConT_SubHask_Category_Polynomial_Polynomial_____VarT_a_1627677543_ (PrimRef m (ProofOf * Polynomial_ a)) Source 
data Mutable m (ProofOf * (IncreasingT cat0) a0) = Mutable_AppT__AppT__ConT_SubHask_Category_ProofOf___AppT__ConT_SubHask_Category_Trans_Monotonic_IncreasingT___VarT_cat_1627694764_____VarT_a_1627694763_ (PrimRef m (ProofOf * (IncreasingT cat) a)) Source