compdata-0.2: Compositional Data Types

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

Data.Comp.Product

Description

This module defines products on signatures.

Synopsis

Documentation

data (f :&: a) e Source

This data type adds a constant product to a signature.

Constructors

(f e) :&: a 

Instances

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

data (f :*: g) a Source

Formal product of signatures (functors).

Constructors

(f a) :*: (g a) 

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

Inject a product value over a signature.

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

Project a product value from a signature.

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

Remove products from a signature.

Instances

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

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

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

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

Strip the products from a term over a functor with products.

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

Lift a term homomorphism over signatures f and g to a term homomorphism over the same signatures, but extended with products.

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

Annotate each node of a term with a constant value.

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