compdata-0.3: Compositional Data Types

Portabilitynon-portable (GHC Extensions)
Stabilityexperimental
MaintainerTom Hvitved <hvitved@diku.dk>

Data.Comp.Param.Ops

Description

This module provides operators on difunctors.

Synopsis

Documentation

data (f :+: g) a b Source

Formal sum of signatures (difunctors).

Constructors

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

Instances

f :<: g => f :<: (:+: h g) 
f :<: (:+: f g) 
(Difunctor f, Difunctor g) => Difunctor (:+: 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.

(ShowD f, ShowD g) => ShowD (:+: f g) 
(Desugar f g[aZw0], Desugar g g[aZw0]) => Desugar (:+: f g) g[aZw0] 
(Ditraversable f m a, Ditraversable g m a) => Ditraversable (:+: f g) m a 
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) 

class sub :<: sup whereSource

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 bSource

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 Source

Formal product of signatures (difunctors).

Constructors

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

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

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

data (f :&: p) a b Source

This data type adds a constant product to a signature.

Constructors

(f a b) :&: p 

Instances

DistAnn f p (:&: f p) 
Difunctor f => Difunctor (:&: f p) 
(ShowD f, PShow p) => ShowD (:&: f p) 
RemA (:&: f p) f 
Ditraversable f m a => Ditraversable (:&: f p) m a 
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 whereSource

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

Methods

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

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' whereSource

Methods

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

Remove annotations from a signature.

Instances

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