constraints-0.4.1.3: Constraint manipulation

Copyright(C) 2011-2014 Edward Kmett,
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Constraint

Contents

Description

ConstraintKinds made type classes into types of a new kind, Constraint.

Eq :: * -> Constraint
Ord :: * -> Constraint
Monad :: (* -> *) -> Constraint

The need for this extension was first publicized in the paper

Scrap your boilerplate with class: extensible generic functions

by Ralf Lämmel and Simon Peyton Jones in 2005, which shoehorned all the things they needed into a custom Sat typeclass.

With ConstraintKinds we can put into code a lot of tools for manipulating these new types without such awkward workarounds.

Synopsis

The Kind of Constraints

data Constraint :: BOX

Instances

Category Constraint (:-)

Possible since GHC 7.8, when Category was made polykinded.

Typeable ((* -> *) -> Constraint) Alternative 
Typeable ((* -> *) -> Constraint) Applicative 
Typeable (* -> Constraint) Monoid 
Typeable (Constraint -> Constraint -> *) (:-) 
Typeable (Constraint -> *) Dict 

Dictionary

data Dict :: Constraint -> * where Source

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq 'Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: a => Dict a 

Instances

a :=> (Monoid (Dict a)) 
a :=> (Read (Dict a)) 
a :=> (Bounded (Dict a)) 
a :=> (Enum (Dict a)) 
() :=> (Eq (Dict a)) 
() :=> (Ord (Dict a)) 
() :=> (Show (Dict a)) 
a => Bounded (Dict a) 
a => Enum (Dict a) 
Eq (Dict a) 
(Typeable Constraint p, p) => Data (Dict p) 
Ord (Dict a) 
a => Read (Dict a) 
Show (Dict a) 
a => Monoid (Dict a) 
Typeable (Constraint -> *) Dict 

Entailment

newtype a :- b infixr 9 Source

This is the type of entailment.

a :- b is read as a "entails" b.

With this we can actually build a category for Constraint resolution.

e.g.

Because Eq a is a superclass of Ord a, we can show that Ord a entails Eq a.

Because instance Ord a => Ord [a] exists, we can show that Ord a entails Ord [a] as well.

This relationship is captured in the :- entailment type here.

Since p :- p and entailment composes, :- forms the arrows of a Category of constraints. However, Category only because sufficiently general to support this instance in GHC 7.8, so prior to 7.8 this instance is unavailable.

But due to the coherence of instance resolution in Haskell, this Category has some very interesting properties. Notably, in the absence of IncoherentInstances, this category is "thin", which is to say that between any two objects (constraints) there is at most one distinguishable arrow.

This means that for instance, even though there are two ways to derive Ord a :- Eq [a], the answers from these two paths _must_ by construction be equal. This is a property that Haskell offers that is pretty much unique in the space of languages with things they call "type classes".

What are the two ways?

Well, we can go from Ord a :- Eq a via the superclass relationship, and them from Eq a :- Eq [a] via the instance, or we can go from Ord a :- Ord [a] via the instance then from Ord [a] :- Eq [a] through the superclass relationship and this diagram by definition must "commute".

Diagrammatically,

                   Ord a
               ins /     \ cls
                  v       v
            Ord [a]     Eq a
               cls \     / ins
                    v   v
                   Eq [a]

This safety net ensures that pretty much anything you can write with this library is sensible and can't break any assumptions on the behalf of library authors.

Constructors

Sub (a => Dict b) 

Instances

Category Constraint (:-)

Possible since GHC 7.8, when Category was made polykinded.

() :=> (Eq ((:-) a b)) 
() :=> (Ord ((:-) a b)) 
() :=> (Show ((:-) a b)) 
Eq ((:-) a b)

Assumes IncoherentInstances doesn't exist.

(Typeable Constraint p, Typeable Constraint q, p, q) => Data ((:-) p q) 
Ord ((:-) a b)

Assumes IncoherentInstances doesn't exist.

Show ((:-) a b) 
Typeable (Constraint -> Constraint -> *) (:-) 

(\\) :: a => (b => r) -> (a :- b) -> r infixl 1 Source

Given that a :- b, derive something that needs a context b, using the context a

weaken1 :: (a, b) :- a Source

Weakening a constraint product

The category of constraints is Cartesian. We can forget information.

weaken2 :: (a, b) :- b Source

Weakening a constraint product

The category of constraints is Cartesian. We can forget information.

