| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Haskell.TH.Lib
Contents
Description
TH.Lib contains lots of useful helper functions for generating and manipulating Template Haskell terms
- type InfoQ = Q Info
 - type PatQ = Q Pat
 - type FieldPatQ = Q FieldPat
 - type ExpQ = Q Exp
 - type TExpQ a = Q (TExp a)
 - type DecQ = Q Dec
 - type DecsQ = Q [Dec]
 - type ConQ = Q Con
 - type TypeQ = Q Type
 - type TyLitQ = Q TyLit
 - type CxtQ = Q Cxt
 - type PredQ = Q Pred
 - type MatchQ = Q Match
 - type ClauseQ = Q Clause
 - type BodyQ = Q Body
 - type GuardQ = Q Guard
 - type StmtQ = Q Stmt
 - type RangeQ = Q Range
 - type StrictTypeQ = Q StrictType
 - type VarStrictTypeQ = Q VarStrictType
 - type FieldExpQ = Q FieldExp
 - type RuleBndrQ = Q RuleBndr
 - type TySynEqnQ = Q TySynEqn
 - type Role = Role
 - intPrimL :: Integer -> Lit
 - wordPrimL :: Integer -> Lit
 - floatPrimL :: Rational -> Lit
 - doublePrimL :: Rational -> Lit
 - integerL :: Integer -> Lit
 - charL :: Char -> Lit
 - stringL :: String -> Lit
 - stringPrimL :: [Word8] -> Lit
 - rationalL :: Rational -> Lit
 - litP :: Lit -> PatQ
 - varP :: Name -> PatQ
 - tupP :: [PatQ] -> PatQ
 - unboxedTupP :: [PatQ] -> PatQ
 - conP :: Name -> [PatQ] -> PatQ
 - infixP :: PatQ -> Name -> PatQ -> PatQ
 - uInfixP :: PatQ -> Name -> PatQ -> PatQ
 - parensP :: PatQ -> PatQ
 - tildeP :: PatQ -> PatQ
 - bangP :: PatQ -> PatQ
 - asP :: Name -> PatQ -> PatQ
 - wildP :: PatQ
 - recP :: Name -> [FieldPatQ] -> PatQ
 - listP :: [PatQ] -> PatQ
 - sigP :: PatQ -> TypeQ -> PatQ
 - viewP :: ExpQ -> PatQ -> PatQ
 - fieldPat :: Name -> PatQ -> FieldPatQ
 - bindS :: PatQ -> ExpQ -> StmtQ
 - letS :: [DecQ] -> StmtQ
 - noBindS :: ExpQ -> StmtQ
 - parS :: [[StmtQ]] -> StmtQ
 - fromR :: ExpQ -> RangeQ
 - fromThenR :: ExpQ -> ExpQ -> RangeQ
 - fromToR :: ExpQ -> ExpQ -> RangeQ
 - fromThenToR :: ExpQ -> ExpQ -> ExpQ -> RangeQ
 - normalB :: ExpQ -> BodyQ
 - guardedB :: [Q (Guard, Exp)] -> BodyQ
 - normalG :: ExpQ -> GuardQ
 - normalGE :: ExpQ -> ExpQ -> Q (Guard, Exp)
 - patG :: [StmtQ] -> GuardQ
 - patGE :: [StmtQ] -> ExpQ -> Q (Guard, Exp)
 - match :: PatQ -> BodyQ -> [DecQ] -> MatchQ
 - clause :: [PatQ] -> BodyQ -> [DecQ] -> ClauseQ
 - dyn :: String -> ExpQ
 - global :: Name -> ExpQ
 - varE :: Name -> ExpQ
 - conE :: Name -> ExpQ
 - litE :: Lit -> ExpQ
 - appE :: ExpQ -> ExpQ -> ExpQ
 - parensE :: ExpQ -> ExpQ
 - uInfixE :: ExpQ -> ExpQ -> ExpQ -> ExpQ
 - infixE :: Maybe ExpQ -> ExpQ -> Maybe ExpQ -> ExpQ
 - infixApp :: ExpQ -> ExpQ -> ExpQ -> ExpQ
 - sectionL :: ExpQ -> ExpQ -> ExpQ
 - sectionR :: ExpQ -> ExpQ -> ExpQ
 - lamE :: [PatQ] -> ExpQ -> ExpQ
 - lam1E :: PatQ -> ExpQ -> ExpQ
 - lamCaseE :: [MatchQ] -> ExpQ
 - tupE :: [ExpQ] -> ExpQ
 - unboxedTupE :: [ExpQ] -> ExpQ
 - condE :: ExpQ -> ExpQ -> ExpQ -> ExpQ
 - multiIfE :: [Q (Guard, Exp)] -> ExpQ
 - letE :: [DecQ] -> ExpQ -> ExpQ
 - caseE :: ExpQ -> [MatchQ] -> ExpQ
 - doE :: [StmtQ] -> ExpQ
 - compE :: [StmtQ] -> ExpQ
 - arithSeqE :: RangeQ -> ExpQ
 - listE :: [ExpQ] -> ExpQ
 - sigE :: ExpQ -> TypeQ -> ExpQ
 - recConE :: Name -> [Q (Name, Exp)] -> ExpQ
 - recUpdE :: ExpQ -> [Q (Name, Exp)] -> ExpQ
 - stringE :: String -> ExpQ
 - fieldExp :: Name -> ExpQ -> Q (Name, Exp)
 - fromE :: ExpQ -> ExpQ
 - fromThenE :: ExpQ -> ExpQ -> ExpQ
 - fromToE :: ExpQ -> ExpQ -> ExpQ
 - fromThenToE :: ExpQ -> ExpQ -> ExpQ -> ExpQ
 - valD :: PatQ -> BodyQ -> [DecQ] -> DecQ
 - funD :: Name -> [ClauseQ] -> DecQ
 - tySynD :: Name -> [TyVarBndr] -> TypeQ -> DecQ
 - dataD :: CxtQ -> Name -> [TyVarBndr] -> [ConQ] -> [Name] -> DecQ
 - newtypeD :: CxtQ -> Name -> [TyVarBndr] -> ConQ -> [Name] -> DecQ
 - classD :: CxtQ -> Name -> [TyVarBndr] -> [FunDep] -> [DecQ] -> DecQ
 - instanceD :: CxtQ -> TypeQ -> [DecQ] -> DecQ
 - sigD :: Name -> TypeQ -> DecQ
 - forImpD :: Callconv -> Safety -> String -> Name -> TypeQ -> DecQ
 - infixLD :: Int -> Name -> DecQ
 - infixRD :: Int -> Name -> DecQ
 - infixND :: Int -> Name -> DecQ
 - pragInlD :: Name -> Inline -> RuleMatch -> Phases -> DecQ
 - pragSpecD :: Name -> TypeQ -> Phases -> DecQ
 - pragSpecInlD :: Name -> TypeQ -> Inline -> Phases -> DecQ
 - pragSpecInstD :: TypeQ -> DecQ
 - pragRuleD :: String -> [RuleBndrQ] -> ExpQ -> ExpQ -> Phases -> DecQ
 - pragAnnD :: AnnTarget -> ExpQ -> DecQ
 - familyNoKindD :: FamFlavour -> Name -> [TyVarBndr] -> DecQ
 - familyKindD :: FamFlavour -> Name -> [TyVarBndr] -> Kind -> DecQ
 - dataInstD :: CxtQ -> Name -> [TypeQ] -> [ConQ] -> [Name] -> DecQ
 - newtypeInstD :: CxtQ -> Name -> [TypeQ] -> ConQ -> [Name] -> DecQ
 - tySynInstD :: Name -> TySynEqnQ -> DecQ
 - closedTypeFamilyNoKindD :: Name -> [TyVarBndr] -> [TySynEqnQ] -> DecQ
 - closedTypeFamilyKindD :: Name -> [TyVarBndr] -> Kind -> [TySynEqnQ] -> DecQ
 - roleAnnotD :: Name -> [Role] -> DecQ
 - tySynEqn :: [TypeQ] -> TypeQ -> TySynEqnQ
 - cxt :: [PredQ] -> CxtQ
 - classP :: Name -> [TypeQ] -> PredQ
 - equalP :: TypeQ -> TypeQ -> PredQ
 - normalC :: Name -> [StrictTypeQ] -> ConQ
 - recC :: Name -> [VarStrictTypeQ] -> ConQ
 - infixC :: Q (Strict, Type) -> Name -> Q (Strict, Type) -> ConQ
 - forallC :: [TyVarBndr] -> CxtQ -> ConQ -> ConQ
 - forallT :: [TyVarBndr] -> CxtQ -> TypeQ -> TypeQ
 - varT :: Name -> TypeQ
 - conT :: Name -> TypeQ
 - appT :: TypeQ -> TypeQ -> TypeQ
 - arrowT :: TypeQ
 - listT :: TypeQ
 - litT :: TyLitQ -> TypeQ
 - tupleT :: Int -> TypeQ
 - unboxedTupleT :: Int -> TypeQ
 - sigT :: TypeQ -> Kind -> TypeQ
 - promotedT :: Name -> TypeQ
 - promotedTupleT :: Int -> TypeQ
 - promotedNilT :: TypeQ
 - promotedConsT :: TypeQ
 - isStrict :: Q Strict
 - unpacked :: Q Strict
 - notStrict :: Q Strict
 - strictType :: Q Strict -> TypeQ -> StrictTypeQ
 - varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ
 - numTyLit :: Integer -> TyLitQ
 - strTyLit :: String -> TyLitQ
 - plainTV :: Name -> TyVarBndr
 - kindedTV :: Name -> Kind -> TyVarBndr
 - varK :: Name -> Kind
 - conK :: Name -> Kind
 - tupleK :: Int -> Kind
 - arrowK :: Kind
 - listK :: Kind
 - appK :: Kind -> Kind -> Kind
 - starK :: Kind
 - constraintK :: Kind
 - nominalR :: Role
 - inferR :: Role
 - phantomR :: Role
 - representationalR :: Role
 - cCall :: Callconv
 - stdCall :: Callconv
 - unsafe :: Safety
 - interruptible :: Safety
 - safe :: Safety
 - funDep :: [Name] -> [Name] -> FunDep
 - typeFam :: FamFlavour
 - dataFam :: FamFlavour
 - ruleVar :: Name -> RuleBndrQ
 - typedRuleVar :: Name -> TypeQ -> RuleBndrQ
 - appsE :: [ExpQ] -> ExpQ
 - thisModule :: Q Module
 
