compdata-0.8: Compositional Data Types

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

GetEmbD (Found p) f g => GetEmbD (Found (GoRight p)) f ((:+:) g' g) 
GetEmbD (Found p) f g => GetEmbD (Found (GoLeft p)) f ((:+:) g g') 
(GetEmbD (Found p1) f1 g, GetEmbD (Found p2) f2 g) => GetEmbD (Found (Sum p1 p2)) ((:+:) f1 f2) g 
(Functor f, Functor g) => Functor ((:+:) f g) 
(Foldable f, Foldable g) => Foldable ((:+:) f g) 
(Traversable f, Traversable g) => Traversable ((:+:) f g) 
(ShowConstr f, ShowConstr g) => ShowConstr ((:+:) f g) 
(ShowF f, ShowF g) => ShowF ((:+:) f g) 
(ArbitraryF f, ArbitraryF g) => ArbitraryF ((:+:) f g)

Instances of ArbitraryF are closed under forming sums.

(NFDataF f, NFDataF g) => NFDataF ((:+:) f g) 
(EqF f, EqF g) => EqF ((:+:) f g)

EqF is propagated through sums.

(OrdF f, OrdF g) => OrdF ((:+:) f g)

OrdF is propagated through sums.

(Render f, Render g) => Render ((:+:) f g) 
(HasVars f v0, HasVars g v0) => HasVars ((:+:) f g) v 
(Desugar f h, Desugar g h) => Desugar ((:+:) f g) h 
DistAnn s p s' => DistAnn ((:+:) f s) p ((:+:) ((:&:) f p) s') 
RemA s s' => RemA ((:+:) ((:&:) f p) s) ((:+:) f s') 
(Eq (f a), Eq (g a)) => Eq ((:+:) f g a) 
(Ord (f a), Ord (g a)) => Ord ((:+:) f g a) 
(Show (f a), Show (g a)) => Show ((:+:) f g a) 

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.

data Pos Source

Constructors

Here 
GoLeft Pos 
GoRight Pos 
Sum Pos Pos 

data Emb Source

Constructors

NotFound 
Ambiguous 
Found Pos 

type family GetEmb f g :: Emb Source

Equations

GetEmb f f = Found Here 
GetEmb f (g1 :+: g2) = Pick f (g1 :+: g2) (GetEmb f g1) (GetEmb f g2) 
GetEmb f g = NotFound 

type family Pick f g e1 r :: Emb Source

Equations

Pick f g (Found x) (Found y) = Ambiguous 
Pick f g Ambiguous y = Ambiguous 
Pick f g x Ambiguous = Ambiguous 
Pick f g (Found x) y = Found (GoLeft x) 
Pick f g x (Found y) = Found (GoRight y) 
Pick f g x y = Split f g 

type family Split f g :: Emb Source

Equations

Split (f1 :+: f2) g = Pick2 (GetEmb f1 g) (GetEmb f2 g) 
Split f g = NotFound 

type family Pick2 e1 r :: Emb Source

data EmbD e f g where Source

Constructors

HereD :: EmbD (Found Here) f f 
GoLeftD :: EmbD (Found p) f g -> EmbD (Found (GoLeft p)) f (g :+: g') 
GoRightD :: EmbD (Found p) f g -> EmbD (Found (GoRight p)) f (g' :+: g) 
SumD :: EmbD (Found p1) f1 g -> EmbD (Found p2) f2 g -> EmbD (Found (Sum p1 p2)) (f1 :+: f2) g 

class GetEmbD e f g where Source

Methods

getEmbD :: EmbD e f g Source

Instances

GetEmbD (Found Here) f f 
GetEmbD (Found p) f g => GetEmbD (Found (GoRight p)) f ((:+:) g' g) 
GetEmbD (Found p) f g => GetEmbD (Found (GoLeft p)) f ((:+:) g g') 
(GetEmbD (Found p1) f1 g, GetEmbD (Found p2) f2 g) => GetEmbD (Found (Sum p1 p2)) ((:+:) f1 f2) g 

type family DestrPos e :: Res Source

type family ResLeft r :: Res Source

Equations

ResLeft (CompPos p e) = CompPos (SimpLeft p) (GoLeft e) 
ResLeft (SingPos p) = SingPos (SimpLeft p) 

type family ResRight r :: Res Source

Equations

ResRight (CompPos p e) = CompPos (SimpRight p) (GoRight e) 
ResRight (SingPos p) = SingPos (SimpRight p) 

type family ResSum r e :: Res Source

Equations

ResSum (CompPos p e1) e2 = CompPos p (Sum e1 e2) 
ResSum (SingPos p) e = CompPos p e 

type family Or x y Source

Equations

Or x False = x 
Or False y = y 
Or x y = True 

type family In p e :: Bool Source

Equations

In SimpHere e = True 
In p Here = True 
In (SimpLeft p) (GoLeft e) = In p e 
In (SimpRight p) (GoRight e) = In p e 
In p (Sum e1 e2) = Or (In p e1) (In p e2) 
In p e = False 

type family Duplicates' r :: Bool Source

Equations

Duplicates' (SingPos p) = False 
Duplicates' (CompPos p e) = Or (In p e) (Duplicates' (DestrPos e)) 

type family Duplicates e Source

Equations

Duplicates (Found p) = Duplicates' (DestrPos p) 

class NoDup b f g Source

Instances

NoDup False f g 

inj_ :: EmbD e f g -> f a -> g a Source

type (:<:) f g = (GetEmbD (GetEmb f g) f g, NoDup (Duplicates (GetEmb f g)) f g) infixl 5 Source

The :<: constraint is a conjunction of two constraints. The first one is used to construct the evidence that is used to implement the injection and projection functions. The first constraint alone would allow instances such as F :+: F :<: F or F :+: (F :+: G) :<: F :+: G which have multiple occurrences of the same sub-signature on the left-hand side. Such instances are usually unintended and yield injection functions that are not injective. The second constraint excludes such instances.

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

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

proj_ :: EmbD e f g -> g a -> Maybe (f a) Source

proj :: forall f g a. f :<: g => g a -> Maybe (f a) 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 

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 f p ((:&:) f p) 
Functor f => Functor ((:&:) f a) 
Foldable f => Foldable ((:&:) f a) 
Traversable f => Traversable ((:&:) f a) 
(ShowConstr f, Show p) => ShowConstr ((:&:) f p) 
(ShowF f, Show p) => ShowF ((:&:) f p) 
(ArbitraryF f, Arbitrary p) => ArbitraryF ((:&:) f p) 
(NFDataF f, NFData a) => NFDataF ((:&:) f a) 
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 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 f p ((:&:) f p) 
DistAnn s p s' => DistAnn ((:+:) f s) p ((:+:) ((:&:) f p) s') 

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

Methods

remA :: s a -> s' a Source

Remove annotations from a signature.

Instances

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