RepLib-0.5.4.1: 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 # 
Instance details

Defined in Generics.RepLib.R

Methods

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

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

Ord (R a) Source # 
Instance details

Defined in Generics.RepLib.R

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 # 
Instance details

Defined in Generics.RepLib.R

Methods

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

show :: R a -> String #

showList :: [R a] -> ShowS #

TestEquality R # 
Instance details

Defined in Generics.RepLib.RepAux

Methods

testEquality :: R a -> R b -> Maybe (a :~: b) #

Show (MTup R l) Source # 
Instance details

Defined in Generics.RepLib.R

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
Eq DT # 
Instance details

Defined in Generics.RepLib.RepAux

Methods

(==) :: DT -> DT -> Bool #

(/=) :: DT -> DT -> Bool #

Ord DT # 
Instance details

Defined in Generics.RepLib.RepAux

Methods

compare :: DT -> DT -> Ordering #

(<) :: DT -> DT -> Bool #

(<=) :: DT -> DT -> Bool #

(>) :: DT -> DT -> Bool #

(>=) :: DT -> DT -> Bool #

max :: DT -> DT -> DT #

min :: DT -> DT -> DT #

Show DT Source # 
Instance details

Defined in Generics.RepLib.R

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 # 
Instance details

Defined in Generics.RepLib.R

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 Bool Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R Bool Source #

Rep Char Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Char Source #

Rep Double Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Double Source #

Rep Float Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Float Source #

Rep Int Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Int Source #

Rep Integer Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Integer Source #

Rep Ordering Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R Ordering Source #

Rep Rational Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R Rational Source #

Rep () Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R () Source #

Rep IOError Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R IOError Source #

Rep a => Rep [a] Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R [a] Source #

Rep a => Rep (Maybe a) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (Maybe a) Source #

Rep a => Rep (IO a) Source # 
Instance details

Defined in Generics.RepLib.R

Methods

rep :: R (IO a) Source #

Rep a => Rep (Set a) Source # 
Instance details

Defined in Generics.RepLib.AbstractReps

Methods

rep :: R (Set a) Source #

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

Defined in Generics.RepLib.R

Methods

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

(Rep a, Rep b) => Rep (Either a b) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (Either a b) Source #

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

Defined in Generics.RepLib.R

Methods

rep :: R (a, b) Source #

(Rep k, Rep a) => Rep (Map k a) Source # 
Instance details

Defined in Generics.RepLib.AbstractReps

Methods

rep :: R (Map k a) Source #

(Rep a, Rep b, Rep c) => Rep (a, b, c) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (a, b, c) Source #

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

Defined in Generics.RepLib.R

Methods

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

(Rep a, Rep b, Rep c, Rep d) => Rep (a, b, c, d) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (a, b, c, d) Source #

(Rep a, Rep b, Rep c, Rep d, Rep e) => Rep (a, b, c, d, e) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (a, b, c, d, e) Source #

(Rep a, Rep b, Rep c, Rep d, Rep e, Rep f) => Rep (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (a, b, c, d, e, f) Source #

(Rep a, Rep b, Rep c, Rep d, Rep e, Rep f, Rep g) => Rep (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.RepLib.PreludeReps

Methods

rep :: R (a, b, c, d, e, f, g) 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 #