compdata-param-0.9: Parametric Compositional Data Types

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

Data.Comp.Param.Multi.Annotation

Description

This module defines annotations on signatures.

Synopsis

Documentation

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

This data type adds a constant product to a signature.

Constructors

(f a b i) :&: p infixr 7 

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

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

Formal product of signatures (higher-order difunctors).

Constructors

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

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

liftA :: RemA s s' => (s' a b :-> t) -> s a b :-> t Source

Transform a function with a domain constructed from a higher-order difunctor to a function with a domain constructed with the same higher-order difunctor, but with an additional annotation.

liftA' :: (DistAnn s' p s, HDifunctor s') => (s' a b :-> Cxt h s' c d) -> s a b :-> Cxt h s c d Source

Transform a function with a domain constructed from a higher-order difunctor to a function with a domain constructed with the same higher-order difunctor, but with an additional annotation.

stripA :: (RemA g f, HDifunctor g) => CxtFun g f Source

Strip the annotations from a term over a higher-order difunctor with annotations.

propAnn :: (DistAnn f p f', DistAnn g p g', HDifunctor g) => Hom f g -> Hom f' g' Source

Lift a term homomorphism over signatures f and g to a term homomorphism over the same signatures, but extended with annotations.

propAnnM :: (DistAnn f p f', DistAnn g p g', HDifunctor g, Monad m) => HomM m f g -> HomM m f' g' Source

Lift a monadic term homomorphism over signatures f and g to a monadic term homomorphism over the same signatures, but extended with annotations.

ann :: (DistAnn f p g, HDifunctor f) => p -> CxtFun f g Source

Annotate each node of a term with a constant value.

project' :: (RemA f f', s :<: f') => Cxt h f a b i -> Maybe (s a (Cxt h f a b) i) Source

This function is similar to project but applies to signatures with an annotation which is then ignored.