Type synonyms
type StrictTypeQ = Q StrictType Source
type VarStrictTypeQ = Q VarStrictType Source
Lowercase pattern syntax functions
floatPrimL :: Rational -> Lit Source
doublePrimL :: Rational -> Lit Source
stringPrimL :: [Word8] -> Lit Source
unboxedTupP :: [PatQ] -> PatQ Source
Stmt
Range
Body
Guard
Match and Clause
Exp
unboxedTupE :: [ExpQ] -> ExpQ Source
arithSeqE Shortcuts
Dec
pragSpecInstD :: TypeQ -> DecQ Source
familyNoKindD :: FamFlavour -> Name -> [TyVarBndr] -> DecQ Source
familyKindD :: FamFlavour -> Name -> [TyVarBndr] -> Kind -> DecQ Source
tySynInstD :: Name -> TySynEqnQ -> DecQ Source
roleAnnotD :: Name -> [Role] -> DecQ Source
normalC :: Name -> [StrictTypeQ] -> ConQ Source
recC :: Name -> [VarStrictTypeQ] -> ConQ Source
Type
unboxedTupleT :: Int -> TypeQ Source
promotedTupleT :: Int -> TypeQ Source
strictType :: Q Strict -> TypeQ -> StrictTypeQ Source
varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ Source
Type Literals
Kind
Role
Callconv
Safety
FunDep
FamFlavour
RuleBndr
typedRuleVar :: Name -> TypeQ -> RuleBndrQ Source
Useful helper function
thisModule :: Q Module Source
Return the Module at the place of splicing.  Can be used as an
 input for reifyModule.