The AST in Nimrod
This section describes how the AST is modelled with Nimrod's type system. The AST consists of nodes (PNimrodNode) with a variable number of children. Each node has a field named kind which describes what the node contains:
type TNimrodNodeKind = enum ## kind of a node; only explanatory nnkNone, ## invalid node kind nnkEmpty, ## empty node nnkIdent, ## node contains an identifier nnkIntLit, ## node contains an int literal (example: 10) nnkStrLit, ## node contains a string literal (example: "abc") nnkNilLit, ## node contains a nil literal (example: nil) nnkCaseStmt, ## node represents a case statement ... ## many more PNimrodNode = ref TNimrodNode TNimrodNode {.final.} = object case kind: TNimrodNodeKind ## the node's kind of nnkNone, nnkEmpty, nnkNilLit: nil ## node contains no additional fields of nnkCharLit..nnkInt64Lit: intVal: biggestInt ## the int literal of nnkFloatLit..nnkFloat64Lit: floatVal: biggestFloat ## the float literal of nnkStrLit..nnkTripleStrLit: strVal: string ## the string literal of nnkIdent: ident: TNimrodIdent ## the identifier of nnkSym: symbol: PNimrodSymbol ## the symbol (after symbol lookup phase) else: sons: seq[PNimrodNode] ## the node's sons (or children)
For the PNimrodNode type, the [] operator has been overloaded: n[i] is n's i-th child.
To specify the AST for the different Nimrod constructs, the notation nodekind(son1, son2, ...) or nodekind(value) or nodekind(field=value) is used.
Some child may be missing. A missing child is a node of kind nnkEmpty; a child can never be nil.
Leaf nodes/Atoms
A leaf of the AST often corresponds to a terminal symbol in the concrete syntax.
Nimrod expression | corresponding AST |
---|---|
42 | nnkIntLit(intVal = 42) |
42'i8 | nnkInt8Lit(intVal = 42) |
42'i16 | nnkInt16Lit(intVal = 42) |
42'i32 | nnkInt32Lit(intVal = 42) |
42'i64 | nnkInt64Lit(intVal = 42) |
42.0 | nnkFloatLit(floatVal = 42.0) |
42.0'f32 | nnkFloat32Lit(floatVal = 42.0) |
42.0'f64 | nnkFloat64Lit(floatVal = 42.0) |
"abc" | nnkStrLit(strVal = "abc") |
r"abc" | nnkRStrLit(strVal = "abc") |
"""abc""" | nnkTripleStrLit(strVal = "abc") |
' ' | nnkCharLit(intVal = 32) |
nil | nnkNilLit() |
myIdentifier | nnkIdent(ident = !"myIdentifier") |
myIdentifier | after lookup pass: nnkSym(symbol = ...) |
Identifiers are nnkIdent nodes. After the name lookup pass these nodes get transferred into nnkSym nodes. However, a macro receives an AST that has not been checked for semantics and thus the identifiers have not been looked up. Macros should deal with nnkIdent nodes and do not need to deal with nnkSym nodes.
Calls/expressions
Command call
Concrete syntax:
echo "abc", "xyz"
AST:
nnkCommand(nnkIdent(!"echo"), nnkStrLit("abc"), nnkStrLit("xyz"))
Call with ()
Concrete syntax:
echo("abc", "xyz")
AST:
nnkCall(nnkIdent(!"echo"), nnkStrLit("abc"), nnkStrLit("xyz"))
Infix operator call
Concrete syntax:
"abc" & "xyz"
AST:
nnkInfix(nnkIdent(!"&"), nnkStrLit("abc"), nnkStrLit("xyz"))
Prefix operator call
Concrete syntax:
? "xyz"
AST:
nnkPrefix(nnkIdent(!"?"), nnkStrLit("abc"))
Postfix operator call
Note: There are no postfix operators in Nimrod. However, the nnkPostfix node is used for the asterisk export marker *:
Concrete syntax:
identifier*
AST:
nnkPostfix(nnkIdent(!"*"), nnkIdent(!"identifier"))
Call with named arguments
Concrete syntax:
writeln(file=stdout, "hallo")
AST:
nnkCall(nnkIdent(!"writeln"), nnkExprEqExpr(nnkIdent(!"file"), nnkIdent(!"stdout")), nnkStrLit("hallo"))
Dereference operator ^
Concrete syntax:
x^
AST:
nnkDerefExpr(nnkIdent(!"x"))
Addr operator
Concrete syntax:
addr(x)
AST:
nnkAddr(nnkIdent(!"x"))
Cast operator
Concrete syntax:
cast[T](x)
AST:
nnkCast(nnkIdent(!"T"), nnkIdent(!"x"))
Object access operator .
Concrete syntax:
x.y
AST:
nnkDotExpr(nnkIdent(!"x"), nnkIdent(!"y"))
Array access operator []
Concrete syntax:
x[y]
AST:
nnkBracketExpr(nnkIdent(!"x"), nnkIdent(!"y"))
Parentheses
Parentheses for affecting operator precedence or tuple construction are built with the nnkPar node.
Concrete syntax:
(1, 2, (3))
AST:
nnkPar(nnkIntLit(1), nnkIntLit(2), nnkPar(nnkIntLit(3)))
Curly braces
Curly braces are used as the set constructor.
Concrete syntax:
{1, 2, 3}
AST:
nnkCurly(nnkIntLit(1), nnkIntLit(2), nnkIntLit(3))
Brackets
Brackets are used as the array constructor.
Concrete syntax:
[1, 2, 3]
AST:
nnkBracket(nnkIntLit(1), nnkIntLit(2), nnkIntLit(3))
Ranges
Ranges occur in set constructors, case statement branches or array slices.
Concrete syntax:
1..3
AST:
nnkRange(nnkIntLit(1), nnkIntLit(3))
If expression
The representation of the if expression is subtle, but easy to traverse.
Concrete syntax:
if cond1: expr1 elif cond2: expr2 else: expr3
AST:
nnkIfExpr( nnkElifExpr(cond1, expr1), nnkElifExpr(cond2, expr2), nnkElseExpr(expr3) )
Statements
If statement
The representation of the if statement is subtle, but easy to traverse. If there is no else branch, no nnkElse child exists.
Concrete syntax:
if cond1: stmt1 elif cond2: stmt2 elif cond3: stmt3 else: stmt4
AST:
nnkIfStmt( nnkElifBranch(cond1, stmt1), nnkElifBranch(cond2, stmt2), nnkElifBranch(cond3, stmt3), nnkElse(stmt4) )
When statement
Like the if statement, but the root has the kind nnkWhenStmt.
Assignment
Concrete syntax:
x = 42
AST:
nnkAsgn(nnkIdent(!"x"), nnkIntLit(42))
Statement list
Concrete syntax:
stmt1 stmt2 stmt3
AST:
nnkStmtList(stmt1, stmt2, stmt3)
Case statement
Concrete syntax:
case expr1 of expr2, expr3..expr4: stmt1 of expr5: stmt2 elif cond1: stmt3 else: stmt4
AST:
nnkCaseStmt( expr1, nnkOfBranch(expr2, nnkRange(expr3, expr4), stmt1), nnkOfBranch(expr5, stmt2), nnkElifBranch(cond1, stmt3), nnkElse(stmt4) )
The nnkElifBranch and nnkElse parts may be missing.
While statement
Concrete syntax:
while expr1: stmt1
AST:
nnkWhileStmt(expr1, stmt1)
For statement
Concrete syntax:
for ident1, ident2 in expr1: stmt1
AST:
nnkForStmt(ident1, ident2, expr1, stmt1)
Try statement
Concrete syntax:
try: stmt1 except e1, e2: stmt2 except e3: stmt3 except: stmt4 finally: stmt5
AST:
nnkTryStmt( stmt1, nnkExceptBranch(e1, e2, stmt2), nnkExceptBranch(e3, stmt3), nnkExceptBranch(stmt4), nnkFinally(stmt5) )
Return statement
Concrete syntax:
return expr1
AST:
nnkReturnStmt(expr1)
Yield statement
Like return, but with nnkYieldStmt kind.
Discard statement
Like return, but with nnkDiscardStmt kind.
Continue statement
Concrete syntax:
continue
AST:
nnkContinueStmt()
Var section
To be written.
Const section
To be written.
Type section
To be written.
Procedure declaration
To be written.
Iterator declaration
To be written.
Template declaration
To be written.
Macro declaration
To be written.
Special node kinds
There are several node kinds that are used for semantic checking or code generation. These are accessible from this module, but should not be used. Other node kinds are especially designed to make AST manipulations easier. These are explained here.
To be written.
Types
TNimrodNodeKind = enum nnkNone, nnkEmpty, nnkIdent, nnkSym, nnkType, nnkCharLit, nnkIntLit, nnkInt8Lit, nnkInt16Lit, nnkInt32Lit, nnkInt64Lit, nnkUIntLit, nnkUInt8Lit, nnkUInt16Lit, nnkUInt32Lit, nnkUInt64Lit, nnkFloatLit, nnkFloat32Lit, nnkFloat64Lit, nnkFloat128Lit, nnkStrLit, nnkRStrLit, nnkTripleStrLit, nnkNilLit, nnkMetaNode, nnkDotCall, nnkCommand, nnkCall, nnkCallStrLit, nnkInfix, nnkPrefix, nnkPostfix, nnkHiddenCallConv, nnkExprEqExpr, nnkExprColonExpr, nnkIdentDefs, nnkVarTuple, nnkPar, nnkObjConstr, nnkCurly, nnkCurlyExpr, nnkBracket, nnkBracketExpr, nnkPragmaExpr, nnkRange, nnkDotExpr, nnkCheckedFieldExpr, nnkDerefExpr, nnkIfExpr, nnkElifExpr, nnkElseExpr, nnkLambda, nnkDo, nnkAccQuoted, nnkTableConstr, nnkBind, nnkClosedSymChoice, nnkOpenSymChoice, nnkHiddenStdConv, nnkHiddenSubConv, nnkConv, nnkCast, nnkStaticExpr, nnkAddr, nnkHiddenAddr, nnkHiddenDeref, nnkObjDownConv, nnkObjUpConv, nnkChckRangeF, nnkChckRange64, nnkChckRange, nnkStringToCString, nnkCStringToString, nnkAsgn, nnkFastAsgn, nnkGenericParams, nnkFormalParams, nnkOfInherit, nnkImportAs, nnkProcDef, nnkMethodDef, nnkConverterDef, nnkMacroDef, nnkTemplateDef, nnkIteratorDef, nnkOfBranch, nnkElifBranch, nnkExceptBranch, nnkElse, nnkAsmStmt, nnkPragma, nnkPragmaBlock, nnkIfStmt, nnkWhenStmt, nnkForStmt, nnkParForStmt, nnkWhileStmt, nnkCaseStmt, nnkTypeSection, nnkVarSection, nnkLetSection, nnkConstSection, nnkConstDef, nnkTypeDef, nnkYieldStmt, nnkTryStmt, nnkFinally, nnkRaiseStmt, nnkReturnStmt, nnkBreakStmt, nnkContinueStmt, nnkBlockStmt, nnkStaticStmt, nnkDiscardStmt, nnkStmtList, nnkImportStmt, nnkImportExceptStmt, nnkExportStmt, nnkExportExceptStmt, nnkFromStmt, nnkIncludeStmt, nnkBindStmt, nnkMixinStmt, nnkUsingStmt, nnkCommentStmt, nnkStmtListExpr, nnkBlockExpr, nnkStmtListType, nnkBlockType, nnkTypeOfExpr, nnkObjectTy, nnkTupleTy, nnkTypeClassTy, nnkStaticTy, nnkRecList, nnkRecCase, nnkRecWhen, nnkRefTy, nnkPtrTy, nnkVarTy, nnkConstTy, nnkMutableTy, nnkDistinctTy, nnkProcTy, nnkIteratorTy, nnkSharedTy, nnkEnumTy, nnkEnumFieldDef, nnkArglist, nnkPattern, nnkReturnToken
TNimNodeKinds = set[TNimrodNodeKind]
TNimrodTypeKind = enum ntyNone, ntyBool, ntyChar, ntyEmpty, ntyArrayConstr, ntyNil, ntyExpr, ntyStmt, ntyTypeDesc, ntyGenericInvokation, ntyGenericBody, ntyGenericInst, ntyGenericParam, ntyDistinct, ntyEnum, ntyOrdinal, ntyArray, ntyObject, ntyTuple, ntySet, ntyRange, ntyPtr, ntyRef, ntyVar, ntySequence, ntyProc, ntyPointer, ntyOpenArray, ntyString, ntyCString, ntyForward, ntyInt, ntyInt8, ntyInt16, ntyInt32, ntyInt64, ntyFloat, ntyFloat32, ntyFloat64, ntyFloat128
TNimTypeKinds = set[TNimrodTypeKind]
TNimrodSymKind = enum nskUnknown, nskConditional, nskDynLib, nskParam, nskGenericParam, nskTemp, nskModule, nskType, nskVar, nskLet, nskConst, nskResult, nskProc, nskMethod, nskIterator, nskClosureIterator, nskConverter, nskMacro, nskTemplate, nskField, nskEnumField, nskForVar, nskLabel, nskStub
TNimSymKinds = set[TNimrodSymKind]
TNimrodIdent = object of TObject
- represents a Nimrod identifier in the AST
PNimrodSymbol = ref TNimrodSymbol
- represents a Nimrod symbol in the compiler; a symbol is a looked-up ident.
TBindSymRule = enum brClosed, ## only the symbols in current scope are bound brOpen, ## open wrt overloaded symbols, but may be a single ## symbol if not ambiguous (the rules match that of ## binding in generics) brForceOpen ## same as brOpen, but it will always be open even ## if not ambiguous (this cannot be achieved with ## any other means in the language currently)
- specifies how bindSym behaves
Consts
nnkLiterals = {nnkCharLit..nnkNilLit}
nnkCallKinds = {nnkCall, nnkInfix, nnkPrefix, nnkPostfix, nnkCommand, nnkCallStrLit}
RoutineNodes = {nnkProcDef, nnkMethodDef, nnkDo, nnkLambda, nnkIteratorDef}
AtomicNodes = {nnkNone..nnkNilLit}
CallNodes = {nnkCall, nnkInfix, nnkPrefix, nnkPostfix, nnkCommand, nnkCallStrLit, nnkHiddenCallConv}
Procs
proc `[]`(n: PNimrodNode; i: int): PNimrodNode {.magic: "NChild".}
- get n's i'th child.
proc `[]=`(n: PNimrodNode; i: int; child: PNimrodNode) {.magic: "NSetChild".}
- set n's i'th child to child.
proc `!`(s: string): TNimrodIdent {.magic: "StrToIdent".}
- constructs an identifier from the string s
proc `$`(i: TNimrodIdent): string {.magic: "IdentToStr".}
- converts a Nimrod identifier to a string
proc `$`(s: PNimrodSymbol): string {.magic: "IdentToStr".}
- converts a Nimrod symbol to a string
proc `==`(a, b: TNimrodIdent): bool {.magic: "EqIdent", noSideEffect.}
- compares two Nimrod identifiers
proc `==`(a, b: PNimrodNode): bool {.magic: "EqNimrodNode", noSideEffect.}
- compares two Nimrod nodes
proc len(n: PNimrodNode): int {.magic: "NLen".}
- returns the number of children of n.
proc add(father, child: PNimrodNode): PNimrodNode {.magic: "NAdd", discardable.}
- Adds the child to the father node. Returns the father node so that calls can be nested.
proc add(father: PNimrodNode; children: varargs[PNimrodNode]): PNimrodNode {. magic: "NAddMultiple", discardable.}
- Adds each child of children to the father node. Returns the father node so that calls can be nested.
proc del(father: PNimrodNode; idx = 0; n = 1) {.magic: "NDel".}
- deletes n children of father starting at index idx.
proc kind(n: PNimrodNode): TNimrodNodeKind {.magic: "NKind".}
- returns the kind of the node n.
proc intVal(n: PNimrodNode): BiggestInt {.magic: "NIntVal".}
proc floatVal(n: PNimrodNode): BiggestFloat {.magic: "NFloatVal".}
proc symbol(n: PNimrodNode): PNimrodSymbol {.magic: "NSymbol".}
proc ident(n: PNimrodNode): TNimrodIdent {.magic: "NIdent".}
proc typ[](n: PNimrodNode): typedesc {.magic: "NGetType".}
proc strVal(n: PNimrodNode): string {.magic: "NStrVal".}
proc intVal=(n: PNimrodNode; val: BiggestInt) {.magic: "NSetIntVal".}
proc floatVal=(n: PNimrodNode; val: BiggestFloat) {.magic: "NSetFloatVal".}
proc symbol=(n: PNimrodNode; val: PNimrodSymbol) {.magic: "NSetSymbol".}
proc ident=(n: PNimrodNode; val: TNimrodIdent) {.magic: "NSetIdent".}
proc strVal=(n: PNimrodNode; val: string) {.magic: "NSetStrVal".}
proc newNimNode(kind: TNimrodNodeKind; n: PNimrodNode = nil): PNimrodNode {. magic: "NNewNimNode".}
proc copyNimNode(n: PNimrodNode): PNimrodNode {.magic: "NCopyNimNode".}
proc copyNimTree(n: PNimrodNode): PNimrodNode {.magic: "NCopyNimTree".}
proc error(msg: string) {.magic: "NError".}
- writes an error message at compile time
proc warning(msg: string) {.magic: "NWarning".}
- writes a warning message at compile time
proc hint(msg: string) {.magic: "NHint".}
- writes a hint message at compile time
proc newStrLitNode(s: string): PNimrodNode {.compileTime, raises: [], tags: [].}
- creates a string literal node from s
proc newIntLitNode(i: BiggestInt): PNimrodNode {.compileTime, raises: [], tags: [].}
- creates a int literal node from i
proc newFloatLitNode(f: BiggestFloat): PNimrodNode {.compileTime, raises: [], tags: [].}
- creates a float literal node from f
proc newIdentNode(i: TNimrodIdent): PNimrodNode {.compileTime, raises: [], tags: [].}
- creates an identifier node from i
proc newIdentNode(i: string): PNimrodNode {.compileTime, raises: [], tags: [].}
- creates an identifier node from i
proc bindSym(ident: string; rule: TBindSymRule = brClosed): PNimrodNode {. magic: "NBindSym".}
- creates a node that binds ident to a symbol node. The bound symbol may be an overloaded symbol. If rule == brClosed either an nkClosedSymChoice tree is returned or nkSym if the symbol is not ambiguous. If rule == brOpen either an nkOpenSymChoice tree is returned or nkSym if the symbol is not ambiguous. If rule == brForceOpen always an nkOpenSymChoice tree is returned even if the symbol is not ambiguous.
proc genSym(kind: TNimrodSymKind = nskLet; ident = ""): PNimrodNode {. magic: "NGenSym".}
- generates a fresh symbol that is guaranteed to be unique. The symbol needs to occur in a declaration context.
proc callsite(): PNimrodNode {.magic: "NCallSite".}
- returns the AST if the invokation expression that invoked this macro.
proc toStrLit(n: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- converts the AST n to the concrete Nimrod code and wraps that in a string literal node
proc lineinfo(n: PNimrodNode): string {.magic: "NLineInfo".}
- returns the position the node appears in the original source file in the form filename(line, col)
proc parseExpr(s: string): PNimrodNode {.magic: "ParseExprToAst".}
- Compiles the passed string to its AST representation. Expects a single expression.
proc parseStmt(s: string): PNimrodNode {.magic: "ParseStmtToAst".}
- Compiles the passed string to its AST representation. Expects one or more statements.
proc getAst[expr](macroOrTemplate: expr): PNimrodNode {.magic: "ExpandToAst".}
-
Obtains the AST nodes returned from a macro or template invocation. Example:
macro FooMacro() = var ast = getAst(BarTemplate())
proc quote(bl: stmt; op = "``"): PNimrodNode {.magic: "QuoteAst".}
-
Quasi-quoting operator. Accepts an expression or a block and returns the AST that represents it. Within the quoted AST, you are able to interpolate PNimrodNode expressions from the surrounding scope. If no operator is given, quoting is done using backticks. Otherwise, the given operator must be used as a prefix operator for any interpolated expression. The original meaning of the interpolation operator may be obtained by escaping it (by prefixing it with itself): e.g. @ is escaped as @@, @@ is escaped as @@@ and so on.
Example:
macro check(ex: expr): stmt = # this is a simplified version of the check macro from the # unittest module. # If there is a failed check, we want to make it easy for # the user to jump to the faulty line in the code, so we # get the line info here: var info = ex.lineinfo # We will also display the code string of the failed check: var expString = ex.toStrLit # Finally we compose the code to implement the check: result = quote do: if not `ex`: echo `info` & ": Check failed: " & `expString`
proc expectKind(n: PNimrodNode; k: TNimrodNodeKind) {.compileTime, raises: [], tags: [].}
- checks that n is of kind k. If this is not the case, compilation aborts with an error message. This is useful for writing macros that check the AST that is passed to them.
proc expectMinLen(n: PNimrodNode; min: int) {.compileTime, raises: [], tags: [].}
- checks that n has at least min children. If this is not the case, compilation aborts with an error message. This is useful for writing macros that check its number of arguments.
proc expectLen(n: PNimrodNode; len: int) {.compileTime, raises: [], tags: [].}
- checks that n has exactly len children. If this is not the case, compilation aborts with an error message. This is useful for writing macros that check its number of arguments.
proc newCall(theProc: PNimrodNode; args: varargs[PNimrodNode]): PNimrodNode {. compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..].
proc newCall(theProc: TNimrodIdent; args: varargs[PNimrodNode]): PNimrodNode {. compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..].
proc newCall(theProc: string; args: varargs[PNimrodNode]): PNimrodNode {. compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..].
proc newLit(c: char): PNimrodNode {.compileTime, raises: [], tags: [].}
- produces a new character literal node.
proc newLit(i: BiggestInt): PNimrodNode {.compileTime, raises: [], tags: [].}
- produces a new integer literal node.
proc newLit(f: BiggestFloat): PNimrodNode {.compileTime, raises: [], tags: [].}
- produces a new float literal node.
proc newLit(s: string): PNimrodNode {.compileTime, raises: [], tags: [].}
- produces a new string literal node.
proc nestList(theProc: TNimrodIdent; x: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- nests the list x into a tree of call expressions: [a, b, c] is transformed into theProc(a, theProc(c, d)).
proc treeRepr(n: PNimrodNode): string {.compileTime, raises: [], tags: [].}
-
Convert the AST n to a human-readable tree-like string.
See also repr and lispRepr.
proc lispRepr(n: PNimrodNode): string {.compileTime, raises: [], tags: [].}
-
Convert the AST n to a human-readable lisp-like string,
See also repr and treeRepr.
proc newEmptyNode(): PNimrodNode {.compileTime, noSideEffect, raises: [], tags: [].}
- Create a new empty node
proc newStmtList(stmts: varargs[PNimrodNode]): PNimrodNode {.compileTime, raises: [], tags: [].}
- Create a new statement list
proc newBlockStmt(label, body: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- Create a new block statement with label
proc newBlockStmt(body: PNimrodNode): PNimrodNode {.compiletime, raises: [], tags: [].}
- Create a new block: stmt
proc newVarStmt(name, value: PNimrodNode): PNimrodNode {.compiletime, raises: [], tags: [].}
- Create a new var stmt
proc newLetStmt(name, value: PNimrodNode): PNimrodNode {.compiletime, raises: [], tags: [].}
- Create a new let stmt
proc newAssignment(lhs, rhs: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
proc newDotExpr(a, b: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- Create new dot expression a.dot(b) -> a.b
proc newIdentDefs(name, kind: PNimrodNode; default = newEmptyNode()): PNimrodNode {. compileTime, raises: [], tags: [].}
proc newNilLit(): PNimrodNode {.compileTime, raises: [], tags: [].}
- New nil literal shortcut
proc high(node: PNimrodNode): int {.compileTime, raises: [], tags: [].}
- Return the highest index available for a node
proc last(node: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- Return the last item in nodes children. Same as node[node.high()]
proc expectKind(n: PNimrodNode; k: set[TNimrodNodeKind]) {.compileTime, raises: [EInvalidValue], tags: [].}
proc newProc(name = newEmptyNode(); params: openArray[PNimrodNode] = [newEmptyNode()]; body: PNimrodNode = newStmtList(); procType = nnkProcDef): PNimrodNode {. compileTime, raises: [], tags: [].}
-
shortcut for creating a new proc
The params array must start with the return type of the proc, followed by a list of IdentDefs which specify the params.
proc newIfStmt(branches: varargs[tuple[cond, body: PNimrodNode]]): PNimrodNode {. compiletime, raises: [], tags: [].}
-
Constructor for if statements.
newIfStmt( (Ident, StmtList), ... )
proc copyChildrenTo(src, dest: PNimrodNode) {.compileTime, raises: [], tags: [].}
- Copy all children from src to dest
proc name(someProc: PNimrodNode): PNimrodNode {.compileTime, raises: [EInvalidValue], tags: [].}
proc name=(someProc: PNimrodNode; val: PNimrodNode) {.compileTime, raises: [EInvalidValue], tags: [].}
proc params(someProc: PNimrodNode): PNimrodNode {.compileTime, raises: [EInvalidValue], tags: [].}
proc params=(someProc: PNimrodNode; params: PNimrodNode) {.compileTime, raises: [EInvalidValue], tags: [].}
proc pragma(someProc: PNimrodNode): PNimrodNode {.compileTime, raises: [EInvalidValue], tags: [].}
- Get the pragma of a proc type These will be expanded
proc pragma=(someProc: PNimrodNode; val: PNimrodNode) {.compileTime, raises: [EInvalidValue], tags: [].}
- Set the pragma of a proc type
proc body(someProc: PNimrodNode): PNimrodNode {.compileTime, raises: [EInvalidValue], tags: [].}
proc body=(someProc: PNimrodNode; val: PNimrodNode) {.compileTime, raises: [EInvalidValue], tags: [].}
proc `$`(node: PNimrodNode): string {.compileTime, raises: [EInvalidValue], tags: [].}
- Get the string of an identifier node
proc ident(name: string): PNimrodNode {.compileTime, inline, raises: [], tags: [].}
- Create a new ident node from a string
proc insert(a: PNimrodNode; pos: int; b: PNimrodNode) {.compileTime, raises: [], tags: [].}
- Insert node B into A at pos
proc basename(a: PNimrodNode): PNimrodNode {.compiletime, raises: [], tags: [].}
- Pull an identifier from prefix/postfix expressions
proc basename=(a: PNimrodNode; val: string) {.compileTime, raises: [], tags: [].}
proc postfix(node: PNimrodNode; op: string): PNimrodNode {.compileTime, raises: [], tags: [].}
proc prefix(node: PNimrodNode; op: string): PNimrodNode {.compileTime, raises: [], tags: [].}
proc infix(a: PNimrodNode; op: string; b: PNimrodNode): PNimrodNode {. compileTime, raises: [], tags: [].}
proc unpackPostfix(node: PNimrodNode): tuple[node: PNimrodNode, op: string] {. compileTime, raises: [EInvalidValue], tags: [].}
proc unpackPrefix(node: PNimrodNode): tuple[node: PNimrodNode, op: string] {. compileTime, raises: [EInvalidValue], tags: [].}
proc unpackInfix(node: PNimrodNode): tuple[left: PNimrodNode, op: string, right: PNimrodNode] {.compileTime, raises: [EInvalidValue], tags: [].}
proc copy(node: PNimrodNode): PNimrodNode {.compileTime, raises: [], tags: [].}
- An alias for copyNimTree().
proc eqIdent(a, b: string): bool {.raises: [], tags: [].}
- Check if two idents are identical.
proc hasArgOfName(params: PNimrodNode; name: string): bool {.compiletime, raises: [EInvalidValue], tags: [].}
- Search nnkFormalParams for an argument.
proc addIdentIfAbsent(dest: PNimrodNode; ident: string) {.compiletime, raises: [EInvalidValue], tags: [].}
- Add ident to dest if it is not present. This is intended for use with pragmas.
Iterators
iterator children(n: PNimrodNode): PNimrodNode {.inline, raises: [], tags: [].}
Macros
macro dumpTree(s: stmt): stmt {.immediate.}
-
Accepts a block of nimrod code and prints the parsed abstract syntax tree using the toTree function. Printing is done at compile time.
You can use this as a tool to explore the Nimrod's abstract syntax tree and to discover what kind of nodes must be created to represent a certain expression/statement.
macro dumpLisp(s: stmt): stmt {.immediate.}
-
Accepts a block of nimrod code and prints the parsed abstract syntax tree using the toLisp function. Printing is done at compile time.
See dumpTree.
macro dumpTreeImm(s: stmt): stmt {.immediate, deprecated.}
- The immediate version of dumpTree.
macro dumpLispImm(s: stmt): stmt {.immediate, deprecated.}
- The immediate version of dumpLisp.
Templates
template findChild(n: PNimrodNode; cond: expr): PNimrodNode {.immediate, dirty.}
template emit[](e: static[string]): stmt
-
accepts a single string argument and treats it as nimrod code that should be inserted verbatim in the program Example:
emit("echo " & '"' & "hello world".toUpper & '"')