compdata-0.7.0.2: Compositional Data Types

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

Data.Comp.Ops

Description

This module provides operators on functors.

Synopsis

Documentation

data (f :+: g) e infixr 6 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) v 
(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), 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) 

caseF :: (f a -> b) -> (g a -> b) -> (f :+: g) a -> b Source

Utility function to case on a functor 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 -> sup a Source

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

Instances

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

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

Formal product of signatures (functors).

Constructors

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

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

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

data (f :&: a) e infixr 7 Source

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

Constructors

(f e) :&: a infixr 7 

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) 
(NFDataF f, NFData a) => NFDataF ((:&:) f a) 
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 -> s' a Source

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' where Source

Methods

remA :: s a -> s' a Source

Remove annotations from a signature.

Instances

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