This module contains the interface to the compiler's abstract syntax tree (AST). Macros operate on this tree.
The AST in Nim
This section describes how the AST is modelled with Nim's type system. The AST consists of nodes (NimNode) with a variable number of children. Each node has a field named kind which describes what the node contains:
type NimNodeKind = 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 NimNode = ref NimNodeObj NimNodeObj = object case kind: NimNodeKind ## the node's kind of nnkNone, nnkEmpty, nnkNilLit: discard ## 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: NimIdent ## the identifier of nnkSym: symbol: NimSymbol ## the symbol (after symbol lookup phase) else: sons: seq[NimNode] ## the node's sons (or children)
For the NimNode type, the [] operator has been overloaded: n[i] is n's i-th child.
To specify the AST for the different Nim 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.
Nim 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.
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 Nim. 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
NimNodeKind = 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, nnkDefer, nnkTryStmt, nnkFinally, nnkRaiseStmt, nnkReturnStmt, nnkBreakStmt, nnkContinueStmt, nnkBlockStmt, nnkStaticStmt, nnkDiscardStmt, nnkStmtList, nnkImportStmt, nnkImportExceptStmt, nnkExportStmt, nnkExportExceptStmt, nnkFromStmt, nnkIncludeStmt, nnkBindStmt, nnkMixinStmt, nnkUsingStmt, nnkCommentStmt, nnkStmtListExpr, nnkBlockExpr, nnkStmtListType, nnkBlockType, nnkWith, nnkWithout, nnkTypeOfExpr, nnkObjectTy, nnkTupleTy, nnkTupleClassTy, nnkTypeClassTy, nnkStaticTy, nnkRecList, nnkRecCase, nnkRecWhen, nnkRefTy, nnkPtrTy, nnkVarTy, nnkConstTy, nnkMutableTy, nnkDistinctTy, nnkProcTy, nnkIteratorTy, nnkSharedTy, nnkEnumTy, nnkEnumFieldDef, nnkArglist, nnkPattern, nnkReturnToken
- Source
NimNodeKinds = set[NimNodeKind]
- Source
NimTypeKind = enum ntyNone, ntyBool, ntyChar, ntyEmpty, ntyArrayConstr, ntyNil, ntyExpr, ntyStmt, ntyTypeDesc, ntyGenericInvocation, 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, ntyUInt, ntyUInt8, ntyUInt16, ntyUInt32, ntyUInt64, ntyBigNum, ntyConst, ntyMutable, ntyVarargs, ntyIter, ntyError, ntyBuiltinTypeClass, ntyConcept, ntyConceptInst, ntyComposite, ntyAnd, ntyOr, ntyNot
- Source
TNimTypeKinds = set[NimTypeKind]
- Source
NimSymKind = 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
- Source
TNimSymKinds = set[NimSymKind]
- Source
NimIdent = object of RootObj
- represents a Nim identifier in the AST Source
NimSym = ref NimSymObj
- represents a Nim symbol in the compiler; a symbol is a looked-up ident. Source
BindSymRule = 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 Source
Consts
nnkLiterals = {nnkCharLit..nnkNilLit}
- Source
nnkCallKinds = {nnkCall, nnkInfix, nnkPrefix, nnkPostfix, nnkCommand, nnkCallStrLit}
- Source
RoutineNodes = {nnkProcDef, nnkMethodDef, nnkDo, nnkLambda, nnkIteratorDef}
- Source
AtomicNodes = {nnkNone..nnkNilLit}
- Source
CallNodes = {nnkCall, nnkInfix, nnkPrefix, nnkPostfix, nnkCommand, nnkCallStrLit, nnkHiddenCallConv}
- Source
Procs
proc `[]`(n: NimNode; i: int): NimNode {.magic: "NChild", noSideEffect.}
- get n's i'th child. Source
proc `[]=`(n: NimNode; i: int; child: NimNode) {.magic: "NSetChild", noSideEffect.}
- set n's i'th child to child. Source
proc `!`(s: string): NimIdent {.magic: "StrToIdent", noSideEffect.}
- constructs an identifier from the string s Source
proc `$`(i: NimIdent): string {.magic: "IdentToStr", noSideEffect.}
- converts a Nim identifier to a string Source
proc `$`(s: NimSym): string {.magic: "IdentToStr", noSideEffect.}
- converts a Nim symbol to a string Source
proc `==`(a, b: NimIdent): bool {.magic: "EqIdent", noSideEffect.}
- compares two Nim identifiers Source
proc `==`(a, b: NimNode): bool {.magic: "EqNimrodNode", noSideEffect.}
- compares two Nim nodes Source
proc len(n: NimNode): int {.magic: "NLen", noSideEffect.}
- returns the number of children of n. Source
proc add(father, child: NimNode): NimNode {.magic: "NAdd", discardable, noSideEffect, locks: 0.}
- Adds the child to the father node. Returns the father node so that calls can be nested. Source
proc add(father: NimNode; children: varargs[NimNode]): NimNode {. magic: "NAddMultiple", discardable, noSideEffect, locks: 0.}
- Adds each child of children to the father node. Returns the father node so that calls can be nested. Source
proc del(father: NimNode; idx = 0; n = 1) {.magic: "NDel", noSideEffect.}
- deletes n children of father starting at index idx. Source
proc kind(n: NimNode): NimNodeKind {.magic: "NKind", noSideEffect.}
- returns the kind of the node n. Source
proc intVal(n: NimNode): BiggestInt {.magic: "NIntVal", noSideEffect.}
- Source
proc boolVal(n: NimNode): bool {.compileTime, noSideEffect, raises: [], tags: [].}
- Source
proc floatVal(n: NimNode): BiggestFloat {.magic: "NFloatVal", noSideEffect.}
- Source
proc symbol(n: NimNode): NimSym {.magic: "NSymbol", noSideEffect.}
- Source
proc ident(n: NimNode): NimIdent {.magic: "NIdent", noSideEffect.}
- Source
proc getType(n: NimNode): NimNode {.magic: "NGetType", noSideEffect.}
- with 'getType' you can access the node's type. A Nim type is mapped to a Nim AST too, so it's slightly confusing but it means the same API can be used to traverse types. Recursive types are flattened for you so there is no danger of infinite recursions during traversal. To resolve recursive types, you have to call 'getType' again. To see what kind of type it is, call typeKind on getType's result. Source
proc typeKind(n: NimNode): NimTypeKind {.magic: "NGetType", noSideEffect.}
- Returns the type kind of the node 'n' that should represent a type, that means the node should have been obtained via getType. Source
proc strVal(n: NimNode): string {.magic: "NStrVal", noSideEffect.}
- Source
proc intVal=(n: NimNode; val: BiggestInt) {.magic: "NSetIntVal", noSideEffect.}
- Source
proc floatVal=(n: NimNode; val: BiggestFloat) {.magic: "NSetFloatVal", noSideEffect.}
- Source
proc symbol=(n: NimNode; val: NimSym) {.magic: "NSetSymbol", noSideEffect.}
- Source
proc ident=(n: NimNode; val: NimIdent) {.magic: "NSetIdent", noSideEffect.}
- Source
proc strVal=(n: NimNode; val: string) {.magic: "NSetStrVal", noSideEffect.}
- Source
proc newNimNode(kind: NimNodeKind; n: NimNode = nil): NimNode {. magic: "NNewNimNode", noSideEffect.}
- Source
proc copyNimNode(n: NimNode): NimNode {.magic: "NCopyNimNode", noSideEffect.}
- Source
proc copyNimTree(n: NimNode): NimNode {.magic: "NCopyNimTree", noSideEffect.}
- Source
proc error(msg: string) {.magic: "NError", gcsafe, locks: 0.}
- writes an error message at compile time Source
proc warning(msg: string) {.magic: "NWarning", gcsafe, locks: 0.}
- writes a warning message at compile time Source
proc hint(msg: string) {.magic: "NHint", gcsafe, locks: 0.}
- writes a hint message at compile time Source
proc newStrLitNode(s: string): NimNode {.compileTime, noSideEffect, raises: [], tags: [].}
- creates a string literal node from s Source
proc newIntLitNode(i: BiggestInt): NimNode {.compileTime, raises: [], tags: [].}
- creates a int literal node from i Source
proc newFloatLitNode(f: BiggestFloat): NimNode {.compileTime, raises: [], tags: [].}
- creates a float literal node from f Source
proc newIdentNode(i: NimIdent): NimNode {.compileTime, raises: [], tags: [].}
- creates an identifier node from i Source
proc newIdentNode(i: string): NimNode {.compileTime, raises: [], tags: [].}
- creates an identifier node from i Source
proc bindSym(ident: string; rule: BindSymRule = brClosed): NimNode {. magic: "NBindSym", noSideEffect.}
- 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. Source
proc genSym(kind: NimSymKind = nskLet; ident = ""): NimNode {.magic: "NGenSym", noSideEffect.}
- generates a fresh symbol that is guaranteed to be unique. The symbol needs to occur in a declaration context. Source
proc callsite(): NimNode {.magic: "NCallSite", gcsafe, locks: 0.}
- returns the AST of the invocation expression that invoked this macro. Source
proc toStrLit(n: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- converts the AST n to the concrete Nim code and wraps that in a string literal node Source
proc lineinfo(n: NimNode): string {.magic: "NLineInfo", noSideEffect.}
- returns the position the node appears in the original source file in the form filename(line, col) Source
proc internalErrorFlag(): string {.magic: "NError", noSideEffect.}
- Some builtins set an error flag. This is then turned into a proper exception. Note: Ordinary application code should not call this. Source
proc parseExpr(s: string): NimNode {.noSideEffect, compileTime, raises: [ValueError], tags: [].}
- Compiles the passed string to its AST representation. Expects a single expression. Raises ValueError for parsing errors. Source
proc parseStmt(s: string): NimNode {.noSideEffect, compileTime, raises: [ValueError], tags: [].}
- Compiles the passed string to its AST representation. Expects one or more statements. Raises ValueError for parsing errors. Source
proc getAst[expr](macroOrTemplate: expr): NimNode {.magic: "ExpandToAst", noSideEffect.}
-
Obtains the AST nodes returned from a macro or template invocation. Example:
macro FooMacro() = var ast = getAst(BarTemplate())
Source proc quote(bl: stmt; op = "``"): NimNode {.magic: "QuoteAst", noSideEffect.}
-
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 NimNode 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`
Source proc expectKind(n: NimNode; k: NimNodeKind) {.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. Source
proc expectMinLen(n: NimNode; 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. Source
proc expectLen(n: NimNode; 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. Source
proc newTree(kind: NimNodeKind; children: varargs[NimNode]): NimNode {. compileTime, raises: [], tags: [].}
- produces a new node with children. Source
proc newCall(theProc: NimNode; args: varargs[NimNode]): NimNode {.compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..]. Source
proc newCall(theProc: NimIdent; args: varargs[NimNode]): NimNode {.compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..]. Source
proc newCall(theProc: string; args: varargs[NimNode]): NimNode {.compileTime, raises: [], tags: [].}
- produces a new call node. theProc is the proc that is called with the arguments args[0..]. Source
proc newLit(c: char): NimNode {.compileTime, raises: [], tags: [].}
- produces a new character literal node. Source
proc newLit(i: BiggestInt): NimNode {.compileTime, raises: [], tags: [].}
- produces a new integer literal node. Source
proc newLit(b: bool): NimNode {.compileTime, raises: [], tags: [].}
- produces a new boolean literal node. Source
proc newLit(f: BiggestFloat): NimNode {.compileTime, raises: [], tags: [].}
- produces a new float literal node. Source
proc newLit(s: string): NimNode {.compileTime, raises: [], tags: [].}
- produces a new string literal node. Source
proc nestList(theProc: NimIdent; x: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- nests the list x into a tree of call expressions: [a, b, c] is transformed into theProc(a, theProc(c, d)). Source
proc treeRepr(n: NimNode): string {.compileTime, gcsafe, locks: 0, raises: [], tags: [].}
-
Convert the AST n to a human-readable tree-like string.
See also repr and lispRepr.
Source proc lispRepr(n: NimNode): string {.compileTime, gcsafe, locks: 0, raises: [], tags: [].}
-
Convert the AST n to a human-readable lisp-like string,
See also repr and treeRepr.
Source proc newEmptyNode(): NimNode {.compileTime, noSideEffect, raises: [], tags: [].}
- Create a new empty node Source
proc newStmtList(stmts: varargs[NimNode]): NimNode {.compileTime, raises: [], tags: [].}
- Create a new statement list Source
proc newPar(exprs: varargs[NimNode]): NimNode {.compileTime, raises: [], tags: [].}
- Create a new parentheses-enclosed expression Source
proc newBlockStmt(label, body: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Create a new block statement with label Source
proc newBlockStmt(body: NimNode): NimNode {.compiletime, raises: [], tags: [].}
- Create a new block: stmt Source
proc newVarStmt(name, value: NimNode): NimNode {.compiletime, raises: [], tags: [].}
- Create a new var stmt Source
proc newLetStmt(name, value: NimNode): NimNode {.compiletime, raises: [], tags: [].}
- Create a new let stmt Source
proc newConstStmt(name, value: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Create a new const stmt Source
proc newAssignment(lhs, rhs: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc newDotExpr(a, b: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Create new dot expression a.dot(b) -> a.b Source
proc newColonExpr(a, b: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Create new colon expression newColonExpr(a, b) -> a: b Source
proc newIdentDefs(name, kind: NimNode; default = newEmptyNode()): NimNode {. compileTime, raises: [], tags: [].}
-
Creates a new nnkIdentDefs node of a specific kind and value.
nnkIdentDefs need to have at least three children, but they can have more: first comes a list of identifiers followed by a type and value nodes. This helper proc creates a three node subtree, the first subnode being a single identifier name. Both the kind node and default (value) nodes may be empty depending on where the nnkIdentDefs appears: tuple or object definitions will have an empty default node, let or var blocks may have an empty kind node if the identifier is being assigned a value. Example:
var varSection = newNimNode(nnkVarSection).add( newIdentDefs(ident("a"), ident("string")), newIdentDefs(ident("b"), newEmptyNode(), newLit(3))) # --> var # a: string # b = 3
If you need to create multiple identifiers you need to use the lower level newNimNode:
result = newNimNode(nnkIdentDefs).add( ident("a"), ident("b"), ident("c"), ident("string"), newStrLitNode("Hello"))
Source proc newNilLit(): NimNode {.compileTime, raises: [], tags: [].}
- New nil literal shortcut Source
proc high(node: NimNode): int {.compileTime, raises: [], tags: [].}
- Return the highest index available for a node Source
proc last(node: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Return the last item in nodes children. Same as node[node.high()] Source
proc expectKind(n: NimNode; k: set[NimNodeKind]) {.compileTime, raises: [], tags: [].}
- Source
proc newProc(name = newEmptyNode(); params: openArray[NimNode] = [newEmptyNode()]; body: NimNode = newStmtList(); procType = nnkProcDef): NimNode {. 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.
Source proc newIfStmt(branches: varargs[tuple[cond, body: NimNode]]): NimNode {. compiletime, raises: [], tags: [].}
-
Constructor for if statements.
newIfStmt( (Ident, StmtList), ... )
Source proc copyChildrenTo(src, dest: NimNode) {.compileTime, raises: [], tags: [].}
- Copy all children from src to dest Source
proc name(someProc: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc name=(someProc: NimNode; val: NimNode) {.compileTime, raises: [], tags: [].}
- Source
proc params(someProc: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc params=(someProc: NimNode; params: NimNode) {.compileTime, raises: [], tags: [].}
- Source
proc pragma(someProc: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Get the pragma of a proc type These will be expanded Source
proc pragma=(someProc: NimNode; val: NimNode) {.compileTime, raises: [], tags: [].}
- Set the pragma of a proc type Source
proc body(someProc: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc body=(someProc: NimNode; val: NimNode) {.compileTime, raises: [], tags: [].}
- Source
proc `$`(node: NimNode): string {.compileTime, raises: [Exception], tags: [RootEffect].}
- Get the string of an identifier node Source
proc ident(name: string): NimNode {.compileTime, inline, raises: [], tags: [].}
- Create a new ident node from a string Source
proc insert(a: NimNode; pos: int; b: NimNode) {.compileTime, raises: [], tags: [].}
- Insert node B into A at pos Source
proc basename(a: NimNode): NimNode {.compiletime, gcsafe, locks: 0, raises: [], tags: [].}
- Pull an identifier from prefix/postfix expressions Source
proc basename=(a: NimNode; val: string) {.compileTime, raises: [], tags: [].}
- Source
proc postfix(node: NimNode; op: string): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc prefix(node: NimNode; op: string): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc infix(a: NimNode; op: string; b: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- Source
proc unpackPostfix(node: NimNode): tuple[node: NimNode, op: string] {. compileTime, raises: [Exception], tags: [RootEffect].}
- Source
proc unpackPrefix(node: NimNode): tuple[node: NimNode, op: string] {. compileTime, raises: [Exception], tags: [RootEffect].}
- Source
proc unpackInfix(node: NimNode): tuple[left: NimNode, op: string, right: NimNode] {. compileTime, raises: [Exception], tags: [RootEffect].}
- Source
proc copy(node: NimNode): NimNode {.compileTime, raises: [], tags: [].}
- An alias for copyNimTree(). Source
proc eqIdent(a, b: string): bool {.raises: [], tags: [].}
- Check if two idents are identical. Source
proc hasArgOfName(params: NimNode; name: string): bool {.compiletime, raises: [Exception], tags: [RootEffect].}
- Search nnkFormalParams for an argument. Source
proc addIdentIfAbsent(dest: NimNode; ident: string) {.compiletime, raises: [Exception], tags: [RootEffect].}
- Add ident to dest if it is not present. This is intended for use with pragmas. Source
Macros
macro dumpTree(s: stmt): stmt {.immediate.}
-
Accepts a block of nim 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.
Source macro dumpLisp(s: stmt): stmt {.immediate.}
-
Accepts a block of nim code and prints the parsed abstract syntax tree using the toLisp function. Printing is done at compile time.
See dumpTree.
Source macro dumpTreeImm(s: stmt): stmt {.immediate, deprecated.}
- The immediate version of dumpTree. Source
macro dumpLispImm(s: stmt): stmt {.immediate, deprecated.}
- The immediate version of dumpLisp. Source