th-desugar-1.3.0: Functions to desugar Template Haskell

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. Other Decs are not desugared.

data DPat Source

Corresponds to TH's Pat type.

data DType Source

Corresponds to TH's Type 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 

Main desugaring functions

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

Desugar an expression

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

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

Desugar a type

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

Desugar a kind

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

Desugar a TyVarBndr

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

Desugar a Pred, flattening any internal tuples

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.

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

Desugar a pattern.

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

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

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

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

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