summary refs log tree commit diff stats
path: root/compiler/cgen.nim
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/cgen.nim')
-rw-r--r--compiler/cgen.nim698
1 files changed, 443 insertions, 255 deletions
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index e85cfd773..091f5c842 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -10,12 +10,17 @@
 ## This module implements the C code generator.
 
 import
-  ast, astalgo, hashes, trees, platform, magicsys, extccomp, options, intsets,
+  ast, astalgo, trees, platform, magicsys, extccomp, options,
   nversion, nimsets, msgs, bitsets, idents, types,
-  ccgutils, os, ropes, math, passes, wordrecg, treetab, cgmeth,
+  ccgutils, ropes, wordrecg, treetab, cgmeth,
   rodutils, renderer, cgendata, aliases,
-  lowerings, tables, sets, ndi, lineinfos, pathutils, transf,
-  injectdestructors, astmsgs, modulepaths
+  lowerings, ndi, lineinfos, pathutils, transf,
+  injectdestructors, astmsgs, modulepaths, pushpoppragmas,
+  mangleutils
+
+from expanddefaults import caseObjDefaultBranch
+
+import pipelineutils
 
 when defined(nimPreviewSlimSystem):
   import std/assertions
@@ -23,10 +28,16 @@ when defined(nimPreviewSlimSystem):
 when not defined(leanCompiler):
   import spawn, semparallel
 
-import strutils except `%`, addf # collides with ropes.`%`
+import std/strutils except `%`, addf # collides with ropes.`%`
 
 from ic / ic import ModuleBackendFlag
-import dynlib
+import std/[dynlib, math, tables, sets, os, intsets, hashes]
+
+const
+  # we use some ASCII control characters to insert directives that will be converted to real code in a postprocessing pass
+  postprocessDirStart = '\1'
+  postprocessDirSep = '\31'
+  postprocessDirEnd = '\23'
 
 when not declared(dynlib.libCandidates):
   proc libCandidates(s: string, dest: var seq[string]) =
@@ -59,12 +70,9 @@ proc findPendingModule(m: BModule, s: PSym): BModule =
     var ms = getModule(s)
     result = m.g.modules[ms.position]
 
-proc initLoc(result: var TLoc, k: TLocKind, lode: PNode, s: TStorageLoc) =
-  result.k = k
-  result.storage = s
-  result.lode = lode
-  result.r = ""
-  result.flags = {}
+proc initLoc(k: TLocKind, lode: PNode, s: TStorageLoc, flags: TLocFlags = {}): TLoc =
+  result = TLoc(k: k, storage: s, lode: lode,
+                snippet: "", flags: flags)
 
 proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, r: Rope, s: TStorageLoc) {.inline.} =
   # fills the loc if it is not already initialized
@@ -72,7 +80,7 @@ proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, r: Rope, s: TStorageLoc) {.i
     a.k = k
     a.lode = lode
     a.storage = s
-    if a.r == "": a.r = r
+    if a.snippet == "": a.snippet = r
 
 proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, s: TStorageLoc) {.inline.} =
   # fills the loc if it is not already initialized
@@ -119,7 +127,7 @@ proc getModuleDllPath(m: BModule, module: int): Rope =
 proc getModuleDllPath(m: BModule, s: PSym): Rope =
   result = getModuleDllPath(m.g.modules[s.itemId.module])
 
-import macros
+import std/macros
 
 proc cgFormatValue(result: var string; value: string) =
   result.add value
@@ -214,20 +222,20 @@ macro ropecg(m: BModule, frmt: static[FormatStr], args: untyped): Rope =
     elif frmt[i] == '#' and frmt[i+1] == '#':
       inc(i, 2)
       strLit.add("#")
-
-    var start = i
-    while i < frmt.len:
-      if frmt[i] != '$' and frmt[i] != '#': inc(i)
-      else: break
-    if i - 1 >= start:
-      strLit.add(substr(frmt, start, i - 1))
+    else:
+      strLit.add(frmt[i])
+      inc(i)
 
   flushStrLit()
   result.add newCall(ident"rope", resVar)
 
 proc addIndent(p: BProc; result: var Rope) =
-  for i in 0..<p.blocks.len:
-    result.add "\t".rope
+  var i = result.len
+  let newLen = i + p.blocks.len
+  result.setLen newLen
+  while i < newLen:
+    result[i] = '\t'
+    inc i
 
 template appcg(m: BModule, c: var Rope, frmt: FormatStr,
            args: untyped) =
@@ -264,14 +272,28 @@ proc safeLineNm(info: TLineInfo): int =
   result = toLinenumber(info)
   if result < 0: result = 0 # negative numbers are not allowed in #line
 
-proc genCLineDir(r: var Rope, filename: string, line: int; conf: ConfigRef) =
+proc genPostprocessDir(field1, field2, field3: string): string =
+  result = postprocessDirStart & field1 & postprocessDirSep & field2 & postprocessDirSep & field3 & postprocessDirEnd
+
+proc genCLineDir(r: var Rope, fileIdx: FileIndex, line: int; conf: ConfigRef) =
   assert line >= 0
   if optLineDir in conf.options and line > 0:
-    r.addf("$N#line $2 $1$N",
-        [rope(makeSingleLineCString(filename)), rope(line)])
+    if fileIdx == InvalidFileIdx:
+      r.add(rope("\n#line " & $line & " \"generated_not_to_break_here\"\n"))
+    else:
+      r.add(rope("\n#line " & $line & " FX_" & $fileIdx.int32 & "\n"))
+
+proc genCLineDir(r: var Rope, fileIdx: FileIndex, line: int; p: BProc; info: TLineInfo; lastFileIndex: FileIndex) =
+  assert line >= 0
+  if optLineDir in p.config.options and line > 0:
+    if fileIdx == InvalidFileIdx:
+      r.add(rope("\n#line " & $line & " \"generated_not_to_break_here\"\n"))
+    else:
+      r.add(rope("\n#line " & $line & " FX_" & $fileIdx.int32 & "\n"))
 
 proc genCLineDir(r: var Rope, info: TLineInfo; conf: ConfigRef) =
-  genCLineDir(r, toFullPath(conf, info), info.safeLineNm, conf)
+  if optLineDir in conf.options:
+    genCLineDir(r, info.fileIndex, info.safeLineNm, conf)
 
 proc freshLineInfo(p: BProc; info: TLineInfo): bool =
   if p.lastLineInfo.line != info.line or
@@ -279,18 +301,29 @@ proc freshLineInfo(p: BProc; info: TLineInfo): bool =
     p.lastLineInfo.line = info.line
     p.lastLineInfo.fileIndex = info.fileIndex
     result = true
+  else:
+    result = false
+
+proc genCLineDir(r: var Rope, p: BProc, info: TLineInfo; conf: ConfigRef) =
+  if optLineDir in conf.options:
+    let lastFileIndex = p.lastLineInfo.fileIndex
+    if freshLineInfo(p, info):
+      genCLineDir(r, info.fileIndex, info.safeLineNm, p, info, lastFileIndex)
 
 proc genLineDir(p: BProc, t: PNode) =
+  if p == p.module.preInitProc: return
   let line = t.info.safeLineNm
 
   if optEmbedOrigSrc in p.config.globalOptions:
     p.s(cpsStmts).add("//" & sourceLine(p.config, t.info) & "\L")
-  genCLineDir(p.s(cpsStmts), toFullPath(p.config, t.info), line, p.config)
+  let lastFileIndex = p.lastLineInfo.fileIndex
+  let freshLine = freshLineInfo(p, t.info)
+  if freshLine:
+    genCLineDir(p.s(cpsStmts), t.info.fileIndex, line, p, t.info, lastFileIndex)
   if ({optLineTrace, optStackTrace} * p.options == {optLineTrace, optStackTrace}) and
       (p.prc == nil or sfPure notin p.prc.flags) and t.info.fileIndex != InvalidFileIdx:
-    if freshLineInfo(p, t.info):
-      linefmt(p, cpsStmts, "nimln_($1, $2);$n",
-              [line, quotedFilename(p.config, t.info)])
+      if freshLine:
+        line(p, cpsStmts, genPostprocessDir("nimln", $line, $t.info.fileIndex.int32))
 
 proc accessThreadLocalVar(p: BProc, s: PSym)
 proc emulatedThreadVars(conf: ConfigRef): bool {.inline.}
@@ -307,15 +340,15 @@ proc getTempName(m: BModule): Rope =
 proc rdLoc(a: TLoc): Rope =
   # 'read' location (deref if indirect)
   if lfIndirect in a.flags:
-    result = "(*" & a.r & ")"
+    result = "(*" & a.snippet & ")"
   else:
-    result = a.r
+    result = a.snippet
 
 proc addRdLoc(a: TLoc; result: var Rope) =
   if lfIndirect in a.flags:
-    result.add "(*" & a.r & ")"
+    result.add "(*" & a.snippet & ")"
   else:
-    result.add a.r
+    result.add a.snippet
 
 proc lenField(p: BProc): Rope {.inline.} =
   result = rope(if p.module.compileToCpp: "len" else: "Sup.len")
@@ -338,6 +371,9 @@ proc dataField(p: BProc): Rope =
   else:
     result = rope"->data"
 
+proc genProcPrototype(m: BModule, sym: PSym)
+
+include cbuilder
 include ccgliterals
 include ccgtypes
 
@@ -349,23 +385,23 @@ template mapTypeChooser(n: PNode): TSymKind =
 template mapTypeChooser(a: TLoc): TSymKind = mapTypeChooser(a.lode)
 
 proc addAddrLoc(conf: ConfigRef; a: TLoc; result: var Rope) =
