summary refs log tree commit diff stats
diff options
context:
space:
mode:
authorAndreas Rumpf <rumpf_a@web.de>2024-03-18 20:27:00 +0100
committerGitHub <noreply@github.com>2024-03-18 20:27:00 +0100
commit6c4c60eade66e45448a220f4c8a91f866b76baf7 (patch)
treeed9d6bf6c2f87225bc045bec55731a8f720b6265
parentcbf48a253f134dea5cc8d8b2393b7bf6310cc8fe (diff)
downloadNim-6c4c60eade66e45448a220f4c8a91f866b76baf7.tar.gz
Adds support for custom ASTs in the Nim parser (#23417)
-rw-r--r--compiler/ast.nim242
-rw-r--r--compiler/nodekinds.nim210
-rw-r--r--compiler/parser.nim104
-rw-r--r--compiler/plugins/customast.nim136
-rw-r--r--compiler/plugins/plugins.nimble0
-rw-r--r--lib/pure/pegs.nim2
6 files changed, 449 insertions, 245 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 431740543..ada4b6665 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -20,6 +20,9 @@ when defined(nimPreviewSlimSystem):
 
 export int128
 
+import nodekinds
+export nodekinds
+
 type
   TCallingConvention* = enum
     ccNimCall = "nimcall"           # nimcall, also the default
@@ -34,202 +37,6 @@ type
     ccClosure  = "closure"          # proc has a closure
     ccNoConvention = "noconv"       # needed for generating proper C procs sometimes
 
-type
-  TNodeKind* = enum # order is extremely important, because ranges are used
-                    # to check whether a node belongs to a certain class
-    nkNone,               # unknown node kind: indicates an error
-                          # Expressions:
-                          # Atoms:
-    nkEmpty,              # the node is empty
-    nkIdent,              # node is an identifier
-    nkSym,                # node is a symbol
-    nkType,               # node is used for its typ field
-
-    nkCharLit,            # a character literal ''
-    nkIntLit,             # an integer literal
-    nkInt8Lit,
-    nkInt16Lit,
-    nkInt32Lit,
-    nkInt64Lit,
-    nkUIntLit,            # an unsigned integer literal
-    nkUInt8Lit,
-    nkUInt16Lit,
-    nkUInt32Lit,
-    nkUInt64Lit,
-    nkFloatLit,           # a floating point literal
-    nkFloat32Lit,
-    nkFloat64Lit,
-    nkFloat128Lit,
-    nkStrLit,             # a string literal ""
-    nkRStrLit,            # a raw string literal r""
-    nkTripleStrLit,       # a triple string literal """
-    nkNilLit,             # the nil literal
-                          # end of atoms
-    nkComesFrom,          # "comes from" template/macro information for
-                          # better stack trace generation
-    nkDotCall,            # used to temporarily flag a nkCall node;
-                          # this is used
-                          # for transforming ``s.len`` to ``len(s)``
-
-    nkCommand,            # a call like ``p 2, 4`` without parenthesis
-    nkCall,               # a call like p(x, y) or an operation like +(a, b)
-    nkCallStrLit,         # a call with a string literal
-                          # x"abc" has two sons: nkIdent, nkRStrLit
-                          # x"""abc""" has two sons: nkIdent, nkTripleStrLit
-    nkInfix,              # a call like (a + b)
-    nkPrefix,             # a call like !a
-    nkPostfix,            # something like a! (also used for visibility)
-    nkHiddenCallConv,     # an implicit type conversion via a type converter
-
-    nkExprEqExpr,         # a named parameter with equals: ''expr = expr''
-    nkExprColonExpr,      # a named parameter with colon: ''expr: expr''
-    nkIdentDefs,          # a definition like `a, b: typeDesc = expr`
-                          # either typeDesc or expr may be nil; used in
-                          # formal parameters, var statements, etc.
-    nkVarTuple,           # a ``var (a, b) = expr`` construct
-    nkPar,                # syntactic (); may be a tuple constructor
-    nkObjConstr,          # object constructor: T(a: 1, b: 2)
-    nkCurly,              # syntactic {}
-    nkCurlyExpr,          # an expression like a{i}
-    nkBracket,            # syntactic []
-    nkBracketExpr,        # an expression like a[i..j, k]
-    nkPragmaExpr,         # an expression like a{.pragmas.}
-    nkRange,              # an expression like i..j
-    nkDotExpr,            # a.b
-    nkCheckedFieldExpr,   # a.b, but b is a field that needs to be checked
-    nkDerefExpr,          # a^
-    nkIfExpr,             # if as an expression
-    nkElifExpr,
-    nkElseExpr,
-    nkLambda,             # lambda expression
-    nkDo,                 # lambda block appering as trailing proc param
-    nkAccQuoted,          # `a` as a node
-
-    nkTableConstr,        # a table constructor {expr: expr}
-    nkBind,               # ``bind expr`` node
-    nkClosedSymChoice,    # symbol choice node; a list of nkSyms (closed)
-    nkOpenSymChoice,      # symbol choice node; a list of nkSyms (open)
-    nkHiddenStdConv,      # an implicit standard type conversion
-    nkHiddenSubConv,      # an implicit type conversion from a subtype
-                          # to a supertype
-    nkConv,               # a type conversion
-    nkCast,               # a type cast
-    nkStaticExpr,         # a static expr
-    nkAddr,               # a addr expression
-    nkHiddenAddr,         # implicit address operator
-    nkHiddenDeref,        # implicit ^ operator
-    nkObjDownConv,        # down conversion between object types
-    nkObjUpConv,          # up conversion between object types
-    nkChckRangeF,         # range check for floats
-    nkChckRange64,        # range check for 64 bit ints
-    nkChckRange,          # range check for ints
-    nkStringToCString,    # string to cstring
-    nkCStringToString,    # cstring to string
-                          # end of expressions
-
-    nkAsgn,               # a = b
-    nkFastAsgn,           # internal node for a fast ``a = b``
-                          # (no string copy)
-    nkGenericParams,      # generic parameters
-    nkFormalParams,       # formal parameters
-    nkOfInherit,          # inherited from symbol
-
-    nkImportAs,           # a 'as' b in an import statement
-    nkProcDef,            # a proc
-    nkMethodDef,          # a method
-    nkConverterDef,       # a converter
-    nkMacroDef,           # a macro
-    nkTemplateDef,        # a template
-    nkIteratorDef,        # an iterator
-
-    nkOfBranch,           # used inside case statements
-                          # for (cond, action)-pairs
-    nkElifBranch,         # used in if statements
-    nkExceptBranch,       # an except section
-    nkElse,               # an else part
-    nkAsmStmt,            # an assembler block
-    nkPragma,             # a pragma statement
-    nkPragmaBlock,        # a pragma with a block
-    nkIfStmt,             # an if statement
-    nkWhenStmt,           # a when expression or statement
-    nkForStmt,            # a for statement
-    nkParForStmt,         # a parallel for statement
-    nkWhileStmt,          # a while statement
-    nkCaseStmt,           # a case statement
-    nkTypeSection,        # a type section (consists of type definitions)
-    nkVarSection,         # a var section
-    nkLetSection,         # a let section
-    nkConstSection,       # a const section
-    nkConstDef,           # a const definition
-    nkTypeDef,            # a type definition
-    nkYieldStmt,          # the yield statement as a tree
-    nkDefer,              # the 'defer' statement
-    nkTryStmt,            # a try statement
-    nkFinally,            # a finally section
-    nkRaiseStmt,          # a raise statement
-    nkReturnStmt,         # a return statement
-    nkBreakStmt,          # a break statement
-    nkContinueStmt,       # a continue statement
-    nkBlockStmt,          # a block statement
-    nkStaticStmt,         # a static statement
-    nkDiscardStmt,        # a discard statement
-    nkStmtList,           # a list of statements
-    nkImportStmt,         # an import statement
-    nkImportExceptStmt,   # an import x except a statement
-    nkExportStmt,         # an export statement
-    nkExportExceptStmt,   # an 'export except' statement
-    nkFromStmt,           # a from * import statement
-    nkIncludeStmt,        # an include statement
-    nkBindStmt,           # a bind statement
-    nkMixinStmt,          # a mixin statement
-    nkUsingStmt,          # an using statement
-    nkCommentStmt,        # a comment statement
-    nkStmtListExpr,       # a statement list followed by an expr; this is used
-                          # to allow powerful multi-line templates
-    nkBlockExpr,          # a statement block ending in an expr; this is used
-                          # to allow powerful multi-line templates that open a
-                          # temporary scope
-    nkStmtListType,       # a statement list ending in a type; for macros
-    nkBlockType,          # a statement block ending in a type; for macros
-                          # types as syntactic trees:
-
-    nkWith,               # distinct with `foo`
-    nkWithout,            # distinct without `foo`
-
-    nkTypeOfExpr,         # type(1+2)
-    nkObjectTy,           # object body
-    nkTupleTy,            # tuple body
-    nkTupleClassTy,       # tuple type class
-    nkTypeClassTy,        # user-defined type class
-    nkStaticTy,           # ``static[T]``
-    nkRecList,            # list of object parts
-    nkRecCase,            # case section of object
-    nkRecWhen,            # when section of object
-    nkRefTy,              # ``ref T``
-    nkPtrTy,              # ``ptr T``
-    nkVarTy,              # ``var T``
-    nkConstTy,            # ``const T``
-    nkOutTy,              # ``out T``
-    nkDistinctTy,         # distinct type
-    nkProcTy,             # proc type
-    nkIteratorTy,         # iterator type
-    nkSinkAsgn,           # '=sink(x, y)'
-    nkEnumTy,             # enum body
-    nkEnumFieldDef,       # `ident = expr` in an enumeration
-    nkArgList,            # argument list
-    nkPattern,            # a special pattern; used for matching
-    nkHiddenTryStmt,      # a hidden try statement
-    nkClosure,            # (prc, env)-pair (internally used for code gen)
-    nkGotoState,          # used for the state machine (for iterators)
-    nkState,              # give a label to a code section (for iterators)
-    nkBreakState,         # special break statement for easier code generation
-    nkFuncDef,            # a func
-    nkTupleConstr         # a tuple constructor
-    nkError               # erroneous AST node
-    nkModuleRef           # for .rod file support: A (moduleId, itemId) pair
-    nkReplayAction        # for .rod file support: A replay action
-    nkNilRodNode          # for .rod file support: a 'nil' PNode
-
   TNodeKinds* = set[TNodeKind]
 
 type
@@ -1090,8 +897,6 @@ const
 
   nfAllFieldsSet* = nfBase2
 
-  nkCallKinds* = {nkCall, nkInfix, nkPrefix, nkPostfix,
-                  nkCommand, nkCallStrLit, nkHiddenCallConv}
   nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice,
                    nkClosedSymChoice}
 
