diff options
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/ccgexprs.nim | 2 | ||||
-rw-r--r-- | compiler/evalffi.nim | 56 | ||||
-rw-r--r-- | compiler/main.nim | 7 | ||||
-rw-r--r-- | compiler/parser.nim | 16 | ||||
-rw-r--r-- | compiler/semexprs.nim | 4 | ||||
-rw-r--r-- | compiler/vm.nim | 16 | ||||
-rw-r--r-- | compiler/vmdef.nim | 2 | ||||
-rw-r--r-- | compiler/vmgen.nim | 92 |
8 files changed, 116 insertions, 79 deletions
diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index ba543039e..be47ac0c4 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -343,7 +343,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = of tyPtr, tyPointer, tyChar, tyBool, tyEnum, tyCString, tyInt..tyUInt64, tyRange, tyVar: linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src)) - else: internalError("genAssignment(" & $ty.kind & ')') + else: internalError("genAssignment: " & $ty.kind) proc getDestLoc(p: BProc, d: var TLoc, typ: PType) = if d.k == locNone: getTemp(p, typ, d) diff --git a/compiler/evalffi.nim b/compiler/evalffi.nim index 74f0663f3..54be0ccb2 100644 --- a/compiler/evalffi.nim +++ b/compiler/evalffi.nim @@ -1,7 +1,7 @@ # # # The Nimrod Compiler -# (c) Copyright 2012 Andreas Rumpf +# (c) Copyright 2014 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -102,7 +102,7 @@ proc mapCallConv(cc: TCallingConvention, info: TLineInfo): TABI = of ccStdCall: result = when defined(windows): STDCALL else: DEFAULT_ABI of ccCDecl: result = DEFAULT_ABI else: - GlobalError(info, "cannot map calling convention to FFI") + globalError(info, "cannot map calling convention to FFI") template rd(T, p: expr): expr {.immediate.} = (cast[ptr T](p))[] template wr(T, p, v: expr) {.immediate.} = (cast[ptr T](p))[] = v @@ -164,7 +164,7 @@ proc packObject(x: PNode, typ: PType, res: pointer) = let field = getField(typ.n, i) pack(it, field.typ, res +! field.offset) else: - GlobalError(x.info, "cannot pack unnamed tuple") + globalError(x.info, "cannot pack unnamed tuple") const maxPackDepth = 20 var packRecCheck = 0 @@ -193,7 +193,7 @@ proc pack(v: PNode, typ: PType, res: pointer) = of 4: awr(int32, v.intVal.int32) of 8: awr(int64, v.intVal.int64) else: - GlobalError(v.info, "cannot map value to FFI (tyEnum, tySet)") + globalError(v.info, "cannot map value to FFI (tyEnum, tySet)") of tyFloat: awr(float, v.floatVal) of tyFloat32: awr(float32, v.floatVal) of tyFloat64: awr(float64, v.floatVal) @@ -207,7 +207,7 @@ proc pack(v: PNode, typ: PType, res: pointer) = elif v.kind in {nkStrLit..nkTripleStrLit}: awr(cstring, cstring(v.strVal)) else: - GlobalError(v.info, "cannot map pointer/proc value to FFI") + globalError(v.info, "cannot map pointer/proc value to FFI") of tyPtr, tyRef, tyVar: if v.kind == nkNilLit: # nothing to do since the memory is 0 initialized anyway @@ -217,7 +217,7 @@ proc pack(v: PNode, typ: PType, res: pointer) = else: if packRecCheck > maxPackDepth: packRecCheck = 0 - GlobalError(v.info, "cannot map value to FFI " & typeToString(v.typ)) + globalError(v.info, "cannot map value to FFI " & typeToString(v.typ)) inc packRecCheck pack(v.sons[0], typ.sons[0], res +! sizeof(pointer)) dec packRecCheck @@ -233,7 +233,7 @@ proc pack(v: PNode, typ: PType, res: pointer) = of tyDistinct, tyGenericInst: pack(v, typ.sons[0], res) else: - GlobalError(v.info, "cannot map value to FFI " & typeToString(v.typ)) + globalError(v.info, "cannot map value to FFI " & typeToString(v.typ)) proc unpack(x: pointer, typ: PType, n: PNode): PNode @@ -243,7 +243,7 @@ proc unpackObjectAdd(x: pointer, n, result: PNode) = for i in countup(0, sonsLen(n) - 1): unpackObjectAdd(x, n.sons[i], result) of nkRecCase: - GlobalError(result.info, "case objects cannot be unpacked") + globalError(result.info, "case objects cannot be unpacked") of nkSym: var pair = newNodeI(nkExprColonExpr, result.info, 2) pair.sons[0] = n @@ -262,14 +262,14 @@ proc unpackObject(x: pointer, typ: PType, n: PNode): PNode = result = newNode(nkPar) result.typ = typ if typ.n.isNil: - InternalError("cannot unpack unnamed tuple") + internalError("cannot unpack unnamed tuple") unpackObjectAdd(x, typ.n, result) else: result = n if result.kind notin {nkObjConstr, nkPar}: - GlobalError(n.info, "cannot map value from FFI") + globalError(n.info, "cannot map value from FFI") if typ.n.isNil: - GlobalError(n.info, "cannot unpack unnamed tuple") + globalError(n.info, "cannot unpack unnamed tuple") for i in countup(ord(n.kind == nkObjConstr), sonsLen(n) - 1): var it = n.sons[i] if it.kind == nkExprColonExpr: @@ -288,7 +288,7 @@ proc unpackArray(x: pointer, typ: PType, n: PNode): PNode = else: result = n if result.kind != nkBracket: - GlobalError(n.info, "cannot map value from FFI") + globalError(n.info, "cannot map value from FFI") let baseSize = typ.sons[1].getSize for i in 0 .. < result.len: result.sons[i] = unpack(x +! i * baseSize, typ.sons[1], result.sons[i]) @@ -312,7 +312,7 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode = #echo "expected ", k, " but got ", result.kind #debug result return newNodeI(nkExceptBranch, n.info) - #GlobalError(n.info, "cannot map value from FFI") + #globalError(n.info, "cannot map value from FFI") result.field = v template setNil() = @@ -337,19 +337,19 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode = of tyInt16: awi(nkInt16Lit, rd(int16, x)) of tyInt32: awi(nkInt32Lit, rd(int32, x)) of tyInt64: awi(nkInt64Lit, rd(int64, x)) - of tyUInt: awi(nkUIntLit, rd(uint, x).biggestInt) - of tyUInt8: awi(nkUInt8Lit, rd(uint8, x).biggestInt) - of tyUInt16: awi(nkUInt16Lit, rd(uint16, x).biggestInt) - of tyUInt32: awi(nkUInt32Lit, rd(uint32, x).biggestInt) - of tyUInt64: awi(nkUInt64Lit, rd(uint64, x).biggestInt) + of tyUInt: awi(nkUIntLit, rd(uint, x).BiggestInt) + of tyUInt8: awi(nkUInt8Lit, rd(uint8, x).BiggestInt) + of tyUInt16: awi(nkUInt16Lit, rd(uint16, x).BiggestInt) + of tyUInt32: awi(nkUInt32Lit, rd(uint32, x).BiggestInt) + of tyUInt64: awi(nkUInt64Lit, rd(uint64, x).BiggestInt) of tyEnum: case typ.getSize - of 1: awi(nkIntLit, rd(uint8, x).biggestInt) - of 2: awi(nkIntLit, rd(uint16, x).biggestInt) - of 4: awi(nkIntLit, rd(int32, x).biggestInt) - of 8: awi(nkIntLit, rd(int64, x).biggestInt) + of 1: awi(nkIntLit, rd(uint8, x).BiggestInt) + of 2: awi(nkIntLit, rd(uint16, x).BiggestInt) + of 4: awi(nkIntLit, rd(int32, x).BiggestInt) + of 8: awi(nkIntLit, rd(int64, x).BiggestInt) else: - GlobalError(n.info, "cannot map value from FFI (tyEnum, tySet)") + globalError(n.info, "cannot map value from FFI (tyEnum, tySet)") of tyFloat: awf(nkFloatLit, rd(float, x)) of tyFloat32: awf(nkFloat32Lit, rd(float32, x)) of tyFloat64: awf(nkFloat64Lit, rd(float64, x)) @@ -374,7 +374,7 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode = n.sons[0] = unpack(p, typ.sons[0], n.sons[0]) result = n else: - GlobalError(n.info, "cannot map value from FFI " & typeToString(typ)) + globalError(n.info, "cannot map value from FFI " & typeToString(typ)) of tyObject, tyTuple: result = unpackObject(x, typ, n) of tyArray, tyArrayConstr: @@ -391,7 +391,7 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode = result = unpack(x, typ.sons[0], n) else: # XXX what to do with 'array' here? - GlobalError(n.info, "cannot map value from FFI " & typeToString(typ)) + globalError(n.info, "cannot map value from FFI " & typeToString(typ)) proc fficast*(x: PNode, destTyp: PType): PNode = if x.kind == nkPtrLit and x.typ.kind in {tyPtr, tyRef, tyVar, tyPointer, @@ -414,7 +414,7 @@ proc fficast*(x: PNode, destTyp: PType): PNode = dealloc a proc callForeignFunction*(call: PNode): PNode = - InternalAssert call.sons[0].kind == nkPtrLit + internalAssert call.sons[0].kind == nkPtrLit var cif: TCif var sig: TParamList @@ -422,12 +422,12 @@ proc callForeignFunction*(call: PNode): PNode = for i in 1..call.len-1: sig[i-1] = mapType(call.sons[i].typ) if sig[i-1].isNil: - GlobalError(call.info, "cannot map FFI type") + globalError(call.info, "cannot map FFI type") let typ = call.sons[0].typ if prep_cif(cif, mapCallConv(typ.callConv, call.info), cuint(call.len-1), mapType(typ.sons[0]), sig) != OK: - GlobalError(call.info, "error in FFI call") + globalError(call.info, "error in FFI call") var args: TArgList let fn = cast[pointer](call.sons[0].intVal) diff --git a/compiler/main.nim b/compiler/main.nim index cdea7b5ca..f6d11d960 100644 --- a/compiler/main.nim +++ b/compiler/main.nim @@ -135,7 +135,7 @@ proc interactivePasses = #setTarget(osNimrodVM, cpuNimrodVM) initDefines() defineSymbol("nimrodvm") - when hasFFI: DefineSymbol("nimffi") + when hasFFI: defineSymbol("nimffi") registerPass(verbosePass) registerPass(semPass) registerPass(evalPass) @@ -324,7 +324,7 @@ proc mainCommand* = wantMainModule() when hasTinyCBackend: extccomp.setCC("tcc") - CommandCompileToC() + commandCompileToC() else: rawMessage(errInvalidCommandX, command) of "js", "compiletojs": @@ -450,7 +450,8 @@ proc mainCommand* = echo " tries : ", gCacheTries echo " misses: ", gCacheMisses echo " int tries: ", gCacheIntTries - echo " efficiency: ", formatFloat(1-(gCacheMisses.float/gCacheTries.float), ffDecimal, 3) + echo " efficiency: ", formatFloat(1-(gCacheMisses.float/gCacheTries.float), + ffDecimal, 3) when SimiluateCaasMemReset: resetMemory() diff --git a/compiler/parser.nim b/compiler/parser.nim index 3765557b9..4497e360a 100644 --- a/compiler/parser.nim +++ b/compiler/parser.nim @@ -672,12 +672,14 @@ proc primarySuffix(p: var TParser, r: PNode): PNode = let a = result result = newNodeP(nkCommand, p) addSon(result, a) - while p.tok.tokType != tkEof: - let a = parseExpr(p) - addSon(result, a) - if p.tok.tokType != tkComma: break - getTok(p) - optInd(p, a) + addSon result, parseExpr(p) + when false: + while p.tok.tokType != tkEof: + let a = parseExpr(p) + addSon(result, a) + if p.tok.tokType != tkComma: break + getTok(p) + optInd(p, a) if p.tok.tokType == tkDo: parseDoBlocks(p, result) else: @@ -1103,7 +1105,9 @@ proc parseExprStmt(p: var TParser): PNode = #| doBlocks #| / macroColon #| ))? + inc p.inPragma var a = simpleExpr(p) + dec p.inPragma if p.tok.tokType == tkEquals: getTok(p) optInd(p, result) diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim index 84303b6cd..a384c41fd 100644 --- a/compiler/semexprs.nim +++ b/compiler/semexprs.nim @@ -1706,8 +1706,8 @@ proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode = result = n result.typ = t result.kind = nkObjConstr - t = skipTypes(t, abstractInst) - if t.kind == tyRef: t = skipTypes(t.sons[0], abstractInst) + t = skipTypes(t, {tyGenericInst}) + if t.kind == tyRef: t = skipTypes(t.sons[0], {tyGenericInst}) if t.kind != tyObject: localError(n.info, errGenerated, "object constructor needs an object type") return diff --git a/compiler/vm.nim b/compiler/vm.nim index deca288b5..aec76f307 100644 --- a/compiler/vm.nim +++ b/compiler/vm.nim @@ -337,7 +337,7 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): PNode = asgnRef(c.globals.sons[instr.regBx-wordExcess-1], regs[ra]) of opcWrGlobal: asgnComplex(c.globals.sons[instr.regBx-wordExcess-1], regs[ra]) - of opcLdArr: + of opcLdArr, opcLdArrRef: # a = b[c] let rb = instr.regB let rc = instr.regC @@ -348,7 +348,11 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): PNode = assert regs[rb].kind != nkMetaNode let src = regs[rb] if src.kind notin {nkEmpty..nkNilLit} and idx <% src.len: - asgnComplex(regs[ra], src.sons[idx]) + if instr.opcode == opcLdArrRef and false: + # XXX activate when seqs are fixed + asgnRef(regs[ra], src.sons[idx]) + else: + asgnComplex(regs[ra], src.sons[idx]) else: stackTrace(c, tos, pc, errIndexOutOfBounds) of opcLdStrIdx: @@ -379,9 +383,15 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): PNode = # a = b.c let rb = instr.regB let rc = instr.regC - # XXX this creates a wrong alias #Message(c.debug[pc], warnUser, $regs[rb].safeLen & " " & $rc) asgnComplex(regs[ra], regs[rb].sons[rc]) + of opcLdObjRef: + # a = b.c + let rb = instr.regB + let rc = instr.regC + # XXX activate when seqs are fixed + asgnComplex(regs[ra], regs[rb].sons[rc]) + #asgnRef(regs[ra], regs[rb].sons[rc]) of opcWrObj: # a.b = c let rb = instr.regB diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim index 480c7f31b..87159c813 100644 --- a/compiler/vmdef.nim +++ b/compiler/vmdef.nim @@ -34,9 +34,11 @@ type opcAsgnComplex, opcLdArr, # a = b[c] + opcLdArrRef, opcWrArr, # a[b] = c opcWrArrRef, opcLdObj, # a = b.c + opcLdObjRef, opcWrObj, # a.b = c opcWrObjRef, opcAddr, diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim index a41e60e7d..e0ff5b235 100644 --- a/compiler/vmgen.nim +++ b/compiler/vmgen.nim @@ -1,7 +1,7 @@ # # # The Nimrod Compiler -# (c) Copyright 2013 Andreas Rumpf +# (c) Copyright 2014 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -13,9 +13,18 @@ import unsigned, strutils, ast, astalgo, types, msgs, renderer, vmdef, trees, intsets, rodread, magicsys, options +from os import splitFile + when hasFFI: import evalffi +type + TGenFlag = enum gfNone, gfAddrOf + TGenFlags = set[TGenFlag] + +proc debugInfo(info: TLineInfo): string = + result = info.toFilename.splitFile.name & ":" & $info.line + proc codeListing(c: PCtx, result: var string, start=0) = # first iteration: compute all necessary labels: var jumpTargets = initIntSet() @@ -44,7 +53,7 @@ proc codeListing(c: PCtx, result: var string, start=0) = else: result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, x.regBx-wordExcess) result.add("\t#") - result.add(toFileLine(c.debug[i])) + result.add(debugInfo(c.debug[i])) result.add("\n") inc i @@ -190,20 +199,20 @@ template withBlock(labl: PSym; body: stmt) {.immediate, dirty.} = body popBlock(c, oldLen) -proc gen(c: PCtx; n: PNode; dest: var TDest) -proc gen(c: PCtx; n: PNode; dest: TRegister) = +proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) +proc gen(c: PCtx; n: PNode; dest: TRegister; flags: TGenFlags = {}) = var d: TDest = dest - gen(c, n, d) + gen(c, n, d, flags) internalAssert d == dest -proc gen(c: PCtx; n: PNode) = +proc gen(c: PCtx; n: PNode; flags: TGenFlags = {}) = var tmp: TDest = -1 - gen(c, n, tmp) + gen(c, n, tmp, flags) #if n.typ.isEmptyType: InternalAssert tmp < 0 -proc genx(c: PCtx; n: PNode): TRegister = +proc genx(c: PCtx; n: PNode; flags: TGenFlags = {}): TRegister = var tmp: TDest = -1 - gen(c, n, tmp) + gen(c, n, tmp, flags) internalAssert tmp >= 0 result = TRegister(tmp) @@ -477,8 +486,8 @@ proc genNew(c: PCtx; n: PNode) = proc genNewSeq(c: PCtx; n: PNode) = let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(n.sons[1].typ) else: c.genx(n.sons[1]) - c.gABx(n, opcNewSeq, dest, c.genType(n.sons[1].typ.skipTypes(abstractVar))) let tmp = c.genx(n.sons[2]) + c.gABx(n, opcNewSeq, dest, c.genType(n.sons[1].typ.skipTypes(abstractVar))) c.gABx(n, opcNewSeq, tmp, 0) c.freeTemp(tmp) c.genAsgnPatch(n.sons[1], dest) @@ -528,6 +537,14 @@ proc genBinaryStmt(c: PCtx; n: PNode; opc: TOpcode) = c.gABC(n, opc, dest, tmp, 0) c.freeTemp(tmp) +proc genBinaryStmtVar(c: PCtx; n: PNode; opc: TOpcode) = + let + dest = c.genx(n.sons[1], {gfAddrOf}) + tmp = c.genx(n.sons[2]) + c.gABC(n, opc, dest, tmp, 0) + #c.genAsgnPatch(n.sons[1], dest) + c.freeTemp(tmp) + proc genUnaryStmt(c: PCtx; n: PNode; opc: TOpcode) = let tmp = c.genx(n.sons[1]) c.gABC(n, opc, tmp, 0, 0) @@ -754,13 +771,13 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = c.freeTempRange(x, n.len-1) of mAppendStrCh: unused(n, dest) - genBinaryStmt(c, n, opcAddStrCh) + genBinaryStmtVar(c, n, opcAddStrCh) of mAppendStrStr: unused(n, dest) - genBinaryStmt(c, n, opcAddStrStr) + genBinaryStmtVar(c, n, opcAddStrStr) of mAppendSeqElem: unused(n, dest) - genBinaryStmt(c, n, opcAddSeqElem) + genBinaryStmtVar(c, n, opcAddSeqElem) of mParseExprToAst: genUnaryABC(c, n, dest, opcParseExprToAst) of mParseStmtToAst: @@ -890,12 +907,14 @@ proc skipDeref(n: PNode): PNode = else: result = n -proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) = +proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode; + flags: TGenFlags) = # a nop for certain types + let flags = if opc == opcAddr: flags+{gfAddrOf} else: flags if unneededIndirection(n.sons[0]): - gen(c, n.sons[0], dest) + gen(c, n.sons[0], dest, flags) else: - let tmp = c.genx(n.sons[0]) + let tmp = c.genx(n.sons[0], flags) if dest < 0: dest = c.getTemp(n.typ) gABC(c, n, opc, dest, tmp) c.freeTemp(tmp) @@ -1026,26 +1045,27 @@ proc genRdVar(c: PCtx; n: PNode; dest: var TDest) = cannotEval(n) #InternalError(n.info, s.name.s & " " & $s.position) -proc genAccess(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) = - let a = c.genx(n.sons[0]) - let b = c.genx(n.sons[1]) +proc genAccess(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode; + flags: TGenFlags) = + let a = c.genx(n.sons[0], flags) + let b = c.genx(n.sons[1], {}) if dest < 0: dest = c.getTemp(n.typ) - c.gABC(n, opc, dest, a, b) + c.gABC(n, (if gfAddrOf in flags: succ(opc) else: opc), dest, a, b) c.freeTemp(a) c.freeTemp(b) -proc genObjAccess(c: PCtx; n: PNode; dest: var TDest) = - genAccess(c, n, dest, opcLdObj) +proc genObjAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) = + genAccess(c, n, dest, opcLdObj, flags) -proc genCheckedObjAccess(c: PCtx; n: PNode; dest: var TDest) = +proc genCheckedObjAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) = # XXX implement field checks! - genAccess(c, n.sons[0], dest, opcLdObj) + genAccess(c, n.sons[0], dest, opcLdObj, flags) -proc genArrAccess(c: PCtx; n: PNode; dest: var TDest) = +proc genArrAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) = if n.sons[0].typ.skipTypes(abstractVarRange).kind in {tyString, tyCString}: - genAccess(c, n, dest, opcLdStrIdx) + genAccess(c, n, dest, opcLdStrIdx, {}) else: - genAccess(c, n, dest, opcLdArr) + genAccess(c, n, dest, opcLdArr, flags) proc getNullValue*(typ: PType, info: TLineInfo): PNode proc getNullValueAux(obj: PNode, result: PNode) = @@ -1222,7 +1242,7 @@ proc genTupleConstr(c: PCtx, n: PNode, dest: var TDest) = proc genProc*(c: PCtx; s: PSym): int -proc gen(c: PCtx; n: PNode; dest: var TDest) = +proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = case n.kind of nkSym: let s = n.sym @@ -1271,11 +1291,11 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) = of nkAsgn, nkFastAsgn: unused(n, dest) genAsgn(c, n.sons[0], n.sons[1], n.kind == nkAsgn) - of nkDotExpr: genObjAccess(c, n, dest) - of nkCheckedFieldExpr: genCheckedObjAccess(c, n, dest) - of nkBracketExpr: genArrAccess(c, n, dest) - of nkDerefExpr, nkHiddenDeref: genAddrDeref(c, n, dest, opcDeref) - of nkAddr, nkHiddenAddr: genAddrDeref(c, n, dest, opcAddr) + of nkDotExpr: genObjAccess(c, n, dest, flags) + of nkCheckedFieldExpr: genCheckedObjAccess(c, n, dest, flags) + of nkBracketExpr: genArrAccess(c, n, dest, flags) + of nkDerefExpr, nkHiddenDeref: genAddrDeref(c, n, dest, opcDeref, flags) + of nkAddr, nkHiddenAddr: genAddrDeref(c, n, dest, opcAddr, flags) of nkWhenStmt, nkIfStmt, nkIfExpr: genIf(c, n, dest) of nkCaseStmt: genCase(c, n, dest) of nkWhileStmt: @@ -1298,7 +1318,7 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) = of nkStmtListExpr: let L = n.len-1 for i in 0 .. <L: gen(c, n.sons[i]) - gen(c, n.sons[L], dest) + gen(c, n.sons[L], dest, flags) of nkDiscardStmt: unused(n, dest) gen(c, n.sons[0]) @@ -1460,9 +1480,9 @@ proc genProc(c: PCtx; s: PSym): int = c.gABC(body, opcEof, eofInstr.regA) c.optimizeJumps(result) s.offset = c.prc.maxSlots - #if s.name.s == "rawGet": + #if s.name.s == "concatStyleInterpolation": # c.echoCode(result) - # echo renderTree(body) + # echo renderTree(body) c.prc = oldPrc else: c.prc.maxSlots = s.offset |