Safe Haskell | None |
---|
Desugars full Template Haskell syntax into a smaller core syntax for further processing. The desugared types and constructors are prefixed with a D.
- data DExp
- data DLetDec
- data DPat
- data DType
- data DKind
- type DCxt = [DPred]
- data DPred
- data DTyVarBndr
- data DMatch = DMatch DPat DExp
- data DClause = DClause [DPat] DExp
- dsExp :: Quasi q => Exp -> q DExp
- dsPatOverExp :: Quasi q => Pat -> DExp -> q (DPat, DExp)
- dsPatsOverExp :: Quasi q => [Pat] -> DExp -> q ([DPat], DExp)
- dsPatX :: Quasi q => Pat -> q (DPat, [(Name, DExp)])
- dsLetDecs :: Quasi q => [Dec] -> q [DLetDec]
- dsType :: Quasi q => Type -> q DType
- dsKind :: Quasi q => Kind -> q DKind
- dsTvb :: Quasi q => TyVarBndr -> q DTyVarBndr
- dsPred :: Quasi q => Pred -> q DCxt
- type PatM q = WriterT [(Name, DExp)] q
- dsPat :: Quasi q => Pat -> PatM q DPat
- dsLetDec :: Quasi q => Dec -> q [DLetDec]
- dsMatches :: Quasi q => Name -> [Match] -> q [DMatch]
- dsBody :: Quasi q => Body -> [Dec] -> DExp -> q DExp
- dsGuards :: Quasi q => [(Guard, Exp)] -> DExp -> q DExp
- dsDoStmts :: Quasi q => [Stmt] -> q DExp
- dsComp :: Quasi q => [Stmt] -> q DExp
- dsClauses :: Quasi q => Name -> [Clause] -> q [DClause]
- dPatToDExp :: DPat -> DExp
- removeWilds :: Quasi q => DPat -> q DPat
- reifyWithWarning :: Quasi q => Name -> q Info
- getDataD :: Quasi q => String -> Name -> q ([TyVarBndr], [Con])
- dataConNameToCon :: Quasi q => Name -> q Con
- mkTupleDExp :: [DExp] -> DExp
- mkTupleDPat :: [DPat] -> DPat
- maybeDLetE :: [DLetDec] -> DExp -> DExp
- maybeDCaseE :: String -> DExp -> [DMatch] -> DExp
- extractBoundNamesStmt :: Stmt -> Set Name
- extractBoundNamesDec :: Dec -> Set Name
- extractBoundNamesPat :: Pat -> Set Name
Desugared data types
Corresponds to TH's Exp
type. Note that DLamE
takes names, not patterns.
Declarations as used in a let
statement. Other Dec
s are not desugared.
Corresponds to TH's Pat
type.
Corresponds to TH's Type
type.
Corresponds to TH's Kind
type, which is a synonym for Type
. DKind
, though,
only contains constructors that make sense for kinds.
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.
Corresponds to TH's Match
type.
Corresponds to TH's Clause
type.
Main desugaring functions
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
dsTvb :: Quasi q => TyVarBndr -> q DTyVarBndrSource
Desugar a TyVarBndr
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.
dsLetDec :: Quasi q => Dec -> q [DLetDec]Source
Desugar a single Dec
, perhaps producing multiple DLetDec
s
:: Quasi q | |
=> Name | Name of the scrutinee, which must be a bare var |
-> [Match] | Matches of the |
-> q [DMatch] |
Desugar a list of matches for a case
statement
:: Quasi q | |
=> Body | body to desugar |
-> [Dec] | where declarations |
-> DExp | what to do if the guards don't match |
-> q DExp |
Desugar a Body
:: Quasi q | |
=> [(Guard, Exp)] | Guarded expressions |
-> DExp | What to do if none of the guards match |
-> q DExp |
Desugar guarded expressions
Desugar clauses to a function definition
Utility functions
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.
:: Quasi q | |
=> String | Print this out on failure |
-> Name | Name of the datatype ( |
-> q ([TyVarBndr], [Con]) |
Extract the TyVarBndr
s and constructors given the Name
of a type
dataConNameToCon :: Quasi q => Name -> q ConSource
From the name of a data constructor, retrieve its definition as a Con
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