@@ -1328,6 +1133,33 @@ proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
   result.info = info
   result.typ = typ
 
+proc newNode*(kind: TNodeKind, info: TLineInfo): PNode =
+  ## new node with line info, no type, and no children
+  newNodeImpl(info)
+  setIdMaybe()
+
+proc newAtom*(ident: PIdent, info: TLineInfo): PNode =
+  result = newNode(nkIdent, info)
+  result.ident = ident
+
+proc newAtom*(kind: TNodeKind, intVal: BiggestInt, info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.intVal = intVal
+
+proc newAtom*(kind: TNodeKind, floatVal: BiggestFloat, info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.floatVal = floatVal
+
+proc newAtom*(kind: TNodeKind; strVal: sink string; info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.strVal = strVal
+
+proc newTree*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode =
+  result = newNodeI(kind, info)
+  if children.len > 0:
+    result.info = children[0].info
+  result.sons = @children
+
 proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode =
   result = newNode(kind)
   if children.len > 0:
@@ -1463,6 +1295,20 @@ proc newIntNode*(kind: TNodeKind, intVal: Int128): PNode =
   result.intVal = castToInt64(intVal)
 
 proc lastSon*(n: PNode): PNode {.inline.} = n.sons[^1]
+template setLastSon*(n: PNode, s: PNode) = n.sons[^1] = s
+
+template firstSon*(n: PNode): PNode = n.sons[0]
+template secondSon*(n: PNode): PNode = n.sons[1]
+
+template hasSon*(n: PNode): bool = n.len > 0
+template has2Sons*(n: PNode): bool = n.len > 1
+
+proc replaceFirstSon*(n, newson: PNode) {.inline.} =
+  n.sons[0] = newson
+
+proc replaceSon*(n: PNode; i: int; newson: PNode) {.inline.} =
+  n.sons[i] = newson
+
 proc last*(n: PType): PType {.inline.} = n.sons[^1]
 
 proc elementType*(n: PType): PType {.inline.} = n.sons[^1]
diff --git a/compiler/nodekinds.nim b/compiler/nodekinds.nim
new file mode 100644
index 000000000..98ae9405d
--- /dev/null
+++ b/compiler/nodekinds.nim
@@ -0,0 +1,210 @@
+#
+#
+#           The Nim Compiler
+#        (c) Copyright 2015 Andreas Rumpf
+#
+#    See the file "copying.txt", included in this
+#    distribution, for details about the copyright.
+#
+
+## NodeKind enum.
+
+type
+  TNodeKind* = enum # order is extremely important, because ranges are used
+                    # to check whether a node belongs to a certain class
+    nkNone,               # unknown node kind: indicates an error
+                          # Expressions:
+                          # Atoms:
+    nkEmpty,              # the node is empty
+    nkIdent,              # node is an identifier
+    nkSym,                # node is a symbol
+    nkType,               # node is used for its typ field
+
+    nkCharLit,            # a character literal ''
+    nkIntLit,             # an integer literal
+    nkInt8Lit,
+    nkInt16Lit,
+    nkInt32Lit,
+    nkInt64Lit,
+    nkUIntLit,            # an unsigned integer literal
+    nkUInt8Lit,
+    nkUInt16Lit,
+    nkUInt32Lit,
+    nkUInt64Lit,
+    nkFloatLit,           # a floating point literal
+    nkFloat32Lit,
+    nkFloat64Lit,
+    nkFloat128Lit,
+    nkStrLit,             # a string literal ""
+    nkRStrLit,            # a raw string literal r""
+    nkTripleStrLit,       # a triple string literal """
+    nkNilLit,             # the nil literal
+                          # end of atoms
+    nkComesFrom,          # "comes from" template/macro information for
+                          # better stack trace generation
+    nkDotCall,            # used to temporarily flag a nkCall node;
+                          # this is used
+                          # for transforming ``s.len`` to ``len(s)``
+
+    nkCommand,            # a call like ``p 2, 4`` without parenthesis
+    nkCall,               # a call like p(x, y) or an operation like +(a, b)
+    nkCallStrLit,         # a call with a string literal
+                          # x"abc" has two sons: nkIdent, nkRStrLit
+                          # x"""abc""" has two sons: nkIdent, nkTripleStrLit
+    nkInfix,              # a call like (a + b)
+    nkPrefix,             # a call like !a
+    nkPostfix,            # something like a! (also used for visibility)
+    nkHiddenCallConv,     # an implicit type conversion via a type converter
+
+    nkExprEqExpr,         # a named parameter with equals: ''expr = expr''
+    nkExprColonExpr,      # a named parameter with colon: ''expr: expr''
+    nkIdentDefs,          # a definition like `a, b: typeDesc = expr`
+                          # either typeDesc or expr may be nil; used in
+                          # formal parameters, var statements, etc.
+    nkVarTuple,           # a ``var (a, b) = expr`` construct
+    nkPar,                # syntactic (); may be a tuple constructor
+    nkObjConstr,          # object constructor: T(a: 1, b: 2)
+    nkCurly,              # syntactic {}
+    nkCurlyExpr,          # an expression like a{i}
+    nkBracket,            # syntactic []
+    nkBracketExpr,        # an expression like a[i..j, k]
+    nkPragmaExpr,         # an expression like a{.pragmas.}
+    nkRange,              # an expression like i..j
+    nkDotExpr,            # a.b
+    nkCheckedFieldExpr,   # a.b, but b is a field that needs to be checked
+    nkDerefExpr,          # a^
+    nkIfExpr,             # if as an expression
+    nkElifExpr,
+    nkElseExpr,
+    nkLambda,             # lambda expression
+    nkDo,                 # lambda block appering as trailing proc param
+    nkAccQuoted,          # `a` as a node
+
+    nkTableConstr,        # a table constructor {expr: expr}
+    nkBind,               # ``bind expr`` node
+    nkClosedSymChoice,    # symbol choice node; a list of nkSyms (closed)
+    nkOpenSymChoice,      # symbol choice node; a list of nkSyms (open)
+    nkHiddenStdConv,      # an implicit standard type conversion
+    nkHiddenSubConv,      # an implicit type conversion from a subtype
+                          # to a supertype
+    nkConv,               # a type conversion
+    nkCast,               # a type cast
+    nkStaticExpr,         # a static expr
+    nkAddr,               # a addr expression
+    nkHiddenAddr,         # implicit address operator
+    nkHiddenDeref,        # implicit ^ operator
+    nkObjDownConv,        # down conversion between object types
+    nkObjUpConv,          # up conversion between object types
+    nkChckRangeF,         # range check for floats
+    nkChckRange64,        # range check for 64 bit ints
+    nkChckRange,          # range check for ints
+    nkStringToCString,    # string to cstring
+    nkCStringToString,    # cstring to string
+                          # end of expressions
+
+    nkAsgn,               # a = b
+    nkFastAsgn,           # internal node for a fast ``a = b``
+                          # (no string copy)
+    nkGenericParams,      # generic parameters
+    nkFormalParams,       # formal parameters
+    nkOfInherit,          # inherited from symbol
+
+    nkImportAs,           # a 'as' b in an import statement
+    nkProcDef,            # a proc
+    nkMethodDef,          # a method
+    nkConverterDef,       # a converter
+    nkMacroDef,           # a macro
+    nkTemplateDef,        # a template
+    nkIteratorDef,        # an iterator
+
+    nkOfBranch,           # used inside case statements
+                          # for (cond, action)-pairs
+    nkElifBranch,         # used in if statements
+    nkExceptBranch,       # an except section
+    nkElse,               # an else part
+    nkAsmStmt,            # an assembler block
+    nkPragma,             # a pragma statement
+    nkPragmaBlock,        # a pragma with a block
+    nkIfStmt,             # an if statement
+    nkWhenStmt,           # a when expression or statement
+    nkForStmt,            # a for statement
+    nkParForStmt,         # a parallel for statement
+    nkWhileStmt,          # a while statement
+    nkCaseStmt,           # a case statement
+    nkTypeSection,        # a type section (consists of type definitions)
+    nkVarSection,         # a var section
+    nkLetSection,         # a let section
+    nkConstSection,       # a const section
+    nkConstDef,           # a const definition
+    nkTypeDef,            # a type definition
+    nkYieldStmt,          # the yield statement as a tree
+    nkDefer,              # the 'defer' statement
+    nkTryStmt,            # a try statement
+    nkFinally,            # a finally section
+    nkRaiseStmt,          # a raise statement
+    nkReturnStmt,         # a return statement
+    nkBreakStmt,          # a break statement
+    nkContinueStmt,       # a continue statement
+    nkBlockStmt,          # a block statement
+    nkStaticStmt,         # a static statement
+    nkDiscardStmt,        # a discard statement
+    nkStmtList,           # a list of statements
+    nkImportStmt,         # an import statement
+    nkImportExceptStmt,   # an import x except a statement
+    nkExportStmt,         # an export statement
+    nkExportExceptStmt,   # an 'export except' statement
+    nkFromStmt,           # a from * import statement
+    nkIncludeStmt,        # an include statement
+    nkBindStmt,           # a bind statement
+    nkMixinStmt,          # a mixin statement
+    nkUsingStmt,          # an using statement
+    nkCommentStmt,        # a comment statement
+    nkStmtListExpr,       # a statement list followed by an expr; this is used
+                          # to allow powerful multi-line templates
+    nkBlockExpr,          # a statement block ending in an expr; this is used
+                          # to allow powerful multi-line templates that open a
+                          # temporary scope
+    nkStmtListType,       # a statement list ending in a type; for macros
+    nkBlockType,          # a statement block ending in a type; for macros
+                          # types as syntactic trees:
+
+    nkWith,               # distinct with `foo`
+    nkWithout,            # distinct without `foo`
+
+    nkTypeOfExpr,         # type(1+2)
+    nkObjectTy,           # object body
+    nkTupleTy,            # tuple body
+    nkTupleClassTy,       # tuple type class
+    nkTypeClassTy,        # user-defined type class
+    nkStaticTy,           # ``static[T]``
+    nkRecList,            # list of object parts
+    nkRecCase,            # case section of object
+    nkRecWhen,            # when section of object
+    nkRefTy,              # ``ref T``
+    nkPtrTy,              # ``ptr T``
+    nkVarTy,              # ``var T``
+    nkConstTy,            # ``const T``
+    nkOutTy,              # ``out T``
+    nkDistinctTy,         # distinct type
+    nkProcTy,             # proc type
+    nkIteratorTy,         # iterator type
+    nkSinkAsgn,           # '=sink(x, y)'
+    nkEnumTy,             # enum body
+    nkEnumFieldDef,       # `ident = expr` in an enumeration
+    nkArgList,            # argument list
+    nkPattern,            # a special pattern; used for matching
+    nkHiddenTryStmt,      # a hidden try statement
+    nkClosure,            # (prc, env)-pair (internally used for code gen)
+    nkGotoState,          # used for the state machine (for iterators)
+    nkState,              # give a label to a code section (for iterators)
+    nkBreakState,         # special break statement for easier code generation
+    nkFuncDef,            # a func
+    nkTupleConstr         # a tuple constructor
+    nkError               # erroneous AST node
+    nkModuleRef           # for .rod file support: A (moduleId, itemId) pair
+    nkReplayAction        # for .rod file support: A replay action
+    nkNilRodNode          # for .rod file support: a 'nil' PNode
+
+const
+  nkCallKinds* = {nkCall, nkInfix, nkPrefix, nkPostfix,
+                  nkCommand, nkCallStrLit, nkHiddenCallConv}
diff --git a/compiler/parser.nim b/compiler/parser.nim
index b261e584f..eb7b8c289 100644
--- a/compiler/parser.nim
+++ b/compiler/parser.nim
@@ -49,9 +49,14 @@ when isMainModule or defined(nimTestGrammar):
     checkGrammarFile()
 
 import
-  llstream, lexer, idents, ast, msgs, options, lineinfos,
+  llstream, lexer, idents, msgs, options, lineinfos,
   pathutils
 
+when not defined(nimCustomAst):
+  import ast
+else:
+  import plugins / customast
+
 import std/strutils
 
 when defined(nimpretty):
@@ -73,7 +78,8 @@ type
     bufposPrevious*: int
     inPragma*: int            # Pragma level
     inSemiStmtList*: int
-    emptyNode: PNode
+    when not defined(nimCustomAst):
+      emptyNode: PNode
     when defined(nimpretty):
       em*: Emitter
 
@@ -83,6 +89,10 @@ type
   PrimaryMode = enum
     pmNormal, pmTypeDesc, pmTypeDef, pmTrySimple
 
+when defined(nimCustomAst):
+  # For the `customast` version we cannot share nodes, not even empty nodes:
+  template emptyNode(p: Parser): PNode = newNode(nkEmpty)
+
 # helpers for the other parsers
 proc isOperator*(tok: Token): bool
 proc getTok*(p: var Parser)
@@ -91,7 +101,7 @@ proc skipComment*(p: var Parser, node: PNode)
 proc newNodeP*(kind: TNodeKind, p: Parser): PNode
 proc newIntNodeP*(kind: TNodeKind, intVal: BiggestInt, p: Parser): PNode
 proc newFloatNodeP*(kind: TNodeKind, floatVal: BiggestFloat, p: Parser): PNode
-proc newStrNodeP*(kind: TNodeKind, strVal: string, p: Parser): PNode
+proc newStrNodeP*(kind: TNodeKind, strVal: sink string, p: Parser): PNode
 proc newIdentNodeP*(ident: PIdent, p: Parser): PNode
 proc expectIdentOrKeyw*(p: Parser)
 proc expectIdent*(p: Parser)
@@ -146,7 +156,8 @@ proc openParser*(p: var Parser, fileIdx: FileIndex, inputStream: PLLStream,
     openEmitter(p.em, cache, config, fileIdx)
   getTok(p)                   # read the first token
   p.firstTok = true
-  p.emptyNode = newNode(nkEmpty)
+  when not defined(nimCustomAst):
+    p.emptyNode = newNode(nkEmpty)
 
 proc openParser*(p: var Parser, filename: AbsoluteFile, inputStream: PLLStream,
                  cache: IdentCache; config: ConfigRef) =
@@ -261,24 +272,20 @@ proc indAndComment(p: var Parser, n: PNode, maybeMissEquals = false) =
     skipComment(p, n)
 
 proc newNodeP(kind: TNodeKind, p: Parser): PNode =
-  result = newNodeI(kind, parLineInfo(p))
+  result = newNode(kind, parLineInfo(p))
 
 proc newIntNodeP(kind: TNodeKind, intVal: BiggestInt, p: Parser): PNode =
-  result = newNodeP(kind, p)
-  result.intVal = intVal
+  result = newAtom(kind, intVal, parLineInfo(p))
 
 proc newFloatNodeP(kind: TNodeKind, floatVal: BiggestFloat,
                    p: Parser): PNode =
-  result = newNodeP(kind, p)
-  result.floatVal = floatVal
+  result = newAtom(kind, floatVal, parLineInfo(p))
 
-proc newStrNodeP(kind: TNodeKind, strVal: string, p: Parser): PNode =
-  result = newNodeP(kind, p)
-  result.strVal = strVal
+proc newStrNodeP(kind: TNodeKind, strVal: sink string, p: Parser): PNode =
+  result = newAtom(kind, strVal, parLineInfo(p))
 
 proc newIdentNodeP(ident: PIdent, p: Parser): PNode =
-  result = newNodeP(nkIdent, p)
-  result.ident = ident
+  result = newAtom(ident, parLineInfo(p))
 
 proc parseExpr(p: var Parser): PNode
 proc parseStmt(p: var Parser): PNode
@@ -381,7 +388,7 @@ proc parseSymbol(p: var Parser, mode = smNormal): PNode =
     while true:
       case p.tok.tokType
       of tkAccent:
-        if result.len == 0:
+        if not result.hasSon:
           parMessage(p, errIdentifierExpected, p.tok)
         break
       of tkOpr, tkDot, tkDotDot, tkEquals, tkParLe..tkParDotRi:
@@ -391,8 +398,7 @@ proc parseSymbol(p: var Parser, mode = smNormal): PNode =
                                 tkParLe..tkParDotRi}:
           accm.add($p.tok)
           getTok(p)
-        let node = newNodeI(nkIdent, lineinfo)
-        node.ident = p.lex.cache.getIdent(accm)
+        let node = newAtom(p.lex.cache.getIdent(accm), lineinfo)
         result.add(node)
       of tokKeywordLow..tokKeywordHigh, tkSymbol, tkIntLit..tkCustomLit:
         result.add(newIdentNodeP(p.lex.cache.getIdent($p.tok), p))
@@ -509,26 +515,26 @@ proc exprColonEqExprList(p: var Parser, kind: TNodeKind,
 proc dotExpr(p: var Parser, a: PNode): PNode =
   var info = p.parLineInfo
   getTok(p)
-  result = newNodeI(nkDotExpr, info)
+  result = newNode(nkDotExpr, info)
   optInd(p, result)
   result.add(a)
   result.add(parseSymbol(p, smAfterDot))
   if p.tok.tokType == tkBracketLeColon and tsLeading notin p.tok.spacing:
-    var x = newNodeI(nkBracketExpr, p.parLineInfo)
+    var x = newNode(nkBracketExpr, p.parLineInfo)
     # rewrite 'x.y[:z]()' to 'y[z](x)'
-    x.add result[1]
+    x.add result.secondSon
     exprList(p, tkBracketRi, x)
     eat(p, tkBracketRi)
-    var y = newNodeI(nkCall, p.parLineInfo)
+    var y = newNode(nkCall, p.parLineInfo)
     y.add x
-    y.add result[0]
+    y.add result.firstSon
     if p.tok.tokType == tkParLe and tsLeading notin p.tok.spacing:
       exprColonEqExprListAux(p, tkParRi, y)
     result = y
 
 proc dotLikeExpr(p: var Parser, a: PNode): PNode =
   var info = p.parLineInfo
-  result = newNodeI(nkInfix, info)
+  result = newNode(nkInfix, info)
   optInd(p, result)
   var opNode = newIdentNodeP(p.tok.ident, p)
   getTok(p)
@@ -584,12 +590,18 @@ proc parseCast(p: var Parser): PNode =
   eat(p, tkParRi)
   setEndInfo()
 
+template setNodeFlag(n: PNode; f: untyped) =
+  when defined(nimCustomAst):
+    discard
+  else:
+    incl n.flags, f
+
 proc setBaseFlags(n: PNode, base: NumericalBase) =
   case base
   of base10: discard
-  of base2: incl(n.flags, nfBase2)
-  of base8: incl(n.flags, nfBase8)
-  of base16: incl(n.flags, nfBase16)
+  of base2: setNodeFlag(n, nfBase2)
+  of base8: setNodeFlag(n, nfBase8)
+  of base16: setNodeFlag(n, nfBase16)
 
 proc parseGStrLit(p: var Parser, a: PNode): PNode =
   case p.tok.tokType
@@ -885,7 +897,7 @@ proc primarySuffix(p: var Parser, r: PNode,
         result = commandExpr(p, result, mode)
         break
       result = namedParams(p, result, nkCall, tkParRi)
-      if result.len > 1 and result[1].kind == nkExprColonExpr:
+      if result.has2Sons and result.secondSon.kind == nkExprColonExpr:
         result.transitionSonsKind(nkObjConstr)
     of tkDot:
       # progress guaranteed
@@ -1156,7 +1168,7 @@ proc parseParamList(p: var Parser, retColon = true): PNode =
   if hasRet and p.tok.indent < 0:
     getTok(p)
     optInd(p, result)
-    result[0] = parseTypeDesc(p)
+    result.replaceFirstSon parseTypeDesc(p)
   elif not retColon and not hasParLe:
     # Mark as "not there" in order to mark for deprecation in the semantic pass:
     result = p.emptyNode
@@ -1201,9 +1213,9 @@ proc parseProcExpr(p: var Parser; isExpr: bool; kind: TNodeKind): PNode =
       params = params, name = p.emptyNode, pattern = p.emptyNode,
       genericParams = p.emptyNode, pragmas = pragmas, exceptions = p.emptyNode)
     skipComment(p, result)
-    result[bodyPos] = parseStmt(p)
+    result.replaceSon bodyPos, parseStmt(p)
   else:
-    result = newNodeI(if kind == nkIteratorDef: nkIteratorTy else: nkProcTy, info)
+    result = newNode(if kind == nkIteratorDef: nkIteratorTy else: nkProcTy, info)
     if hasSignature or pragmas.kind != nkEmpty:
       if hasSignature:
         result.add(params)
@@ -1316,7 +1328,7 @@ proc parseExpr(p: var Parser): PNode =
       result = parseFor(p)
   of tkWhen:
     nimprettyDontTouch:
-      result = parseIfOrWhenExpr(p, nkWhenExpr)
+      result = parseIfOrWhenExpr(p, nkWhenStmt)
   of tkCase:
     # Currently we think nimpretty is good enough with case expressions,
     # so it is allowed to touch them:
@@ -1475,7 +1487,7 @@ proc makeCall(n: PNode): PNode =
   if n.kind in nkCallKinds:
     result = n
   else:
-    result = newNodeI(nkCall, n.info)
+    result = newNode(nkCall, n.info)
     result.add n
 
 proc postExprBlocks(p: var Parser, x: PNode): PNode =
@@ -1506,9 +1518,9 @@ proc postExprBlocks(p: var Parser, x: PNode): PNode =
       var stmtList = newNodeP(nkStmtList, p)
       stmtList.add parseStmt(p)
       # to keep backwards compatibility (see tests/vm/tstringnil)
-      if stmtList[0].kind == nkStmtList: stmtList = stmtList[0]
+      if stmtList.firstSon.kind == nkStmtList: stmtList = stmtList.firstSon
 
-      stmtList.flags.incl nfBlockArg
+      setNodeFlag stmtList, nfBlockArg
       if openingParams.kind != nkEmpty or openingPragmas.kind != nkEmpty:
         if openingParams.kind == nkEmpty:
           openingParams = newNodeP(nkFormalParams, p)
@@ -1552,7 +1564,7 @@ proc postExprBlocks(p: var Parser, x: PNode): PNode =
         eat(p, tkColon)
         nextBlock.add parseStmt(p)
 
-      nextBlock.flags.incl nfBlockArg
+      setNodeFlag nextBlock, nfBlockArg
       result.add nextBlock
 
       if nextBlock.kind in {nkElse, nkFinally}: break
@@ -1578,7 +1590,7 @@ proc parseExprStmt(p: var Parser): PNode =
     # if an expression is starting here, a simplePrimary was parsed and
     # this is the start of a command
     if p.tok.indent < 0 and isExprStart(p):
-      result = newTreeI(nkCommand, a.info, a)
+      result = newTree(nkCommand, a.info, a)
       let baseIndent = p.currInd
       while true:
         result.add(commandParam(p, isFirstParam, pmNormal))
@@ -1969,13 +1981,13 @@ proc parseRoutine(p: var Parser, kind: TNodeKind): PNode =
   else:
     result.add(p.emptyNode)
   indAndComment(p, result, maybeMissEquals)
-  let body = result[^1]
-  if body.kind == nkStmtList and body.len > 0 and body[0].comment.len > 0 and body[0].kind != nkCommentStmt:
+  let body = result.lastSon
+  if body.kind == nkStmtList and body.hasSon and body.firstSon.comment.len > 0 and body.firstSon.kind != nkCommentStmt:
     if result.comment.len == 0:
       # proc fn*(a: int): int = a ## foo
       # => moves comment `foo` to `fn`
-      result.comment = body[0].comment
-      body[0].comment = ""
+      result.comment = body.firstSon.comment
+      body.firstSon.comment = ""
     #else:
     #  assert false, p.lex.config$body.info # avoids hard to track bugs, fail early.
     # Yeah, that worked so well. There IS a bug in this logic, now what?
@@ -2009,7 +2021,7 @@ proc parseSection(p: var Parser, kind: TNodeKind,
         else:
           parMessage(p, errIdentifierExpected, p.tok)
           break
-    if result.len == 0: parMessage(p, errIdentifierExpected, p.tok)
+    if not result.hasSon: parMessage(p, errIdentifierExpected, p.tok)
   elif p.tok.tokType in {tkSymbol, tkAccent, tkParLe} and p.tok.indent < 0:
     # tkParLe is allowed for ``var (x, y) = ...`` tuple parsing
     result.add(defparser(p))
@@ -2060,7 +2072,7 @@ proc parseEnum(p: var Parser): PNode =
     if p.tok.indent >= 0 and p.tok.indent <= p.currInd or
         p.tok.tokType == tkEof:
       break
-  if result.len <= 1:
+  if not result.has2Sons:
     parMessage(p, errIdentifierExpected, p.tok)
   setEndInfo()
 
@@ -2320,7 +2332,7 @@ proc parseVariable(p: var Parser): PNode =
     optInd(p, result)
     result.add(parseExpr(p))
   else: result = parseIdentColonEquals(p, {withPragma, withDot})
-  result[^1] = postExprBlocks(p, result[^1])
+  result.setLastSon postExprBlocks(p, result.lastSon)
   indAndComment(p, result)
   setEndInfo()
 
@@ -2339,8 +2351,8 @@ proc parseConstant(p: var Parser): PNode =
   eat(p, tkEquals)
   optInd(p, result)
   #add(result, parseStmtListExpr(p))
-  result.add(parseExpr(p))
-  result[^1] = postExprBlocks(p, result[^1])
+  let a = parseExpr(p)
+  result.add postExprBlocks(p, a)
   indAndComment(p, result)
   setEndInfo()
 
@@ -2365,7 +2377,7 @@ proc parseStmtPragma(p: var Parser): PNode =
   result = parsePragma(p)
   if p.tok.tokType == tkColon and p.tok.indent < 0:
     let a = result
-    result = newNodeI(nkPragmaBlock, a.info)
+    result = newNode(nkPragmaBlock, a.info)
     getTok(p)
     skipComment(p, result)
     result.add a
diff --git a/compiler/plugins/customast.nim b/compiler/plugins/customast.nim
new file mode 100644
index 000000000..87461ae39
--- /dev/null
+++ b/compiler/plugins/customast.nim
@@ -0,0 +1,136 @@
+# This file exists to make it overridable via
+# patchFile("plugins", "customast.nim", "customast.nim")
+
+## This also serves as a blueprint for a possible implementation.
+
+import "$nim" / compiler / [lineinfos, idents]
+
+when defined(nimPreviewSlimSystem):
+  import std/assertions
+
+import "$nim" / compiler / nodekinds
+export nodekinds
+
+type
+  PNode* = ref TNode
+  TNode*{.final, acyclic.} = object
+    case kind*: TNodeKind
+    of nkCharLit..nkUInt64Lit:
+      intVal: BiggestInt
+    of nkFloatLit..nkFloat128Lit:
+      floatVal: BiggestFloat
+    of nkStrLit..nkTripleStrLit:
+      strVal: string
+    of nkSym:
+      discard
+    of nkIdent:
+      ident: PIdent
+    else:
+      son, next, last: PNode # linked structure instead of a `seq`
+    info*: TLineInfo
+
+const
+  bodyPos* = 6
+  paramsPos* = 3
+
+proc comment*(n: PNode): string =
+  result = ""
+
+proc `comment=`*(n: PNode, a: string) =
+  discard "XXX implement me"
+
+proc add*(father, son: PNode) =
+  assert son != nil
+  if father.son == nil:
+    father.son = son
+    father.last = son
+  else:
+    father.last.next = son
+    father.last = son
+
+template firstSon*(n: PNode): PNode = n.son
+template secondSon*(n: PNode): PNode = n.son.next
+
+proc replaceFirstSon*(n, newson: PNode) {.inline.} =
+  let old = n.son
+  n.son = newson
+  newson.next = old
+
+proc replaceSon*(n: PNode; i: int; newson: PNode) =
+  assert i > 0
+  assert newson.next == nil
+  var i = i
+  var it = n.son
+  while i > 0:
+    it = it.next
+    dec i
+  let old = it.next
+  it.next = newson
+  newson.next = old
+
+template newNodeImpl(info2) =
+  result = PNode(kind: kind, info: info2)
+
+proc newNode*(kind: TNodeKind): PNode =
+  ## new node with unknown line info, no type, and no children
+  newNodeImpl(unknownLineInfo)
+
+proc newNode*(kind: TNodeKind, info: TLineInfo): PNode =
+  ## new node with line info, no type, and no children
+  newNodeImpl(info)
+
+proc newTree*(kind: TNodeKind; info: TLineInfo; child: PNode): PNode =
+  result = newNode(kind, info)
+  result.son = child
+
+proc newAtom*(ident: PIdent, info: TLineInfo): PNode =
+  result = newNode(nkIdent)
+  result.ident = ident
+  result.info = info
+
+proc newAtom*(kind: TNodeKind, intVal: BiggestInt, info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.intVal = intVal
+
+proc newAtom*(kind: TNodeKind, floatVal: BiggestFloat, info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.floatVal = floatVal
+
+proc newAtom*(kind: TNodeKind; strVal: sink string; info: TLineInfo): PNode =
+  result = newNode(kind, info)
+  result.strVal = strVal
+
+proc lastSon*(n: PNode): PNode {.inline.} = n.last
+proc setLastSon*(n: PNode, s: PNode) =
+  assert s.next == nil
+  n.last = s
+  if n.son == nil: n.son = s
+
+proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
+                 params,
+                 name, pattern, genericParams,
+                 pragmas, exceptions: PNode): PNode =
+  result = newNode(kind, info)
+  result.add name
+  result.add pattern
+  result.add genericParams
+  result.add params
+  result.add pragmas
+  result.add exceptions
+  result.add body
+
+template transitionNodeKindCommon(k: TNodeKind) =
+  let obj {.inject.} = n[]
+  n[] = TNode(kind: k, info: obj.info)
+  # n.comment = obj.comment # shouldn't be needed, the address doesnt' change
+
+proc transitionSonsKind*(n: PNode, kind: range[nkComesFrom..nkTupleConstr]) =
+  transitionNodeKindCommon(kind)
+  n.son = obj.son
+
+template hasSon*(n: PNode): bool = n.son != nil
+template has2Sons*(n: PNode): bool = n.son != nil and n.son.next != nil
+
+proc isNewStyleConcept*(n: PNode): bool {.inline.} =
+  assert n.kind == nkTypeClassTy
+  result = n.firstSon.kind == nkEmpty
diff --git a/compiler/plugins/plugins.nimble b/compiler/plugins/plugins.nimble
new file mode 100644
index 000000000..e69de29bb
--- /dev/null
+++ b/compiler/plugins/plugins.nimble
diff --git a/lib/pure/pegs.nim b/lib/pure/pegs.nim
index 935cea5e6..ca2e80021 100644
--- a/lib/pure/pegs.nim
+++ b/lib/pure/pegs.nim
@@ -1198,7 +1198,7 @@ template `=~`*(s: string, pattern: Peg): bool =
   ##   ```
   bind MaxSubpatterns
   when not declaredInScope(matches):
-    var matches {.inject.}: array[0..MaxSubpatterns-1, string]
+    var matches {.inject.} = default(array[0..MaxSubpatterns-1, string])
   match(s, pattern, matches)
 
 # ------------------------- more string handling ------------------------------