pads-haskell-0.1.0.0: PADS data description language for Haskell.

Copyright(c) 2011
Kathleen Fisher <kathleen.fisher@gmail.com>
John Launchbury <john.launchbury@gmail.com>
LicenseMIT
MaintainerKarl Cronburg <karl@cs.tufts.edu>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.Pads.CodeGen

Contents

Description

To the best of my knowledge, all functions defined herein are only ever run at compile time. These compile time functions are intended to be used in a quasiquoted context where the runtime system support modules have been properly imported. See Examples.First for the necessary imports.

The crucial piece of the code generator is genParseTy, which translates Pads syntactic forms into Haskell code for parsing them.

Synopsis

Documentation

type Derivation = Dec -> Q [Dec] Source #

A function passed into the code generator which gets called on data type declarations and returns a list of standalone-deriving declarations. Presently this is unused by Pads.

make_pads_declarations :: [PadsDecl] -> Q [Dec] Source #

Top level code gen function from Pads decls to Haskell decls

make_pads_asts :: [PadsDecl] -> Q Exp Source #

Top level code gen function from Pads decls to Haskell expression with just the PADS AST (no parser codegen)

make_pads_declarations' :: Derivation -> [PadsDecl] -> Q [Dec] Source #

Top level code gen function from Pads decls to Haskell decls with the specified list of type classes for all of the generated Pads types to derive.

Generating Declarations and Code from Individual Pads Declarations

genPadsDecl :: Derivation -> PadsDecl -> Q [Dec] Source #

Generate all the top level Haskell declarations associated with a single Pads declaration.

astDecl :: Lift t => [Char] -> t -> DecQ Source #

A Haskell declaration containing the literal Pads AST representation of a Pads description (the syntax of Pads encoded as Haskell data constructors)

patType :: Pat -> Type Source #

The Haskell Type of a Haskell pattern Pat.

Generating Rep/MD Type Declarations

mkTyRepMDDecl :: UString -> [UString] -> PadsTy -> [Dec] Source #

Make the type declarations for the representation and the metadata of a Pads-defined type, PadsTy.

Generating Rep/MD Data Declarations

mkDataRepMDDecl :: Derivation -> UString -> [LString] -> PadsData -> [QString] -> Q [Dec] Source #

Make the data type declarations for the representation and the metadata of a Pads-defined data type, PadsData.

mkStrict :: PadsStrict -> Q Strict Source #

Convert a Pads strictness annotation into the appropriate Haskell strictness annotation in the template haskell Q monad for splicing.

mkRepUnion :: BranchInfo -> ConQ Source #

Make the Haskell data type *constructor* (normalC and recC) for the given fragment of a Pads type (BranchInfo).

mkMDUnion :: BranchInfo -> Q Con Source #

Make the Con metadata constructor definition for an individual branch of a Pads type, which gets used to create the Haskell data type declaration for the metadata of a Pads type.

derive :: [QString] -> DerivClauseQ Source #

Make the type context of a data declaration, consisting of the typeclasses instanced by Pads data types. derive :: [QString] -> CxtQ

Generating Rep/MD Newtype Declarations

mkNewRepMDDecl :: Derivation -> UString -> [LString] -> BranchInfo -> [QString] -> Q [Dec] Source #

Construct the newtype Haskell data declaration from a Pads type defined using the "newtype" keyword.

Generating MD Type from Obtain Declarations

mkObtainMDDecl :: UString -> [UString] -> PadsTy -> [Dec] Source #

Construct the Haskell type synonym declaration for a Pads type declared using the "obtain" keyword.

Generating Representation Type of a Type Expression

mkRepTy :: PadsTy -> Type Source #

Make the template haskell Type for the given PadsTy pads type, to be used anywhere in generated Haskell code where the representation type is expected.

mkRepTuple :: [PadsTy] -> Type Source #

Make the template haskell Type corresponding to a tuple consisting of the given pads types given in list form at compile time '[PadsTy]'.

Generating Meta-Data Representation of Type Expression

mkMDTy :: Bool -> PadsTy -> Type Source #

Make the template haskell Type corresponding to the externally visible metadata of a given PadsTy. The boolean indicates whether or not Pads type variables PTyvars should be put in a Meta constructor or merely stuffed into a VarT and appended with "_md" postfix. Currently we always do the latter (all calls to mkMDTy give False as the boolean).

