emgm-0.1: Extensible and Modular Generics for the MassesSource codeContentsIndex
Generics.EMGM.Common.Representation
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Structure representation
Constructor description
Fixity and precedence
Embedding-projection pair
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
data Unit = Unit
data a :+: b
= L a
| R b
data a :*: b = a :*: b
data ConDescr = ConDescr {
conName :: String
conArity :: Int
conLabels :: [String]
conFixity :: Fixity
}
data ConType
= ConStd
| ConRec [String]
| ConIfx String
data Fixity
= Nonfix
| Infix Prec
| Infixl Prec
| Infixr Prec
Prec
prec :: Fixity -> Prec
minPrec
maxPrec :: Prec
appPrec :: Prec
recPrec :: Prec
data EP d r = EP {
from :: d -> r
to :: r -> d
}
Structure representation
The generic sum-of-products view of a Haskell datatype.
data Unit Source
Unit encodes a constructor with no arguments. An analogous standard Haskell type is ().
Constructors
UnitThe only value of type Unit (ignoring _|_).
show/hide Instances
data a :+: b Source
The "sum" encodes 2 constructor alternatives. An analogous standard Haskell type is Either a b.
Constructors
L aLeft alternative
R bRight alternative
show/hide Instances
(Generic g, Rep g a, Rep g b) => Rep g (a :+: b)
(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)
data a :*: b Source
The "product" encodes 2 constructor arguments. An analogous standard Haskell type is (a, b).
Constructors
a :*: bA pair of arguments
show/hide Instances
(Generic g, Rep g a, Rep g b) => Rep g (a :*: b)
(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)
Constructor description
Since this library does not have access to the syntax of a data declaration, it relies on ConDescr for meta-information. It is important that the ConDescr for a constructor accurately describe the actual syntax in the declaration. An incorrect description may lead to bad Read or Show operation.
data ConDescr Source
A constructor description containing useful meta-information about the syntax used in the data declaration. This is particularly useful in Read and Show but may also be helpful in other generic functions.
Constructors
ConDescr
conName :: StringName of the constructor. If it is infix, don't provide parentheses.
conArity :: IntArity or number of arguments.
conLabels :: [String]A list of labels used in record syntax. They must be declared in the same order as the data declaration. The list should be empty if the constructor is not a record.
conFixity :: FixityInfix or not, associativity, precedence.
show/hide Instances
data ConType Source
The constructor type used in Read and Show to determine how to parse or print the constructor.
Constructors
ConStdStandard (function-type, nonfix)
ConRec [String]Record-style (nonfix or infix)
ConIfx StringInfix (no record syntax)
show/hide Instances
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
Determine an identifier's status as infix or not. If infix, the associativity and precedence are also determined.
Constructors
NonfixNot infix. Precedence is same as function application (see appPrec).
Infix PrecNon-associative infix with precedence.
Infixl PrecLeft-associative infix with precedence.
Infixr PrecRight-associative Infix with precedence.
show/hide Instances
Prec
prec :: Fixity -> PrecSource
Get the precedence of a fixity value.
minPrec
maxPrec :: PrecSource
Maximum precedence: 11
appPrec :: PrecSource
Precedence for function application: 10
recPrec :: PrecSource
Precedence for record construction: 11
Embedding-projection pair
data EP d r Source
The Embedding-Projection pair contains two functions for converting between the datatype and its representation. This pair preserves an isomorphism (ignoring _|_s) between a datatype and its structure.
Constructors
EP
from :: d -> rEmbed a datatype into its representation.
to :: r -> dProject datatype from its representation.
Produced by Haddock version 2.4.2