contract :: a :- (a, a) Source

Contracting a constraint / diagonal morphism

The category of constraints is Cartesian. We can reuse information.

(&&&) :: (a :- b) -> (a :- c) -> a :- (b, c) Source

Constraint product

trans weaken1 (f &&& g) = f
trans weaken2 (f &&& g) = g

(***) :: (a :- b) -> (c :- d) -> (a, c) :- (b, d) Source

due to the hack for the kind of (,) in the current version of GHC we can't actually make instances for (,) :: Constraint -> Constraint -> Constraint, but (,) is a bifunctor on the category of constraints. This lets us map over both sides.

trans :: (b :- c) -> (a :- b) -> a :- c Source

Transitivity of entailment

If we view (:-) as a Constraint-indexed category, then this is (.)

refl :: a :- a Source

Reflexivity of entailment

If we view (:-) as a Constraint-indexed category, then this is id

top :: a :- () Source

Every constraint implies truth

These are the terminal arrows of the category, and () is the terminal object.

Given any constraint there is a unique entailment of the () constraint from that constraint.

bottom :: (() ~ Bool) :- c Source

A bad type coercion lets you derive any constraint you want.

These are the initial arrows of the category and (() ~ Bool) is the initial object

This demonstrates the law of classical logic "ex falso quodlibet"

Dict is fully faithful

mapDict :: (a :- b) -> Dict a -> Dict b Source

Apply an entailment to a dictionary.

From a category theoretic perspective Dict is a functor that maps from the category of constraints (with arrows in :-) to the category Hask of Haskell data types.

unmapDict :: (Dict a -> Dict b) -> a :- b Source

This functor is fully faithful, which is to say that given any function you can write Dict a -> Dict b there also exists an entailment a :- b in the category of constraints that you can build.

Reflection

class Class b h | h -> b where Source

Reify the relationship between a class and its superclass constraints as a class

Given a definition such as

class Foo a => Bar a

you can capture the relationship between 'Bar a' and its superclass 'Foo a' with

instance Class (Foo a) (Bar a) where cls = Sub Dict

Now the user can use 'cls :: Bar a :- Foo a'

Methods

cls :: h :- b Source

Instances

Class () () 
Class () (Bounded a) 
Class () (Enum a) 
Class () (Eq a) 
Class () (Monad f) 
Class () (Functor f) 
Class () (Num a) 
Class () (Read a) 
Class () (Show a) 
Class () (Monoid a) 
Class b a => () :=> (Class b a) 
Class () ((:=>) b a) 
Class () (Class b a) 
Class (Eq a) (Ord a) 
Class (Fractional a) (Floating a) 
Class (Monad f) (MonadPlus f) 
Class (Functor f) (Applicative f) 
Class (Num a) (Fractional a) 
Class (Applicative f) (Alternative f) 
Class (Num a, Ord a) (Real a) 
Class (Real a, Fractional a) (RealFrac a) 
Class (Real a, Enum a) (Integral a) 
Class (RealFrac a, Floating a) (RealFloat a) 

class b :=> h | h -> b where infixr 9 Source

Reify the relationship between an instance head and its body as a class

Given a definition such as

instance Foo a => Foo [a]

you can capture the relationship between the instance head and its body with

instance Foo a :=> Foo [a] where ins = Sub Dict

Methods

ins :: b :- h Source

Instances

