compdata-0.2: Compositional Data Types

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

Data.Comp.Multi.Product

Description

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

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 productHTermHom.

Constructors

(f g e) :&: a 

Instances

DistProd f p (:&: f p) 
HFunctor f => HFunctor (:&: f a) 
HFoldable f => HFoldable (:&: f a) 
HTraversable f => HTraversable (:&: f a) 
(HShowF f, Show p) => HShowF (:&: f p) 
RemoveP (:&: f p) f 
DistProd s p s' => DistProd (:+: f s) p (:+: (:&: f p) s') 
RemoveP s s' => RemoveP (:+: (:&: f p) s) (:+: f s') 

class DistProd s p s' | s' -> s, s' -> p whereSource

This class defines how to distribute a product over a sum of signatures.

Methods

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

This function injects a product a value over a signature.

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

Instances

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

class RemoveP s s' | s -> s' whereSource

Methods

removeP :: s a :-> s' aSource

Instances

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

liftP :: RemoveP 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 product.

constP :: (DistProd f p g, HFunctor f, HFunctor g) => p -> Cxt h f a :-> Cxt h g aSource

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

liftP' :: (DistProd s' p s, HFunctor 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 product.

stripP :: (HFunctor f, RemoveP g f, HFunctor g) => Cxt h g a :-> Cxt h f aSource

This function strips the products from a term over a functor whith products.

productTermHom :: (DistProd f p f', DistProd g p g', HFunctor g, HFunctor g') => TermHom f g -> TermHom f' g'Source

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