----------------------------------------------------------------------------- -- | -- Module : Generics.EMGM.Common.Representation -- Copyright : (c) 2008 Universiteit Utrecht -- License : BSD3 -- -- Maintainer : generics@haskell.org -- Stability : experimental -- Portability : non-portable -- -- 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. -- ----------------------------------------------------------------------------- module Generics.EMGM.Common.Representation ( -- * Structure representation -- | The generic sum-of-products view of a Haskell datatype. Unit(..), (:+:)(..), (:*:)(..), -- * 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. ConDescr(..), ConType(..), -- * 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. Fixity(..), Prec, prec, minPrec, maxPrec, appPrec, recPrec, -- * Embedding-projection pair EP(..), ) where import Text.ParserCombinators.ReadPrec (minPrec, Prec) infixr 5 :+: infixr 6 :*: -- | 'Unit' encodes a constructor with no arguments. An analogous standard -- Haskell type is @()@. data Unit = Unit -- ^ The only value of type 'Unit' (ignoring @_|_@). deriving (Enum, Eq, Ord) -- | The Read instance for Unit should always return a value and consume nothing -- of the input, because there is no string representation for it. This allows -- us to use 'readPrec' in the 'rconstant' method of the generic 'Read' -- definition. instance Read Unit where readsPrec _ s = [(Unit, s)] -- | The Show instance for Unit should return an empty string, because there is -- no representation for it. This allows us to use 'showsPrec' in the -- 'rconstant' method of the generic 'Show' definition. instance Show Unit where showsPrec _ _ = id -- | The \"sum\" encodes 2 constructor alternatives. An analogous standard -- Haskell type is @'Either' a b@. data a :+: b = L a -- ^ Left alternative | R b -- ^ Right alternative deriving (Eq, Ord, Read, Show) -- | The \"product\" encodes 2 constructor arguments. An analogous standard -- Haskell type is @(a, b)@. data a :*: b = a :*: b -- ^ A pair of arguments deriving (Eq, Ord, Read, Show) -- | 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. data EP d r = EP { from :: (d -> r) -- ^ Embed a @d@atatype into its @r@epresentation. , to :: (r -> d) -- ^ Project @d@atatype from its @r@epresentation. } -- | 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. data ConDescr = ConDescr { conName :: String -- ^ Name of the constructor. If it is infix, -- don't provide parentheses. , conArity :: Int -- ^ Arity 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 :: Fixity -- ^ Infix or not, associativity, precedence. } deriving Show -- | The constructor type used in 'Read' and 'Show' to determine how to parse or -- print the constructor. data ConType = ConStd -- ^ Standard (function-type, nonfix) | ConRec [String] -- ^ Record-style (nonfix or infix) | ConIfx String -- ^ Infix (no record syntax) deriving Show -- TODO: Need smart constructor(s) for ConDescr, so we can verify things. -- | Determine an identifier's status as infix or not. If infix, the -- associativity and precedence are also determined. data Fixity = Nonfix -- ^ Not infix. Precedence is same as function application (see 'appPrec'). | Infix Prec -- ^ Non-associative infix with precedence. | Infixl Prec -- ^ Left-associative infix with precedence. | Infixr Prec -- ^ Right-associative Infix with precedence. deriving (Eq, Show) -- | Get the precedence of a fixity value. prec :: Fixity -> Prec prec Nonfix = appPrec prec (Infix n) = n prec (Infixl n) = n prec (Infixr n) = n -- | Maximum precedence: 11 maxPrec :: Prec maxPrec = 11 -- | Precedence for function application: 10 appPrec :: Prec appPrec = 10 -- | Precedence for record construction: 11 recPrec :: Prec recPrec = appPrec + 1