mkMDTuple :: Bool -> [PadsTy] -> Type Source #

Make the template haskell Type corresponding to a Haskell tuple type consisting of the metadata types for the given Pads types '[PadsTy]'.

Generating Instance Declarations from Data / New Declarations

mkPadsInstance :: UString -> [LString] -> Maybe Type -> [Dec] Source #

Make the following instance and type instance declarations for a Pads data type and new type declaration:

[pads| data Foo (Bar1, Bar2, Bar3) = Foo
   { i1 :: Bar1
   , i2 :: Bar2 i1
   , i3 :: Bar3 i2
   } |]
instance Pads1 (Bar1, Bar2, Bar3) Foo Foo_md where
  parsePP1 = foo_parseM
  printFL1 = foo_printFL
  def1     = foo_def
type instance Meta Foo = Foo_md
type instance PadsArg Foo = (Bar1, Bar2, Bar3)

buildInst :: Maybe Type -> [Char] -> [String] -> Type -> [Dec] Source #

See mkPadsInstance above.

mkPadsSignature :: UString -> [LString] -> Maybe Type -> [Dec] Source #

Make the following type signatures, applicable for all the forms of a Pads declaration:

foo_printFL :: (Bar1, Bar2, Bar3) -> PadsPrinter (Foo, Foo_md)
foo_def     :: (Bar1, Bar2, Bar3) -> Foo

See mkPadsInstance above for the definition of the Pads type Foo.

buildSignature :: Maybe Type -> [Char] -> [[Char]] -> Type -> [Dec] Source #

See mkPadsSignature above.

Generating Parser Declaration from Type Data New Declarations

genPadsParseM :: UString -> [LString] -> Maybe Pat -> PadsTy -> Q [Dec] Source #

Construct the function body and resulting declaration of the "_parseM" function for a given PadsTy type declaration.

genPadsDataParseM :: UString -> [LString] -> Maybe Pat -> PadsData -> Q [Dec] Source #

PadsData data declaration flavour of the "_parseM" function.

genPadsNewParseM :: UString -> [LString] -> Maybe Pat -> BranchInfo -> Q [Dec] Source #

BranchInfo new type declaration flavour of the "_parseM" function.

genPadsObtainParseM :: UString -> [LString] -> PadsTy -> Exp -> Q [Dec] Source #

Pads Obtain declaration flavour of the "_parseM" function.

mkParserFunction :: UString -> [LString] -> Maybe Pat -> Q Exp -> Q [Dec] Source #

Construct the declaration for a function which monadically parses a Pads type given the body of the function as input.

Generating String-Parser Declaration

genPadsParseS :: UString -> [LString] -> Maybe Pat -> Q [Dec] Source #

Construct the "_parseS" function at compile time such that it makes a call to parseStringInput at runtime.

Generating Parser from Type Expression

genParseTy :: PadsTy -> Q Exp Source #

This function only ever gets called at compile time in order to construct a template haskell expression to be used somewhere in the body of a "_parseM" function. This expression is the meat of the pads-haskell parsing algorithm and semantics - we use metaprogramming to map the Pads syntax onto expressions which return a tuple consisting of the parsed representation followed by the metadata (with parse errors).

genParseConstrain :: Q Pat -> PadsTy -> Q Exp -> Q Exp Source #

Simply generate a call to the runtime system function parseConstraint where the first argument is a Haskell expression spliced directly into the call to parseConstraint which parses the thing being constrained and the second argument is the (Haskell) predicate function used to constrain the Pads type.

genParseTyTrans :: PadsTy -> PadsTy -> Q Exp -> Q Exp Source #

Simply generate a call to the runtime system function parseTransform where the first argument is the spliced-in-place parser for the "source" Pads type being transformed and the second argument is the (Haskell) transformation function for producing something of the desired destination type. Note that we can ignore the destination PadsTy at compile time in *this* function because the Haskell type checker will type check the result of parseTransform for us.

genParseList :: PadsTy -> Maybe PadsTy -> Maybe TermCond -> Q Exp Source #

This compile time function figures out which runtime system support function to generate a call to for parsing a Pads list type based on the given separator Pads type and the desired termination condition TermCond.

