compdata-0.7.0.2: Compositional Data Types

Copyright(c) 2010-2013 Patrick Bahr
LicenseBSD3
MaintainerPatrick Bahr <paba@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell98

Data.Comp.Annotation

Description

This module defines annotations on signatures.

Synopsis

Documentation

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

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

Formal product of signatures (functors).

Constructors

(f a) :*: (g a) 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 -> 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') 

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

Transform a function with a domain constructed from a functor to a function with a domain constructed with the same functor, but with an additional annotation.

liftA' :: (DistAnn s' p s, Functor s') => (s' a -> Cxt h s' a) -> s a -> Cxt h s a Source

Transform a function with a domain constructed from a functor to a function with a domain constructed with the same functor, but with an additional annotation.

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

Strip the annotations from a term over a functor with annotations.

propAnn :: (DistAnn f p f', DistAnn g p g', Functor 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.

propAnnQ :: (DistAnn f p f', DistAnn g p g', Functor g) => QHom f q g -> QHom f' q g' Source

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

propAnnUp :: (DistAnn f p f', DistAnn g p g', Functor g) => UpTrans f q g -> UpTrans f' q g' Source

Lift a bottom-up tree transducer over signatures f and g to a bottom-up tree transducer over the same signatures, but extended with annotations.

propAnnDown :: (DistAnn f p f', DistAnn g p g', Functor g) => DownTrans f q g -> DownTrans f' q g' Source

Lift a top-down tree transducer over signatures f and g to a top-down tree transducer over the same signatures, but extended with annotations.

propAnnMacro :: (Functor f, Functor q, DistAnn f p f', DistAnn g p g', Functor g) => MacroTrans f q g -> MacroTrans f' q g' Source

Lift a macro tree transducer over signatures f and g to a macro tree transducer over the same signatures, but extended with annotations.

propAnnMacroLA :: (Functor f, Functor q, DistAnn f p f', DistAnn g p g', Functor g) => MacroTransLA f q p g -> MacroTransLA f' q p g' Source

Lift a macro tree transducer with regular look-ahead over signatures f and g to a macro tree transducer with regular look-ahead over the same signatures, but extended with annotations.

propAnnM :: (DistAnn f p f', DistAnn g p g', Functor 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, Functor f) => p -> CxtFun f g Source

Annotate each node of a term with a constant value.

pathAnn :: forall g. Traversable g => CxtFun g (g :&: [Int]) Source

This function adds unique annotations to a term/context. Each node in the term/context is annotated with its path from the root, which is represented as an integer list. It is implemented as a DTT.

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

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