-  if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a)) != ctArray:
-    result.add "(&" & a.r & ")"
+  if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a) == skParam) != ctArray:
+    result.add "(&" & a.snippet & ")"
   else:
-    result.add a.r
+    result.add a.snippet
 
 proc addrLoc(conf: ConfigRef; a: TLoc): Rope =
-  if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a)) != ctArray:
-    result = "(&" & a.r & ")"
+  if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a) == skParam) != ctArray:
+    result = "(&" & a.snippet & ")"
   else:
-    result = a.r
+    result = a.snippet
 
 proc byRefLoc(p: BProc; a: TLoc): Rope =
-  if lfIndirect notin a.flags and mapType(p.config, a.t, mapTypeChooser(a)) != ctArray and not
+  if lfIndirect notin a.flags and mapType(p.config, a.t, mapTypeChooser(a) == skParam) != ctArray and not
       p.module.compileToCpp:
-    result = "(&" & a.r & ")"
+    result = "(&" & a.snippet & ")"
   else:
-    result = a.r
+    result = a.snippet
 
 proc rdCharLoc(a: TLoc): Rope =
   # read a location that may need a char-cast:
@@ -376,6 +412,9 @@ proc rdCharLoc(a: TLoc): Rope =
 type
   TAssignmentFlag = enum
     needToCopy
+    needToCopySinkParam
+    needTempForOpenArray
+    needAssignCall
   TAssignmentFlags = set[TAssignmentFlag]
 
 proc genObjConstr(p: BProc, e: PNode, d: var TLoc)
@@ -407,13 +446,13 @@ proc genObjectInit(p: BProc, section: TCProcSection, t: PType, a: var TLoc,
       linefmt(p, section, "$1.m_type = $2;$n", [r, genTypeInfoV1(p.module, t, a.lode.info)])
   of frEmbedded:
     if optTinyRtti in p.config.globalOptions:
-      var tmp: TLoc
+      var tmp: TLoc = default(TLoc)
       if mode == constructRefObj:
         let objType = t.skipTypes(abstractInst+{tyRef})
         rawConstExpr(p, newNodeIT(nkType, a.lode.info, objType), tmp)
         linefmt(p, cpsStmts,
             "#nimCopyMem((void*)$1, (NIM_CONST void*)&$2, sizeof($3));$n",
-            [rdLoc(a), rdLoc(tmp), getTypeDesc(p.module, objType, mapTypeChooser(a))])
+            [rdLoc(a), rdLoc(tmp), getTypeDesc(p.module, objType, descKindFromSymKind mapTypeChooser(a))])
       else:
         rawConstExpr(p, newNodeIT(nkType, a.lode.info, t), tmp)
         genAssignment(p, a, tmp, {})
@@ -444,9 +483,12 @@ include ccgreset
 proc resetLoc(p: BProc, loc: var TLoc) =
   let containsGcRef = optSeqDestructors notin p.config.globalOptions and containsGarbageCollectedRef(loc.t)
   let typ = skipTypes(loc.t, abstractVarRange)
-  if isImportedCppType(typ): return
+  if isImportedCppType(typ): 
+    var didGenTemp = false
+    linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(loc), genCppInitializer(p.module, p, typ, didGenTemp)])
+    return
   if optSeqDestructors in p.config.globalOptions and typ.kind in {tyString, tySequence}:
-    assert loc.r != ""
+    assert loc.snippet != ""
 
     let atyp = skipTypes(loc.t, abstractInst)
     if atyp.kind in {tyVar, tyLent}:
@@ -455,9 +497,8 @@ proc resetLoc(p: BProc, loc: var TLoc) =
       linefmt(p, cpsStmts, "$1.len = 0; $1.p = NIM_NIL;$n", [rdLoc(loc)])
   elif not isComplexValueType(typ):
     if containsGcRef:
-      var nilLoc: TLoc
-      initLoc(nilLoc, locTemp, loc.lode, OnStack)
-      nilLoc.r = rope("NIM_NIL")
+      var nilLoc: TLoc = initLoc(locTemp, loc.lode, OnStack)
+      nilLoc.snippet = rope("NIM_NIL")
       genRefAssign(p, loc, nilLoc)
     else:
       linefmt(p, cpsStmts, "$1 = 0;$n", [rdLoc(loc)])
@@ -473,9 +514,17 @@ proc resetLoc(p: BProc, loc: var TLoc) =
     else:
       # array passed as argument decayed into pointer, bug #7332
       # so we use getTypeDesc here rather than rdLoc(loc)
-      linefmt(p, cpsStmts, "#nimZeroMem((void*)$1, sizeof($2));$n",
-              [addrLoc(p.config, loc),
-              getTypeDesc(p.module, loc.t, mapTypeChooser(loc))])
+      let tyDesc = getTypeDesc(p.module, loc.t, descKindFromSymKind mapTypeChooser(loc))
+      if p.module.compileToCpp and isOrHasImportedCppType(typ):
+        if lfIndirect in loc.flags:
+          #C++ cant be just zeroed. We need to call the ctors
+          var tmp = getTemp(p, loc.t)
+          linefmt(p, cpsStmts,"#nimCopyMem((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n",
+                  [addrLoc(p.config, loc), addrLoc(p.config, tmp), tyDesc])
+      else:
+        linefmt(p, cpsStmts, "#nimZeroMem((void*)$1, sizeof($2));$n",
+                [addrLoc(p.config, loc), tyDesc])
+
       # XXX: We can be extra clever here and call memset only
       # on the bytes following the m_type field?
       genObjectInit(p, cpsStmts, loc.t, loc, constructObj)
@@ -486,20 +535,19 @@ proc constructLoc(p: BProc, loc: var TLoc, isTemp = false) =
     linefmt(p, cpsStmts, "$1.len = 0; $1.p = NIM_NIL;$n", [rdLoc(loc)])
   elif not isComplexValueType(typ):
     if containsGarbageCollectedRef(loc.t):
-      var nilLoc: TLoc
-      initLoc(nilLoc, locTemp, loc.lode, OnStack)
-      nilLoc.r = rope("NIM_NIL")
+      var nilLoc: TLoc = initLoc(locTemp, loc.lode, OnStack)
+      nilLoc.snippet = rope("NIM_NIL")
       genRefAssign(p, loc, nilLoc)
     else:
       linefmt(p, cpsStmts, "$1 = ($2)0;$n", [rdLoc(loc),
-        getTypeDesc(p.module, typ, mapTypeChooser(loc))])
+        getTypeDesc(p.module, typ, descKindFromSymKind mapTypeChooser(loc))])
   else:
-    if not isTemp or containsGarbageCollectedRef(loc.t):
+    if (not isTemp or containsGarbageCollectedRef(loc.t)) and not hasNoInit(loc.t):
       # don't use nimZeroMem for temporary values for performance if we can
       # avoid it:
-      if not isImportedCppType(typ):
+      if not isOrHasImportedCppType(typ):
         linefmt(p, cpsStmts, "#nimZeroMem((void*)$1, sizeof($2));$n",
-                [addrLoc(p.config, loc), getTypeDesc(p.module, typ, mapTypeChooser(loc))])
+                [addrLoc(p.config, loc), getTypeDesc(p.module, typ, descKindFromSymKind mapTypeChooser(loc))])
     genObjectInit(p, cpsStmts, loc.t, loc, constructObj)
 
 proc initLocalVar(p: BProc, v: PSym, immediateAsgn: bool) =
@@ -514,14 +562,16 @@ proc initLocalVar(p: BProc, v: PSym, immediateAsgn: bool) =
     if not immediateAsgn:
       constructLoc(p, v.loc)
 
-proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) =
+proc getTemp(p: BProc, t: PType, needsInit=false): TLoc =
   inc(p.labels)
-  result.r = "T" & rope(p.labels) & "_"
-  linefmt(p, cpsLocals, "$1 $2;$n", [getTypeDesc(p.module, t, skVar), result.r])
-  result.k = locTemp
-  result.lode = lodeTyp t
-  result.storage = OnStack
-  result.flags = {}
+  result = TLoc(snippet: "T" & rope(p.labels) & "_", k: locTemp, lode: lodeTyp t,
+                storage: OnStack, flags: {})
+  if p.module.compileToCpp and isOrHasImportedCppType(t):
+    var didGenTemp = false
+    linefmt(p, cpsLocals, "$1 $2$3;$n", [getTypeDesc(p.module, t, dkVar), result.snippet,
+      genCppInitializer(p.module, p, t, didGenTemp)])
+  else:
+    linefmt(p, cpsLocals, "$1 $2;$n", [getTypeDesc(p.module, t, dkVar), result.snippet])
   constructLoc(p, result, not needsInit)
   when false:
     # XXX Introduce a compiler switch in order to detect these easily.
@@ -532,25 +582,21 @@ proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) =
         echo "ENORMOUS TEMPORARY! ", p.config $ p.lastLineInfo
       writeStackTrace()
 
-proc getTempCpp(p: BProc, t: PType, result: var TLoc; value: Rope) =
+proc getTempCpp(p: BProc, t: PType, value: Rope): TLoc =
   inc(p.labels)
-  result.r = "T" & rope(p.labels) & "_"
-  linefmt(p, cpsStmts, "$1 $2 = $3;$n", [getTypeDesc(p.module, t, skVar), result.r, value])
-  result.k = locTemp
-  result.lode = lodeTyp t
-  result.storage = OnStack
-  result.flags = {}
-
-proc getIntTemp(p: BProc, result: var TLoc) =
+  result = TLoc(snippet: "T" & rope(p.labels) & "_", k: locTemp, lode: lodeTyp t,
+                storage: OnStack, flags: {})
+  linefmt(p, cpsStmts, "auto $1 = $2;$n", [result.snippet, value])
+
+proc getIntTemp(p: BProc): TLoc =
   inc(p.labels)
