compdata-0.5.1: Compositional Data Types

Portabilitynon-portable (GHC Extensions)
Stabilityexperimental
MaintainerPatrick Bahr <paba@diku.dk>

Data.Comp.Ops

Description

This module provides operators on functors.

Synopsis

Documentation

data (f :+: g) e Source

Formal sum of signatures (functors).

Constructors

Inl (f e) 
Inr (g e) 

Instances

f :<: g => f :<: (:+: h g) 
f :<: (:+: f g) 
(Functor f, Functor g) => Functor (:+: f g) 
(Foldable f, Foldable g) => Foldable (:+: f g) 
(Traversable f, Traversable g) => Traversable (:+: f g) 
(ShowF f, ShowF g) => ShowF (:+: f g) 
(ArbitraryF f, ArbitraryF g) => ArbitraryF (:+: f g)

Instances of ArbitraryF are closed under forming sums.

(NFDataF f, NFDataF g) => NFDataF (:+: f g) 
(EqF f, EqF g) => EqF (:+: f g)

EqF is propagated through sums.

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

OrdF is propagated through sums.

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

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 -> sup aSource

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

Instances

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

data (f :*: g) a Source

Formal product of signatures (functors).

Constructors

(f a) :*: (g a) 

ffst :: (f :*: g) a -> f aSource

fsnd :: (f :*: g) a -> g aSource

data (f :&: a) e Source

This data type adds a constant product (annotation) to a signature.

Constructors

(f e) :&: a 

Instances

DistAnn f p (:&: f p) 
Functor f => Functor (:&: f a) 
Foldable f => Foldable (:&: f a) 
Traversable f => Traversable (:&: f a) 
(ShowF f, Show p) => ShowF (:&: f p) 
(ArbitraryF f, Arbitrary p) => ArbitraryF (:&: 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 -> s' aSource

Inject an annotation over a signature.

projectA :: s' a -> (s a, 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 -> s' aSource

Remove annotations from a signature.

Instances

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