compdata-0.1: 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

HDistProd 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) 
HRemoveP (:&&: f p) f 
HDistProd s p s' => HDistProd (:++: f s) p (:++: (:&&: f p) s') 
HRemoveP s s' => HRemoveP (:++: (:&&: f p) s) (:++: f s') 

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

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

Methods

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

This function injects a product a value over a signature.

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

Instances

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

class HRemoveP s s' | s -> s' whereSource

Methods

hremoveP :: s a :-> s' aSource

Instances

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

liftP :: HRemoveP 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 :: (HDistProd f p g, HFunctor f, HFunctor g) => p -> HCxt h f a :-> HCxt h g aSource

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

liftP' :: (HDistProd s' p s, HFunctor s, HFunctor s') => (s' a :-> HCxt h s' a) -> s a :-> HCxt 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, HRemoveP g f, HFunctor g) => HCxt h g a :-> HCxt h f aSource

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

productHTermHom :: (HDistProd f p f', HDistProd g p g', HFunctor g, HFunctor g') => HTermHom f g -> HTermHom f' g'Source

hproject' :: (HRemoveP g s', g :<<: f) => HCxt h f a i -> Maybe (s' (HCxt h f a) i)Source