| Copyright | (c) 2010-2013 Patrick Bahr | 
|---|---|
| License | BSD3 | 
| Maintainer | Patrick Bahr <paba@diku.dk> | 
| Stability | experimental | 
| Portability | non-portable (GHC Extensions) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Data.Comp.Annotation
Description
This module defines annotations on signatures.
- data (f :&: a) e = (f e) :&: a
 - data (f :*: g) a = (f a) :*: (g a)
 - class DistAnn s p s' | s' -> s, s' -> p where
 - class RemA s s' | s -> s' where
 - liftA :: RemA s s' => (s' a -> t) -> s a -> t
 - liftA' :: (DistAnn s' p s, Functor s') => (s' a -> Cxt h s' a) -> s a -> Cxt h s a
 - stripA :: (RemA g f, Functor g) => CxtFun g f
 - propAnn :: (DistAnn f p f', DistAnn g p g', Functor g) => Hom f g -> Hom f' g'
 - propAnnM :: (DistAnn f p f', DistAnn g p g', Functor g, Monad m) => HomM m f g -> HomM m f' g'
 - ann :: (DistAnn f p g, Functor f) => p -> CxtFun f g
 - project' :: (RemA f f', s :<: f') => Cxt h f a -> Maybe (s (Cxt h f a))
 
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 k f p ((:&:) k f p) Source # | |
| RemA k ((:&:) k f p) f Source # | |
| DistAnn k s p s' => DistAnn k ((:+:) k f s) p ((:+:) k ((:&:) k f p) s') Source # | |
| RemA k s s' => RemA k ((:+:) k ((:&:) k f p) s) ((:+:) k f s') Source # | |
| Functor f => Functor ((:&:) * f a) Source # | |
| Foldable f => Foldable ((:&:) * f a) Source # | |
| Traversable f => Traversable ((:&:) * f a) Source # | |
| HasVars f v => HasVars ((:&:) * f a) v Source # | |
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.
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. 
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.