RepLib-0.5.4: Generic programming library with representation types

LicenseBSD
Maintainersweirich@cis.upenn.edu
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Generics.RepLib.R

Description

Basic data structure and class for representation types

Synopsis

Documentation

data R a where Source #

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 
Equal :: (Rep a, Rep b) => R a -> R b -> R (a :~: b) 

Instances

Eq (R a) Source # 

Methods

(==) :: R a -> R a -> Bool #

(/=) :: R a -> R a -> Bool #

Ord (R a) Source # 

Methods

compare :: R a -> R a -> Ordering #

(<) :: R a -> R a -> Bool #

(<=) :: R a -> R a -> Bool #

(>) :: R a -> R a -> Bool #

(>=) :: R a -> R a -> Bool #

max :: R a -> R a -> R a #

min :: R a -> R a -> R a #

Show (R a) Source # 

Methods

showsPrec :: Int -> R a -> ShowS #

show :: R a -> String #

showList :: [R a] -> ShowS #

Show (MTup R l) Source # 

Methods

showsPrec :: Int -> MTup R l -> ShowS #

show :: MTup R l -> String #

showList :: [MTup R l] -> ShowS #

data Con r a where 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

Con :: Emb l a -> MTup r l -> Con r a 

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

data Fixity Source #

Constructors

Nonfix 
Infix 

Fields

Infixl 

Fields

Infixr 

Fields

data DT Source #

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

Constructors

DT String (MTup R l) 

Instances

Show DT Source # 

Methods

showsPrec :: Int -> DT -> ShowS #

show :: DT -> String #

showList :: [DT] -> ShowS #

data Nil Source #

An empty list of types

Constructors

Nil 

data a :*: l infixr 7 Source #

Cons for a list of types

Constructors

a :*: l infixr 7 

data MTup r l where Source #

A heterogeneous list

Constructors

MNil :: MTup r Nil 
(:+:) :: Rep a => r a -> MTup r l -> MTup r (a :*: l) infixr 7 

Instances

Show (MTup R l) Source # 

Methods

showsPrec :: Int -> MTup R l -> ShowS #

show :: MTup R l -> String #

showList :: [MTup R l] -> ShowS #

class Rep a where Source #

A class of representable types

Minimal complete definition

rep

Methods

rep :: R a Source #

Instances

Rep Char Source # 

Methods

rep :: R Char Source #

Rep Double Source # 

Methods

rep :: R Double Source #

Rep Float Source # 

Methods

rep :: R Float Source #

Rep Int Source # 

Methods

rep :: R Int Source #

Rep Integer Source # 

Methods

rep :: R Integer Source #

Rep Rational Source # 

Methods

rep :: R Rational Source #

Rep () Source # 

Methods

rep :: R () Source #

Rep IOError Source # 

Methods

rep :: R IOError Source #

Rep a => Rep [a] Source # 

Methods

rep :: R [a] Source #

Rep a => Rep (IO a) Source # 

Methods

rep :: R (IO a) Source #

(Rep a, Rep b) => Rep (a -> b) Source # 

Methods

rep :: R (a -> b) Source #

(Rep a, Rep b) => Rep (a, b) Source # 

Methods

rep :: R (a, b) Source #

(Rep a, Rep b) => Rep ((:~:) * a b) Source # 

Methods

rep :: R ((* :~: a) b) Source #

withRep :: R a -> (Rep a => r) -> r Source #

Use a concrete R a for a Rep a dictionary

rUnit :: R () Source #

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 #