diff options
Diffstat (limited to 'compiler/cgen.nim')
-rw-r--r-- | compiler/cgen.nim | 1056 |
1 files changed, 677 insertions, 379 deletions
diff --git a/compiler/cgen.nim b/compiler/cgen.nim index b88999088..091f5c842 100644 --- a/compiler/cgen.nim +++ b/compiler/cgen.nim @@ -10,22 +10,34 @@ ## 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 + lowerings, ndi, lineinfos, pathutils, transf, + injectdestructors, astmsgs, modulepaths, pushpoppragmas, + mangleutils + +from expanddefaults import caseObjDefaultBranch + +import pipelineutils + +when defined(nimPreviewSlimSystem): + import std/assertions when not defined(leanCompiler): import spawn, semparallel -import strutils except `%` # collides with ropes.`%` +import std/strutils except `%`, addf # collides with ropes.`%` -from modulegraphs import ModuleGraph, PPassContext -from lineinfos import - warnGcMem, errXMustBeCompileTime, hintDependency, errGenerated, errCannotOpenFile -import dynlib +from ic / ic import ModuleBackendFlag +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]) = @@ -50,23 +62,32 @@ proc addForwardedProc(m: BModule, prc: PSym) = m.g.forwardedProcs.add(prc) proc findPendingModule(m: BModule, s: PSym): BModule = - let ms = s.itemId.module #getModule(s) - result = m.g.modules[ms] + # TODO fixme + if m.config.symbolFiles == v2Sf: + let ms = s.itemId.module #getModule(s) + result = m.g.modules[ms] + else: + var ms = getModule(s) + result = m.g.modules[ms.position] + +proc initLoc(k: TLocKind, lode: PNode, s: TStorageLoc, flags: TLocFlags = {}): TLoc = + result = TLoc(k: k, storage: s, lode: lode, + snippet: "", flags: flags) -proc initLoc(result: var TLoc, k: TLocKind, lode: PNode, s: TStorageLoc) = - result.k = k - result.storage = s - result.lode = lode - result.r = nil - result.flags = {} +proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, r: Rope, s: TStorageLoc) {.inline.} = + # fills the loc if it is not already initialized + if a.k == locNone: + a.k = k + a.lode = lode + a.storage = s + if a.snippet == "": a.snippet = r -proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, r: Rope, s: TStorageLoc) = +proc fillLoc(a: var TLoc, k: TLocKind, lode: PNode, s: TStorageLoc) {.inline.} = # fills the loc if it is not already initialized if a.k == locNone: a.k = k a.lode = lode a.storage = s - if a.r == nil: a.r = r proc t(a: TLoc): PType {.inline.} = if a.lode.kind == nkSym: @@ -90,7 +111,8 @@ proc useHeader(m: BModule, sym: PSym) = let str = getStr(sym.annex.path) m.includeHeader(str) -proc cgsym(m: BModule, name: string): Rope +proc cgsym(m: BModule, name: string) +proc cgsymValue(m: BModule, name: string): Rope proc getCFile(m: BModule): AbsoluteFile @@ -105,11 +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 - -proc cgFormatValue(result: var string; value: Rope) = - for str in leaves(value): - result.add str +import std/macros proc cgFormatValue(result: var string; value: string) = result.add value @@ -156,6 +174,11 @@ macro ropecg(m: BModule, frmt: static[FormatStr], args: untyped): Rope = inc(i) result.add newCall(formatValue, resVar, args[num]) inc(num) + of '^': + flushStrLit() + inc(i) + result.add newCall(formatValue, resVar, args[^1]) + inc(num) of '0'..'9': var j = 0 while true: @@ -186,7 +209,7 @@ macro ropecg(m: BModule, frmt: static[FormatStr], args: untyped): Rope = var ident = newLit(substr(frmt, i, j-1)) i = j flushStrLit() - result.add newCall(formatValue, resVar, newCall(ident"cgsym", m, ident)) + result.add newCall(formatValue, resVar, newCall(ident"cgsymValue", m, ident)) elif frmt[i] == '#' and frmt[i+1] == '$': inc(i, 2) var j = 0 @@ -195,21 +218,24 @@ macro ropecg(m: BModule, frmt: static[FormatStr], args: untyped): Rope = inc(i) let ident = args[j-1] flushStrLit() - result.add newCall(formatValue, resVar, newCall(ident"cgsym", m, ident)) - 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)) + result.add newCall(formatValue, resVar, newCall(ident"cgsymValue", m, ident)) + elif frmt[i] == '#' and frmt[i+1] == '#': + inc(i, 2) + strLit.add("#") + else: + strLit.add(frmt[i]) + inc(i) flushStrLit() result.add newCall(ident"rope", resVar) -proc indentLine(p: BProc, r: Rope): Rope = - result = r - for i in 0..<p.blocks.len: - prepend(result, "\t".rope) +proc addIndent(p: BProc; result: var 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) = @@ -223,36 +249,51 @@ template appcg(p: BProc, sec: TCProcSection, frmt: FormatStr, args: untyped) = p.s(sec).add(ropecg(p.module, frmt, args)) -template line(p: BProc, sec: TCProcSection, r: Rope) = - p.s(sec).add(indentLine(p, r)) - template line(p: BProc, sec: TCProcSection, r: string) = - p.s(sec).add(indentLine(p, r.rope)) + addIndent p, p.s(sec) + p.s(sec).add(r) template lineF(p: BProc, sec: TCProcSection, frmt: FormatStr, args: untyped) = - p.s(sec).add(indentLine(p, frmt % args)) + addIndent p, p.s(sec) + p.s(sec).add(frmt % args) template lineCg(p: BProc, sec: TCProcSection, frmt: FormatStr, args: untyped) = - p.s(sec).add(indentLine(p, ropecg(p.module, frmt, args))) + addIndent p, p.s(sec) + p.s(sec).add(ropecg(p.module, frmt, args)) template linefmt(p: BProc, sec: TCProcSection, frmt: FormatStr, args: untyped) = - p.s(sec).add(indentLine(p, ropecg(p.module, frmt, args))) + addIndent p, p.s(sec) + p.s(sec).add(ropecg(p.module, frmt, args)) 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 @@ -260,26 +301,34 @@ 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) + p.s(cpsStmts).add("//" & sourceLine(p.config, t.info) & "\L") + 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)]) - -proc postStmtActions(p: BProc) {.inline.} = - p.s(cpsStmts).add(p.module.injectStmt) + if freshLine: + line(p, cpsStmts, genPostprocessDir("nimln", $line, $t.info.fileIndex.int32)) proc accessThreadLocalVar(p: BProc, s: PSym) proc emulatedThreadVars(conf: ConfigRef): bool {.inline.} proc genProc(m: BModule, prc: PSym) -proc raiseInstr(p: BProc): Rope +proc raiseInstr(p: BProc; result: var Rope) template compileToCpp(m: BModule): untyped = m.config.backend == backendCpp or sfCompileToCpp in m.module.flags @@ -290,10 +339,18 @@ proc getTempName(m: BModule): Rope = proc rdLoc(a: TLoc): Rope = # 'read' location (deref if indirect) - result = a.r - if lfIndirect in a.flags: result = "(*$1)" % [result] + if lfIndirect in a.flags: + result = "(*" & a.snippet & ")" + else: + result = a.snippet -proc lenField(p: BProc): Rope = +proc addRdLoc(a: TLoc; result: var Rope) = + if lfIndirect in a.flags: + result.add "(*" & a.snippet & ")" + else: + result.add a.snippet + +proc lenField(p: BProc): Rope {.inline.} = result = rope(if p.module.compileToCpp: "len" else: "Sup.len") proc lenExpr(p: BProc; a: TLoc): Rope = @@ -302,12 +359,21 @@ proc lenExpr(p: BProc; a: TLoc): Rope = else: result = "($1 ? $1->$2 : 0)" % [rdLoc(a), lenField(p)] +proc dataFieldAccessor(p: BProc, sym: Rope): Rope = + if optSeqDestructors in p.config.globalOptions: + result = "(" & sym & ").p" + else: + result = sym + proc dataField(p: BProc): Rope = if optSeqDestructors in p.config.globalOptions: result = rope".p->data" else: result = rope"->data" +proc genProcPrototype(m: BModule, sym: PSym) + +include cbuilder include ccgliterals include ccgtypes @@ -318,16 +384,24 @@ 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) == skParam) != ctArray: + result.add "(&" & a.snippet & ")" + else: + result.add a.snippet + proc addrLoc(conf: ConfigRef; a: TLoc): Rope = - result = a.r - if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a)) != ctArray: - result = "(&" & result & ")" + if lfIndirect notin a.flags and mapType(conf, a.t, mapTypeChooser(a) == skParam) != ctArray: + result = "(&" & a.snippet & ")" + else: + result = a.snippet proc byRefLoc(p: BProc; a: TLoc): Rope = - result = a.r - 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 = "(&" & result & ")" + result = "(&" & a.snippet & ")" + else: + result = a.snippet proc rdCharLoc(a: TLoc): Rope = # read a location that may need a char-cast: @@ -338,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) @@ -369,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, {}) @@ -406,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 rdLoc(loc) != nil + assert loc.snippet != "" let atyp = skipTypes(loc.t, abstractInst) if atyp.kind in {tyVar, tyLent}: @@ -417,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)]) @@ -435,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) @@ -447,15 +534,20 @@ proc constructLoc(p: BProc, loc: var TLoc, isTemp = false) = if optSeqDestructors in p.config.globalOptions and skipTypes(typ, abstractInst + {tyStatic}).kind in {tyString, tySequence}: linefmt(p, cpsStmts, "$1.len = 0; $1.p = NIM_NIL;$n", [rdLoc(loc)]) elif not isComplexValueType(typ): - linefmt(p, cpsStmts, "$1 = ($2)0;$n", [rdLoc(loc), - getTypeDesc(p.module, typ, mapTypeChooser(loc))]) + if containsGarbageCollectedRef(loc.t): + 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, 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) = @@ -470,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. @@ -488,49 +582,53 @@ 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: - fillLoc(s.loc, locLocalVar, n, mangleLocalName(p, s), OnStack) + fillLocalName(p, s) + fillLoc(s.loc, locLocalVar, n, OnStack) 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 @@ -543,10 +641,34 @@ 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: - fillLoc(s.loc, locGlobalVar, n, mangleName(p.module, s), OnHeap) + fillBackendName(p.module, s) + fillLoc(s.loc, locGlobalVar, n, OnHeap) if treatGlobalDifferentlyForHCR(p.module, s): incl(s.loc.flags, lfIndirect) if lfDynamicLib in s.loc.flags: @@ -554,8 +676,8 @@ 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) - if value != nil: + s.loc.snippet = mangleDynLibProc(s) + if value != "": internalError(p.config, n.info, ".dynlib variables cannot have a value") return useHeader(p.module, s) @@ -563,71 +685,86 @@ proc assignGlobalVar(p: BProc, n: PNode; value: Rope) = if not containsOrIncl(p.module.declaredThings, s.id): if sfThread in s.flags: declareThreadVar(p.module, s, sfImportc in s.flags) - if value != nil: + if value != "": internalError(p.config, n.info, ".threadvar variables cannot have a value") else: - var decl: Rope = nil - var td = getTypeDesc(p.module, s.loc.t, skVar) + var decl: Rope = "" + 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 != nil: 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 != nil: - decl.addf(" $1 = $2;$n", [s.loc.r, value]) + if 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 != nil: - 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 == nil: + 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 != nil) + assert(s.loc.snippet != "") scopeMangledParam(p, s) proc fillProcLoc(m: BModule; n: PNode) = let sym = n.sym if sym.loc.k == locNone: - fillLoc(sym.loc, locProc, n, mangleName(m, sym), OnStack) + fillBackendName(m, sym) + fillLoc(sym.loc, locProc, n, OnStack) proc getLabel(p: BProc): TLabel = inc(p.labels) 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): Rope -proc genLiteral(p: BProc, n: PNode): Rope -proc genOtherArg(p: BProc; ri: PNode; i: int; typ: PType): Rope +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" @@ -643,25 +780,25 @@ include ccgcalls, "ccgstmts.nim" proc initFrame(p: BProc, procname, filename: Rope): Rope = const frameDefines = """ - $1 define nimfr_(proc, file) \ - TFrame FR_; \ - FR_.procname = proc; FR_.filename = file; FR_.line = 0; FR_.len = 0; #nimFrame(&FR_); +$1define nimfr_(proc, file) \ + TFrame FR_; \ + FR_.procname = proc; FR_.filename = file; FR_.line = 0; FR_.len = 0; #nimFrame(&FR_); - $1 define 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; - $1 define nimln_(n, file) \ - FR_.line = n; FR_.filename = file; - """ +$1define nimlf_(n, file) \ + FR_.line = n; FR_.filename = file; + +""" if p.module.s[cfsFrameDefines].len == 0: appcg(p.module, p.module.s[cfsFrameDefines], frameDefines, ["#"]) - discard cgsym(p.module, "nimFrame") + cgsym(p.module, "nimFrame") result = ropecg(p.module, "\tnimfr_($1, $2);$n", [procname, filename]) proc initFrameNoDebug(p: BProc; frame, procname, filename: Rope; line: int): Rope = - discard cgsym(p.module, "nimFrame") + cgsym(p.module, "nimFrame") p.blocks[0].sections[cpsLocals].addf("TFrame $1;$n", [frame]) result = ropecg(p.module, "\t$1.procname = $2; $1.filename = $3; " & " $1.line = $4; $1.len = -1; nimFrame(&$1);$n", @@ -688,33 +825,36 @@ proc loadDynamicLib(m: BModule, lib: PLib) = if not lib.generated: lib.generated = true var tmp = getTempName(m) - assert(lib.name == nil) + assert(lib.name == "") lib.name = tmp # BUGFIX: cgsym has awful side-effects m.s[cfsVars].addf("static void* $1;$n", [tmp]) if lib.path.kind in {nkStrLit..nkTripleStrLit}: var s: TStringSeq = @[] libCandidates(lib.path.strVal, s) rawMessage(m.config, hintDependency, lib.path.strVal) - var loadlib: Rope = nil + var loadlib: Rope = "" for i in 0..high(s): inc(m.labels) if i > 0: loadlib.add("||") let n = newStrNode(nkStrLit, s[i]) n.info = lib.path.info - appcg(m, loadlib, "($1 = #nimLoadLibrary($2))$n", - [tmp, genStringLiteral(m, n)]) + appcg(m, loadlib, "($1 = #nimLoadLibrary(", [tmp]) + genStringLiteral(m, n, loadlib) + loadlib.addf "))$n", [] appcg(m, m.s[cfsDynLibInit], - "if (!($1)) #nimLoadLibraryError($2);$n", - [loadlib, genStringLiteral(m, lib.path)]) + "if (!($1)) #nimLoadLibraryError(", + [loadlib]) + genStringLiteral(m, lib.path, m.s[cfsDynLibInit]) + m.s[cfsDynLibInit].addf ");$n", [] + else: 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)) @@ -724,13 +864,13 @@ proc loadDynamicLib(m: BModule, lib: PLib) = "if (!($1 = #nimLoadLibrary($2))) #nimLoadLibraryError($2);$n", [tmp, rdLoc(dest)]) - if lib.name == nil: internalError(m.config, "loadDynamicLib") + if lib.name == "": internalError(m.config, "loadDynamicLib") 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)) @@ -738,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) @@ -768,46 +907,55 @@ 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 cgsym(m: BModule, name: string): Rope = +proc cgsymImpl(m: BModule; sym: PSym) {.inline.} = + case sym.kind + of skProc, skFunc, skMethod, skConverter, skIterator: genProc(m, sym) + of skVar, skResult, skLet: genVarPrototype(m, newSymNode sym) + of skType: discard getTypeDesc(m, sym.typ) + else: internalError(m.config, "cgsym: " & $sym.kind) + +proc cgsym(m: BModule, name: string) = + let sym = magicsys.getCompilerProc(m.g.graph, name) + if sym != nil: + cgsymImpl m, sym + else: + rawMessage(m.config, errGenerated, "system module needs: " & name) + +proc cgsymValue(m: BModule, name: string): Rope = let sym = magicsys.getCompilerProc(m.g.graph, name) if sym != nil: - case sym.kind - of skProc, skFunc, skMethod, skConverter, skIterator: genProc(m, sym) - of skVar, skResult, skLet: genVarPrototype(m, newSymNode sym) - of skType: discard getTypeDesc(m, sym.typ) - else: internalError(m.config, "cgsym: " & name & ": " & $sym.kind) + cgsymImpl m, sym else: - # we used to exclude the system module from this check, but for DLL - # generation support this sloppyness leads to hard to detect bugs, so - # we're picky here for the system module too: 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] == '#': @@ -831,12 +979,12 @@ proc generateHeaders(m: BModule) = #undef unix """) -proc openNamespaceNim(namespace: string): Rope = +proc openNamespaceNim(namespace: string; result: var Rope) = result.add("namespace ") result.add(namespace) result.add(" {\L") -proc closeNamespaceNim(): Rope = +proc closeNamespaceNim(result: var Rope) = result.add("}\L") proc closureSetup(p: BProc, prc: PSym) = @@ -856,24 +1004,34 @@ 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 = - if n.kind == nkSym and n.sym.kind == skResult: - result = true + result = false + case n.kind + 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 else: - for i in 0..<n.safeLen: + for i in 0..<n.len: if containsResult(n[i]): return true -const harmless = {nkConstSection, nkTypeSection, nkEmpty, nkCommentStmt, nkTemplateDef, - nkMacroDef, nkMixinStmt, nkBindStmt} + - declarativeDefs - proc easyResultAsgn(n: PNode): PNode = + result = nil case n.kind of nkStmtList, nkStmtListExpr: var i = 0 while i < n.len and n[i].kind in harmless: inc i if i < n.len: result = easyResultAsgn(n[i]) - of nkAsgn, nkFastAsgn: + of nkAsgn, nkFastAsgn, nkSinkAsgn: if n[0].kind == nkSym and n[0].sym.kind == skResult and not containsResult(n[1]): incl n.flags, nfPreventCg return n[1] @@ -886,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(...) @@ -901,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 @@ -913,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: + 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: @@ -929,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 @@ -946,7 +1110,7 @@ proc allPathsAsgnResult(n: PNode): InitResultEnum = if containsResult(n[0]): return InitRequired result = InitSkippable var exhaustive = skipTypes(n[0].typ, - abstractVarRange-{tyTypeDesc}).kind notin {tyFloat..tyFloat128, tyString} + abstractVarRange-{tyTypeDesc}).kind notin {tyFloat..tyFloat128, tyString, tyCstring} for i in 1..<n.len: let it = n[i] allPathsInBranch(it.lastSon) @@ -955,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: @@ -982,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]) @@ -992,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", [])) @@ -1007,37 +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 = genProcHeader(m, prc) - var returnStmt: Rope = nil + var header = newRopeAppender() + 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, cache = false) + 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[0]): + 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 != nil) - 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) - assignParam(p, res, prc.typ[0]) + fillResult(p.config, resNode, prc.typ) + 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 @@ -1045,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: @@ -1055,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)]) @@ -1090,14 +1285,14 @@ proc genProcAux(m: BModule, prc: PSym) = if beforeRetNeeded in p.flags: generatedProc.add("{") generatedProc.add(p.s(cpsInit)) generatedProc.add(p.s(cpsStmts)) - if beforeRetNeeded in p.flags: generatedProc.add(~"\t}BeforeRet_: ;$n") + if beforeRetNeeded in p.flags: generatedProc.add("\t}BeforeRet_: ;\n") if optStackTrace in prc.options: generatedProc.add(deinitFrame(p)) generatedProc.add(returnStmt) - generatedProc.add(~"}$N") + generatedProc.add("}\n") 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 @@ -1110,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): @@ -1122,7 +1317,8 @@ proc genProcPrototype(m: BModule, sym: PSym) = [mangleDynLibProc(sym), getTypeDesc(m, sym.loc.t), getModuleDllPath(m, sym)]) elif not containsOrIncl(m.declaredProtos, sym.id): let asPtr = isReloadable(m, sym) - var header = genProcHeader(m, sym, asPtr) + var header = newRopeAppender() + genProcHeader(m, sym, header, asPtr) if not asPtr: if isNoReturn(m, sym) and hasDeclspec in extccomp.CC[m.config.cCompiler].props: header = "__declspec(noreturn) " & header @@ -1140,11 +1336,25 @@ proc genProcNoForward(m: BModule, prc: PSym) = fillProcLoc(m, prc.ast[namePos]) useHeader(m, prc) # dependency to a compilerproc: - discard cgsym(m, prc.name.s) + cgsym(m, prc.name.s) return 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 @@ -1159,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]) @@ -1186,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 @@ -1231,31 +1427,32 @@ proc genVarPrototype(m: BModule, n: PNode) = #assert(sfGlobal in sym.flags) let sym = n.sym useHeader(m, sym) - fillLoc(sym.loc, locGlobalVar, n, mangleName(m, sym), OnHeap) + fillBackendName(m, sym) + fillLoc(sym.loc, locGlobalVar, n, OnHeap) if treatGlobalDifferentlyForHCR(m, sym): incl(sym.loc.flags, lfIndirect) if (lfNoDecl in sym.loc.flags) or contains(m.declaredThings, sym.id): return if sym.owner.id != m.module.id: # else we already have the symbol generated! - assert(sym.loc.r != nil) + 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", [ @@ -1285,23 +1482,27 @@ proc getFileHeader(conf: ConfigRef; cfile: Cfile): Rope = if conf.hcrOn: result.add("#define NIM_HOT_CODE_RELOADING\L") addNimDefines(result, conf) -proc getSomeNameForModule(m: PSym): Rope = - assert m.kind == skModule - assert m.owner.kind == skPackage - if {sfSystemModule, sfMainModule} * m.flags == {}: - result = m.owner.name.s.mangle.rope - result.add "_" - result.add m.name.s.mangle +proc getSomeNameForModule(conf: ConfigRef, filename: AbsoluteFile): Rope = + ## Returns a mangled module name. + 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 = mangleModuleName(m.g.config, m.filename).mangle proc getSomeInitName(m: BModule, suffix: string): Rope = if not m.hcrOn: - result = getSomeNameForModule(m.module) + result = getSomeNameForModule(m) + else: + result = "" result.add suffix proc getInitName(m: BModule): Rope = if sfMainModule in m.module.flags: # generate constant name for main module, for "easy" debugging. - result = rope"NimMainModule" + result = rope(m.config.nimMainPrefix) & rope"NimMainModule" else: result = getSomeInitName(m, "Init000") @@ -1314,67 +1515,84 @@ 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) n.info = prc.annex.path.info + var strLit = newRopeAppender() + genStringLiteral(m, n, strLit) appcg(m, result, "\tif (!($1 = #nimLoadLibrary($2)))$N" & "\t\t#nimLoadLibraryError($2);$N", - [handle, genStringLiteral(m, n)]) + [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("\tPreMain();\L") + preMainCode.add("\t$1PreMain();\L" % [rope m.config.nimMainPrefix]) - const - # not a big deal if we always compile these 3 global vars... makes the HCR code easier - PosixCmdLine = - "N_LIB_PRIVATE int cmdCount;$N" & - "N_LIB_PRIVATE char** cmdLine;$N" & - "N_LIB_PRIVATE char** gEnv;$N" + var posixCmdLine: Rope = "" + if optNoMain notin m.config.globalOptions: + 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 # prevents inlining of the NimMainInner function and dependent # functions, which might otherwise merge their stack frames. + PreMainBody = "$N" & - "N_LIB_PRIVATE void PreMainInner(void) {$N" & + "N_LIB_PRIVATE void $3PreMainInner(void) {$N" & "$2" & "}$N$N" & - PosixCmdLine & - "N_LIB_PRIVATE void PreMain(void) {$N" & + "$4" & + "N_LIB_PRIVATE void $3PreMain(void) {$N" & + "##if $5$N" & # 1 for volatile call, 0 for non-volatile "\tvoid (*volatile inner)(void);$N" & - "\tinner = PreMainInner;$N" & + "\tinner = $3PreMainInner;$N" & "$1" & "\t(*inner)();$N" & + "##else$N" & + "$1" & + "\t$3PreMainInner();$N" & + "##endif$N" & "}$N$N" MainProcs = - "\tNimMain();$N" + "\t$^NimMain();$N" MainProcsWithResult = MainProcs & ("\treturn $1nim_program_result;$N") - NimMainInner = "N_LIB_PRIVATE N_CDECL(void, NimMainInner)(void) {$N" & + NimMainInner = "N_LIB_PRIVATE N_CDECL(void, $5NimMainInner)(void) {$N" & "$1" & "}$N$N" NimMainProc = - "N_CDECL(void, NimMain)(void) {$N" & - "\tvoid (*volatile inner)(void);$N" & - "$4" & - "\tinner = NimMainInner;$N" & - "$2" & - "\t(*inner)();$N" & + "N_CDECL(void, $5NimMain)(void) {$N" & + "##if $6$N" & # 1 for volatile call, 0 for non-volatile + "\tvoid (*volatile inner)(void);$N" & + "$4" & + "\tinner = $5NimMainInner;$N" & + "$2" & + "\t(*inner)();$N" & + "##else$N" & + "$4" & + "$2" & + "\t$5NimMainInner();$N" & + "##endif$N" & "}$N$N" NimMainBody = NimMainInner & NimMainProc @@ -1405,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 @@ -1417,7 +1635,7 @@ proc genMainProc(m: BModule) = GenodeNimMain = "extern Genode::Env *nim_runtime_env;$N" & - "extern void nim_component_construct(Genode::Env*);$N$N" & + "extern \"C\" void nim_component_construct(Genode::Env*);$N$N" & NimMainBody ComponentConstruct = @@ -1439,67 +1657,91 @@ proc genMainProc(m: BModule) = m.includeHeader("<libc/component.h>") let initStackBottomCall = - if m.config.target.targetOS == osStandalone or m.config.selectedGC == gcNone: "".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) - appcg(m, m.s[cfsProcs], PreMainBody, [m.g.mainDatInit, m.g.otherModsInit]) + + 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 m.config.globalOptions * {optGenGuiApp, optGenDynLib} != {}: if optGenGuiApp in m.config.globalOptions: const nimMain = WinNimMain appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) + [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode, m.config.nimMainPrefix, isVolatile]) else: const nimMain = WinNimDllMain appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) + [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode, m.config.nimMainPrefix, isVolatile]) elif m.config.target.targetOS == osGenode: const nimMain = GenodeNimMain appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) + [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode, m.config.nimMainPrefix, isVolatile]) elif optGenDynLib in m.config.globalOptions: const nimMain = PosixNimDllMain appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) - elif m.config.target.targetOS == osStandalone: - const nimMain = NimMainBody - appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) + [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode, m.config.nimMainPrefix, isVolatile]) else: const nimMain = NimMainBody appcg(m, m.s[cfsProcs], nimMain, - [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode]) - + [m.g.mainModInit, initStackBottomCall, m.labels, preMainCode, m.config.nimMainPrefix, isVolatile]) if optNoMain notin m.config.globalOptions: if m.config.cppCustomNamespace.len > 0: - m.s[cfsProcs].add closeNamespaceNim() & "using namespace " & m.config.cppCustomNamespace & ";\L" + closeNamespaceNim(m.s[cfsProcs]) + m.s[cfsProcs].add "using namespace " & m.config.cppCustomNamespace & ";\L" if m.config.target.targetOS == osWindows and m.config.globalOptions * {optGenGuiApp, optGenDynLib} != {}: if optGenGuiApp in m.config.globalOptions: const otherMain = WinCMain - appcg(m, m.s[cfsProcs], otherMain, [if m.hcrOn: "*" else: ""]) + appcg(m, m.s[cfsProcs], otherMain, [if m.hcrOn: "*" else: "", m.config.nimMainPrefix]) else: const otherMain = WinCDllMain - appcg(m, m.s[cfsProcs], otherMain, []) + appcg(m, m.s[cfsProcs], otherMain, [m.config.nimMainPrefix]) elif m.config.target.targetOS == osGenode: const otherMain = ComponentConstruct - appcg(m, m.s[cfsProcs], otherMain, []) + appcg(m, m.s[cfsProcs], otherMain, [m.config.nimMainPrefix]) elif optGenDynLib in m.config.globalOptions: const otherMain = PosixCDllMain - appcg(m, m.s[cfsProcs], otherMain, []) + appcg(m, m.s[cfsProcs], otherMain, [m.config.nimMainPrefix]) elif m.config.target.targetOS == osStandalone: const otherMain = StandaloneCMain - appcg(m, m.s[cfsProcs], otherMain, []) + appcg(m, m.s[cfsProcs], otherMain, [m.config.nimMainPrefix]) else: const otherMain = PosixCMain - appcg(m, m.s[cfsProcs], otherMain, [if m.hcrOn: "*" else: ""]) - + appcg(m, m.s[cfsProcs], otherMain, [if m.hcrOn: "*" else: "", m.config.nimMainPrefix]) if m.config.cppCustomNamespace.len > 0: - m.s[cfsProcs].add openNamespaceNim(m.config.cppCustomNamespace) + openNamespaceNim(m.config.cppCustomNamespace, m.s[cfsProcs]) + +proc registerInitProcs*(g: BModuleList; m: PSym; flags: set[ModuleBackendFlag]) = + ## Called from the IC backend. + if HasDatInitProc in flags: + let datInit = getSomeNameForModule(g.config, g.config.toFullPath(m.info.fileIndex).AbsoluteFile) & "DatInit000" + g.mainModProcs.addf("N_LIB_PRIVATE N_NIMCALL(void, $1)(void);$N", [datInit]) + g.mainDatInit.addf("\t$1();$N", [datInit]) + if HasModuleInitProc in flags: + let init = getSomeNameForModule(g.config, g.config.toFullPath(m.info.fileIndex).AbsoluteFile) & "Init000" + g.mainModProcs.addf("N_LIB_PRIVATE N_NIMCALL(void, $1)(void);$N", [init]) + let initCall = "\t$1();$N" % [init] + if sfMainModule in m.flags: + g.mainModInit.add(initCall) + elif sfSystemModule in m.flags: + g.mainDatInit.add(initCall) # systemInit must called right after systemDatInit if any + else: + g.otherModsInit.add(initCall) + +proc whichInitProcs*(m: BModule): set[ModuleBackendFlag] = + # called from IC. + result = {} + if m.hcrOn or m.preInitProc.s(cpsInit).len > 0 or m.preInitProc.s(cpsStmts).len > 0: + result.incl HasModuleInitProc + for i in cfsTypeInit1..cfsDynLibInit: + if m.s[i].len != 0: + result.incl HasDatInitProc + break proc registerModuleToMain(g: BModuleList; m: BModule) = let @@ -1518,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", []) @@ -1559,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: @@ -1584,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: @@ -1595,6 +1837,7 @@ proc genDatInitCode(m: BModule) = if moduleDatInitRequired: m.s[cfsDatInitProc].add(prc) + #rememberFlag(m.g.graph, m.module, HasDatInitProc) # Very similar to the contents of symInDynamicLib - basically only the # things needed for the hot code reloading runtime procs to be loaded @@ -1605,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, @@ -1624,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]) @@ -1654,7 +1897,7 @@ proc genInitCode(m: BModule) = # Give this small function its own scope prc.addf("{$N", []) # Keep a bogus frame in case the code needs one - prc.add(~"\tTFrame FR_; FR_.len = 0;$N") + prc.add("\tTFrame FR_; FR_.len = 0;\n") writeSection(preInitProc, cpsLocals) writeSection(preInitProc, cpsInit, m.hcrOn) @@ -1680,15 +1923,15 @@ proc genInitCode(m: BModule) = var procname = makeCString(m.module.name.s) prc.add(initFrame(m.initProc, procname, quotedFilename(m.config, m.module.info))) else: - prc.add(~"\tTFrame FR_; FR_.len = 0;$N") + prc.add("\tTFrame FR_; FR_.len = 0;\n") writeSection(initProc, cpsInit, m.hcrOn) writeSection(initProc, cpsStmts) if beforeRetNeeded in m.initProc.flags: - prc.add(~"\tBeforeRet_: ;$n") + 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", []) @@ -1717,7 +1960,7 @@ proc genInitCode(m: BModule) = m.s[cfsInitProc].addf("}$N$N", []) for i, el in pairs(m.extensionLoaders): - if el != nil: + if el != "": let ex = "NIM_EXTERNC N_NIMCALL(void, nimLoadProcs$1)(void) {$2}$N$N" % [(i.ord - '0'.ord).rope, el] moduleInitRequired = true @@ -1725,6 +1968,7 @@ proc genInitCode(m: BModule) = if moduleInitRequired or sfMainModule in m.module.flags: m.s[cfsInitProc].add(prc) + #rememberFlag(m.g.graph, m.module, HasModuleInitProc) genDatInitCode(m) @@ -1735,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 @@ -1744,11 +2022,9 @@ proc genModule(m: BModule, cfile: Cfile): Rope = generateHeaders(m) result.add(m.s[cfsHeaders]) if m.config.cppCustomNamespace.len > 0: - result.add openNamespaceNim(m.config.cppCustomNamespace) + 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: @@ -1763,10 +2039,18 @@ proc genModule(m: BModule, cfile: Cfile): Rope = result.add(m.s[cfsDatInitProc]) if m.config.cppCustomNamespace.len > 0: - result.add closeNamespaceNim() + 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 = nil + result = "" + + postprocessCode(m.config, result) proc initProcOptions(m: BModule): TOptions = let opts = m.config.options @@ -1787,11 +2071,12 @@ proc rawNewModule(g: BModuleList; module: PSym, filename: AbsoluteFile): BModule result.typeInfoMarker = initTable[SigHash, Rope]() result.sigConflicts = initCountTable[SigHash]() result.initProc = newProc(nil, result) + for i in low(result.s)..high(result.s): result.s[i] = newRopeAppender() result.initProc.options = initProcOptions(result) 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) @@ -1820,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 @@ -1844,13 +2126,14 @@ proc writeHeader(m: BModule) = generateThreadLocalStorage(m) for i in cfsHeaders..cfsProcs: result.add(m.s[i]) - if m.config.cppCustomNamespace.len > 0 and i == cfsHeaders: result.add openNamespaceNim(m.config.cppCustomNamespace) + if m.config.cppCustomNamespace.len > 0 and i == cfsHeaders: + openNamespaceNim(m.config.cppCustomNamespace, result) result.add(m.s[cfsInitProc]) if optGenDynLib in m.config.globalOptions: result.add("N_LIB_IMPORT ") - result.addf("N_CDECL(void, NimMain)(void);$n", []) - if m.config.cppCustomNamespace.len > 0: result.add closeNamespaceNim() + result.addf("N_CDECL(void, $1NimMain)(void);$n", [rope m.config.nimMainPrefix]) + if m.config.cppCustomNamespace.len > 0: closeNamespaceNim(result) result.addf("#endif /* $1 */$n", [guard]) if not writeRope(result, m.filename): rawMessage(m.config, errCannotOpenFile, m.filename.string) @@ -1860,7 +2143,7 @@ proc getCFile(m: BModule): AbsoluteFile = if m.compileToCpp: ".nim.cpp" elif m.config.backend == backendObjc or sfCompileToObjc in m.module.flags: ".nim.m" else: ".nim.c" - result = changeFileExt(completeCfilePath(m.config, withPackageName(m.config, m.cfilename)), ext) + result = changeFileExt(completeCfilePath(m.config, mangleModuleName(m.config, m.cfilename).AbsoluteFile), ext) when false: proc myOpenCached(graph: ModuleGraph; module: PSym, rd: PRodReader): PPassContext = @@ -1890,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! @@ -1903,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): @@ -1954,7 +2231,7 @@ proc writeModule(m: BModule, pending: bool) = var cf = Cfile(nimname: m.module.name.s, cname: cfile, obj: completeCfilePath(m.config, toObjFile(m.config, cfile)), flags: {}) var code = genModule(m, cf) - if code != nil or m.config.symbolFiles != disabledSf: + if code != "" or m.config.symbolFiles != disabledSf: when hasTinyCBackend: if m.config.cmd == cmdTcc: tccgen.compileCCode($code, m.config) @@ -1974,18 +2251,41 @@ 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: # phase ordering problem here: We need to announce this # dependency to 'nimTestErrorFlag' before system.c has been written to disk. if m.config.exc == excGoto and getCompilerProc(graph, "nimTestErrorFlag") != nil: - discard cgsym(m, "nimTestErrorFlag") + cgsym(m, "nimTestErrorFlag") 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? @@ -1996,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) - discard 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) @@ -2006,32 +2309,29 @@ proc finalCodegenActions*(graph: ModuleGraph; m: BModule; n: PNode) = # so it can load the HCR runtime and later pass the library handle to the HCR runtime which # will in turn pass it to the other modules it initializes so they can initialize the # register/get procs so they don't have to have the definitions of these functions as well - discard cgsym(m, "nimLoadLibrary") - discard cgsym(m, "nimLoadLibraryError") - discard cgsym(m, "nimGetProcAddr") - discard cgsym(m, "procAddrError") - discard cgsym(m, "rawWrite") + cgsym(m, "nimLoadLibrary") + cgsym(m, "nimLoadLibraryError") + cgsym(m, "nimGetProcAddr") + cgsym(m, "procAddrError") + cgsym(m, "rawWrite") # raise dependencies on behalf of genMainProc - if m.config.target.targetOS != osStandalone and m.config.selectedGC != gcNone: - discard cgsym(m, "initStackBottomWith") + 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: - discard cgsym(m, "initThreadVarsEmulation") + 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 @@ -2058,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) |