genParsePartition :: PadsTy -> Exp -> Q Exp Source #

Simply generate a call to the runtime system function parsePartition where the first argument is an expression for parsing the PadsTy pads type we're partitioning on and the second argument is the Haskell expression given in the Pads syntactic form specifying the record discipline with which to partition things. For example the following code:

type Foo = (partition [Bar] using none)

declares a type Foo which is a list of Bars where Bars are separated by nothing.

genParseValue :: Exp -> Q Exp Source #

This compile time function generates code which wraps a Pads Value type's Haskell expression in the appropriate type to be returned for use in the pads parsing monad, namely of type 'PadsParser (rep, md)' where rep and md are the representation and metadata type variables.

genParseTuple :: [PadsTy] -> Q Exp Source #

Construct the sequentially-defined parser for a Pads tuple type.

parseNext :: Q Exp -> PadsTy -> Q Exp Source #

Glom the generated parser for the given PadsTy onto the given parser using the =@= and =@ runtime system operators.

buildF_rep :: Name -> [Name] -> Dec Source #

Construct the "f_rep" let-bound function inside of a Pads tuple type for uncurrying the result of parsing the tuple sequentially at runtime. The "f_rep" function generated by *this* function gets passed into the =@= and =@ runtime system operators which call f_rep on the result of parsing each of the members of the tuple.

buildF_md :: Name -> [Name] -> Dec Source #

Same as buildF_rep above but for the metadata instead of the parse representation. In this case we need to pull off just the Base_md from the metadata resulting from whatever the parser returned to us for each of the tuple results using the get_md_header type class function provided by the runtime system.

mkMergeBaseMDs :: [Exp] -> Exp Source #

Generate a call to mergeBaseMDs

genParseExp :: Exp -> Q Exp Source #

Construct a call to the litParse runtime system type class function so that we can parse a literal (Haskell) expression. The type of the expression provided as a Haskell expression must be Literally Parseable (LitParse type class), otherwise the code generated by *this* compile time function produces a type error.

genParseTyApp :: [PadsTy] -> Maybe Exp -> Q Exp Source #

Generate the parser for a Pads type application.

mkParseTycon :: QString -> Exp Source #

Make the parser for a Pads type constructor - just return it as a Haskell variable expression.

mkParseTyvar :: String -> Exp Source #

Make the parser for a Pads type variable - just return it as a Haskell variable expression.

Generating Parsers from Union/Switch Expressions

genParseData :: PadsData -> Q Exp Source #

A data declaration in pads is either a union or a switch expression - generate the template haskell for parsing them.

genParseUnion :: [BranchInfo] -> Q Exp Source #

Generate the template haskell for parsing a Pads union expression. Namely generate the metadata constructors for each of the branches of the union and stuff them into let-bound functions so that nested parsers have them in scope. Then generate a call to the runtime system function choiceP for choosing among the different parsers.

genParseSwitch :: Exp -> [(Pat, BranchInfo)] -> Q Exp Source #

Generate the template haskell case expression from a Pads switch type. This is almost entirely just matching the syntax of a Pads case onto the syntax of a Haskell case expression. Semantically the case just figures out which parser needs to be run by pattern matching on something already parsed from the input.

genParseBranchInfo :: BranchInfo -> Q (Dec, Exp) Source #

Generate the parser for an individual branch of a Pads new type, Pads union, or Pads switch.

buildConstr_md :: Name -> Exp -> [PadsTy] -> Dec Source #

Build the constructor function for tupling together the metadata results of parsing a bunch of Pads types.

Generating Parsers from Record Expressions

genParseRecord :: UString -> [FieldInfo] -> Maybe Exp -> Q (Dec, Exp) Source #

Generate the template haskell code for parsing a Pads record.

genLabMDName :: String -> Maybe String -> Q Name Source #

Generate the name (label?) for the metadata of a field in a record.

genParseField :: FieldInfo -> Name -> Q [Stmt] Source #

Generate the parser for a field of a Pads record.

genParseRecConstrain :: Q Pat -> Q Pat -> PadsTy -> Q Exp -> Q Exp Source #

Generate the parser for a constrained field on a record.

Generating generation functions

