th-desugar-1.4.1: Functions to desugar Template Haskell

Portabilitynon-portable
Stabilityexperimental
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Safe HaskellNone

Language.Haskell.TH.Desugar

Contents

Description

Desugars full Template Haskell syntax into a smaller core syntax for further processing. The desugared types and constructors are prefixed with a D.

Synopsis

Desugared data types

data DExp Source

Corresponds to TH's Exp type. Note that DLamE takes names, not patterns.

data DLetDec Source

Declarations as used in a let statement.

data DPat Source

Corresponds to TH's Pat type.

data DKind Source

Corresponds to TH's Kind type, which is a synonym for Type. DKind, though, only contains constructors that make sense for kinds.

type DCxt = [DPred]Source

Corresponds to TH's Cxt

data DPred Source

Corresponds to TH's Pred

data DTyVarBndr Source

Corresponds to TH's TyVarBndr. Note that PlainTV x and KindedTV x StarT are distinct, so we retain that distinction here.

data DMatch Source

Corresponds to TH's Match type.

Constructors

DMatch DPat DExp 

data DClause Source

Corresponds to TH's Clause type.

Constructors

DClause [DPat] DExp 

data NewOrData Source

Is it a newtype or a data type?

Constructors

Newtype 
Data 

data DCon Source

Corresponds to TH's Con type.

data DConFields Source

A list of fields either for a standard data constructor or a record data constructor.

type DStrictType = (Strict, DType)Source

Corresponds to TH's StrictType type.

type DVarStrictType = (Name, Strict, DType)Source

Corresponds to TH's VarStrictType type.

data DRuleBndr Source

Corresponds to TH's RuleBndr type.

data DTySynEqn Source

Corresponds to TH's TySynEqn type (to store type family equations).

Constructors

DTySynEqn [DType] DType 

data DInfo Source

Corresponds to TH's Info type.

Constructors

DTyConI DDec (Maybe [DInstanceDec]) 
DVarI Name DType (Maybe Name) Fixity

The Maybe Name stores the name of the enclosing definition (datatype, for a data constructor; class, for a method), if any

DTyVarI Name DKind 
DPrimTyConI Name Int Bool

The Int is the arity; the Bool is whether this tycon is unlifted.

type DInstanceDecSource

Arguments

 = DDec

Guaranteed to be an instance declaration

data Role Source

Same as Role from TH; defined here for GHC 7.6.3 compatibility.

data AnnTarget Source

Same as AnnTarget from TH; defined here for GHC 7.6.3 compatibility.

The Desugar class

class Desugar th ds | ds -> th whereSource

This class relates a TH type with its th-desugar type and allows conversions back and forth. The functional dependency goes only one way because Type and Kind are type synonyms, but they desugar to different types.

Methods

desugar :: Quasi q => th -> q dsSource

sweeten :: ds -> thSource

Main desugaring functions

dsExp :: Quasi q => Exp -> q DExpSource

Desugar an expression

dsDecs :: Quasi q => [Dec] -> q [DDec]Source

Desugar arbitrary Decs

dsType :: Quasi q => Type -> q DTypeSource

Desugar a type

dsKind :: Quasi q => Kind -> q DKindSource

Desugar a kind

dsInfo :: Quasi q => Info -> q DInfoSource

Desugar Info

dsPatOverExp :: Quasi q => Pat -> DExp -> q (DPat, DExp)Source

Desugar a pattern, along with processing a (desugared) expression that is the entire scope of the variables bound in the pattern.

dsPatsOverExp :: Quasi q => [Pat] -> DExp -> q ([DPat], DExp)Source

Desugar multiple patterns. Like dsPatOverExp.

dsPatX :: Quasi q => Pat -> q (DPat, [(Name, DExp)])Source

Desugar a pattern, returning a list of (Name, DExp) pairs of extra variables that must be bound within the scope of the pattern

dsLetDecs :: Quasi q => [Dec] -> q [DLetDec]Source

Desugar Decs that can appear in a let expression

dsTvb :: Quasi q => TyVarBndr -> q DTyVarBndrSource

Desugar a TyVarBndr

dsCxt :: Quasi q => Cxt -> q DCxtSource

Desugar a Cxt

dsCon :: Quasi q => Con -> q DConSource

Desugar a single Con.

dsForeign :: Quasi q => Foreign -> q DForeignSource

Desugar a Foreign.

dsPragma :: Quasi q => Pragma -> q DPragmaSource

Desugar a Pragma.

dsRuleBndr :: Quasi q => RuleBndr -> q DRuleBndrSource

Desugar a RuleBndr.

Secondary desugaring functions

type PatM q = WriterT [(Name, DExp)] qSource

Desugaring a pattern also returns the list of variables bound in as-patterns and the values they should be bound to. This variables must be brought into scope in the body of the pattern.