-  result.r = "T" & rope(p.labels) & "_"
-  linefmt(p, cpsLocals, "NI $1;$n", [result.r])
-  result.k = locTemp
-  result.storage = OnStack
-  result.lode = lodeTyp getSysType(p.module.g.graph, unknownLineInfo, tyInt)
-  result.flags = {}
+  result = TLoc(snippet: "T" & rope(p.labels) & "_", k: locTemp,
+                storage: OnStack, lode: lodeTyp getSysType(p.module.g.graph, unknownLineInfo, tyInt),
+                flags: {})
+  linefmt(p, cpsLocals, "NI $1;$n", [result.snippet])
 
 proc localVarDecl(p: BProc; n: PNode): Rope =
+  result = ""
   let s = n.sym
   if s.loc.k == locNone:
     fillLocalName(p, s)
@@ -558,24 +604,31 @@ proc localVarDecl(p: BProc; n: PNode): Rope =
     if s.kind == skLet: incl(s.loc.flags, lfNoDeepCopy)
   if s.kind in {skLet, skVar, skField, skForVar} and s.alignment > 0:
     result.addf("NIM_ALIGN($1) ", [rope(s.alignment)])
-  result.add getTypeDesc(p.module, s.typ, skVar)
-  if s.constraint.isNil:
+
+  genCLineDir(result, p, n.info, p.config)
+
+  result.add getTypeDesc(p.module, s.typ, dkVar)
+  if sfCodegenDecl notin s.flags:
     if sfRegister in s.flags: result.add(" register")
     #elif skipTypes(s.typ, abstractInst).kind in GcTypeKinds:
     #  decl.add(" GC_GUARD")
     if sfVolatile in s.flags: result.add(" volatile")
     if sfNoalias in s.flags: result.add(" NIM_NOALIAS")
     result.add(" ")
-    result.add(s.loc.r)
+    result.add(s.loc.snippet)
   else:
-    result = runtimeFormat(s.cgDeclFrmt, [result, s.loc.r])
+    result = runtimeFormat(s.cgDeclFrmt, [result, s.loc.snippet])
 
 proc assignLocalVar(p: BProc, n: PNode) =
   #assert(s.loc.k == locNone) # not yet assigned
   # this need not be fulfilled for inline procs; they are regenerated
   # for each module that uses them!
-  let nl = if optLineDir in p.config.options: "" else: "\L"
-  let decl = localVarDecl(p, n) & ";" & nl
+  let nl = if optLineDir in p.config.options: "" else: "\n"
+  var decl = localVarDecl(p, n)
+  if p.module.compileToCpp and isOrHasImportedCppType(n.typ):
+    var didGenTemp = false
+    decl.add genCppInitializer(p.module, p, n.typ, didGenTemp)
+  decl.add ";" & nl
   line(p, cpsLocals, decl)
 
 include ccgthreadvars
@@ -588,6 +641,29 @@ proc treatGlobalDifferentlyForHCR(m: BModule, s: PSym): bool =
       # and s.owner.kind == skModule # owner isn't always a module (global pragma on local var)
       # and s.loc.k == locGlobalVar  # loc isn't always initialized when this proc is used
 
+proc genGlobalVarDecl(p: BProc, n: PNode; td, value: Rope; decl: var Rope) =
+  let s = n.sym
+  if sfCodegenDecl notin s.flags:
+    if s.kind in {skLet, skVar, skField, skForVar} and s.alignment > 0:
+      decl.addf "NIM_ALIGN($1) ", [rope(s.alignment)]
+    if p.hcrOn: decl.add("static ")
+    elif sfImportc in s.flags: decl.add("extern ")
+    elif lfExportLib in s.loc.flags: decl.add("N_LIB_EXPORT_VAR ")
+    else: decl.add("N_LIB_PRIVATE ")
+    if s.kind == skLet and value != "": decl.add("NIM_CONST ")
+    decl.add(td)
+    if p.hcrOn: decl.add("*")
+    if sfRegister in s.flags: decl.add(" register")
+    if sfVolatile in s.flags: decl.add(" volatile")
+    if sfNoalias in s.flags: decl.add(" NIM_NOALIAS")
+  else:
+    if value != "":
+      decl = runtimeFormat(s.cgDeclFrmt & " = $#;$n", [td, s.loc.snippet, value])
+    else:
+      decl = runtimeFormat(s.cgDeclFrmt & ";$n", [td, s.loc.snippet])
+
+proc genCppVarForCtor(p: BProc; call: PNode; decl: var Rope; didGenTemp: var bool)
+
 proc assignGlobalVar(p: BProc, n: PNode; value: Rope) =
   let s = n.sym
   if s.loc.k == locNone:
@@ -600,7 +676,7 @@ proc assignGlobalVar(p: BProc, n: PNode; value: Rope) =
     if q != nil and not containsOrIncl(q.declaredThings, s.id):
       varInDynamicLib(q, s)
     else:
-      s.loc.r = mangleDynLibProc(s)
+      s.loc.snippet = mangleDynLibProc(s)
     if value != "":
       internalError(p.config, n.info, ".dynlib variables cannot have a value")
     return
@@ -613,36 +689,49 @@ proc assignGlobalVar(p: BProc, n: PNode; value: Rope) =
         internalError(p.config, n.info, ".threadvar variables cannot have a value")
     else:
       var decl: Rope = ""
-      var td = getTypeDesc(p.module, s.loc.t, skVar)
+      let td = getTypeDesc(p.module, s.loc.t, dkVar)
+      genGlobalVarDecl(p, n, td, value, decl)
       if s.constraint.isNil:
-        if s.kind in {skLet, skVar, skField, skForVar} and s.alignment > 0:
-          decl.addf "NIM_ALIGN($1) ", [rope(s.alignment)]
-        if p.hcrOn: decl.add("static ")
-        elif sfImportc in s.flags: decl.add("extern ")
-        elif lfExportLib in s.loc.flags: decl.add("N_LIB_EXPORT_VAR ")
-        else: decl.add("N_LIB_PRIVATE ")
-        if s.kind == skLet and value != "": decl.add("NIM_CONST ")
-        decl.add(td)
-        if p.hcrOn: decl.add("*")
-        if sfRegister in s.flags: decl.add(" register")
-        if sfVolatile in s.flags: decl.add(" volatile")
-        if sfNoalias in s.flags: decl.add(" NIM_NOALIAS")
         if value != "":
-          decl.addf(" $1 = $2;$n", [s.loc.r, value])
+          if p.module.compileToCpp and value.startsWith "{{}":
+            # TODO: taking this branch, re"\{\{\}(,\s\{\})*\}" might be emitted, resulting in
+            # either warnings (GCC 12.2+) or errors (Clang 15, MSVC 19.3+) of C++11+ compilers **when
+            # explicit constructors are around** due to overload resolution rules in place [^0][^1][^2]
+            # *Workaround* here: have C++'s static initialization mechanism do the default init work,
+            # for us lacking a deeper knowledge of an imported object's constructors' ex-/implicitness
+            # (so far) *and yet* trying to achieve default initialization.
+            # Still, generating {}s in genConstObjConstr() just to omit them here is faaaar from ideal;
+            # need to figure out a better way, possibly by keeping around more data about the
+            # imported objects' contructors?
+            #
+            # [^0]: https://en.cppreference.com/w/cpp/language/aggregate_initialization
+            # [^1]: https://cplusplus.github.io/CWG/issues/1518.html
+            # [^2]: https://eel.is/c++draft/over.match.ctor
+            decl.addf(" $1;$n", [s.loc.snippet])
+          else:
+            decl.addf(" $1 = $2;$n", [s.loc.snippet, value])
         else:
-          decl.addf(" $1;$n", [s.loc.r])
-      else:
-        if value != "":
-          decl = runtimeFormat(s.cgDeclFrmt & " = $#;$n", [td, s.loc.r, value])
-        else:
-          decl = runtimeFormat(s.cgDeclFrmt & ";$n", [td, s.loc.r])
+          decl.addf(" $1;$n", [s.loc.snippet])
+
       p.module.s[cfsVars].add(decl)
   if p.withinLoop > 0 and value == "":
     # fixes tests/run/tzeroarray:
     resetLoc(p, s.loc)
 
+proc callGlobalVarCppCtor(p: BProc; v: PSym; vn, value: PNode; didGenTemp: var bool) =
+  let s = vn.sym
+  fillBackendName(p.module, s)
+  fillLoc(s.loc, locGlobalVar, vn, OnHeap)
+  var decl: Rope = ""
+  let td = getTypeDesc(p.module, vn.sym.typ, dkVar)
+  genGlobalVarDecl(p, vn, td, "", decl)
+  decl.add " " & $s.loc.snippet
+  genCppVarForCtor(p, value, decl, didGenTemp)
+  if didGenTemp:  return # generated in the caller
+  p.module.s[cfsVars].add decl
+
 proc assignParam(p: BProc, s: PSym, retType: PType) =
-  assert(s.loc.r != "")
+  assert(s.loc.snippet != "")
   scopeMangledParam(p, s)
 
 proc fillProcLoc(m: BModule; n: PNode) =
@@ -656,25 +745,26 @@ proc getLabel(p: BProc): TLabel =
   result = "LA" & rope(p.labels) & "_"
 
 proc fixLabel(p: BProc, labl: TLabel) =
