diff options
author | Charles Blake <cblake@csail.mit.edu> | 2015-02-07 09:32:27 -0500 |
---|---|---|
committer | Charles Blake <cblake@csail.mit.edu> | 2015-02-07 09:32:27 -0500 |
commit | 8e685585a6a650d14f81bef5fbdfae10ac60a33a (patch) | |
tree | 00dddf0af8de3e0ee8afddc47401faed73a77e48 | |
parent | 65ce08f38c6a8ae05df5529a5b2d51de7aaec2d6 (diff) | |
parent | dc85c2498b2d555125510fe91905cd1beffb6d10 (diff) | |
download | Nim-8e685585a6a650d14f81bef5fbdfae10ac60a33a.tar.gz |
Merge /home/cb/pkg/nim/Nim into devel
-rw-r--r-- | compiler/ast.nim | 9 | ||||
-rw-r--r-- | compiler/ccgcalls.nim | 26 | ||||
-rw-r--r-- | compiler/ccgexprs.nim | 11 | ||||
-rw-r--r-- | compiler/ccgstmts.nim | 23 | ||||
-rw-r--r-- | compiler/ccgtypes.nim | 41 | ||||
-rw-r--r-- | compiler/cgen.nim | 189 | ||||
-rw-r--r-- | compiler/cgendata.nim | 3 | ||||
-rw-r--r-- | compiler/commands.nim | 2 | ||||
-rw-r--r-- | compiler/msgs.nim | 7 | ||||
-rw-r--r-- | compiler/nimconf.nim | 24 | ||||
-rw-r--r-- | compiler/nimsuggest/nimsuggest.nim | 8 | ||||
-rw-r--r-- | compiler/semexprs.nim | 8 | ||||
-rw-r--r-- | compiler/transf.nim | 1 | ||||
-rw-r--r-- | config/nim.cfg | 4 | ||||
-rw-r--r-- | lib/pure/logging.nim | 2 | ||||
-rw-r--r-- | lib/pure/os.nim | 8 | ||||
-rw-r--r-- | lib/pure/strtabs.nim | 4 | ||||
-rw-r--r-- | lib/system/dyncalls.nim | 6 | ||||
-rw-r--r-- | lib/system/sysio.nim | 16 | ||||
-rw-r--r-- | todo.txt | 1 |
20 files changed, 152 insertions, 241 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index f7c1a07ed..1a5ae8aab 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -459,7 +459,7 @@ type tfNeedsInit, # type constains a "not nil" constraint somewhere or some # other type so that it requires inititalization - tfHasShared, # type constains a "shared" constraint modifier somewhere + tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode tfHasMeta, # type contains "wildcard" sub-types such as generic params # or other type classes tfHasGCedMem, # type contains GC'ed memory @@ -522,7 +522,7 @@ const skError* = skUnknown # type flags that are essential for type equality: - eqTypeFlags* = {tfIterator, tfShared, tfNotNil} + eqTypeFlags* = {tfIterator, tfShared, tfNotNil, tfVarIsPtr} type TMagic* = enum # symbols that require compiler magic: @@ -1348,7 +1348,7 @@ proc isGCedMem*(t: PType): bool {.inline.} = proc propagateToOwner*(owner, elem: PType) = const HaveTheirOwnEmpty = {tySequence, tySet} - owner.flags = owner.flags + (elem.flags * {tfHasShared, tfHasMeta}) + owner.flags = owner.flags + (elem.flags * {tfHasMeta}) if tfNotNil in elem.flags: if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvokation}: owner.flags.incl tfNotNil @@ -1359,9 +1359,6 @@ proc propagateToOwner*(owner, elem: PType) = if owner.kind in HaveTheirOwnEmpty: discard else: owner.flags.incl tfNeedsInit - if tfShared in elem.flags: - owner.flags.incl tfHasShared - if elem.isMetaType: owner.flags.incl tfHasMeta diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim index ad9d18257..b9fc694cb 100644 --- a/compiler/ccgcalls.nim +++ b/compiler/ccgcalls.nim @@ -124,8 +124,8 @@ proc genArgStringToCString(p: BProc, n: PNode): PRope {.inline.} = var a: TLoc initLocExpr(p, n.sons[0], a) result = ropef("$1->data", [a.rdLoc]) - -proc genArg(p: BProc, n: PNode, param: PSym): PRope = + +proc genArg(p: BProc, n: PNode, param: PSym; call: PNode): PRope = var a: TLoc if n.kind == nkStringToCString: result = genArgStringToCString(p, n) @@ -138,7 +138,15 @@ proc genArg(p: BProc, n: PNode, param: PSym): PRope = elif p.module.compileToCpp and param.typ.kind == tyVar and n.kind == nkHiddenAddr: initLocExprSingleUse(p, n.sons[0], a) - result = rdLoc(a) + # if the proc is 'importc'ed but not 'importcpp'ed then 'var T' still + # means '*T'. See posix.nim for lots of examples that do that in the wild. + let callee = call.sons[0] + if callee.kind == nkSym and + {sfImportC, sfInfixCall, sfCompilerProc} * callee.sym.flags == {sfImportC} and + {lfHeader, lfNoDecl} * callee.sym.loc.flags != {}: + result = addrLoc(a) + else: + result = rdLoc(a) else: initLocExprSingleUse(p, n, a) result = rdLoc(a) @@ -166,7 +174,7 @@ proc genPrefixCall(p: BProc, le, ri: PNode, d: var TLoc) = if params != nil: app(params, ~", ") if i < sonsLen(typ): assert(typ.n.sons[i].kind == nkSym) - app(params, genArg(p, ri.sons[i], typ.n.sons[i].sym)) + app(params, genArg(p, ri.sons[i], typ.n.sons[i].sym, ri)) else: app(params, genArgNoParam(p, ri.sons[i])) fixupCall(p, le, ri, d, op.r, params) @@ -192,7 +200,7 @@ proc genClosureCall(p: BProc, le, ri: PNode, d: var TLoc) = assert(sonsLen(typ) == sonsLen(typ.n)) if i < sonsLen(typ): assert(typ.n.sons[i].kind == nkSym) - app(pl, genArg(p, ri.sons[i], typ.n.sons[i].sym)) + app(pl, genArg(p, ri.sons[i], typ.n.sons[i].sym, ri)) else: app(pl, genArgNoParam(p, ri.sons[i])) if i < length - 1: app(pl, ~", ") @@ -295,7 +303,7 @@ proc genThisArg(p: BProc; ri: PNode; i: int; typ: PType): PRope = if x.typ.kind == tyPtr: result = genArgNoParam(p, x) result.app("->") - elif x.kind in {nkHiddenDeref, nkDerefExpr}: + elif x.kind in {nkHiddenDeref, nkDerefExpr} and x[0].typ.kind == tyPtr: result = genArgNoParam(p, x[0]) result.app("->") else: @@ -424,12 +432,12 @@ proc genNamedParamCall(p: BProc, ri: PNode, d: var TLoc) = assert(sonsLen(typ) == sonsLen(typ.n)) if length > 1: - app(pl, genArg(p, ri.sons[1], typ.n.sons[1].sym)) + app(pl, genArg(p, ri.sons[1], typ.n.sons[1].sym, ri)) app(pl, ~" ") app(pl, op.r) if length > 2: app(pl, ~": ") - app(pl, genArg(p, ri.sons[2], typ.n.sons[2].sym)) + app(pl, genArg(p, ri.sons[2], typ.n.sons[2].sym, ri)) for i in countup(3, length-1): assert(sonsLen(typ) == sonsLen(typ.n)) if i >= sonsLen(typ): @@ -439,7 +447,7 @@ proc genNamedParamCall(p: BProc, ri: PNode, d: var TLoc) = app(pl, ~" ") app(pl, param.name.s) app(pl, ~": ") - app(pl, genArg(p, ri.sons[i], param)) + app(pl, genArg(p, ri.sons[i], param, ri)) if typ.sons[0] != nil: if isInvalidReturnType(typ.sons[0]): if sonsLen(ri) > 1: app(pl, ~" ") diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index bd116d6fb..32678d472 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -664,7 +664,8 @@ proc unaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) = proc isCppRef(p: BProc; typ: PType): bool {.inline.} = result = p.module.compileToCpp and - skipTypes(typ, abstractInst).kind == tyVar + skipTypes(typ, abstractInst).kind == tyVar and + tfVarIsPtr notin skipTypes(typ, abstractInst).flags proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = let mt = mapType(e.sons[0].typ) @@ -677,12 +678,14 @@ proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = else: var a: TLoc initLocExprSingleUse(p, e.sons[0], a) - case skipTypes(a.t, abstractInst).kind + let typ = skipTypes(a.t, abstractInst) + case typ.kind of tyRef: d.s = OnHeap of tyVar: d.s = OnUnknown - if p.module.compileToCpp: + if tfVarIsPtr notin typ.flags and p.module.compileToCpp and + e.kind == nkHiddenDeref: putIntoDest(p, d, e.typ, rdLoc(a)) return of tyPtr: @@ -923,6 +926,7 @@ proc genAndOr(p: BProc, e: PNode, d: var TLoc, m: TMagic) = L: TLabel tmp: TLoc getTemp(p, e.typ, tmp) # force it into a temp! + inc p.splitDecls expr(p, e.sons[1], tmp) L = getLabel(p) if m == mOr: @@ -935,6 +939,7 @@ proc genAndOr(p: BProc, e: PNode, d: var TLoc, m: TMagic) = d = tmp else: genAssignment(p, d, tmp, {}) # no need for deep copying + dec p.splitDecls proc genEcho(p: BProc, n: PNode) = # this unusal way of implementing it ensures that e.g. ``echo("hallo", 45)`` diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim index 5d348c4e4..f5a2c0ef4 100644 --- a/compiler/ccgstmts.nim +++ b/compiler/ccgstmts.nim @@ -203,7 +203,7 @@ proc genSingleVar(p: BProc, a: PNode) = registerGcRoot(p, v) else: let imm = isAssignedImmediately(a.sons[2]) - if imm and p.module.compileToCpp: + if imm and p.module.compileToCpp and p.splitDecls == 0: # C++ really doesn't like things like 'Foo f; f = x' as that invokes a # parameterless constructor followed by an assignment operator. So we # generate better code here: @@ -262,7 +262,7 @@ proc genConstStmt(p: BProc, t: PNode) = else: appf(p.module.s[cfsData], "NIM_CONST $1 $2 = $3;$n", [getTypeDesc(p.module, c.typ), c.loc.r, genConstExpr(p, c.ast)]) - + proc genIf(p: BProc, n: PNode, d: var TLoc) = # # { if (!expr1) goto L1; @@ -286,17 +286,22 @@ proc genIf(p: BProc, n: PNode, d: var TLoc) = let it = n.sons[i] if it.len == 2: when newScopeForIf: startBlock(p) - initLocExpr(p, it.sons[0], a) + initLocExprSingleUse(p, it.sons[0], a) lelse = getLabel(p) inc(p.labels) - lineFF(p, cpsStmts, "if (!$1) goto $2;$n", - "br i1 $1, label %LOC$3, label %$2$nLOC$3: $n", - [rdLoc(a), lelse, toRope(p.labels)]) + lineF(p, cpsStmts, "if (!$1) goto $2;$n", + [rdLoc(a), lelse]) when not newScopeForIf: startBlock(p) - expr(p, it.sons[1], d) + if p.module.compileToCpp: + # avoid "jump to label crosses initialization" error: + app(p.s(cpsStmts), "{") + expr(p, it.sons[1], d) + app(p.s(cpsStmts), "}") + else: + expr(p, it.sons[1], d) endBlock(p) if sonsLen(n) > 1: - lineFF(p, cpsStmts, "goto $1;$n", "br label %$1$n", [lend]) + lineF(p, cpsStmts, "goto $1;$n", [lend]) fixLabel(p, lelse) elif it.len == 1: startBlock(p) @@ -355,7 +360,7 @@ proc genReturnStmt(p: BProc, t: PNode) = # consume it before we return. var safePoint = p.finallySafePoints[p.finallySafePoints.len-1] linefmt(p, cpsStmts, "if ($1.status != 0) #popCurrentException();$n", safePoint) - lineFF(p, cpsStmts, "goto BeforeRet;$n", "br label %BeforeRet$n", []) + lineF(p, cpsStmts, "goto BeforeRet;$n", []) proc genComputedGoto(p: BProc; n: PNode) = # first pass: Generate array of computed labels: diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim index 823e3bc1b..0220d2066 100644 --- a/compiler/ccgtypes.nim +++ b/compiler/ccgtypes.nim @@ -27,17 +27,7 @@ proc isKeyword(w: PIdent): bool = proc mangleName(s: PSym): PRope = result = s.loc.r - if result == nil: - if gCmd == cmdCompileToLLVM: - case s.kind - of skProc, skMethod, skConverter, skConst, skIterators: - result = ~"@" - of skVar, skForVar, skResult, skLet: - if sfGlobal in s.flags: result = ~"@" - else: result = ~"%" - of skTemp, skParam, skType, skEnumField, skModule: - result = ~"%" - else: internalError(s.info, "mangleName") + if result == nil: when oKeepVariableNames: let keepOrigName = s.kind in skLocalVars - {skForVar} and {sfFromGeneric, sfGlobal, sfShadowed, sfGenSym} * s.flags == {} and @@ -103,13 +93,11 @@ proc typeName(typ: PType): PRope = else: ~"TY" proc getTypeName(typ: PType): PRope = - if (typ.sym != nil) and ({sfImportc, sfExportc} * typ.sym.flags != {}) and - (gCmd != cmdCompileToLLVM): + if typ.sym != nil and {sfImportc, sfExportc} * typ.sym.flags != {}: result = typ.sym.loc.r else: if typ.loc.r == nil: - typ.loc.r = if gCmd != cmdCompileToLLVM: con(typ.typeName, typ.id.toRope) - else: con([~"%", typ.typeName, typ.id.toRope]) + typ.loc.r = con(typ.typeName, typ.id.toRope) result = typ.loc.r if result == nil: internalError("getTypeName: " & $typ.kind) @@ -200,9 +188,6 @@ const "N_SYSCALL", # this is probably not correct for all platforms, # but one can #define it to what one wants "N_INLINE", "N_NOINLINE", "N_FASTCALL", "N_CLOSURE", "N_NOCONV"] - CallingConvToStrLLVM: array[TCallingConvention, string] = ["fastcc $1", - "stdcall $1", "ccc $1", "safecall $1", "syscall $1", "$1 alwaysinline", - "$1 noinline", "fastcc $1", "ccc $1", "$1"] proc cacheGetType(tab: TIdTable, key: PType): PRope = # returns nil if we need to declare this type @@ -284,23 +269,23 @@ proc genProcParams(m: BModule, t: PType, rettype, params: var PRope, # this fixes the 'sort' bug: if param.typ.kind == tyVar: param.loc.s = OnUnknown # need to pass hidden parameter: - appff(params, ", NI $1Len$2", ", @NI $1Len$2", [param.loc.r, j.toRope]) + appf(params, ", NI $1Len$2", [param.loc.r, j.toRope]) inc(j) arr = arr.sons[0] - if (t.sons[0] != nil) and isInvalidReturnType(t.sons[0]): + if (t.sons[0] != nil) and isInvalidReturnType(t.sons[0]): var arr = t.sons[0] if params != nil: app(params, ", ") app(params, getTypeDescAux(m, arr, check)) - if (mapReturnType(t.sons[0]) != ctArray) or (gCmd == cmdCompileToLLVM): + if (mapReturnType(t.sons[0]) != ctArray): app(params, "*") - appff(params, " Result", " @Result", []) + appf(params, " Result", []) if t.callConv == ccClosure and declareEnvironment: if params != nil: app(params, ", ") app(params, "void* ClEnv") if tfVarargs in t.flags: if params != nil: app(params, ", ") app(params, "...") - if params == nil and gCmd != cmdCompileToLLVM: app(params, "void)") + if params == nil: app(params, "void)") else: app(params, ")") params = con("(", params) @@ -505,8 +490,9 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): PRope = # but determining when this needs to be done is hard. We should split # C type generation into an analysis and a code generation phase somehow. case t.kind - of tyRef, tyPtr, tyVar: - let star = if t.kind == tyVar and compileToCpp(m): "&" else: "*" + of tyRef, tyPtr, tyVar: + var star = if t.kind == tyVar and tfVarIsPtr notin typ.flags and + compileToCpp(m): "&" else: "*" var et = t.lastSon var etB = et.skipTypes(abstractInst) if etB.kind in {tyArrayConstr, tyArray, tyOpenArray, tyVarargs}: @@ -514,6 +500,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): PRope = # ``var set[char]`` in `getParamTypeDesc` et = elemType(etB) etB = et.skipTypes(abstractInst) + star[0] = '*' case etB.kind of tyObject, tyTuple: if isImportedCppType(etB) and et.kind == tyGenericInst: @@ -529,7 +516,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): PRope = # no restriction! We have a forward declaration for structs let x = getUniqueType(etB) let name = getTypeForward(m, x) - result = con(name, "**") + result = con(name, "*" & star) idTablePut(m.typeCache, t, result) pushType(m, x) else: @@ -677,7 +664,7 @@ proc genProcHeader(m: BModule, prc: PSym): PRope = rettype, params: PRope genCLineDir(result, prc.info) # using static is needed for inline procs - if gCmd != cmdCompileToLLVM and lfExportLib in prc.loc.flags: + if lfExportLib in prc.loc.flags: if m.isHeaderFile: result.app "N_LIB_IMPORT " else: diff --git a/compiler/cgen.nim b/compiler/cgen.nim index e16d5d0ce..a606cb5b9 100644 --- a/compiler/cgen.nim +++ b/compiler/cgen.nim @@ -25,15 +25,6 @@ when options.hasTinyCBackend: var generatedHeader: BModule -proc ropeff(cformat, llvmformat: string, args: varargs[PRope]): PRope = - if gCmd == cmdCompileToLLVM: result = ropef(llvmformat, args) - else: result = ropef(cformat, args) - -proc appff(dest: var PRope, cformat, llvmformat: string, - args: varargs[PRope]) = - if gCmd == cmdCompileToLLVM: appf(dest, llvmformat, args) - else: appf(dest, cformat, args) - proc addForwardedProc(m: BModule, prc: PSym) = m.forwardedProcs.add(prc) inc(gForwardedProcsCounter) @@ -137,79 +128,8 @@ proc ropecg(m: BModule, frmt: TFormatStr, args: varargs[PRope]): PRope = if i - 1 >= start: app(result, substr(frmt, start, i - 1)) -const compileTimeRopeFmt = false - -when compileTimeRopeFmt: - import macros - - type TFmtFragmentKind = enum - ffSym, - ffLit, - ffParam - - type TFragment = object - case kind: TFmtFragmentKind - of ffSym, ffLit: - value: string - of ffParam: - intValue: int - - iterator fmtStringFragments(s: string): tuple[kind: TFmtFragmentKind, - value: string, - intValue: int] = - # This is a bit less featured version of the ropecg's algorithm - # (be careful when replacing ropecg calls) - var - i = 0 - length = s.len - - while i < length: - var start = i - case s[i] - of '$': - let n = s[i+1] - case n - of '$': - inc i, 2 - of '0'..'9': - # XXX: use the new case object construction syntax when it's ready - yield (kind: ffParam, value: "", intValue: n.ord - ord('1')) - inc i, 2 - start = i - else: - inc i - of '#': - inc i - var j = i - while s[i] in IdentChars: inc i - yield (kind: ffSym, value: substr(s, j, i-1), intValue: 0) - start = i - else: discard - - while i < length: - if s[i] != '$' and s[i] != '#': inc i - else: break - - if i - 1 >= start: - yield (kind: ffLit, value: substr(s, start, i-1), intValue: 0) - - macro rfmt(m: BModule, fmt: static[string], args: varargs[PRope]): expr = - ## Experimental optimized rope-formatting operator - ## The run-time code it produces will be very fast, but will it speed up - ## the compilation of nimrod itself or will the macro execution time - ## offset the gains? - result = newCall(bindSym"ropeConcat") - for frag in fmtStringFragments(fmt): - case frag.kind - of ffSym: - result.add(newCall(bindSym"cgsym", m, newStrLitNode(frag.value))) - of ffLit: - result.add(newCall(bindSym"~", newStrLitNode(frag.value))) - of ffParam: - result.add(args[frag.intValue]) -else: - template rfmt(m: BModule, fmt: string, args: varargs[PRope]): expr = - ropecg(m, fmt, args) +template rfmt(m: BModule, fmt: string, args: varargs[PRope]): expr = + ropecg(m, fmt, args) proc appcg(m: BModule, c: var PRope, frmt: TFormatStr, args: varargs[PRope]) = @@ -242,24 +162,14 @@ proc lineCg(p: BProc, s: TCProcSection, frmt: TFormatStr, args: varargs[PRope]) = app(p.s(s), indentLine(p, ropecg(p.module, frmt, args))) -when compileTimeRopeFmt: - template linefmt(p: BProc, s: TCProcSection, frmt: TFormatStr, - args: varargs[PRope]) = - line(p, s, rfmt(p.module, frmt, args)) -else: - proc linefmt(p: BProc, s: TCProcSection, frmt: TFormatStr, - args: varargs[PRope]) = - app(p.s(s), indentLine(p, ropecg(p.module, frmt, args))) +proc linefmt(p: BProc, s: TCProcSection, frmt: TFormatStr, + args: varargs[PRope]) = + app(p.s(s), indentLine(p, ropecg(p.module, frmt, args))) proc appLineCg(p: BProc, r: var PRope, frmt: TFormatStr, args: varargs[PRope]) = app(r, indentLine(p, ropecg(p.module, frmt, args))) -proc lineFF(p: BProc, s: TCProcSection, cformat, llvmformat: string, - args: varargs[PRope]) = - if gCmd == cmdCompileToLLVM: lineF(p, s, llvmformat, args) - else: lineF(p, s, cformat, args) - proc safeLineNm(info: TLineInfo): int = result = toLinenumber(info) if result < 0: result = 0 # negative numbers are not allowed in #line @@ -267,8 +177,8 @@ proc safeLineNm(info: TLineInfo): int = proc genCLineDir(r: var PRope, filename: string, line: int) = assert line >= 0 if optLineDir in gOptions: - appff(r, "$N#line $2 $1$N", "; line $2 \"$1\"$n", - [toRope(makeSingleLineCString(filename)), toRope(line)]) + appf(r, "$N#line $2 $1$N", + [toRope(makeSingleLineCString(filename)), toRope(line)]) proc genCLineDir(r: var PRope, info: TLineInfo) = genCLineDir(r, info.toFullPath, info.safeLineNm) @@ -443,29 +353,6 @@ proc deinitGCFrame(p: BProc): PRope = if p.gcFrameId > 0: result = ropecg(p.module, "if (((NU)&GCFRAME) < 4096) #nimGCFrame(&GCFRAME);$n") - -proc cstringLit(p: BProc, r: var PRope, s: string): PRope = - if gCmd == cmdCompileToLLVM: - inc(p.module.labels) - inc(p.labels) - result = ropef("%LOC$1", [toRope(p.labels)]) - appf(p.module.s[cfsData], "@C$1 = private constant [$2 x i8] $3$n", - [toRope(p.module.labels), toRope(len(s)), makeLLVMString(s)]) - appf(r, "$1 = getelementptr [$2 x i8]* @C$3, %NI 0, %NI 0$n", - [result, toRope(len(s)), toRope(p.module.labels)]) - else: - result = makeCString(s) - -proc cstringLit(m: BModule, r: var PRope, s: string): PRope = - if gCmd == cmdCompileToLLVM: - inc(m.labels, 2) - result = ropef("%MOC$1", [toRope(m.labels - 1)]) - appf(m.s[cfsData], "@MOC$1 = private constant [$2 x i8] $3$n", - [toRope(m.labels), toRope(len(s)), makeLLVMString(s)]) - appf(r, "$1 = getelementptr [$2 x i8]* @MOC$3, %NI 0, %NI 0$n", - [result, toRope(len(s)), toRope(m.labels)]) - else: - result = makeCString(s) proc allocParam(p: BProc, s: PSym) = assert(s.kind == skParam) @@ -507,7 +394,7 @@ proc localVarDecl(p: BProc; s: PSym): PRope = result = ropef(s.cgDeclFrmt, result, s.loc.r) proc assignLocalVar(p: BProc, s: PSym) = - #assert(s.loc.k == locNone) // not yet assigned + #assert(s.loc.k == locNone) # not yet assigned # this need not be fullfilled for inline procs; they are regenerated # for each module that uses them! let decl = localVarDecl(p, s).con(";" & tnl) @@ -553,13 +440,11 @@ proc assignGlobalVar(p: BProc, s: PSym) = {optStackTrace, optEndb}: appcg(p.module, p.module.s[cfsDebugInit], "#dbgRegisterGlobal($1, &$2, $3);$n", - [cstringLit(p, p.module.s[cfsDebugInit], - normalize(s.owner.name.s & '.' & s.name.s)), + [makeCString(normalize(s.owner.name.s & '.' & s.name.s)), s.loc.r, genTypeInfo(p.module, s.typ)]) proc assignParam(p: BProc, s: PSym) = assert(s.loc.r != nil) - if sfAddrTaken in s.flags and gCmd == cmdCompileToLLVM: allocParam(p, s) localDebugInfo(p, s) proc fillProcLoc(sym: PSym) = @@ -653,7 +538,6 @@ proc symInDynamicLib(m: BModule, sym: PSym) = let isCall = isGetProcAddr(lib) var extname = sym.loc.r if not isCall: loadDynamicLib(m, lib) - if gCmd == cmdCompileToLLVM: incl(sym.loc.flags, lfIndirect) var tmp = mangleDynLibProc(sym) sym.loc.r = tmp # from now on we only need the internal name sym.typ.sym = nil # generate a new name @@ -669,7 +553,7 @@ proc symInDynamicLib(m: BModule, sym: PSym) = params.app(", ") let load = ropef("\t$1 = ($2) ($3$4));$n", [tmp, getTypeDesc(m, sym.typ), - params, cstringLit(m, m.s[cfsDynLibInit], ropeToStr(extname))]) + params, makeCString(ropeToStr(extname))]) var last = lastSon(n) if last.kind == nkHiddenStdConv: last = last.sons[1] internalAssert(last.kind == nkStrLit) @@ -684,10 +568,8 @@ proc symInDynamicLib(m: BModule, sym: PSym) = appcg(m, m.s[cfsDynLibInit], "\t$1 = ($2) #nimGetProcAddr($3, $4);$n", [tmp, getTypeDesc(m, sym.typ), - lib.name, cstringLit(m, m.s[cfsDynLibInit], ropeToStr(extname))]) - appff(m.s[cfsVars], "$2 $1;$n", - "$1 = linkonce global $2 zeroinitializer$n", - [sym.loc.r, getTypeDesc(m, sym.loc.t)]) + lib.name, makeCString(ropeToStr(extname))]) + appf(m.s[cfsVars], "$2 $1;$n", [sym.loc.r, getTypeDesc(m, sym.loc.t)]) proc varInDynamicLib(m: BModule, sym: PSym) = var lib = sym.annex @@ -700,7 +582,7 @@ proc varInDynamicLib(m: BModule, sym: PSym) = appcg(m, m.s[cfsDynLibInit], "$1 = ($2*) #nimGetProcAddr($3, $4);$n", [tmp, getTypeDesc(m, sym.typ), - lib.name, cstringLit(m, m.s[cfsDynLibInit], ropeToStr(extname))]) + lib.name, makeCString(ropeToStr(extname))]) appf(m.s[cfsVars], "$2* $1;$n", [sym.loc.r, getTypeDesc(m, sym.loc.t)]) @@ -723,13 +605,13 @@ proc cgsym(m: BModule, name: string): PRope = rawMessage(errSystemNeeds, name) result = sym.loc.r -proc generateHeaders(m: BModule) = +proc generateHeaders(m: BModule) = app(m.s[cfsHeaders], tnl & "#include \"nimbase.h\"" & tnl) var it = PStrEntry(m.headerFiles.head) - while it != nil: + while it != nil: if it.data[0] notin {'\"', '<'}: appf(m.s[cfsHeaders], "$N#include \"$1\"$N", [toRope(it.data)]) - else: + else: appf(m.s[cfsHeaders], "$N#include $1$N", [toRope(it.data)]) it = PStrEntry(it.next) @@ -802,16 +684,17 @@ proc genProcAux(m: BModule, prc: PSym) = app(generatedProc, initGCFrame(p)) if optStackTrace in prc.options: app(generatedProc, p.s(cpsLocals)) - var procname = cstringLit(p, generatedProc, prc.name.s) + var procname = makeCString(prc.name.s) app(generatedProc, initFrame(p, procname, prc.info.quotedFilename)) else: app(generatedProc, p.s(cpsLocals)) - if (optProfiler in prc.options) and (gCmd != cmdCompileToLLVM): + if optProfiler in prc.options: # invoke at proc entry for recursion: appcg(p, cpsInit, "\t#nimProfile();$n", []) + if p.beforeRetNeeded: app(generatedProc, "{") app(generatedProc, p.s(cpsInit)) app(generatedProc, p.s(cpsStmts)) - if p.beforeRetNeeded: app(generatedProc, ~"\tBeforeRet: ;$n") + if p.beforeRetNeeded: app(generatedProc, ~"\t}BeforeRet: ;$n") app(generatedProc, deinitGCFrame(p)) if optStackTrace in prc.options: app(generatedProc, deinitFrame(p)) app(generatedProc, returnStmt) @@ -831,7 +714,6 @@ proc genProcPrototype(m: BModule, sym: PSym) = not containsOrIncl(m.declaredThings, sym.id): app(m.s[cfsVars], rfmt(nil, "extern $1 $2;$n", getTypeDesc(m, sym.loc.t), mangleDynLibProc(sym))) - if gCmd == cmdCompileToLLVM: incl(sym.loc.flags, lfIndirect) elif not containsOrIncl(m.declaredProtos, sym.id): var header = genProcHeader(m, sym) if sym.typ.callConv != ccInline and crossesCppBoundary(m, sym): @@ -929,21 +811,17 @@ proc addIntTypes(result: var PRope) {.inline.} = proc getCopyright(cfile: string): PRope = if optCompileOnly in gGlobalOptions: - result = ropeff("/* Generated by Nim Compiler v$1 */$N" & + result = ropef("/* Generated by Nim Compiler v$1 */$N" & "/* (c) 2015 Andreas Rumpf */$N" & "/* The generated code is subject to the original license. */$N", - "; Generated by Nim Compiler v$1$N" & - "; (c) 2012 Andreas Rumpf$N", [toRope(VersionAsString)]) + [toRope(VersionAsString)]) else: - result = ropeff("/* Generated by Nim Compiler v$1 */$N" & + result = ropef("/* Generated by Nim Compiler v$1 */$N" & "/* (c) 2015 Andreas Rumpf */$N" & "/* The generated code is subject to the original license. */$N" & "/* Compiled for: $2, $3, $4 */$N" & "/* Command for C compiler:$n $5 */$N", - "; Generated by Nim Compiler v$1$N" & - "; (c) 2015 Andreas Rumpf$N" & - "; Compiled for: $2, $3, $4$N" & - "; Command for LLVM compiler:$N $5$N", [toRope(VersionAsString), + [toRope(VersionAsString), toRope(platform.OS[targetOS].name), toRope(platform.CPU[targetCPU].name), toRope(extccomp.CC[extccomp.cCompiler].name), @@ -1094,13 +972,11 @@ proc registerModuleToMain(m: PSym) = var init = m.getInitName datInit = m.getDatInitName - appff(mainModProcs, "NIM_EXTERNC N_NOINLINE(void, $1)(void);$N", - "declare void $1() noinline$N", [init]) - appff(mainModProcs, "NIM_EXTERNC N_NOINLINE(void, $1)(void);$N", - "declare void $1() noinline$N", [datInit]) + appf(mainModProcs, "NIM_EXTERNC N_NOINLINE(void, $1)(void);$N", [init]) + appf(mainModProcs, "NIM_EXTERNC N_NOINLINE(void, $1)(void);$N", [datInit]) if sfSystemModule notin m.flags: - appff(mainDatInit, "\t$1();$N", "call void ()* $1$n", [datInit]) - let initCall = ropeff("\t$1();$N", "call void ()* $1$n", [init]) + appf(mainDatInit, "\t$1();$N", [datInit]) + let initCall = ropef("\t$1();$N", [init]) if sfMainModule in m.flags: app(mainModInit, initCall) else: @@ -1108,8 +984,7 @@ proc registerModuleToMain(m: PSym) = proc genInitCode(m: BModule) = var initname = getInitName(m.module) - var prc = ropeff("NIM_EXTERNC N_NOINLINE(void, $1)(void) {$N", - "define void $1() noinline {$n", [initname]) + var prc = ropef("NIM_EXTERNC N_NOINLINE(void, $1)(void) {$N", [initname]) if m.typeNodes > 0: appcg(m, m.s[cfsTypeInit1], "static #TNimNode $1[$2];$n", [m.typeNodesName, toRope(m.typeNodes)]) @@ -1130,7 +1005,7 @@ proc genInitCode(m: BModule) = # declare it nevertheless: m.frameDeclared = true if not m.preventStackTrace: - var procname = cstringLit(m.initProc, prc, m.module.name.s) + var procname = makeCString(m.module.name.s) app(prc, initFrame(m.initProc, procname, m.module.info.quotedFilename)) else: app(prc, ~"\tTFrame F; F.len = 0;$N") @@ -1151,8 +1026,8 @@ proc genInitCode(m: BModule) = app(prc, deinitGCFrame(m.initProc)) appf(prc, "}$N$N") - prc.appff("NIM_EXTERNC N_NOINLINE(void, $1)(void) {$N", - "define void $1() noinline {$n", [getDatInitName(m.module)]) + prc.appf("NIM_EXTERNC N_NOINLINE(void, $1)(void) {$N", + [getDatInitName(m.module)]) for i in cfsTypeInit1..cfsDynLibInit: app(prc, genSectionStart(i)) diff --git a/compiler/cgendata.nim b/compiler/cgendata.nim index 508f98074..bb98454a7 100644 --- a/compiler/cgendata.nim +++ b/compiler/cgendata.nim @@ -82,6 +82,9 @@ type maxFrameLen*: int # max length of frame descriptor module*: BModule # used to prevent excessive parameter passing withinLoop*: int # > 0 if we are within a loop + splitDecls*: int # > 0 if we are in some context for C++ that + # requires 'T x = T()' to become 'T x; x = T()' + # (yes, C++ is weird like that) gcFrameId*: Natural # for the GC stack marking gcFrameType*: PRope # the struct {} we put the GC markers into diff --git a/compiler/commands.nim b/compiler/commands.nim index 78fa9249c..c81b81d19 100644 --- a/compiler/commands.nim +++ b/compiler/commands.nim @@ -52,7 +52,7 @@ proc processSwitch*(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) const HelpMessage = "Nim Compiler Version $1 (" & CompileDate & ") [$2: $3]\n" & - "Copyright (c) 2006-2014 by Andreas Rumpf\n" + "Copyright (c) 2006-2015 by Andreas Rumpf\n" const Usage = slurp"doc/basicopt.txt".replace("//", "") diff --git a/compiler/msgs.nim b/compiler/msgs.nim index 35a121769..62e6d5281 100644 --- a/compiler/msgs.nim +++ b/compiler/msgs.nim @@ -522,7 +522,7 @@ proc newFileInfo(fullPath, projPath: string): TFileInfo = if optEmbedOrigSrc in gGlobalOptions or true: result.lines = @[] -proc fileInfoIdx*(filename: string): int32 = +proc fileInfoIdx*(filename: string; isKnownFile: var bool): int32 = var canon: string pseudoPath = false @@ -539,11 +539,16 @@ proc fileInfoIdx*(filename: string): int32 = if filenameToIndexTbl.hasKey(canon): result = filenameToIndexTbl[canon] else: + isKnownFile = false result = fileInfos.len.int32 fileInfos.add(newFileInfo(canon, if pseudoPath: filename else: canon.shortenDir)) filenameToIndexTbl[canon] = result +proc fileInfoIdx*(filename: string): int32 = + var dummy: bool + result = fileInfoIdx(filename, dummy) + proc newLineInfo*(fileInfoIdx: int32, line, col: int): TLineInfo = result.fileIndex = fileInfoIdx result.line = int16(line) diff --git a/compiler/nimconf.nim b/compiler/nimconf.nim index bcf9b5359..a433bf98e 100644 --- a/compiler/nimconf.nim +++ b/compiler/nimconf.nim @@ -11,7 +11,7 @@ import llstream, nversion, commands, os, strutils, msgs, platform, condsyms, lexer, - options, idents, wordrecg + options, idents, wordrecg, strtabs # ---------------- configuration file parser ----------------------------- # we use Nim's scanner here to safe space and work @@ -82,17 +82,17 @@ proc doElif(L: var TLexer, tok: var TToken) = proc jumpToDirective(L: var TLexer, tok: var TToken, dest: TJumpDest) = var nestedIfs = 0 while true: - if (tok.ident != nil) and (tok.ident.s == "@"): + if tok.ident != nil and tok.ident.s == "@": ppGetTok(L, tok) case whichKeyword(tok.ident) of wIf: inc(nestedIfs) of wElse: - if (dest == jdElseEndif) and (nestedIfs == 0): + if dest == jdElseEndif and nestedIfs == 0: doElse(L, tok) break of wElif: - if (dest == jdElseEndif) and (nestedIfs == 0): + if dest == jdElseEndif and nestedIfs == 0: doElif(L, tok) break of wEnd: @@ -119,9 +119,10 @@ proc parseDirective(L: var TLexer, tok: var TToken) = of wElif: doElif(L, tok) of wElse: doElse(L, tok) of wEnd: doEnd(L, tok) - of wWrite: + of wWrite: ppGetTok(L, tok) - msgs.msgWriteln(tokToStr(tok)) + msgs.msgWriteln(strtabs.`%`(tokToStr(tok), options.gConfigVars, + {useEnvironment, useKey})) ppGetTok(L, tok) else: case tok.ident.s.normalize @@ -178,9 +179,10 @@ proc parseAssignment(L: var TLexer, tok: var TToken) = if tok.tokType == tkBracketRi: confTok(L, tok) else: lexMessage(L, errTokenExpected, "']'") add(val, ']') - if tok.tokType in {tkColon, tkEquals}: + let percent = tok.ident.id == getIdent("%=").id + if tok.tokType in {tkColon, tkEquals} or percent: if len(val) > 0: add(val, ':') - confTok(L, tok) # skip ':' or '=' + confTok(L, tok) # skip ':' or '=' or '%' checkSymbol(L, tok) add(val, tokToStr(tok)) confTok(L, tok) # skip symbol @@ -189,7 +191,11 @@ proc parseAssignment(L: var TLexer, tok: var TToken) = checkSymbol(L, tok) add(val, tokToStr(tok)) confTok(L, tok) - processSwitch(s, val, passPP, info) + if percent: + processSwitch(s, strtabs.`%`(val, options.gConfigVars, + {useEnvironment, useEmpty}), passPP, info) + else: + processSwitch(s, val, passPP, info) proc readConfigFile(filename: string) = var diff --git a/compiler/nimsuggest/nimsuggest.nim b/compiler/nimsuggest/nimsuggest.nim index 6edea06e5..cac078127 100644 --- a/compiler/nimsuggest/nimsuggest.nim +++ b/compiler/nimsuggest/nimsuggest.nim @@ -87,8 +87,9 @@ proc action(cmd: string) = i += skipWhile(cmd, seps, i) i += parseInt(cmd, col, i) + var isKnownFile = true if orig.len == 0: err() - let dirtyIdx = orig.fileInfoIdx + let dirtyIdx = orig.fileInfoIdx(isKnownFile) if dirtyfile.len != 0: msgs.setDirtyFile(dirtyIdx, dirtyfile) else: msgs.setDirtyFile(dirtyIdx, nil) @@ -99,7 +100,10 @@ proc action(cmd: string) = gTrackPos = newLineInfo(dirtyIdx, line, col) #echo dirtyfile, gDirtyBufferIdx, " project ", gProjectMainIdx gErrorCounter = 0 - compileProject() + if not isKnownFile: + compileProject(dirtyIdx) + else: + compileProject() proc serve() = # do not stop after the first error: diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim index 5761e9e88..eeada0006 100644 --- a/compiler/semexprs.nim +++ b/compiler/semexprs.nim @@ -578,11 +578,12 @@ proc skipObjConv(n: PNode): PNode = proc isAssignable(c: PContext, n: PNode): TAssignableResult = result = parampatterns.isAssignable(c.p.owner, n) -proc newHiddenAddrTaken(c: PContext, n: PNode): PNode = - if n.kind == nkHiddenDeref: +proc newHiddenAddrTaken(c: PContext, n: PNode): PNode = + if n.kind == nkHiddenDeref and not (gCmd == cmdCompileToCpp or + sfCompileToCpp in c.module.flags): checkSonsLen(n, 1) result = n.sons[0] - else: + else: result = newNodeIT(nkHiddenAddr, n.info, makeVarType(c, n.typ)) addSon(result, n) if isAssignable(c, n) notin {arLValue, arLocalLValue}: @@ -1209,6 +1210,7 @@ proc asgnToResultVar(c: PContext, n, le, ri: PNode) {.inline.} = if x.typ.kind == tyVar and x.kind == nkSym and x.sym.kind == skResult: n.sons[0] = x # 'result[]' --> 'result' n.sons[1] = takeImplicitAddr(c, ri) + x.typ.flags.incl tfVarIsPtr template resultTypeIsInferrable(typ: PType): expr = typ.isMetaType and typ.kind != tyTypeDesc diff --git a/compiler/transf.nim b/compiler/transf.nim index f511ed69f..cf13630fd 100644 --- a/compiler/transf.nim +++ b/compiler/transf.nim @@ -321,6 +321,7 @@ proc transformYield(c: PTransf, n: PNode): PTransNode = proc transformAddrDeref(c: PTransf, n: PNode, a, b: TNodeKind): PTransNode = result = transformSons(c, n) + if gCmd == cmdCompileToCpp or sfCompileToCpp in c.module.flags: return var n = result.PNode case n.sons[0].kind of nkObjUpConv, nkObjDownConv, nkChckRange, nkChckRangeF, nkChckRange64: diff --git a/config/nim.cfg b/config/nim.cfg index 54c77e573..e4ea43a59 100644 --- a/config/nim.cfg +++ b/config/nim.cfg @@ -5,7 +5,8 @@ # You may set environment variables with # @putenv "key" "val" -# Environment variables cannot be used in the options, however! +# Environment variables can be accessed like so: +# gcc.path %= "$CC_PATH" cc = gcc @@ -21,6 +22,7 @@ mips.linux.gcc.linkerexe = "mips-openwrt-linux-gcc" @end path="$lib/core" + path="$lib/pure" path="$lib/pure/collections" path="$lib/pure/concurrency" diff --git a/lib/pure/logging.nim b/lib/pure/logging.nim index bb1835ed7..de733b75c 100644 --- a/lib/pure/logging.nim +++ b/lib/pure/logging.nim @@ -186,7 +186,7 @@ proc newRollingFileLogger*(filename = defaultFilename(), ## a new log file will be started and the old will be renamed. new(result) result.levelThreshold = levelThreshold - result.fmtStr = defaultFmtStr + result.fmtStr = fmtStr result.maxLines = maxLines result.f = open(filename, mode) result.curLine = 0 diff --git a/lib/pure/os.nim b/lib/pure/os.nim index 147614d3d..f01343673 100644 --- a/lib/pure/os.nim +++ b/lib/pure/os.nim @@ -1074,8 +1074,12 @@ when defined(windows): # because we support Windows GUI applications, things get really # messy here... when useWinUnicode: - proc strEnd(cstr: WideCString, c = 0'i32): WideCString {. - importc: "wcschr", header: "<string.h>".} + when defined(cpp): + proc strEnd(cstr: WideCString, c = 0'i32): WideCString {. + importcpp: "(NI16*)wcschr((const wchar_t *)#, #)", header: "<string.h>".} + else: + proc strEnd(cstr: WideCString, c = 0'i32): WideCString {. + importc: "wcschr", header: "<string.h>".} else: proc strEnd(cstr: cstring, c = 0'i32): cstring {. importc: "strchr", header: "<string.h>".} diff --git a/lib/pure/strtabs.nim b/lib/pure/strtabs.nim index 5b7149d8e..727d5a386 100644 --- a/lib/pure/strtabs.nim +++ b/lib/pure/strtabs.nim @@ -112,7 +112,7 @@ proc `[]`*(t: StringTableRef, key: string): string {.rtl, extern: "nstGet".} = proc mget*(t: StringTableRef, key: string): var string {. rtl, extern: "nstTake".} = ## retrieves the location at ``t[key]``. If `key` is not in `t`, the - ## ``EInvalidKey`` exception is raised. + ## ``KeyError`` exception is raised. var index = rawGet(t, key) if index >= 0: result = t.data[index].val else: raise newException(KeyError, "key does not exist: " & key) @@ -158,7 +158,7 @@ proc getValue(t: StringTableRef, flags: set[FormatFlag], key: string): string = else: result = "" if result.len == 0: if useKey in flags: result = '$' & key - elif not (useEmpty in flags): raiseFormatException(key) + elif useEmpty notin flags: raiseFormatException(key) proc newStringTable*(mode: StringTableMode): StringTableRef {. rtl, extern: "nst$1".} = diff --git a/lib/system/dyncalls.nim b/lib/system/dyncalls.nim index aab2a7b61..539e37aaf 100644 --- a/lib/system/dyncalls.nim +++ b/lib/system/dyncalls.nim @@ -84,16 +84,18 @@ elif defined(windows) or defined(dos): type THINSTANCE {.importc: "HINSTANCE".} = object x: pointer + proc getProcAddress(lib: THINSTANCE, name: cstring): TProcAddr {. + importcpp: "(void*)GetProcAddress(@)", header: "<windows.h>", stdcall.} else: type THINSTANCE {.importc: "HINSTANCE".} = pointer + proc getProcAddress(lib: THINSTANCE, name: cstring): TProcAddr {. + importc: "GetProcAddress", header: "<windows.h>", stdcall.} proc freeLibrary(lib: THINSTANCE) {. importc: "FreeLibrary", header: "<windows.h>", stdcall.} proc winLoadLibrary(path: cstring): THINSTANCE {. importc: "LoadLibraryA", header: "<windows.h>", stdcall.} - proc getProcAddress(lib: THINSTANCE, name: cstring): TProcAddr {. - importc: "GetProcAddress", header: "<windows.h>", stdcall.} proc nimUnloadLibrary(lib: TLibHandle) = freeLibrary(cast[THINSTANCE](lib)) diff --git a/lib/system/sysio.nim b/lib/system/sysio.nim index 7908fbe4d..2e254c87b 100644 --- a/lib/system/sysio.nim +++ b/lib/system/sysio.nim @@ -183,11 +183,17 @@ proc rawEchoNL() {.inline, compilerproc.} = write(stdout, "\n") when (defined(windows) and not defined(useWinAnsi)) or defined(nimdoc): include "system/widestrs" -when defined(windows) and not defined(useWinAnsi): - proc wfopen(filename, mode: WideCString): pointer {. - importc: "_wfopen", nodecl.} - proc wfreopen(filename, mode: WideCString, stream: File): File {. - importc: "_wfreopen", nodecl.} +when defined(windows) and not defined(useWinAnsi): + when defined(cpp): + proc wfopen(filename, mode: WideCString): pointer {. + importcpp: "_wfopen((const wchar_t*)#, (const wchar_t*)#)", nodecl.} + proc wfreopen(filename, mode: WideCString, stream: File): File {. + importc: "_wfreopen((const wchar_t*)#, (const wchar_t*)#)", nodecl.} + else: + proc wfopen(filename, mode: WideCString): pointer {. + importc: "_wfopen", nodecl.} + proc wfreopen(filename, mode: WideCString, stream: File): File {. + importc: "_wfreopen", nodecl.} proc fopen(filename, mode: cstring): pointer = var f = newWideCString(filename) diff --git a/todo.txt b/todo.txt index d64f4fdd4..17b8b3a21 100644 --- a/todo.txt +++ b/todo.txt @@ -25,7 +25,6 @@ Low priority: - support for exception propagation? (hard to implement) - the copying of the 'ref Promise' into the thead local storage only happens to work due to the write barrier's implementation -- clean up the C code generator. Full of cruft. Misc |