Generating Generator Declaration from Type Data New declarations

genPadsGenM :: UString -> [LString] -> Maybe Pat -> PadsTy -> Maybe Exp -> Q [Dec] Source #

PadsDeclType generator declaration

genPadsDataGenM :: UString -> [LString] -> Maybe Pat -> PadsData -> Q [Dec] Source #

PadsDeclData generator declaration

genPadsNewGenM :: UString -> [LString] -> Maybe Pat -> BranchInfo -> Q [Dec] Source #

PadsDeclNew generator declaration

genPadsObtainGenM :: UString -> [LString] -> PadsTy -> Exp -> Maybe Exp -> Q [Dec] Source #

PadsDeclObtain generator declaration - if the user provided a generator, it will be included. If not, the type will lack a generator. If the user includes a function conforming to the naming convention of a generator, i.e. "name_genM" for a PadsTy called "Name," it is redundant (and in fact erroneous) to include "generator name_genM," as this will result in an attempted redefinition of name_genM as itself.

mkGeneratorFunction :: UString -> [LString] -> Maybe Pat -> Q Exp -> Q [Dec] Source #

Create the actual generator function declaration for any PadsDecl flavor

Generating Generators from Union/Switch Expressions

genGenData :: PadsData -> Q Exp Source #

Generate the generators for Pads data declarations.

genGenUnion :: [BranchInfo] -> Q Exp Source #

Creates a runtime function which picks at random from the generators for each branch of the union, all of which are created here.

genGenBranchInfo :: BranchInfo -> Q Exp Source #

Dispatch to genGenRecord or genGenConstr

genGenRecord :: UString -> [FieldInfo] -> Maybe Exp -> Q Exp Source #

Generate the template Haskell code for generating a Pads record.

genGenField :: FieldInfo -> Q [Stmt] Source #

Generate the generator for a field of a Pads record; each one becomes a binding statement in a haskell do-expression.

genGenConstr :: String -> [ConstrArg] -> Maybe Exp -> Q Exp Source #

Generate the generator for a PADS data constructor (BConstr format of BranchInfo).

Generating Generator from Type Expression

genGenTy :: PadsTy -> Q Exp Source #

Driver function for creating generators. Provided a PadsTy, it will return a generator customized to work with that particular type.

genGenConstrain :: Pat -> PadsTy -> Exp -> Q Exp Source #

Generate code that uses the runtime function randWithConstraint to generate random data until one satisfies the constraint. If a predicate requires that the variable in question be exactly equal to a value, randWithConstraint is bypassed and that value is assigned directly.

e.g. constrain tcpDstPort :: Bits16 16 tcpDstPort == 22 | will avoid creating new 16-bit values until one happens to be equal to 22, and will instead assign the literal 22 to tcpDstPort.

genGenTransform :: PadsTy -> PadsTy -> Exp -> Maybe Exp -> Q Exp Source #

If an optional generator is included in the quasiquoted PADS description, simply provide it. If not, fail with a (hopefully) helpful error message.

genGenList :: PadsTy -> Maybe PadsTy -> Maybe TermCond -> Q Exp Source #

Generate a list representing a Pads list type by generating a call to the runtime function randList. We ignore the separator and LTerm termination condition here and incorporate them during serialization, but the LLen termination condition is respected at this stage.

genGenValue :: Exp -> Q Exp Source #

All variables on which a PValue statement depends will be in scope at this point, so the expression can be returned and evaluated at runtime.

genGenTuple :: [PadsTy] -> Q Exp Source #

Generate the generator for a Pads tuple

genGenTyApp :: [PadsTy] -> Maybe Exp -> Q Exp Source #

Generate the generator for a Pads type application.

mkGenTycon :: QString -> Q Exp Source #

Basically same as mkParseTycon, but the name that results is different.

mkGenTyvar :: String -> Q Exp Source #

Basically same as mkParseTyvar, but the name that results is different.

Generating Serialization Functions

genPadsSerialize :: UString -> [LString] -> Maybe Pat -> PadsTy -> Q [Dec] Source #

Create the serializer for a PadsDeclType declaration

genPadsDataSerialize :: UString -> [LString] -> Maybe Pat -> PadsData -> Q [Dec] Source #

Create the serializer for a PadsDeclData declaration

