haskell-src-exts-1.3.5: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printerSource codeContentsIndex
Language.Haskell.Exts.Build
Portabilityportable
Stabilityexperimental
MaintainerNiklas Broberg, d00nibro@chalmers.se
Contents
Syntax building functions
More advanced building
Description
This module contains combinators to use when building Haskell source trees programmatically, as opposed to parsing them from a string. The contents here are quite experimental and will likely receive a lot of attention when the rest has stabilised.
Synopsis
name :: String -> Name
sym :: String -> Name
var :: Name -> Exp
op :: Name -> QOp
qvar :: ModuleName -> Name -> Exp
pvar :: Name -> Pat
app :: Exp -> Exp -> Exp
infixApp :: Exp -> QOp -> Exp -> Exp
appFun :: Exp -> [Exp] -> Exp
pApp :: Name -> [Pat] -> Pat
tuple :: [Exp] -> Exp
pTuple :: [Pat] -> Pat
varTuple :: [Name] -> Exp
pvarTuple :: [Name] -> Pat
function :: String -> Exp
strE :: String -> Exp
charE :: Char -> Exp
intE :: Integer -> Exp
strP :: String -> Pat
charP :: Char -> Pat
intP :: Integer -> Pat
doE :: [Stmt] -> Exp
lamE :: SrcLoc -> [Pat] -> Exp -> Exp
letE :: [Decl] -> Exp -> Exp
caseE :: Exp -> [Alt] -> Exp
alt :: SrcLoc -> Pat -> Exp -> Alt
altGW :: SrcLoc -> Pat -> [Stmt] -> Exp -> Binds -> Alt
listE :: [Exp] -> Exp
eList :: Exp
peList :: Pat
paren :: Exp -> Exp
pParen :: Pat -> Pat
qualStmt :: Exp -> Stmt
genStmt :: SrcLoc -> Pat -> Exp -> Stmt
letStmt :: [Decl] -> Stmt
binds :: [Decl] -> Binds
noBinds :: Binds
wildcard :: Pat
genNames :: String -> Int -> [Name]
sfun :: SrcLoc -> Name -> [Name] -> Rhs -> Binds -> Decl
simpleFun :: SrcLoc -> Name -> Name -> Exp -> Decl
patBind :: SrcLoc -> Pat -> Exp -> Decl
patBindWhere :: SrcLoc -> Pat -> Exp -> [Decl] -> Decl
nameBind :: SrcLoc -> Name -> Exp -> Decl
metaFunction :: String -> [Exp] -> Exp
metaConPat :: String -> [Pat] -> Pat
Syntax building functions
name :: String -> NameSource
An identifier with the given string as its name. The string should be a valid Haskell identifier.
sym :: String -> NameSource
A symbol identifier. The string should be a valid Haskell symbol identifier.
var :: Name -> ExpSource
A local variable as expression.
op :: Name -> QOpSource
Use the given identifier as an operator.
qvar :: ModuleName -> Name -> ExpSource
A qualified variable as expression.
pvar :: Name -> PatSource
A pattern variable.
app :: Exp -> Exp -> ExpSource
Application of expressions by juxtaposition.
infixApp :: Exp -> QOp -> Exp -> ExpSource
Apply an operator infix.
appFun :: Exp -> [Exp] -> ExpSource
Apply a function to a list of arguments.
pApp :: Name -> [Pat] -> PatSource
A constructor pattern, with argument patterns.
tuple :: [Exp] -> ExpSource
A tuple expression.
pTuple :: [Pat] -> PatSource
A tuple pattern.
varTuple :: [Name] -> ExpSource
A tuple expression consisting of variables only.
pvarTuple :: [Name] -> PatSource
A tuple pattern consisting of variables only.
function :: String -> ExpSource
A function with a given name.
strE :: String -> ExpSource
A literal string expression.
charE :: Char -> ExpSource
A literal character expression.
intE :: Integer -> ExpSource
A literal integer expression.
strP :: String -> PatSource
A literal string pattern.
charP :: Char -> PatSource
A literal character pattern.
intP :: Integer -> PatSource
A literal integer pattern.
doE :: [Stmt] -> ExpSource
A do block formed by the given statements. The last statement in the list should be a Qualifier expression.
lamE :: SrcLoc -> [Pat] -> Exp -> ExpSource
Lambda abstraction, given a list of argument patterns and an expression body.
letE :: [Decl] -> Exp -> ExpSource
A let ... in block.
caseE :: Exp -> [Alt] -> ExpSource
A case expression.
alt :: SrcLoc -> Pat -> Exp -> AltSource
An unguarded alternative in a case expression.
altGW :: SrcLoc -> Pat -> [Stmt] -> Exp -> Binds -> AltSource
An alternative with a single guard in a case expression.
listE :: [Exp] -> ExpSource
A list expression.
eList :: ExpSource
The empty list expression.
peList :: PatSource
The empty list pattern.
paren :: Exp -> ExpSource
Put parentheses around an expression.
pParen :: Pat -> PatSource
Put parentheses around a pattern.
qualStmt :: Exp -> StmtSource
A qualifier expression statement.
genStmt :: SrcLoc -> Pat -> Exp -> StmtSource
A generator statement: pat <- exp
letStmt :: [Decl] -> StmtSource
A let binding group as a statement.
binds :: [Decl] -> BindsSource
Hoist a set of declarations to a binding group.
noBinds :: BindsSource
An empty binding group.
wildcard :: PatSource
The wildcard pattern: _
genNames :: String -> Int -> [Name]Source
Generate k names by appending numbers 1 through k to a given string.
More advanced building
sfun :: SrcLoc -> Name -> [Name] -> Rhs -> Binds -> DeclSource
A function with a single clause
simpleFun :: SrcLoc -> Name -> Name -> Exp -> DeclSource
A function with a single clause, a single argument, no guards and no where declarations
patBind :: SrcLoc -> Pat -> Exp -> DeclSource
A pattern bind where the pattern is a variable, and where there are no guards and no 'where' clause.
patBindWhere :: SrcLoc -> Pat -> Exp -> [Decl] -> DeclSource
A pattern bind where the pattern is a variable, and where there are no guards, but with a 'where' clause.
nameBind :: SrcLoc -> Name -> Exp -> DeclSource
Bind an identifier to an expression.
metaFunction :: String -> [Exp] -> ExpSource
Apply function of a given name to a list of arguments.
metaConPat :: String -> [Pat] -> PatSource
Apply a constructor of a given name to a list of pattern arguments, forming a constructor pattern.
Produced by Haddock version 2.6.0