compdata-0.6.1.3: Compositional Data Types

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

Data.Comp.MultiParam.Ops

Description

This module provides operators on higher-order difunctors.

Synopsis

Documentation

data (f :+: g) a b i Source

Formal sum of signatures (difunctors).

Constructors

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

Instances

:<: f g => f :<: (:+: h g) 
f :<: (:+: f g) 
(HDifunctor f, HDifunctor g) => HDifunctor (:+: f g) 
(HDitraversable f, HDitraversable g) => HDitraversable (:+: f g) 
(ShowHD f, ShowHD g) => ShowHD (:+: f g) 
(EqHD f, EqHD g) => EqHD (:+: f g)

EqHD is propagated through sums.

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

OrdHD 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 i), Eq (g a b i)) => Eq (:+: f g a b i) 
(Ord (f a b i), Ord (g a b i)) => Ord (:+: f g a b i) 
(Show (f a b i), Show (g a b i)) => Show (:+: f g a b i) 

caseHD :: (f a b i -> c) -> (g a b i -> c) -> (f :+: g) a b i -> cSource

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

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 :: NatM Maybe (sup a b) (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 (higher-order 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 i Source

This data type adds a constant product to a signature.

Constructors

(f a b i) :&: p 

Instances

DistAnn f p (:&: f p) 
HDifunctor f => HDifunctor (:&: f p) 
HDitraversable f => HDitraversable (:&: f p) 
(ShowHD f, Show p) => ShowHD (:&: 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 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')