genPadsNewSerialize :: UString -> [LString] -> Maybe Pat -> BranchInfo -> Q [Dec] Source #

Create the serializer for a PadsDeclNew declaration

genPadsObtainSerialize :: UString -> [LString] -> PadsTy -> Exp -> Q [Dec] Source #

Create the serializer for a PadsDeclObtain declaration

mkSerializerFunction :: UString -> [LString] -> Maybe Pat -> Exp -> Dec Source #

Create the function declaration for a serialization function

genSerializeData :: PadsData -> Maybe Exp -> Q Exp Source #

Create the serializer for a given form of PadsData

genSerializeUnion :: [BranchInfo] -> Maybe Exp -> Q Exp Source #

Create the serializer for a PUnion type of data constructor

genSerializeSwitch :: Exp -> [(Pat, BranchInfo)] -> Maybe Exp -> Q Exp Source #

At the serialization stage, a PSwitch is simply a sugared PUnion; treat it accordingly here.

genSerializeBranchInfo :: BranchInfo -> Q [Match] Source #

Dispatch to the appropriate function based on the type of BranchInfo.

genSerializeRecord :: UString -> [FieldInfo] -> Maybe Exp -> Q [Match] Source #

Serialization of records is accomplished with a case statement at runtime to bring all names of variables into scope

genSerializeConstr :: String -> [ConstrArg] -> Maybe Exp -> Q [Match] Source #

Serialization of branch constructors is somewhat similar to that of records, but differs in the lack of named variables. Simply create TH newNames for each relevant variable or constant.

genSerializeTy :: PadsTy -> Maybe Exp -> Q Exp Source #

Driver function to serialize PadsTys, dispatches to the appropriate helper. The "Maybe Exp" parameter informs a function whether or not it needs to apply the serializer it creates to the variable standing for the Haskell data representation - usually "rep" in generated code.

genSerializeConstrain :: Pat -> PadsTy -> Exp -> Maybe Exp -> Q Exp Source #

At the serialization stage, already existing data cannot be constrained, unlike in the generation stage. Here we merely pass the type back into genSerializeTy to obtain its serializer.

genSerializeTransform :: PadsTy -> PadsTy -> Exp -> Maybe Exp -> Q Exp Source #

Serialization of a PTransform PadsTy requires only a thin skin atop the functions provided for converting between types.

genSerializeList :: PadsTy -> Maybe PadsTy -> Maybe TermCond -> Maybe Exp -> Q Exp Source #

Create a serializer for a PList, which will intersperse separators and incorporate terminating conditions as necessary.

genSerializePartition :: PadsTy -> Exp -> Maybe Exp -> Q Exp Source #

Create a serializer for a PPartition type. We can ignore "bytes X" and "none" disciplines, as such disciplines are only relevant to parsing, and simply serialize the underlying type. As for "newline" and "windows" disciplines, instead of figure out where to place the relevant characters, provide a helpful error.

genSerializeValue :: Exp -> PadsTy -> Maybe Exp -> Q Exp Source #

PValues are stored in a parse result but do not appear in the original data. Relying on all serializations being concatenated, where each serialization is a CList, we can provide an "empty" serialization for a PValue with (const) id.

genSerializeApp :: [PadsTy] -> Maybe Exp -> Maybe Exp -> Q Exp Source #

A PADS application of types is translated directly to a Template Haskell application (AppE).

genSerializeTuple :: [PadsTy] -> Maybe Exp -> Q Exp Source #

In the runtime function, a case statement is deployed to ensure the input has the correct tuple format, then a serializer for each element of the tuple is bound in a let statement, with their results concatenated to create the function's overall result.

genSerializeExp :: Exp -> Maybe Exp -> Q Exp Source #

The runtime function exp_serialize can be called on literal numbers, characters, and strings, and will serialize them appropriately.

genSerializeTycon :: QString -> Maybe Exp -> Q Exp Source #

A PTycon is represented according to mkTySerializerName, where the resultant name will be an in-scope runtime serializer.

genSerializeTyvar :: String -> Maybe Exp -> Q Exp Source #

A PTyvar is represented according to mkTySerializerVarName, where the resultant name will stand for a serializer the user must provide.

