compdata-0.6.1.4: Compositional Data Types

Portabilitynon-portable (GHC Extensions)
Stabilityexperimental
MaintainerPatrick Bahr <paba@diku.dk>
Safe HaskellNone

Data.Comp.Multi.Annotation

Description

This module defines annotations on signatures. All definitions are generalised versions of those in Data.Comp.Annotation.

Synopsis

Documentation

data (f :&: a) g e Source

This data type adds a constant product to a signature. Alternatively, this could have also been defined as

data (f :&: a) (g ::  * -> *) e = f g e :&: a e

This is too general, however, for example for productHHom.

Constructors

(f g e) :&: a 

Instances

DistAnn f p (:&: f p) 
HFunctor f => HFunctor (:&: f a) 
HFoldable f => HFoldable (:&: f a) 
HTraversable f => HTraversable (:&: f a) 
(ShowHF f, Show p) => ShowHF (:&: 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.

Methods

injectA :: p -> s a :-> s' aSource

This function injects an annotation over a signature.

projectA :: s' a :-> (s a :&: p)Source

Instances

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

class RemA s s' | s -> s' whereSource

Methods

remA :: s a :-> s' aSource

Instances

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

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

This function transforms 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.

ann :: (DistAnn f p g, HFunctor f) => p -> CxtFun f gSource

This function annotates each sub term of the given term with the given value (of type a).

liftA' :: (DistAnn s' p s, HFunctor s') => (s' a :-> Cxt h s' a) -> s a :-> Cxt h s aSource

This function transforms 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, HFunctor g) => CxtFun g fSource

This function strips the annotations from a term over a functor with annotations.

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

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

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