dsPred :: Quasi q => Pred -> q DCxtSource

Desugar a Pred, flattening any internal tuples

dsPat :: Quasi q => Pat -> PatM q DPatSource

Desugar a pattern.

dsDec :: Quasi q => Dec -> q [DDec]Source

Desugar a single Dec, perhaps producing multiple DDecs

dsLetDec :: Quasi q => Dec -> q [DLetDec]Source

Desugar a single Dec, perhaps producing multiple DLetDecs

dsMatchesSource

Arguments

:: Quasi q 
=> Name

Name of the scrutinee, which must be a bare var

-> [Match]

Matches of the case statement

-> q [DMatch] 

Desugar a list of matches for a case statement

dsBodySource

Arguments

:: Quasi q 
=> Body

body to desugar

-> [Dec]

where declarations

-> DExp

what to do if the guards don't match

-> q DExp 

Desugar a Body

dsGuardsSource

Arguments

:: Quasi q 
=> [(Guard, Exp)]

Guarded expressions

-> DExp

What to do if none of the guards match

-> q DExp 

Desugar guarded expressions

dsDoStmts :: Quasi q => [Stmt] -> q DExpSource

Desugar the Stmts in a do expression

dsComp :: Quasi q => [Stmt] -> q DExpSource

Desugar the Stmts in a list or monad comprehension

dsClausesSource

Arguments

:: Quasi q 
=> Name

Name of the function

-> [Clause]

Clauses to desugar

-> q [DClause] 

Desugar clauses to a function definition

Utility functions

applyDExp :: DExp -> [DExp] -> DExpSource

Apply one DExp to a list of arguments

applyDType :: DType -> [DType] -> DTypeSource

Apply one DType to a list of arguments

dPatToDExp :: DPat -> DExpSource

Convert a DPat to a DExp. Fails on DWildP.

removeWilds :: Quasi q => DPat -> q DPatSource

Remove all wildcards from a pattern, replacing any wildcard with a fresh variable

reifyWithWarning :: Quasi q => Name -> q InfoSource

Reify a declaration, warning the user about splices if the reify fails. The warning says that reification can fail if you try to reify a type in the same splice as it is declared.

getDataDSource

Arguments

:: Quasi q 
=> String

Print this out on failure

-> Name

Name of the datatype (data or newtype) of interest

-> q ([TyVarBndr], [Con]) 

Extract the TyVarBndrs and constructors given the Name of a type

dataConNameToDataName :: Quasi q => Name -> q NameSource

From the name of a data constructor, retrive the datatype definition it is a part of.

dataConNameToCon :: Quasi q => Name -> q ConSource

From the name of a data constructor, retrieve its definition as a Con

nameOccursIn :: Data a => Name -> a -> BoolSource

Check if a name occurs anywhere within a TH tree.

allNamesIn :: Data a => a -> [Name]Source

Extract all Names mentioned in a TH tree.

flattenDValD :: Quasi q => DLetDec -> q [DLetDec]Source

If the declaration passed in is a DValD, creates new, equivalent declarations such that the DPat in all DValDs is just a plain DVarPa. Other declarations are passed through unchanged. Note that the declarations that come out of this function are rather less efficient than those that come in: they have many more pattern matches.

getRecordSelectorsSource

Arguments

:: Quasi q 
=> DType

the type of the argument

-> DCon 
-> q [DLetDec] 

Produces DLetDecs representing the record selector functions from the provided DCon.

mkTypeName :: Quasi q => String -> q NameSource

Like TH's lookupTypeName, but if this name is not bound, then we assume it is declared in the current module.

mkDataName :: Quasi q => String -> q NameSource

Like TH's lookupDataName, but if this name is not bound, then we assume it is declared in the current module.

newUniqueName :: Quasi q => String -> q NameSource

Like newName, but even more unique (unique across different splices), and with unique nameBases.

mkTupleDExp :: [DExp] -> DExpSource

Make a tuple DExp from a list of DExps. Avoids using a 1-tuple.

mkTupleDPat :: [DPat] -> DPatSource

Make a tuple DPat from a list of DPats. Avoids using a 1-tuple.

maybeDLetE :: [DLetDec] -> DExp -> DExpSource

If decs is non-empty, delcare them in a let:

maybeDCaseE :: String -> DExp -> [DMatch] -> DExpSource

If matches is non-empty, make a case statement; otherwise make an error statement

Extracting bound names

extractBoundNamesStmt :: Stmt -> Set NameSource

Extract the names bound in a Stmt

extractBoundNamesDec :: Dec -> Set NameSource

Extract the names bound in a Dec that could appear in a let expression.

extractBoundNamesPat :: Pat -> Set NameSource

Extract the names bound in a Pat