| Portability | non-portable (GHC Extensions) | 
|---|---|
| Stability | experimental | 
| Maintainer | Patrick Bahr <paba@diku.dk> | 
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
- remA :: s a -> s' a
 
 - 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 s s', s :<: f) => Cxt h f a -> Maybe (s' (Cxt h f a))
 
Documentation
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.
liftA :: RemA s s' => (s' a -> t) -> s a -> tSource
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 aSource
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 fSource
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.