-  lineF(p, cpsStmts, "$1: ;$n", [labl])
+  p.s(cpsStmts).add("$1: ;$n" % [labl])
 
 proc genVarPrototype(m: BModule, n: PNode)
 proc requestConstImpl(p: BProc, sym: PSym)
 proc genStmts(p: BProc, t: PNode)
 proc expr(p: BProc, n: PNode, d: var TLoc)
-proc genProcPrototype(m: BModule, sym: PSym)
+
 proc putLocIntoDest(p: BProc, d: var TLoc, s: TLoc)
 proc intLiteral(i: BiggestInt; result: var Rope)
 proc genLiteral(p: BProc, n: PNode; result: var Rope)
 proc genOtherArg(p: BProc; ri: PNode; i: int; typ: PType; result: var Rope; argsCounter: var int)
 proc raiseExit(p: BProc)
+proc raiseExitCleanup(p: BProc, destroy: string)
 
-proc initLocExpr(p: BProc, e: PNode, result: var TLoc) =
-  initLoc(result, locNone, e, OnUnknown)
+proc initLocExpr(p: BProc, e: PNode, flags: TLocFlags = {}): TLoc =
+  result = initLoc(locNone, e, OnUnknown, flags)
   expr(p, e, result)
 
-proc initLocExprSingleUse(p: BProc, e: PNode, result: var TLoc) =
-  initLoc(result, locNone, e, OnUnknown)
+proc initLocExprSingleUse(p: BProc, e: PNode): TLoc =
+  result = initLoc(locNone, e, OnUnknown)
   if e.kind in nkCallKinds and (e[0].kind != nkSym or e[0].sym.magic == mNone):
     # We cannot check for tfNoSideEffect here because of mutable parameters.
     discard "bug #8202; enforce evaluation order for nested calls for C++ too"
@@ -694,12 +784,12 @@ $1define nimfr_(proc, file) \
   TFrame FR_; \
   FR_.procname = proc; FR_.filename = file; FR_.line = 0; FR_.len = 0; #nimFrame(&FR_);
 
-  $1define nimfrs_(proc, file, slots, length) \
-    struct {TFrame* prev;NCSTRING procname;NI line;NCSTRING filename;NI len;VarSlot s[slots];} FR_; \
-    FR_.procname = proc; FR_.filename = file; FR_.line = 0; FR_.len = length; #nimFrame((TFrame*)&FR_);
+$1define nimln_(n) \
+  FR_.line = n;
+
+$1define nimlf_(n, file) \
+  FR_.line = n; FR_.filename = file;
 