() :=> () 
a :=> (Monoid (Dict a)) 
a :=> (Read (Dict a)) 
a :=> (Bounded (Dict a)) 
a :=> (Enum (Dict a)) 
() :=> (Alternative []) 
() :=> (Alternative Maybe) 
() :=> (Bounded Bool) 
() :=> (Bounded Char) 
() :=> (Bounded Int) 
() :=> (Bounded Ordering) 
() :=> (Bounded ()) 
() :=> (Enum Bool) 
() :=> (Enum Char) 
() :=> (Enum Double) 
() :=> (Enum Float) 
() :=> (Enum Int) 
() :=> (Enum Integer) 
() :=> (Enum Ordering) 
() :=> (Enum ()) 
() :=> (Eq Bool) 
() :=> (Eq Double) 
() :=> (Eq Float) 
() :=> (Eq Int) 
() :=> (Eq Integer) 
() :=> (Eq ()) 
() :=> (Eq ((:-) a b)) 
() :=> (Eq (Dict a)) 
() :=> (Floating Double) 
() :=> (Floating Float) 
() :=> (Fractional Double) 
() :=> (Fractional Float) 
() :=> (Integral Int) 
() :=> (Integral Integer) 
() :=> (Monad ((->) a)) 
() :=> (Monad []) 
() :=> (Monad IO) 
() :=> (Monad (Either a)) 
() :=> (Functor ((->) a)) 
() :=> (Functor []) 
() :=> (Functor IO) 
() :=> (Functor (Either a)) 
() :=> (Functor ((,) a)) 
() :=> (Functor Maybe) 
() :=> (Num Double) 
() :=> (Num Float) 
() :=> (Num Int) 
() :=> (Num Integer) 
() :=> (Ord Bool) 
() :=> (Ord Char) 
() :=> (Ord Double) 
() :=> (Ord Float) 
() :=> (Ord Int) 
() :=> (Ord Integer) 
() :=> (Ord ()) 
() :=> (Ord ((:-) a b)) 
() :=> (Ord (Dict a)) 
() :=> (Read Bool) 
() :=> (Read Char) 
() :=> (Read Ordering) 
() :=> (Read ()) 
() :=> (Real Double) 
() :=> (Real Float) 
() :=> (Real Int) 
() :=> (Real Integer) 
() :=> (RealFloat Double) 
() :=> (RealFloat Float) 
() :=> (RealFrac Double) 
() :=> (RealFrac Float) 
() :=> (Show Bool) 
() :=> (Show Char) 
() :=> (Show Ordering) 
() :=> (Show ()) 
() :=> (Show ((:-) a b)) 
() :=> (Show (Dict a)) 
() :=> (MonadPlus []) 
() :=> (MonadPlus Maybe) 
() :=> (Applicative ((->) a)) 
() :=> (Applicative []) 
() :=> (Applicative IO) 
() :=> (Applicative (Either a)) 
() :=> (Applicative Maybe) 
() :=> (Monoid [a]) 
() :=> (Monoid Ordering) 
() :=> (Monoid ()) 
(:=>) b a => () :=> ((:=>) b a) 
Class b a => () :=> (Class b a) 
Class () ((:=>) b a) 
(Eq a) :=> (Eq (Ratio a)) 
(Eq a) :=> (Eq (Complex a)) 
(Eq a) :=> (Eq (Maybe a)) 
(Eq a) :=> (Eq [a]) 
(Integral a) :=> (RealFrac (Ratio a)) 
(Integral a) :=> (Fractional (Ratio a)) 
(Integral a) :=> (Real (Ratio a)) 
(Integral a) :=> (Num (Ratio a)) 
(Integral a) :=> (Enum (Ratio a)) 
(Integral a) :=> (Ord (Ratio a)) 
(Monad m) :=> (Applicative (WrappedMonad m)) 
(Monad m) :=> (Functor (WrappedMonad m)) 
(Ord a) :=> (Ord [a]) 
(Ord a) :=> (Ord (Maybe a)) 
(Read a) :=> (Read (Maybe a)) 
(Read a) :=> (Read [a]) 
(Read a) :=> (Read (Complex a)) 
(RealFloat a) :=> (Floating (Complex a)) 
(RealFloat a) :=> (Fractional (Complex a)) 
(RealFloat a) :=> (Num (Complex a)) 
(Show a) :=> (Show (Maybe a)) 
(Show a) :=> (Show [a]) 
(Show a) :=> (Show (Complex a)) 
(MonadPlus m) :=> (Alternative (WrappedMonad m)) 
(Monoid a) :=> (Applicative ((,) a)) 
(Monoid a) :=> (Monoid (Maybe a)) 
(Bounded a, Bounded b) :=> (Bounded (a, b)) 
(Eq a, Eq b) :=> (Eq (Either a b)) 
(Eq a, Eq b) :=> (Eq (a, b)) 
(Integral a, Read a) :=> (Read (Ratio a)) 
(Integral a, Show a) :=> (Show (Ratio a)) 
(Ord a, Ord b) :=> (Ord (Either a b)) 
(Ord a, Ord b) :=> (Ord (a, b)) 
(Read a, Read b) :=> (Read (Either a b)) 
(Read a, Read b) :=> (Read (a, b)) 
(Show a, Show b) :=> (Show (Either a b)) 
(Show a, Show b) :=> (Show (a, b)) 
(Monoid a, Monoid b) :=> (Monoid (a, b))