genPadsPrintFL :: UString -> [LString] -> Maybe Pat -> PadsTy -> Q [Dec] Source #

Generate the lazy "function list" printer for a given PadsTy Pads type as parsed using Pads' plain-type syntactic form..

genPadsDataPrintFL :: UString -> [LString] -> Maybe Pat -> PadsData -> Q [Dec] Source #

Generate the lazy function list printer for the Pads data-type syntactic form.

genPadsNewPrintFL :: UString -> [LString] -> Maybe Pat -> BranchInfo -> Q [Dec] Source #

Generate the lazy function list printer for the Pads newtype syntactic form.

genPadsObtainPrintFL :: UString -> [LString] -> PadsTy -> Exp -> Q [Dec] Source #

Generate the lazy function list printer for the Pads obtain syntactic form.

mkPrinterFunction :: UString -> [LString] -> [Name] -> Maybe Pat -> Exp -> Dec Source #

Make the function declaration for the "lazy function list" printer with the body as generated by genPrintTy, genPrintData, or genPrintBranchInfo as passed into this function as the last Exp parameter.

Generate Printing Function from a Type

genPrintTy :: PadsTy -> Maybe Exp -> Q Exp Source #

Generate the body of the printing function for a Pads type - this function dispatches to the ones below according to the syntactic form being translated.

genPrintValue :: Exp -> Maybe Exp -> Q Exp Source #

Generate the printer for the Pads Value syntactic form PValue. Because a pads value is something that wasn't parsed (it's a way to compute / add an extra field to a parsed Haskell record), we just return the nil printer (prints nothing).

genPrintTrans :: PadsTy -> Exp -> Maybe Exp -> Q Exp Source #

Generate the printer for the Pads Transform syntactic form PTransform. This means we need to grab the second function from the tuple provided by the Pads programmer which corresponds to the inverse of the transform function, and print the format of the resulting (source) type. Source here means what's read from a file and destination type means the type for which we have a value that we want to print out. In order for round-trip parsing to work, we need to reverse the transformation because the on-disk format of the source type is usually different from the on-disk format of the destination type.

applyPrintTy :: Maybe Exp -> Exp -> Q Exp Source #

Some of the printing utilities provided by the runtime system need to know about the representation and the metadata. If the first argument to this function is Nothing, then we don't need to pass the representation and metadata to the expression / utility (e.g. ca case expression printing a union type). Otherwise the first argument contains Just the '(rep, md)' tuple brought into scope as the first parameter to the "*_printFL" functions (e.g. the printList runtime system function needs to know about the rep and md).

genPrintList :: PadsTy -> Maybe PadsTy -> Maybe TermCond -> Q Exp Source #

Generate the template haskell code for printing a PList Pads type.

genPrintTyApp :: [PadsTy] -> Maybe Exp -> Q Exp Source #

Generate the template haskell code for printing a Pads type application by recursively calling genPrintTy on the Pads types of each of the arguments to the Pads type constructor.

genPrintTuple :: [PadsTy] -> Maybe Exp -> Q Exp Source #

Generate the template haskell code for printing a Pads tuple type.

filterByHasRep :: [PadsTy] -> [a] -> [a] Source #

