compdata-0.10.1: Compositional Data Types

Copyright(c) 2010-2011 Patrick Bahr, Tom Hvitved
LicenseBSD3
MaintainerPatrick Bahr <paba@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellSafe
LanguageHaskell98

Data.Comp.Ops

Description

This module provides operators on functors.

Synopsis

Documentation

data (f :+: g) e infixr 6 Source

Formal sum of signatures (functors).

Constructors

Inl (f e) 
Inr (g e) 

Instances

DistAnn k s p s' => DistAnn k ((:+:) k f s) p ((:+:) k ((:&:) k f p) s') Source 
RemA k s s' => RemA k ((:+:) k ((:&:) k f p) s) ((:+:) k f s') Source 
(Functor f, Functor g) => Functor ((:+:) * f g) Source 
(Foldable f, Foldable g) => Foldable ((:+:) * f g) Source 
(Traversable f, Traversable g) => Traversable ((:+:) * f g) Source 
(Render f, Render g) => Render ((:+:) * f g) Source 
(HasVars f v0, HasVars g v0) => HasVars ((:+:) * f g) v Source 
(Desugar f h, Desugar g h) => Desugar ((:+:) * f g) h Source 

fromInl :: (f :+: g) e -> Maybe (f e) Source

fromInr :: (f :+: g) e -> Maybe (g e) Source

caseF :: (f a -> b) -> (g a -> b) -> (f :+: g) a -> b Source

Utility function to case on a functor sum, without exposing the internal representation of sums.

type family Elem f g :: Emb Source

Equations

Elem f f = Found Here 
Elem (f1 :+: f2) g = Sum' (Elem f1 g) (Elem f2 g) 
Elem f (g1 :+: g2) = Choose (Elem f g1) (Elem f g2) 
Elem f g = NotFound 

class Subsume e f g where Source

Methods

inj' :: Proxy e -> f a -> g a Source

prj' :: Proxy e -> g a -> Maybe (f a) Source

type (:<:) f g = Subsume (ComprEmb (Elem f g)) f g infixl 5 Source

A constraint f :<: g expresses that the signature f is subsumed by g, i.e. f can be used to construct elements in g.

inj :: forall f g a. f :<: g => f a -> g a Source

proj :: forall f g a. f :<: g => g a -> Maybe (f a) Source

type (:=:) f g = (f :<: g, g :<: f) infixl 5 Source

spl :: f :=: (f1 :+: f2) => (f1 a -> b) -> (f2 a -> b) -> f a -> b Source

data (f :*: g) a infixr 8 Source

Formal product of signatures (functors).

Constructors

(f a) :*: (g a) infixr 8 

Instances

ffst :: (f :*: g) a -> f a Source

fsnd :: (f :*: g) a -> g a Source

data (f :&: a) e infixr 7 Source

This data type adds a constant product (annotation) to a signature.

Constructors

(f e) :&: a infixr 7 

Instances

DistAnn k f p ((:&:) k f p) Source 
RemA k ((:&:) k f p) f Source 
DistAnn k s p s' => DistAnn k ((:+:) k f s) p ((:+:) k ((:&:) k f p) s') Source 
RemA k s s' => RemA k ((:+:) k ((:&:) k f p) s) ((:+:) k f s') Source 
Functor f => Functor ((:&:) * f a) Source 
Foldable f => Foldable ((:&:) * f a) Source 
Traversable f => Traversable ((:&:) * f a) Source 
HasVars f v => HasVars ((:&:) * f a) v Source 

class DistAnn s p s' | s' -> s, s' -> p where Source

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

Methods

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

Inject an annotation over a signature.

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

Project an annotation from a signature.

Instances

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

class RemA s s' | s -> s' where Source

Methods

remA :: s a -> s' a Source

Remove annotations from a signature.

Instances

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