|
|
|
|
|
Documentation |
|
type InfoQ = Q Info |
|
type PatQ = Q Pat |
|
type FieldPatQ = Q FieldPat |
|
type ExpQ = Q Exp |
|
type DecQ = Q Dec |
|
type ConQ = Q Con |
|
type TypeQ = Q Type |
|
type CxtQ = Q Cxt |
|
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 |
|
intPrimL :: Integer -> Lit |
|
floatPrimL :: Rational -> Lit |
|
doublePrimL :: Rational -> Lit |
|
integerL :: Integer -> Lit |
|
charL :: Char -> Lit |
|
stringL :: String -> Lit |
|
rationalL :: Rational -> Lit |
|
litP :: Lit -> PatQ |
|
varP :: Name -> PatQ |
|
tupP :: [PatQ] -> PatQ |
|
conP :: Name -> [PatQ] -> PatQ |
|
infixP :: PatQ -> Name -> PatQ -> PatQ |
|
tildeP :: PatQ -> PatQ |
|
asP :: Name -> PatQ -> PatQ |
|
wildP :: PatQ |
|
recP :: Name -> [FieldPatQ] -> PatQ |
|
listP :: [PatQ] -> PatQ |
|
sigP :: PatQ -> TypeQ -> 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 -> Q Exp |
|
global :: Name -> ExpQ |
|
varE :: Name -> ExpQ |
|
conE :: Name -> ExpQ |
|
litE :: Lit -> ExpQ |
|
appE :: 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 |
|
tupE :: [ExpQ] -> ExpQ |
|
condE :: ExpQ -> ExpQ -> ExpQ -> ExpQ |
|
letE :: [DecQ] -> ExpQ -> ExpQ |
|
caseE :: ExpQ -> [MatchQ] -> ExpQ |
|
doE :: [StmtQ] -> ExpQ |
|
compE :: [StmtQ] -> ExpQ |
|
arithSeqE :: RangeQ -> ExpQ |
|
fromE :: ExpQ -> ExpQ |
|
fromThenE :: ExpQ -> ExpQ -> ExpQ |
|
fromToE :: ExpQ -> ExpQ -> ExpQ |
|
fromThenToE :: ExpQ -> ExpQ -> ExpQ -> 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) |
|
valD :: PatQ -> BodyQ -> [DecQ] -> DecQ |
|
funD :: Name -> [ClauseQ] -> DecQ |
|
tySynD :: Name -> [Name] -> TypeQ -> DecQ |
|
dataD :: CxtQ -> Name -> [Name] -> [ConQ] -> [Name] -> DecQ |
|
newtypeD :: CxtQ -> Name -> [Name] -> ConQ -> [Name] -> DecQ |
|
classD :: CxtQ -> Name -> [Name] -> [FunDep] -> [DecQ] -> DecQ |
|
instanceD :: CxtQ -> TypeQ -> [DecQ] -> DecQ |
|
sigD :: Name -> TypeQ -> DecQ |
|
forImpD :: Callconv -> Safety -> String -> Name -> TypeQ -> DecQ |
|
cxt :: [TypeQ] -> CxtQ |
|
normalC :: Name -> [StrictTypeQ] -> ConQ |
|
recC :: Name -> [VarStrictTypeQ] -> ConQ |
|
infixC :: Q (Strict, Type) -> Name -> Q (Strict, Type) -> ConQ |
|
forallC :: [Name] -> CxtQ -> ConQ -> ConQ |
|
forallT :: [Name] -> CxtQ -> TypeQ -> TypeQ |
|
varT :: Name -> TypeQ |
|
conT :: Name -> TypeQ |
|
appT :: TypeQ -> TypeQ -> TypeQ |
|
arrowT :: TypeQ |
|
listT :: TypeQ |
|
tupleT :: Int -> TypeQ |
|
isStrict :: Q Strict |
|
notStrict :: Q Strict |
|
strictType :: Q Strict -> TypeQ -> StrictTypeQ |
|
varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ |
|
cCall :: Callconv |
|
stdCall :: Callconv |
|
unsafe :: Safety |
|
safe :: Safety |
|
threadsafe :: Safety |
|
funDep :: [Name] -> [Name] -> FunDep |
|
combine :: [([(Name, Name)], Pat)] -> ([(Name, Name)], [Pat]) |
|
rename :: Pat -> Q ([(Name, Name)], Pat) |
|
genpat :: Pat -> Q (Name -> ExpQ, Pat) |
|
alpha :: [(Name, Name)] -> Name -> ExpQ |
|
appsE :: [ExpQ] -> ExpQ |
|
simpleMatch :: Pat -> Exp -> Match |
|
Produced by Haddock version 0.8 |