Filters a second list based on which corresponding Pads types from the first list have an underlying representation in memory (removing the ones that don't have an underlying representation).

genNamesforTuple :: Bool -> String -> [PadsTy] -> Q [Maybe Name] Source #

Generate a list of names to be used as Haskell pattern variables and expression variables for a Pads tuple type. If the tuple is for the representation then the given Bool is True and we want to ignore data that doesn't have a representation in memory. Otherwise the tuple is for the metadata meaning the given Bool is False and we want to print *everything*.

genPrintTupleInner :: PadsTy -> Maybe Name -> Maybe Name -> Q Exp Source #

Generate the template haskell print function for some type inside of a tuple based on whether or not that type has an in-memory representation '(Just r)' and a metadata representation '(Just m)'.

genPrintExp :: Exp -> Maybe Exp -> Q Exp Source #

Generate the template haskell code for printing the value of a Pads literal (string, character, regex) by simply constructing a runtime system call to litPrint with the code for computing the Haskell value of the literal spliced into the first argument position.

genPrintTycon :: QString -> Q Exp Source #

Generate the printer for a Pads type constructor (hint: it's just the variable name according to mkTyPrinterQName.

genPrintTyVar :: LString -> Q Exp Source #

Generate the printing expression for a Pads type variable according to mkTyPrinterVarName.

genPrintData :: PadsData -> Maybe Exp -> Q Exp Source #

Generate the template haskell expression for printing a Haskell value given the Pads data type declaration defining the type of the Haskell value.

genPrintUnion :: [BranchInfo] -> Maybe Exp -> Q Exp Source #

Generate a Haskell case expression for printing a Pads union type.

genPrintBranchInfo :: Bool -> BranchInfo -> Q [Match] Source #

Generate the printing function body of an individual branch of a Pads data type.

genPrintRecord :: UString -> [FieldInfo] -> Maybe Exp -> Q [Match] Source #

Generate the individual Match of the Haskell case expression for matching on a record being printed.

getPEforField :: (PadsTy -> Q Exp) -> (String -> Q Name) -> FieldInfo -> Q (Exp, Maybe FieldPat) Source #

Get the printer expression for an individual field of a record.

getPEforFields :: (PadsTy -> Q Exp) -> (String -> Q Name) -> [FieldInfo] -> Q ([Exp], [FieldPat]) Source #

Get the printer expressions and corresponding record field pattern matches for each of the given FieldInfos.

genPrintConstr :: Bool -> String -> [ConstrArg] -> Maybe Exp -> Q [Match] Source #

Generate the template haskell code for matching on and printing the value for a Pads value constructor.

genPrintSwitch :: Exp -> [(Pat, BranchInfo)] -> Maybe Exp -> Q Exp Source #

Generate the template haskell code for printing a Pads switch type by ignoring the value we're switching on and simply generating the same case expression that genPrintUnion does for a Pads union type.

Generating Default Function from a Declaration

genPadsDef :: UString -> [LString] -> Maybe Pat -> PadsTy -> Q [Dec] Source #

Generate the Pads default value for a PadsDeclType

genPadsDataDef :: UString -> [LString] -> Maybe Pat -> PadsData -> Q [Dec] Source #

Generate the Pads default value for a Pads data declaration.

genPadsNewDef :: UString -> [LString] -> Maybe Pat -> BranchInfo -> Q [Dec] Source #

Generate the Pads default value for a Pads newtype declaration.

genPadsObtainDef :: UString -> [LString] -> PadsTy -> Exp -> Q [Dec] Source #

Generate the Pads default value for a Pads obtain declaration.

mkDefFunction :: UString -> [LString] -> Maybe Pat -> Exp -> Dec Source #

Generate the Pads default value as a function declaration of the form "foo_def" for a Pads parser named Foo.

Generate Default Function from a Type

genDefTy :: PadsTy -> Q Exp Source #

Generate the default Haskell value for some Pads type.

genDefTuple :: [PadsTy] -> Q Exp Source #

Generate the default Haskell value for a Pads tuple type.

genDefData :: PadsData -> Q Exp Source #

Generate the default Haskell value for a Pads data type PadsData.

genDefBranchInfo :: BranchInfo -> Q Exp Source #

Generate the default Haskell value for a single branch of a Pads type, namely either a Pads constructor or record.

Name Manipulation Functions

Naming types, and accessing the names of types

mkRepName :: String -> Name Source #

Get the template haskell Name for a given Pads type.

mkRepQName :: QString -> Name Source #

Make the template haskell Name of a given PTycon with a qualified name.

mkMDName :: String -> Name Source #

Make externally visible metadata name for a Pads type

mkMDQName :: QString -> Name Source #

Given a Pads type name in the template haskell Q monad, get the metadata type name.

mkIMDName :: [Char] -> Name Source #

Make the internal metadata type name for a given Pads type

mkMDVarName :: [Char] -> Name Source #

Make externally visible metadata name for a Pads variable

Naming fields and constructors

mkFieldName :: String -> Name Source #

Convert Pads source (record) field name into a Q monad name

mkFieldMDName :: [Char] -> Name Source #

Convert Pads source (record) field name into its metadata name in the Q monad.

mkConstrName :: String -> Name Source #

Pads constructor

Naming Parsers

Naming Printers

Naming Generators

Naming Serializers