emgm-0.4: Extensible and Modular Generics for the Masses

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.EMGM.Representation

Contents

Description

Summary: Types and related functions for the representation used in EMGM.

EMGM uses a generic sum-of-products view of datatypes encoded into the Unit, :+: (sum), and :*: (product). Many Haskell datatypes can be represented in this way. Right-nested sums replace the |, and right-nested products replace the arguments to a constructor. Units replace constructors with no arguments.

Since constructors encode more than just a list of arguments, this library uses ConDescr to store that information. This includes name, arity, record labels, fixity, and operator precedence. Constructor descriptions are useful for generic operations such as Read and Show and possibly others.

Generic functions need to convert values between the Haskell datatype and its structure representation. This is done using the embedding-projection pair, which is simply a pair a functions for translating between two types.

Synopsis

Structure Representation

The unit, sum, and product types form the sum-of-products view for a Haskell datatype.

data Unit Source

Encodes a constructor with no arguments. An analogous standard Haskell type is ().

Constructors

Unit

The only value of type Unit (ignoring _|_).

Instances

data a :+: b Source

The "sum" encodes 2 constructor alternatives. An analogous standard Haskell type is Either a b.

Constructors

L a

Left alternative

R b

Right alternative

Instances

HasEP Bool BoolS 
(Generic g, Rep g a, Rep g b) => Rep g (:+: a b) 
HasEP [a] (ListS a) 
HasEP (Maybe a) (MaybeS a) 
(Eq a, Eq b) => Eq (:+: a b) 
(Ord a, Ord b) => Ord (:+: a b) 
(Read a, Read b) => Read (:+: a b) 
(Show a, Show b) => Show (:+: a b) 
HasEP (Either a b) (EitherS a b) 

data a :*: b Source

The "product" encodes 2 constructor arguments. An analogous standard Haskell type is (a, b).

Constructors

a :*: b

A pair of arguments

Instances

(Generic g, Rep g a, Rep g b) => Rep g (:*: a b) 
HasEP [a] (ListS a) 
Integral a => HasEP (Ratio a) (RatioS a) 
(Eq a, Eq b) => Eq (:*: a b) 
(Ord a, Ord b) => Ord (:*: a b) 
(Read a, Read b) => Read (:*: a b) 
(Show a, Show b) => Show (:*: a b) 
HasEP (a, b) (Tuple2S a b) 
HasEP (a, b, c) (Tuple3S a b c) 
HasEP (a, b, c, d) (Tuple4S a b c d) 
HasEP (a, b, c, d, e) (Tuple5S a b c d e) 
HasEP (a, b, c, d, e, f) (Tuple6S a b c d e f) 
HasEP (a, b, c, d, e, f, h) (Tuple7S a b c d e f h) 

Constructor Description

A description of the syntax of each constructor provides useful auxiliary information for some generic functions.

data ConDescr Source

Contains useful meta-information about the syntax used in a constructor declaration.

NOTE: It is important that the ConDescr value accurately describe the syntax in a constructor declaration. An incorrect description may lead to faulty Read or Show operation.

Constructors

ConDescr 

Fields

conName :: String

Name of the constructor (without parenthesese if infix).

conArity :: Int

Number of fields.

conRecord :: Bool

Uses labeled fields (a.k.a. record syntax).

conFixity :: Fixity

Fixity, associativity, precedence.

Instances

data ConType Source

Type of constructor syntax. Used in the generic functions Read and Show.

Constructors

UnknownC

Have not seen the rcon yet

NormalC

Normal prefix-style constructor

InfixC String

Infix with symbol (no record syntax)

RecordC

Record-style (any fixity)

Instances

newtype LblDescr Source

Encodes the string label for a field in a constructor defined with labeled fields (a.k.a. record syntax).

Constructors

LblDescr String 

Embedding-Projection Pair

A pair of a function and its inverse form the isomorphism between a datatype and its structure representation.

data EP d r Source

The embedding-projection pair contains two functions for converting between the datatype and its representation. An EP value preserves an isomorphism (ignoring _|_s) between a datatype and its structure representation.

Constructors

EP 

Fields

from :: d -> r

Embed a datatype into its representation.

to :: r -> d

Project datatype from its representation.

Fixity and Precedence

These are used to determine whether a constructor is infix or not and, if it is infix, what its associativity and precedence are.

data Fixity Source

A constructor's fixity, associativity, and precedence.

Constructors

Prefix

Associativity and precedence are the same as function application.

Infix Associativity Prec 

data Associativity Source

A constructor's associativity.

Constructors

LeftAssoc

Declared with infixl

RightAssoc

Declared with infixr

NonAssoc

Declared with infix

type Prec = Int

prec :: Fixity -> PrecSource

Get the precedence of a fixity value.

maxPrec :: PrecSource

Maximum precedence: 11

appPrec :: PrecSource

Precedence for function application: 10

recPrec :: PrecSource

Precedence for record construction: 11