compdata-param-0.9: Parametric Compositional Data Types

Copyright(c) 2011 Patrick Bahr, Tom Hvitved
LicenseBSD3
MaintainerTom Hvitved <hvitved@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Comp.Param.Ops

Description

This module provides operators on difunctors.

Synopsis

Documentation

data (f :+: g) a b infixr 6 Source

Formal sum of signatures (difunctors).

Constructors

Inl (f a b) 
Inr (g a b) 

Instances

(:<:) f g => f :<: ((:+:) h g) 
f :<: ((:+:) f g) 
(ShowD f, ShowD g) => ShowD ((:+:) f g) 
(Difunctor f, Difunctor g) => Difunctor ((:+:) f g) 
(Ditraversable f, Ditraversable g) => Ditraversable ((:+:) f g) 
(EqD f, EqD g) => EqD ((:+:) f g)

EqD is propagated through sums.

(OrdD f, OrdD g) => OrdD ((:+:) f g)

OrdD is propagated through sums.

(Desugar f h, Desugar g h) => Desugar ((:+:) f g) h 
DistAnn s p s' => DistAnn ((:+:) f s) p ((:+:) ((:&:) f p) s') 
RemA s s' => RemA ((:+:) ((:&:) f p) s) ((:+:) f s') 
(Eq (f a b), Eq (g a b)) => Eq ((:+:) f g a b) 
(Ord (f a b), Ord (g a b)) => Ord ((:+:) f g a b) 
(Show (f a b), Show (g a b)) => Show ((:+:) f g a b) 

caseD :: (f a b -> c) -> (g a b -> c) -> (f :+: g) a b -> c Source

Utility function to case on a difunctor sum, without exposing the internal representation of sums.

class sub :<: sup where Source

Signature containment relation for automatic injections. The left-hand must be an atomic signature, where as the right-hand side must have a list-like structure. Examples include f :<: f :+: g and g :<: f :+: (g :+: h), non-examples include f :+: g :<: f :+: (g :+: h) and f :<: (f :+: g) :+: h.

Methods

inj :: sub a b -> sup a b Source

proj :: sup a b -> Maybe (sub a b) Source

Instances

f :<: f 
(:<:) f g => f :<: ((:+:) h g) 
f :<: ((:+:) f g) 

data (f :*: g) a b infixr 8 Source

Formal product of signatures (difunctors).

Constructors

(f a b) :*: (g a b) infixr 8 

ffst :: (f :*: g) a b -> f a b Source

fsnd :: (f :*: g) a b -> g a b Source

data (f :&: p) a b infixr 7 Source

This data type adds a constant product to a signature.

Constructors

(f a b) :&: p infixr 7 

Instances

DistAnn f p ((:&:) f p) 
(ShowD f, Show p) => ShowD ((:&:) f p) 
Difunctor f => Difunctor ((:&:) f p) 
Ditraversable f => Ditraversable ((:&:) f p) 
RemA ((:&:) f p) f 
DistAnn s p s' => DistAnn ((:+:) f s) p ((:+:) ((:&:) f p) s') 
RemA s s' => RemA ((:+:) ((:&:) f p) s) ((:+:) f s') 

class DistAnn s p s' | s' -> s, s' -> p where Source

This class defines how to distribute an annotation over a sum of signatures.

Methods

injectA :: p -> s a b -> s' a b Source

Inject an annotation over a signature.

projectA :: s' a b -> (s a b, p) Source

Project an annotation from a signature.

Instances

DistAnn f p ((:&:) f p) 
DistAnn s p s' => DistAnn ((:+:) f s) p ((:+:) ((:&:) f p) s') 

class RemA s s' | s -> s' where Source

Methods

remA :: s a b -> s' a b Source

Remove annotations from a signature.

Instances

RemA ((:&:) f p) f 
RemA s s' => RemA ((:+:) ((:&:) f p) s) ((:+:) f s')