-  $1define nimln_(n, file) \
-    FR_.line = n; FR_.filename = file;
 """
   if p.module.s[cfsFrameDefines].len == 0:
     appcg(p.module, p.module.s[cfsFrameDefines], frameDefines, ["#"])
@@ -761,11 +851,10 @@ proc loadDynamicLib(m: BModule, lib: PLib) =
       var p = newProc(nil, m)
       p.options.excl optStackTrace
       p.flags.incl nimErrorFlagDisabled
-      var dest: TLoc
-      initLoc(dest, locTemp, lib.path, OnStack)
-      dest.r = getTempName(m)
+      var dest: TLoc = initLoc(locTemp, lib.path, OnStack)
+      dest.snippet = getTempName(m)
       appcg(m, m.s[cfsDynLibInit],"$1 $2;$n",
-           [getTypeDesc(m, lib.path.typ, skVar), rdLoc(dest)])
+           [getTypeDesc(m, lib.path.typ, dkVar), rdLoc(dest)])
       expr(p, lib.path, dest)
 
       m.s[cfsVars].add(p.s(cpsLocals))
@@ -781,7 +870,7 @@ proc mangleDynLibProc(sym: PSym): Rope =
   # we have to build this as a single rope in order not to trip the
   # optimization in genInfixCall, see test tests/cpp/t8241.nim
   if sfCompilerProc in sym.flags:
-    # NOTE: sym.loc.r is the external name!
+    # NOTE: sym.loc.snippet is the external name!
     result = rope(sym.name.s)
   else:
     result = rope(strutils.`%`("Dl_$1_", $sym.id))
@@ -789,23 +878,22 @@ proc mangleDynLibProc(sym: PSym): Rope =
 proc symInDynamicLib(m: BModule, sym: PSym) =
   var lib = sym.annex
   let isCall = isGetProcAddr(lib)
-  var extname = sym.loc.r
+  var extname = sym.loc.snippet
   if not isCall: loadDynamicLib(m, lib)
   var tmp = mangleDynLibProc(sym)
-  sym.loc.r = tmp             # from now on we only need the internal name
+  sym.loc.snippet = tmp             # from now on we only need the internal name
   sym.typ.sym = nil           # generate a new name
   inc(m.labels, 2)
   if isCall:
     let n = lib.path
-    var a: TLoc
-    initLocExpr(m.initProc, n[0], a)
+    var a: TLoc = initLocExpr(m.initProc, n[0])
     var params = rdLoc(a) & "("
     for i in 1..<n.len-1:
-      initLocExpr(m.initProc, n[i], a)
+      a = initLocExpr(m.initProc, n[i])
       params.add(rdLoc(a))
       params.add(", ")
     let load = "\t$1 = ($2) ($3$4));$n" %
-        [tmp, getTypeDesc(m, sym.typ, skVar), params, makeCString($extname)]
+        [tmp, getTypeDesc(m, sym.typ, dkVar), params, makeCString($extname)]
     var last = lastSon(n)
     if last.kind == nkHiddenStdConv: last = last[1]
     internalAssert(m.config, last.kind == nkStrLit)
@@ -819,25 +907,25 @@ proc symInDynamicLib(m: BModule, sym: PSym) =
   else:
     appcg(m, m.s[cfsDynLibInit],
         "\t$1 = ($2) #nimGetProcAddr($3, $4);$n",
-        [tmp, getTypeDesc(m, sym.typ, skVar), lib.name, makeCString($extname)])
-  m.s[cfsVars].addf("$2 $1;$n", [sym.loc.r, getTypeDesc(m, sym.loc.t, skVar)])
+        [tmp, getTypeDesc(m, sym.typ, dkVar), lib.name, makeCString($extname)])
+  m.s[cfsVars].addf("$2 $1;$n", [sym.loc.snippet, getTypeDesc(m, sym.loc.t, dkVar)])
 
 proc varInDynamicLib(m: BModule, sym: PSym) =
   var lib = sym.annex
-  var extname = sym.loc.r
+  var extname = sym.loc.snippet
   loadDynamicLib(m, lib)
   incl(sym.loc.flags, lfIndirect)
   var tmp = mangleDynLibProc(sym)
-  sym.loc.r = tmp             # from now on we only need the internal name
+  sym.loc.snippet = tmp             # from now on we only need the internal name
   inc(m.labels, 2)
   appcg(m, m.s[cfsDynLibInit],
       "$1 = ($2*) #nimGetProcAddr($3, $4);$n",
-      [tmp, getTypeDesc(m, sym.typ, skVar), lib.name, makeCString($extname)])
+      [tmp, getTypeDesc(m, sym.typ, dkVar), lib.name, makeCString($extname)])
   m.s[cfsVars].addf("$2* $1;$n",
-      [sym.loc.r, getTypeDesc(m, sym.loc.t, skVar)])
+      [sym.loc.snippet, getTypeDesc(m, sym.loc.t, dkVar)])
 
 proc symInDynamicLibPartial(m: BModule, sym: PSym) =
-  sym.loc.r = mangleDynLibProc(sym)
+  sym.loc.snippet = mangleDynLibProc(sym)
   sym.typ.sym = nil           # generate a new name
 
 proc cgsymImpl(m: BModule; sym: PSym) {.inline.} =
@@ -860,12 +948,14 @@ proc cgsymValue(m: BModule, name: string): Rope =
     cgsymImpl m, sym
   else:
     rawMessage(m.config, errGenerated, "system module needs: " & name)
-  result = sym.loc.r
+  result = sym.loc.snippet
   if m.hcrOn and sym != nil and sym.kind in {skProc..skIterator}:
     result.addActualSuffixForHCR(m.module, sym)
 
 proc generateHeaders(m: BModule) =
-  m.s[cfsHeaders].add("\L#include \"nimbase.h\"\L")
+  var nimbase = m.config.nimbasePattern
+  if nimbase == "": nimbase = "nimbase.h"
+  m.s[cfsHeaders].addf("\L#include \"$1\"\L", [nimbase])
 
   for it in m.headerFiles:
     if it[0] == '#':
@@ -914,11 +1004,19 @@ proc closureSetup(p: BProc, prc: PSym) =
     linefmt(p, cpsStmts, "$1 = ($2) ClE_0;$n",
             [rdLoc(env.loc), getTypeDesc(p.module, env.typ)])
 
+const harmless = {nkConstSection, nkTypeSection, nkEmpty, nkCommentStmt, nkTemplateDef,
+                  nkMacroDef, nkMixinStmt, nkBindStmt, nkFormalParams} +
+                  declarativeDefs
+
 proc containsResult(n: PNode): bool =
   result = false
   case n.kind
-  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit, nkFormalParams:
+  of succ(nkEmpty)..pred(nkSym), succ(nkSym)..nkNilLit, harmless:
     discard
+  of nkReturnStmt:
+    for i in 0..<n.len:
+      if containsResult(n[i]): return true
+    result = n.len > 0 and n[0].kind == nkEmpty
   of nkSym:
     if n.sym.kind == skResult:
       result = true
@@ -926,11 +1024,8 @@ proc containsResult(n: PNode): bool =
     for i in 0..<n.len:
       if containsResult(n[i]): return true
 
-const harmless = {nkConstSection, nkTypeSection, nkEmpty, nkCommentStmt, nkTemplateDef,
-                  nkMacroDef, nkMixinStmt, nkBindStmt, nkFormalParams} +
-                  declarativeDefs
-
 proc easyResultAsgn(n: PNode): PNode =
+  result = nil
   case n.kind
   of nkStmtList, nkStmtListExpr:
     var i = 0
@@ -949,7 +1044,7 @@ proc easyResultAsgn(n: PNode): PNode =
 type
   InitResultEnum = enum Unknown, InitSkippable, InitRequired
 
-proc allPathsAsgnResult(n: PNode): InitResultEnum =
+proc allPathsAsgnResult(p: BProc; n: PNode): InitResultEnum =
   # Exceptions coming from calls don't have not be considered here:
   #
   # proc bar(): string = raise newException(...)
@@ -964,7 +1059,7 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
   #   echo "a was not written to"
   #
   template allPathsInBranch(it) =
-    let a = allPathsAsgnResult(it)
+    let a = allPathsAsgnResult(p, it)
     case a
     of InitRequired: return InitRequired
     of InitSkippable: discard
@@ -976,14 +1071,20 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
   case n.kind
   of nkStmtList, nkStmtListExpr:
     for it in n:
-      result = allPathsAsgnResult(it)
+      result = allPathsAsgnResult(p, it)
       if result != Unknown: return result
   of nkAsgn, nkFastAsgn, nkSinkAsgn:
     if n[0].kind == nkSym and n[0].sym.kind == skResult:
-      if not containsResult(n[1]): result = InitSkippable
+      if not containsResult(n[1]):
+        if allPathsAsgnResult(p, n[1]) == InitRequired:
+          result = InitRequired
+        else:
+          result = InitSkippable
       else: result = InitRequired
     elif containsResult(n):
       result = InitRequired
+    else:
+      result = allPathsAsgnResult(p, n[1])
   of nkReturnStmt:
     if n.len > 0:
       if n[0].kind == nkEmpty and result != InitSkippable:
@@ -992,7 +1093,7 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
         # initialized. This avoids cases like #9286 where this heuristic lead to
         # wrong code being generated.
         result = InitRequired
-      else: result = allPathsAsgnResult(n[0])
+      else: result = allPathsAsgnResult(p, n[0])
   of nkIfStmt, nkIfExpr:
     var exhaustive = false
     result = InitSkippable
@@ -1018,9 +1119,9 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
   of nkWhileStmt:
     # some dubious code can assign the result in the 'while'
     # condition and that would be fine. Everything else isn't:
-    result = allPathsAsgnResult(n[0])
+    result = allPathsAsgnResult(p, n[0])
     if result == Unknown:
-      result = allPathsAsgnResult(n[1])
+      result = allPathsAsgnResult(p, n[1])
       # we cannot assume that the 'while' loop is really executed at least once:
       if result == InitSkippable: result = Unknown
   of harmless:
@@ -1045,9 +1146,21 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
     allPathsInBranch(n[0])
     for i in 1..<n.len:
       if n[i].kind == nkFinally:
-        result = allPathsAsgnResult(n[i].lastSon)
+        result = allPathsAsgnResult(p, n[i].lastSon)
       else:
         allPathsInBranch(n[i].lastSon)
+  of nkCallKinds:
+    if canRaiseDisp(p, n[0]):
+      result = InitRequired
+    else:
+      for i in 0..<n.safeLen:
+        allPathsInBranch(n[i])
+  of nkRaiseStmt:
+    result = InitRequired
+  of nkChckRangeF, nkChckRange64, nkChckRange:
+    # TODO: more checks might need to be covered like overflow, indexDefect etc.
+    # bug #22852
+    result = InitRequired
   else:
     for i in 0..<n.safeLen:
       allPathsInBranch(n[i])
@@ -1055,14 +1168,14 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum =
 proc getProcTypeCast(m: BModule, prc: PSym): Rope =
   result = getTypeDesc(m, prc.loc.t)
   if prc.typ.callConv == ccClosure:
-    var rettype, params: Rope
+    var rettype, params: Rope = ""
     var check = initIntSet()
     genProcParams(m, prc.typ, rettype, params, check)
     result = "$1(*)$2" % [rettype, params]
 
 proc genProcBody(p: BProc; procBody: PNode) =
   genStmts(p, procBody) # modifies p.locals, p.init, etc.
-  if {nimErrorFlagAccessed, nimErrorFlagDeclared} * p.flags == {nimErrorFlagAccessed}:
+  if {nimErrorFlagAccessed, nimErrorFlagDeclared, nimErrorFlagDisabled} * p.flags == {nimErrorFlagAccessed}:
     p.flags.incl nimErrorFlagDeclared
     p.blocks[0].sections[cpsLocals].add(ropecg(p.module, "NIM_BOOL* nimErr_;$n", []))
     p.blocks[0].sections[cpsInit].add(ropecg(p.module, "nimErr_ = #nimErrorFlag();$n", []))
@@ -1070,38 +1183,54 @@ proc genProcBody(p: BProc; procBody: PNode) =
 proc isNoReturn(m: BModule; s: PSym): bool {.inline.} =
   sfNoReturn in s.flags and m.config.exc != excGoto
 
-proc genProcAux(m: BModule, prc: PSym) =
+proc genProcAux*(m: BModule, prc: PSym) =
   var p = newProc(prc, m)
   var header = newRopeAppender()
-  genProcHeader(m, prc, header)
+  let isCppMember = m.config.backend == backendCpp and sfCppMember * prc.flags != {}
+  if isCppMember:
+    genMemberProcHeader(m, prc, header)
+  else:
+    genProcHeader(m, prc, header)
   var returnStmt: Rope = ""
   assert(prc.ast != nil)
 
-  var procBody = transformBody(m.g.graph, m.idgen, prc, dontUseCache)
+  var procBody = transformBody(m.g.graph, m.idgen, prc, {})
   if sfInjectDestructors in prc.flags:
     procBody = injectDestructorCalls(m.g.graph, m.idgen, prc, procBody)
 
-  if sfPure notin prc.flags and prc.typ[0] != nil:
+  let tmpInfo = prc.info
+  discard freshLineInfo(p, prc.info)
+
+  if sfPure notin prc.flags and prc.typ.returnType != nil:
     if resultPos >= prc.ast.len:
       internalError(m.config, prc.info, "proc has no result symbol")
     let resNode = prc.ast[resultPos]
     let res = resNode.sym # get result symbol
-    if not isInvalidReturnType(m.config, prc.typ):
+    if not isInvalidReturnType(m.config, prc.typ) and sfConstructor notin prc.flags:
       if sfNoInit in prc.flags: incl(res.flags, sfNoInit)
       if sfNoInit in prc.flags and p.module.compileToCpp and (let val = easyResultAsgn(procBody); val != nil):
         var decl = localVarDecl(p, resNode)
-        var a: TLoc
-        initLocExprSingleUse(p, val, a)
+        var a: TLoc = initLocExprSingleUse(p, val)
         linefmt(p, cpsStmts, "$1 = $2;$n", [decl, rdLoc(a)])
       else:
         # declare the result symbol:
         assignLocalVar(p, resNode)
-        assert(res.loc.r != "")
-        initLocalVar(p, res, immediateAsgn=false)
+        assert(res.loc.snippet != "")
+        if p.config.selectedGC in {gcArc, gcAtomicArc, gcOrc} and
+            allPathsAsgnResult(p, procBody) == InitSkippable:
+          # In an ideal world the codegen could rely on injectdestructors doing its job properly
+          # and then the analysis step would not be required.
+          discard "result init optimized out"
+        else:
+          initLocalVar(p, res, immediateAsgn=false)
       returnStmt = ropecg(p.module, "\treturn $1;$n", [rdLoc(res.loc)])
+    elif sfConstructor in prc.flags:
+      resNode.sym.loc.flags.incl lfIndirect
+      fillLoc(resNode.sym.loc, locParam, resNode, "this", OnHeap)
+      prc.loc.snippet = getTypeDesc(m, resNode.sym.loc.t, dkVar)
     else:
       fillResult(p.config, resNode, prc.typ)
-      assignParam(p, res, prc.typ[0])
+      assignParam(p, res, prc.typ.returnType)
       # We simplify 'unsureAsgn(result, nil); unsureAsgn(result, x)'
       # to 'unsureAsgn(result, x)'
       # Sketch why this is correct: If 'result' points to a stack location
@@ -1109,7 +1238,7 @@ proc genProcAux(m: BModule, prc: PSym) =
       # global is either 'nil' or points to valid memory and so the RC operation
       # succeeds without touching not-initialized memory.
       if sfNoInit in prc.flags: discard
-      elif allPathsAsgnResult(procBody) == InitSkippable: discard
+      elif allPathsAsgnResult(p, procBody) == InitSkippable: discard
       else:
         resetLoc(p, res.loc)
       if skipTypes(res.typ, abstractInst).kind == tyArray:
@@ -1119,17 +1248,19 @@ proc genProcAux(m: BModule, prc: PSym) =
   for i in 1..<prc.typ.n.len:
     let param = prc.typ.n[i].sym
     if param.typ.isCompileTimeOnly: continue
-    assignParam(p, param, prc.typ[0])
+    assignParam(p, param, prc.typ.returnType)
   closureSetup(p, prc)
   genProcBody(p, procBody)
 
-  var generatedProc: Rope
+  prc.info = tmpInfo
+
+  var generatedProc: Rope = ""
   generatedProc.genCLineDir prc.info, m.config
   if isNoReturn(p.module, prc):
-    if hasDeclspec in extccomp.CC[p.config.cCompiler].props:
+    if hasDeclspec in extccomp.CC[p.config.cCompiler].props and not isCppMember:
       header = "__declspec(noreturn) " & header
   if sfPure in prc.flags:
-    if hasDeclspec in extccomp.CC[p.config.cCompiler].props:
+    if hasDeclspec in extccomp.CC[p.config.cCompiler].props and not isCppMember:
       header = "__declspec(naked) " & header
     generatedProc.add ropecg(p.module, "$1 {$n$2$3$4}$N$N",
                          [header, p.s(cpsLocals), p.s(cpsInit), p.s(cpsStmts)])
@@ -1161,7 +1292,7 @@ proc genProcAux(m: BModule, prc: PSym) =
   m.s[cfsProcs].add(generatedProc)
   if isReloadable(m, prc):
     m.s[cfsDynLibInit].addf("\t$1 = ($3) hcrRegisterProc($4, \"$1\", (void*)$2);$n",
-         [prc.loc.r, prc.loc.r & "_actual", getProcTypeCast(m, prc), getModuleDllPath(m, prc)])
+         [prc.loc.snippet, prc.loc.snippet & "_actual", getProcTypeCast(m, prc), getModuleDllPath(m, prc)])
 
 proc requiresExternC(m: BModule; sym: PSym): bool {.inline.} =
   result = (sfCompileToCpp in m.module.flags and
@@ -1174,7 +1305,7 @@ proc requiresExternC(m: BModule; sym: PSym): bool {.inline.} =
 
 proc genProcPrototype(m: BModule, sym: PSym) =
   useHeader(m, sym)
-  if lfNoDecl in sym.loc.flags: return
+  if lfNoDecl in sym.loc.flags or sfCppMember * sym.flags != {}: return
   if lfDynamicLib in sym.loc.flags:
     if sym.itemId.module != m.module.position and
         not containsOrIncl(m.declaredThings, sym.id):
@@ -1210,6 +1341,20 @@ proc genProcNoForward(m: BModule, prc: PSym) =
   if lfNoDecl in prc.loc.flags:
     fillProcLoc(m, prc.ast[namePos])
     genProcPrototype(m, prc)
+  elif lfDynamicLib in prc.loc.flags:
+    var q = findPendingModule(m, prc)
+    fillProcLoc(q, prc.ast[namePos])
+    genProcPrototype(m, prc)
+    if q != nil and not containsOrIncl(q.declaredThings, prc.id):
+      symInDynamicLib(q, prc)
+      # register the procedure even though it is in a different dynamic library and will not be
+      # reloadable (and has no _actual suffix) - other modules will need to be able to get it through
+      # the hcr dynlib (also put it in the DynLibInit section - right after it gets loaded)
+      if isReloadable(q, prc):
+        q.s[cfsDynLibInit].addf("\t$1 = ($2) hcrRegisterProc($3, \"$1\", (void*)$1);$n",
+            [prc.loc.snippet, getTypeDesc(q, prc.loc.t), getModuleDllPath(m, q.module)])
+    else:
+      symInDynamicLibPartial(m, prc)
   elif prc.typ.callConv == ccInline:
     # We add inline procs to the calling module to enable C based inlining.
     # This also means that a check with ``q.declaredThings`` is wrong, we need
@@ -1224,24 +1369,10 @@ proc genProcNoForward(m: BModule, prc: PSym) =
       #elif {sfExportc, sfImportc} * prc.flags == {}:
       #  # reset name to restore consistency in case of hashing collisions:
       #  echo "resetting ", prc.id, " by ", m.module.name.s
-      #  prc.loc.r = nil
-      #  prc.loc.r = mangleName(m, prc)
+      #  prc.loc.snippet = nil
+      #  prc.loc.snippet = mangleName(m, prc)
       genProcPrototype(m, prc)
       genProcAux(m, prc)
-  elif lfDynamicLib in prc.loc.flags:
-    var q = findPendingModule(m, prc)
-    fillProcLoc(q, prc.ast[namePos])
-    genProcPrototype(m, prc)
-    if q != nil and not containsOrIncl(q.declaredThings, prc.id):
-      symInDynamicLib(q, prc)
-      # register the procedure even though it is in a different dynamic library and will not be
-      # reloadable (and has no _actual suffix) - other modules will need to be able to get it through
-      # the hcr dynlib (also put it in the DynLibInit section - right after it gets loaded)
-      if isReloadable(q, prc):
-        q.s[cfsDynLibInit].addf("\t$1 = ($2) hcrRegisterProc($3, \"$1\", (void*)$1);$n",
-            [prc.loc.r, getTypeDesc(q, prc.loc.t), getModuleDllPath(m, q.module)])
-    else:
-      symInDynamicLibPartial(m, prc)
   elif sfImportc notin prc.flags:
     var q = findPendingModule(m, prc)
     fillProcLoc(q, prc.ast[namePos])
@@ -1251,7 +1382,7 @@ proc genProcNoForward(m: BModule, prc: PSym) =
     if isReloadable(m, prc) and prc.id notin m.declaredProtos and
       q != nil and q.module.id != m.module.id:
       m.s[cfsDynLibInit].addf("\t$1 = ($2) hcrGetProc($3, \"$1\");$n",
-           [prc.loc.r, getProcTypeCast(m, prc), getModuleDllPath(m, prc)])
+           [prc.loc.snippet, getProcTypeCast(m, prc), getModuleDllPath(m, prc)])
     genProcPrototype(m, prc)
     if q != nil and not containsOrIncl(q.declaredThings, prc.id):
       # make sure there is a "prototype" in the external module
@@ -1304,24 +1435,24 @@ proc genVarPrototype(m: BModule, n: PNode) =
     return
   if sym.owner.id != m.module.id:
     # else we already have the symbol generated!
-    assert(sym.loc.r != "")
+    assert(sym.loc.snippet != "")
+    incl(m.declaredThings, sym.id)
     if sfThread in sym.flags:
       declareThreadVar(m, sym, true)
     else:
-      incl(m.declaredThings, sym.id)
       if sym.kind in {skLet, skVar, skField, skForVar} and sym.alignment > 0:
         m.s[cfsVars].addf "NIM_ALIGN($1) ", [rope(sym.alignment)]
       m.s[cfsVars].add(if m.hcrOn: "static " else: "extern ")
-      m.s[cfsVars].add(getTypeDesc(m, sym.loc.t, skVar))
+      m.s[cfsVars].add(getTypeDesc(m, sym.loc.t, dkVar))
       if m.hcrOn: m.s[cfsVars].add("*")
       if lfDynamicLib in sym.loc.flags: m.s[cfsVars].add("*")
       if sfRegister in sym.flags: m.s[cfsVars].add(" register")
       if sfVolatile in sym.flags: m.s[cfsVars].add(" volatile")
       if sfNoalias in sym.flags: m.s[cfsVars].add(" NIM_NOALIAS")
-      m.s[cfsVars].addf(" $1;$n", [sym.loc.r])
+      m.s[cfsVars].addf(" $1;$n", [sym.loc.snippet])
       if m.hcrOn: m.initProc.procSec(cpsLocals).addf(
-        "\t$1 = ($2*)hcrGetGlobal($3, \"$1\");$n", [sym.loc.r,
-        getTypeDesc(m, sym.loc.t, skVar), getModuleDllPath(m, sym)])
+        "\t$1 = ($2*)hcrGetGlobal($3, \"$1\");$n", [sym.loc.snippet,
+        getTypeDesc(m, sym.loc.t, dkVar), getModuleDllPath(m, sym)])
 
 proc addNimDefines(result: var Rope; conf: ConfigRef) {.inline.} =
   result.addf("#define NIM_INTBITS $1\L", [
@@ -1353,17 +1484,19 @@ proc getFileHeader(conf: ConfigRef; cfile: Cfile): Rope =
 
 proc getSomeNameForModule(conf: ConfigRef, filename: AbsoluteFile): Rope =
   ## Returns a mangled module name.
-  result.add mangleModuleName(conf, filename).mangle
+  result = mangleModuleName(conf, filename).mangle
 
 proc getSomeNameForModule(m: BModule): Rope =
   ## Returns a mangled module name.
   assert m.module.kind == skModule
   assert m.module.owner.kind == skPackage
-  result.add mangleModuleName(m.g.config, m.filename).mangle
+  result = mangleModuleName(m.g.config, m.filename).mangle
 
 proc getSomeInitName(m: BModule, suffix: string): Rope =
   if not m.hcrOn:
     result = getSomeNameForModule(m)
+  else:
+    result = ""
   result.add suffix
 
 proc getInitName(m: BModule): Rope =
@@ -1382,10 +1515,10 @@ proc genMainProc(m: BModule) =
   ## this function is called in cgenWriteModules after all modules are closed,
   ## it means raising dependency on the symbols is too late as it will not propagate
   ## into other modules, only simple rope manipulations are allowed
-
-  var preMainCode: Rope
+  var preMainCode: Rope = ""
   if m.hcrOn:
     proc loadLib(handle: string, name: string): Rope =
+      result = ""
       let prc = magicsys.getCompilerProc(m.g.graph, name)
       assert prc != nil
       let n = newStrNode(nkStrLit, prc.annex.path.strVal)
@@ -1397,20 +1530,23 @@ proc genMainProc(m: BModule) =
                        [handle, strLit])
 
     preMainCode.add(loadLib("hcr_handle", "hcrGetProc"))
-    preMainCode.add("\tvoid* rtl_handle;\L")
-    preMainCode.add(loadLib("rtl_handle", "nimGC_setStackBottom"))
-    preMainCode.add(hcrGetProcLoadCode(m, "nimGC_setStackBottom", "nimrtl_", "rtl_handle", "nimGetProcAddr"))
-    preMainCode.add("\tinner = PreMain;\L")
-    preMainCode.add("\tinitStackBottomWith_actual((void *)&inner);\L")
-    preMainCode.add("\t(*inner)();\L")
+    if m.config.selectedGC in {gcArc, gcAtomicArc, gcOrc}:
+      preMainCode.add("\t$1PreMain();\L" % [rope m.config.nimMainPrefix])
+    else:
+      preMainCode.add("\tvoid* rtl_handle;\L")
+      preMainCode.add(loadLib("rtl_handle", "nimGC_setStackBottom"))
+      preMainCode.add(hcrGetProcLoadCode(m, "nimGC_setStackBottom", "nimrtl_", "rtl_handle", "nimGetProcAddr"))
+      preMainCode.add("\tinner = $1PreMain;\L" % [rope m.config.nimMainPrefix])
+      preMainCode.add("\tinitStackBottomWith_actual((void *)&inner);\L")
+      preMainCode.add("\t(*inner)();\L")
   else:
     preMainCode.add("\t$1PreMain();\L" % [rope m.config.nimMainPrefix])
 
-  var posixCmdLine: Rope
+  var posixCmdLine: Rope = ""
   if optNoMain notin m.config.globalOptions:
-    posixCmdLine.add "\tN_LIB_PRIVATE int cmdCount;\L"
-    posixCmdLine.add "\tN_LIB_PRIVATE char** cmdLine;\L"
-    posixCmdLine.add "\tN_LIB_PRIVATE char** gEnv;\L"
+    posixCmdLine.add "N_LIB_PRIVATE int cmdCount;\L"
+    posixCmdLine.add "N_LIB_PRIVATE char** cmdLine;\L"
+    posixCmdLine.add "N_LIB_PRIVATE char** gEnv;\L"
 
   const
     # The use of a volatile function pointer to call Pre/NimMainInner
@@ -1423,15 +1559,15 @@ proc genMainProc(m: BModule) =
       "}$N$N" &
       "$4" &
       "N_LIB_PRIVATE void $3PreMain(void) {$N" &
-      "\t##if $5$N" & # 1 for volatile call, 0 for non-volatile
+      "##if $5$N" & # 1 for volatile call, 0 for non-volatile
       "\tvoid (*volatile inner)(void);$N" &
       "\tinner = $3PreMainInner;$N" &
       "$1" &
       "\t(*inner)();$N" &
-      "\t##else$N" &
+      "##else$N" &
       "$1" &
       "\t$3PreMainInner();$N" &
-      "\t##endif$N" &
+      "##endif$N" &
       "}$N$N"
 
     MainProcs =
@@ -1446,17 +1582,17 @@ proc genMainProc(m: BModule) =
 
     NimMainProc =
       "N_CDECL(void, $5NimMain)(void) {$N" &
-      "\t##if $6$N" & # 1 for volatile call, 0 for non-volatile
+      "##if $6$N" & # 1 for volatile call, 0 for non-volatile
       "\tvoid (*volatile inner)(void);$N" &
       "$4" &
       "\tinner = $5NimMainInner;$N" &
       "$2" &
       "\t(*inner)();$N" &
-      "\t##else$N" &
+      "##else$N" &
       "$4" &
       "$2" &
       "\t$5NimMainInner();$N" &
-      "\t##endif$N" &
+      "##endif$N" &
       "}$N$N"
 
     NimMainBody = NimMainInner & NimMainProc
@@ -1487,7 +1623,7 @@ proc genMainProc(m: BModule) =
     WinCDllMain =
       "BOOL WINAPI DllMain(HINSTANCE hinstDLL, DWORD fwdreason, $N" &
       "                    LPVOID lpvReserved) {$N" &
-      "\tif(fwdreason == DLL_PROCESS_ATTACH) {$N" & MainProcs & "}$N" &
+      "\tif (fwdreason == DLL_PROCESS_ATTACH) {$N" & MainProcs & "\t}$N" &
       "\treturn 1;$N}$N$N"
 
     PosixNimDllMain = WinNimDllMain
@@ -1521,11 +1657,11 @@ proc genMainProc(m: BModule) =
     m.includeHeader("<libc/component.h>")
 
   let initStackBottomCall =
-    if m.config.target.targetOS == osStandalone or m.config.selectedGC in {gcNone, gcArc, gcOrc}: "".rope
+    if m.config.target.targetOS == osStandalone or m.config.selectedGC in {gcNone, gcArc, gcAtomicArc, gcOrc}: "".rope
     else: ropecg(m, "\t#initStackBottomWith((void *)&inner);$N", [])
   inc(m.labels)
 
-  let isVolatile = if m.config.selectedGC notin {gcNone, gcArc, gcOrc}: "1" else: "0"
+  let isVolatile = if m.config.selectedGC notin {gcNone, gcArc, gcAtomicArc, gcOrc}: "1" else: "0"
   appcg(m, m.s[cfsProcs], PreMainBody, [m.g.mainDatInit, m.g.otherModsInit, m.config.nimMainPrefix, posixCmdLine, isVolatile])
 
   if m.config.target.targetOS == osWindows and
@@ -1624,7 +1760,7 @@ proc registerModuleToMain(g: BModuleList; m: BModule) =
     hcrModuleMeta.addf("\t\"\"};$n", [])
     hcrModuleMeta.addf("$nN_LIB_EXPORT N_NIMCALL(void**, HcrGetImportedModules)() { return (void**)hcr_module_list; }$n", [])
     hcrModuleMeta.addf("$nN_LIB_EXPORT N_NIMCALL(char*, HcrGetSigHash)() { return \"$1\"; }$n$n",
-                          [($sigHash(m.module)).rope])
+                          [($sigHash(m.module, m.config)).rope])
     if sfMainModule in m.module.flags:
       g.mainModProcs.add(hcrModuleMeta)
       g.mainModProcs.addf("static void* hcr_handle;$N", [])
@@ -1665,7 +1801,7 @@ proc registerModuleToMain(g: BModuleList; m: BModule) =
   if sfSystemModule in m.module.flags:
     if emulatedThreadVars(m.config) and m.config.target.targetOS != osStandalone:
       g.mainDatInit.add(ropecg(m, "\t#initThreadVarsEmulation();$N", []))
-    if m.config.target.targetOS != osStandalone and m.config.selectedGC notin {gcNone, gcArc, gcOrc}:
+    if m.config.target.targetOS != osStandalone and m.config.selectedGC notin {gcNone, gcArc, gcAtomicArc, gcOrc}:
       g.mainDatInit.add(ropecg(m, "\t#initStackBottomWith((void *)&inner);$N", []))
 
   if m.s[cfsInitProc].len > 0:
@@ -1690,7 +1826,7 @@ proc genDatInitCode(m: BModule) =
 
   # we don't want to break into such init code - could happen if a line
   # directive from a function written by the user spills after itself
-  genCLineDir(prc, "generated_not_to_break_here", 999999, m.config)
+  genCLineDir(prc, InvalidFileIdx, 999999, m.config)
 
   for i in cfsTypeInit1..cfsDynLibInit:
     if m.s[i].len != 0:
@@ -1712,14 +1848,14 @@ proc hcrGetProcLoadCode(m: BModule, sym, prefix, handle, getProcFunc: string): R
 
   var extname = prefix & sym
   var tmp = mangleDynLibProc(prc)
-  prc.loc.r = tmp
+  prc.loc.snippet = tmp
   prc.typ.sym = nil
 
   if not containsOrIncl(m.declaredThings, prc.id):
-    m.s[cfsVars].addf("static $2 $1;$n", [prc.loc.r, getTypeDesc(m, prc.loc.t, skVar)])
+    m.s[cfsVars].addf("static $2 $1;$n", [prc.loc.snippet, getTypeDesc(m, prc.loc.t, dkVar)])
 
   result = "\t$1 = ($2) $3($4, $5);$n" %
-      [tmp, getTypeDesc(m, prc.typ, skVar), getProcFunc.rope, handle.rope, makeCString(prefix & sym)]
+      [tmp, getTypeDesc(m, prc.typ, dkVar), getProcFunc.rope, handle.rope, makeCString(prefix & sym)]
 
 proc genInitCode(m: BModule) =
   ## this function is called in cgenWriteModules after all modules are closed,
@@ -1731,7 +1867,7 @@ proc genInitCode(m: BModule) =
     [rope(if m.hcrOn: "N_LIB_EXPORT" else: "N_LIB_PRIVATE"), initname]
   # we don't want to break into such init code - could happen if a line
   # directive from a function written by the user spills after itself
-  genCLineDir(prc, "generated_not_to_break_here", 999999, m.config)
+  genCLineDir(prc, InvalidFileIdx, 999999, m.config)
   if m.typeNodes > 0:
     if m.hcrOn:
       appcg(m, m.s[cfsTypeInit1], "\t#TNimNode* $1;$N", [m.typeNodesName])
@@ -1795,7 +1931,7 @@ proc genInitCode(m: BModule) =
     if beforeRetNeeded in m.initProc.flags:
       prc.add("\tBeforeRet_: ;\n")
 
-    if sfMainModule in m.module.flags and m.config.exc == excGoto:
+    if m.config.exc == excGoto:
       if getCompilerProc(m.g.graph, "nimTestErrorFlag") != nil:
         m.appcg(prc, "\t#nimTestErrorFlag();$n", [])
 
@@ -1843,6 +1979,40 @@ proc genInitCode(m: BModule) =
 
   registerModuleToMain(m.g, m)
 
+proc postprocessCode(conf: ConfigRef, r: var Rope) =
+  # find the first directive
+  var f = r.find(postprocessDirStart)
+  if f == -1:
+    return
+
+  var
+    nimlnDirLastF = ""
+
+  var res: Rope = r.substr(0, f - 1)
+  while f != -1:
+    var
+      e = r.find(postprocessDirEnd, f + 1)
+      dir = r.substr(f + 1, e - 1).split(postprocessDirSep)
+    case dir[0]
+    of "nimln":
+      if dir[2] == nimlnDirLastF:
+        res.add("nimln_(" & dir[1] & ");")
+      else:
+        res.add("nimlf_(" & dir[1] & ", " & quotedFilename(conf, dir[2].parseInt.FileIndex) & ");")
+        nimlnDirLastF = dir[2]
+    else:
+      raiseAssert "unexpected postprocess directive"
+
+    # find the next directive
+    f = r.find(postprocessDirStart, e + 1)
+    # copy the code until the next directive
+    if f != -1:
+      res.add(r.substr(e + 1, f - 1))
+    else:
+      res.add(r.substr(e + 1))
+
+  r = res
+
 proc genModule(m: BModule, cfile: Cfile): Rope =
   var moduleIsEmpty = true
 
@@ -1855,8 +2025,6 @@ proc genModule(m: BModule, cfile: Cfile): Rope =
     openNamespaceNim(m.config.cppCustomNamespace, result)
   if m.s[cfsFrameDefines].len > 0:
     result.add(m.s[cfsFrameDefines])
-  else:
-    result.add("#define nimfr_(x, y)\n#define nimln_(x, y)\n")
 
   for i in cfsForwardTypes..cfsProcs:
     if m.s[i].len > 0:
@@ -1873,9 +2041,17 @@ proc genModule(m: BModule, cfile: Cfile): Rope =
   if m.config.cppCustomNamespace.len > 0:
     closeNamespaceNim(result)
 
+  if optLineDir in m.config.options:
+    var srcFileDefs = ""
+    for fi in 0..m.config.m.fileInfos.high:
+      srcFileDefs.add("#define FX_" & $fi & " " & makeSingleLineCString(toFullPath(m.config, fi.FileIndex)) & "\n")
+    result = srcFileDefs & result
+
   if moduleIsEmpty:
     result = ""
 
+  postprocessCode(m.config, result)
+
 proc initProcOptions(m: BModule): TOptions =
   let opts = m.config.options
   if sfSystemModule in m.module.flags: opts-{optStackTrace} else: opts
@@ -1900,7 +2076,7 @@ proc rawNewModule(g: BModuleList; module: PSym, filename: AbsoluteFile): BModule
   result.preInitProc = newProc(nil, result)
   result.preInitProc.flags.incl nimErrorFlagDisabled
   result.preInitProc.labels = 100_000 # little hack so that unique temporaries are generated
-  initNodeTable(result.dataCache)
+  result.dataCache = initNodeTable()
   result.typeStack = @[]
   result.typeNodesName = getTempName(result)
   result.nimTypesName = getTempName(result)
@@ -1929,10 +2105,7 @@ template injectG() {.dirty.} =
     graph.backend = newModuleList(graph)
   let g = BModuleList(graph.backend)
 
-when not defined(nimHasSinkInference):
-  {.pragma: nosinks.}
-
-proc myOpen(graph: ModuleGraph; module: PSym; idgen: IdGenerator): PPassContext {.nosinks.} =
+proc setupCgen*(graph: ModuleGraph; module: PSym; idgen: IdGenerator): PPassContext =
   injectG()
   result = newModule(g, module, graph.config)
   result.idgen = idgen
@@ -2000,7 +2173,7 @@ proc addHcrInitGuards(p: BProc, n: PNode, inInitGuard: var bool) =
 
 proc genTopLevelStmt*(m: BModule; n: PNode) =
   ## Also called from `ic/cbackend.nim`.
-  if passes.skipCodegen(m.config, n): return
+  if pipelineutils.skipCodegen(m.config, n): return
   m.initProc.options = initProcOptions(m)
   #softRnl = if optLineDir in m.config.options: noRnl else: rnl
   # XXX replicate this logic!
@@ -2013,12 +2186,6 @@ proc genTopLevelStmt*(m: BModule; n: PNode) =
   else:
     genProcBody(m.initProc, transformedN)
 
-proc myProcess(b: PPassContext, n: PNode): PNode =
-  result = n
-  if b != nil:
-    var m = BModule(b)
-    genTopLevelStmt(m, n)
-
 proc shouldRecompile(m: BModule; code: Rope, cfile: Cfile): bool =
   if optForceFullMake notin m.config.globalOptions:
     if not moduleHasChanged(m.g.graph, m.module):
@@ -2084,6 +2251,22 @@ proc updateCachedModule(m: BModule) =
   cf.flags = {CfileFlag.Cached}
   addFileToCompile(m.config, cf)
 
+proc generateLibraryDestroyGlobals(graph: ModuleGraph; m: BModule; body: PNode; isDynlib: bool): PSym =
+  let procname = getIdent(graph.cache, "NimDestroyGlobals")
+  result = newSym(skProc, procname, m.idgen, m.module.owner, m.module.info)
+  result.typ = newProcType(m.module.info, m.idgen, m.module.owner)
+  result.typ.callConv = ccCDecl
+  incl result.flags, sfExportc
+  result.loc.snippet = "NimDestroyGlobals"
+  if isDynlib:
+    incl(result.loc.flags, lfExportLib)
+
+  let theProc = newNodeI(nkProcDef, m.module.info, bodyPos+1)
+  for i in 0..<theProc.len: theProc[i] = newNodeI(nkEmpty, m.module.info)
+  theProc[namePos] = newSymNode(result)
+  theProc[bodyPos] = body
+  result.ast = theProc
+
 proc finalCodegenActions*(graph: ModuleGraph; m: BModule; n: PNode) =
   ## Also called from IC.
   if sfMainModule in m.module.flags:
@@ -2095,7 +2278,14 @@ proc finalCodegenActions*(graph: ModuleGraph; m: BModule; n: PNode) =
     if {optGenStaticLib, optGenDynLib, optNoMain} * m.config.globalOptions == {}:
       for i in countdown(high(graph.globalDestructors), 0):
         n.add graph.globalDestructors[i]
-  if passes.skipCodegen(m.config, n): return
+    else:
+      var body = newNodeI(nkStmtList, m.module.info)
+      for i in countdown(high(graph.globalDestructors), 0):
+        body.add graph.globalDestructors[i]
+      body.flags.incl nfTransf # should not be further transformed
+      let dtor = generateLibraryDestroyGlobals(graph, m, body, optGenDynLib in m.config.globalOptions)
+      genProcAux(m, dtor)
+  if pipelineutils.skipCodegen(m.config, n): return
   if moduleHasChanged(graph, m.module):
     # if the module is cached, we don't regenerate the main proc
     # nor the dispatchers? But if the dispatchers changed?
@@ -2106,7 +2296,10 @@ proc finalCodegenActions*(graph: ModuleGraph; m: BModule; n: PNode) =
 
     if m.hcrOn:
       # make sure this is pulled in (meaning hcrGetGlobal() is called for it during init)
-      cgsym(m, "programResult")
+      let sym = magicsys.getCompilerProc(m.g.graph, "programResult")
+      # ignore when not available, could be a module imported early in `system`
+      if sym != nil:
+        cgsymImpl m, sym
       if m.inHcrInitGuard:
         endBlock(m.initProc)
 
@@ -2123,25 +2316,22 @@ proc finalCodegenActions*(graph: ModuleGraph; m: BModule; n: PNode) =
         cgsym(m, "rawWrite")
 
       # raise dependencies on behalf of genMainProc
-      if m.config.target.targetOS != osStandalone and m.config.selectedGC notin {gcNone, gcArc, gcOrc}:
+      if m.config.target.targetOS != osStandalone and m.config.selectedGC notin {gcNone, gcArc, gcAtomicArc, gcOrc}:
         cgsym(m, "initStackBottomWith")
       if emulatedThreadVars(m.config) and m.config.target.targetOS != osStandalone:
         cgsym(m, "initThreadVarsEmulation")
 
       if m.g.forwardedProcs.len == 0:
         incl m.flags, objHasKidsValid
-      let disp = generateMethodDispatchers(graph)
-      for x in disp: genProcAux(m, x.sym)
+      if optMultiMethods in m.g.config.globalOptions or
+          m.g.config.selectedGC notin {gcArc, gcOrc, gcAtomicArc} or
+          vtables notin m.g.config.features:
+        generateIfMethodDispatchers(graph, m.idgen)
+
 
   let mm = m
   m.g.modulesClosed.add mm
 
-
-proc myClose(graph: ModuleGraph; b: PPassContext, n: PNode): PNode =
-  result = n
-  if b == nil: return
-  finalCodegenActions(graph, BModule(b), n)
-
 proc genForwardedProcs(g: BModuleList) =
   # Forward declared proc:s lack bodies when first encountered, so they're given
   # a second pass here
@@ -2168,5 +2358,3 @@ proc cgenWriteModules*(backend: RootRef, config: ConfigRef) =
     m.writeModule(pending=true)
   writeMapping(config, g.mapping)
   if g.generatedHeader != nil: writeHeader(g.generatedHeader)
-
-const cgenPass* = makePass(myOpen, myProcess, myClose)