RepLib-0.3: Generic programming library with representation types

Portabilitynon-portable
Stabilityexperimental
Maintainersweirich@cis.upenn.edu

Generics.RepLib.R

Description

Basic data structure and class for representation types

Synopsis

Documentation

data R a whereSource

A value of type R a is a representation of a type a.

Constructors

Int :: R Int 
Char :: R Char 
Integer :: R Integer 
Float :: R Float 
Double :: R Double 
Rational :: R Rational 
IOError :: R IOError 
IO :: Rep a => R a -> R (IO a) 
Arrow :: (Rep a, Rep b) => R a -> R b -> R (a -> b) 
Data :: DT -> [Con R a] -> R a 
Abstract :: DT -> R a 

Instances

Rep a[a2Jp] => Rep1 ctx[aqdM] (R a[a2Jp]) 
Rep a[a2Jp] => Rep1 ctx[aKfo] (R a[a2Jp]) 
Rep a => Subst b (R a) 
Rep a => Subst b (R a) 
Eq (R a) 
Ord (R a) 
Show (R a) 
Rep a[a2Jp] => Rep (R a[a2Jp]) 
Rep a[a2Jp] => Rep (R a[a2Jp]) 
Rep a => Alpha (R a) 
Rep a => Alpha (R a) 
Show (MTup R l) 

data Con r a Source

Representation of a data constructor includes an embedding between the datatype and a list of other types as well as the representation of that list of other types.

Constructors

forall l . Con (Emb l a) (MTup r l) 

data Emb l a Source

An embedding between a list of types l and a datatype a, based on a particular data constructor. The to function is a wrapper for the constructor, the from function pattern matches on the constructor.

Constructors

Emb 

Fields

to :: l -> a
 
from :: a -> Maybe l
 
labels :: Maybe [String]
 
name :: String
 
fixity :: Fixity
 

data Fixity Source

Constructors

Nonfix 
Infix 

Fields

prec :: Int
 
Infixl 

Fields

prec :: Int
 
Infixr 

Fields

prec :: Int
 

data DT Source

Information about a datatype, including its fully qualified name and representation of its type arguments.

Constructors

forall l . DT String (MTup R l) 

Instances

data Nil Source

An empty list of types

Constructors

Nil 

data a :*: l Source

Cons for a list of types

Constructors

a :*: l 

data Ex f Source

Constructors

forall a . Rep a => Ex (f a) 

data MTup r l whereSource

A heterogeneous list

Constructors

MNil :: MTup r Nil 
:+: :: Rep a => r a -> MTup r l -> MTup r (a :*: l) 
MEx :: Rep a => MTup r (f a) -> MTup r (Ex f) 

Instances

Show (MTup R l) 

class Rep a whereSource

A Class of representatble types

Methods

rep :: R aSource

Instances

Rep Bool 
Rep Char 
Rep Double 
Rep Float 
Rep Int 
Rep Integer 
Rep Ordering 
Rep Rational 
Rep () 
Rep IOError 
Rep AnyName 
Rep Exp 
Rep AnyName 
Rep Exp 
Rep a => Rep [a] 
Rep a => Rep (IO a) 
Rep a[a1IU] => Rep (Maybe a[a1IU]) 
Rep a[a2Jp] => Rep (R a[a2Jp]) 
Rep a[a2Jp] => Rep (R a[a2Jp]) 
Rep a[aqeX] => Rep (Annot a[aqeX]) 
Rep a[aqf1] => Rep (Name a[aqf1]) 
Rep a[aKgF] => Rep (Annot a[aKgF]) 
Rep a[aKgL] => Rep (Name a[aKgL]) 
(Rep a, Rep b) => Rep (a -> b) 
(Rep a[aaH6], Rep b[aaH5]) => Rep (Either a[aaH6] b[aaH5]) 
(Rep a, Rep b) => Rep (a, b) 
(Rep a[aqeV], Rep b[aqeW]) => Rep (Rebind a[aqeV] b[aqeW]) 
(Rep a[aqeZ], Rep b[aqf0]) => Rep (Bind a[aqeZ] b[aqf0]) 
(Rep a[aKgD], Rep b[aKgE]) => Rep (Rebind a[aKgD] b[aKgE]) 
(Rep a[aKgI], Rep b[aKgJ]) => Rep (Bind a[aKgI] b[aKgJ]) 
(Rep a[12], Rep b[13], Rep c[14]) => Rep (a[12], b[13], c[14]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15]) => Rep (a[12], b[13], c[14], d[15]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16]) => Rep (a[12], b[13], c[14], d[15], e[16]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16], Rep f[17]) => Rep (a[12], b[13], c[14], d[15], e[16], f[17]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16], Rep f[17], Rep g[18]) => Rep (a[12], b[13], c[14], d[15], e[16], f[17], g[18]) 

rTup2 :: forall a b. (Rep a, Rep b) => R (a, b)Source

rPairEmb :: Emb (a :*: (b :*: Nil)) (a, b)Source

rList :: forall a. Rep a => R [a]Source

rConsEmb :: Emb (a :*: ([a] :*: Nil)) [a]Source