diff options
-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 | ||||
-rw-r--r-- | copying.txt | 2 | ||||
-rw-r--r-- | doc/manual.txt | 131 | ||||
-rw-r--r-- | koch.nim | 5 | ||||
-rw-r--r-- | lib/pure/dynlib.nim | 20 | ||||
-rw-r--r-- | lib/system.nim | 38 | ||||
-rw-r--r-- | lib/system/excpt.nim | 2 | ||||
-rw-r--r-- | lib/system/gc_ms.nim | 28 | ||||
-rw-r--r-- | readme.md | 2 | ||||
-rw-r--r-- | readme.txt | 2 | ||||
-rw-r--r-- | tests/macros/tstringinterp.nim | 6 | ||||
-rw-r--r-- | tests/specials.nim | 238 | ||||
-rw-r--r-- | tests/testament/backend.nim | 12 | ||||
-rw-r--r-- | tests/testament/htmlgen.nim | 19 | ||||
-rw-r--r-- | tests/testament/tester.nim | 15 | ||||
-rw-r--r-- | tests/tester.nim | 457 | ||||
-rw-r--r-- | todo.txt | 5 |
24 files changed, 255 insertions, 922 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 diff --git a/copying.txt b/copying.txt index 0ff6b7d87..4041ca027 100644 --- a/copying.txt +++ b/copying.txt @@ -1,7 +1,7 @@ =============================================================================== Nimrod -- a Compiler for Nimrod. http://nimrod-code.org/ -Copyright (C) 2004-2013 Andreas Rumpf. All rights reserved. +Copyright (C) 2004-2014 Andreas Rumpf. All rights reserved. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal diff --git a/doc/manual.txt b/doc/manual.txt index faf62dcee..260f0807a 100644 --- a/doc/manual.txt +++ b/doc/manual.txt @@ -12,6 +12,8 @@ Nimrod Manual user to one/some of the other players, but the total amount seems to remain pretty much constant for a given task. -- Ran + + About this document =================== @@ -1479,7 +1481,7 @@ But it seems all this boilerplate code needs to be repeated for the ``TEuro`` currency. This can be solved with templates_. .. code-block:: nimrod - template Additive(typ: typedesc): stmt = + template additive(typ: typedesc): stmt = proc `+` *(x, y: typ): typ {.borrow.} proc `-` *(x, y: typ): typ {.borrow.} @@ -1487,26 +1489,26 @@ currency. This can be solved with templates_. proc `+` *(x: typ): typ {.borrow.} proc `-` *(x: typ): typ {.borrow.} - template Multiplicative(typ, base: typedesc): stmt = + template multiplicative(typ, base: typedesc): stmt = proc `*` *(x: typ, y: base): typ {.borrow.} proc `*` *(x: base, y: typ): typ {.borrow.} proc `div` *(x: typ, y: base): typ {.borrow.} proc `mod` *(x: typ, y: base): typ {.borrow.} - template Comparable(typ: typedesc): stmt = + template comparable(typ: typedesc): stmt = proc `<` * (x, y: typ): bool {.borrow.} proc `<=` * (x, y: typ): bool {.borrow.} proc `==` * (x, y: typ): bool {.borrow.} - template DefineCurrency(typ, base: expr): stmt = + template defineCurrency(typ, base: expr): stmt = type typ* = distinct base - Additive(typ) - Multiplicative(typ, base) - Comparable(typ) + additive(typ) + multiplicative(typ, base) + comparable(typ) - DefineCurrency(TDollar, int) - DefineCurrency(TEuro, int) + defineCurrency(TDollar, int) + defineCurrency(TEuro, int) Void type @@ -3440,13 +3442,41 @@ A symbol can be forced to be open by a `mixin`:idx: declaration: .. code-block:: nimrod proc create*[T](): ref T = - # there is no overloaded 'mixin' here, so we need to state that it's an + # there is no overloaded 'init' here, so we need to state that it's an # open symbol explicitly: mixin init new result init result +Bind statement +-------------- + +The `bind`:idx: statement is the counterpart to the ``mixin`` statement. It +can be used to explicitly declare identifiers that should be bound early (i.e. +the identifiers should be looked up in the scope of the template/generic +definition): + +.. code-block:: nimrod + # Module A + var + lastId = 0 + + template genId*: expr = + bind lastId + inc(lastId) + lastId + +.. code-block:: nimrod + # Module B + import A + + echo genId() + +But a ``bind`` is rarely useful because symbol binding from the definition +scope is the default. + + Templates ========= @@ -3506,28 +3536,6 @@ receive undeclared identifiers: declareInt(x) # valid -Scoping in templates --------------------- - -The template body does not open a new scope. To open a new scope a ``block`` -statement can be used: - -.. code-block:: nimrod - template declareInScope(x: expr, t: typedesc): stmt {.immediate.} = - var x: t - - template declareInNewScope(x: expr, t: typedesc): stmt {.immediate.} = - # open a new scope: - block: - var x: t - - declareInScope(a, int) - a = 42 # works, `a` is known here - - declareInNewScope(b, int) - b = 42 # does not work, `b` is unknown - - Passing a code block to a template ---------------------------------- @@ -3538,50 +3546,28 @@ special ``:`` syntax: .. code-block:: nimrod template withFile(f, fn, mode: expr, actions: stmt): stmt {.immediate.} = - block: - var f: TFile - if open(f, fn, mode): - try: - actions - finally: - close(f) - else: - quit("cannot open: " & fn) + var f: TFile + if open(f, fn, mode): + try: + actions + finally: + close(f) + else: + quit("cannot open: " & fn) withFile(txt, "ttempl3.txt", fmWrite): txt.writeln("line 1") txt.writeln("line 2") In the example the two ``writeln`` statements are bound to the ``actions`` -parameter. - -**Note:** The symbol binding rules for templates might change! - -Symbol binding within templates happens after template instantiation: - -.. code-block:: nimrod - # Module A - var - lastId = 0 - - template genId*: expr = - inc(lastId) - lastId - -.. code-block:: nimrod - # Module B - import A - - echo genId() # Error: undeclared identifier: 'lastId' +parameter. -Bind statement --------------- +Symbol binding in templates +--------------------------- -Exporting a template is a often a leaky abstraction as it can depend on -symbols that are not visible from a client module. However, to compensate for -this case, a `bind`:idx: statement can be used: It declares all identifiers -that should be bound early (i.e. when the template is parsed): +A template is a `hygienic`:idx: macro and so opens a new scope. Most symbols are +bound from the definition scope of the template: .. code-block:: nimrod # Module A @@ -3589,7 +3575,6 @@ that should be bound early (i.e. when the template is parsed): lastId = 0 template genId*: expr = - bind lastId inc(lastId) lastId @@ -3597,9 +3582,11 @@ that should be bound early (i.e. when the template is parsed): # Module B import A - echo genId() # Works + echo genId() # Works as 'lastId' has been bound in 'genId's defining scope + +As in generics symbol binding can be influenced via ``mixin`` or ``bind`` +statements. -A ``bind`` statement can also be used in generics for the same purpose. Identifier construction @@ -3942,13 +3929,13 @@ Static params can also appear in the signatures of generic types: type Matrix[M,N: static[int]; T: Number] = array[0..(M*N - 1), T] - # Please, note how `Number` is just a type constraint here, while + # Note how `Number` is just a type constraint here, while # `static[int]` requires us to supply a compile-time int value AffineTransform2D[T] = Matrix[3, 3, T] AffineTransform3D[T] = Matrix[4, 4, T] - AffineTransform3D[float] # OK + AffineTransform3D[float] # OK AffineTransform2D[string] # Error, `string` is not a `Number` diff --git a/koch.nim b/koch.nim index 35a86a597..4d2b3bfb7 100644 --- a/koch.nim +++ b/koch.nim @@ -266,8 +266,9 @@ proc tests(args: string) = # we compile the tester with taintMode:on to have a basic # taint mode test :-) exec "nimrod cc --taintMode:on tests/testament/tester" - exec quoteShell(getCurrentDir() / "tests/testament/tester".exe) & " " & - (args|"all") + let tester = quoteShell(getCurrentDir() / "tests/testament/tester".exe) + exec tester & " " & (args|"all") + exec tester & " html" proc temp(args: string) = var output = "compiler" / "nimrod".exe diff --git a/lib/pure/dynlib.nim b/lib/pure/dynlib.nim index a64b7f138..3ed00fdb2 100644 --- a/lib/pure/dynlib.nim +++ b/lib/pure/dynlib.nim @@ -14,15 +14,15 @@ type TLibHandle* = pointer ## a handle to a dynamically loaded library -proc LoadLib*(path: string): TLibHandle +proc loadLib*(path: string): TLibHandle ## loads a library from `path`. Returns nil if the library could not ## be loaded. -proc LoadLib*(): TLibHandle +proc loadLib*(): TLibHandle ## gets the handle from the current executable. Returns nil if the ## library could not be loaded. -proc UnloadLib*(lib: TLibHandle) +proc unloadLib*(lib: TLibHandle) ## unloads the library `lib` proc raiseInvalidLibrary*(name: cstring) {.noinline, noreturn.} = @@ -60,9 +60,9 @@ when defined(posix): proc dlsym(lib: TLibHandle, name: cstring): pointer {. importc, header: "<dlfcn.h>".} - proc LoadLib(path: string): TLibHandle = return dlopen(path, RTLD_NOW) - proc LoadLib(): TLibHandle = return dlopen(nil, RTLD_NOW) - proc UnloadLib(lib: TLibHandle) = dlclose(lib) + proc loadLib(path: string): TLibHandle = return dlopen(path, RTLD_NOW) + proc loadLib(): TLibHandle = return dlopen(nil, RTLD_NOW) + proc unloadLib(lib: TLibHandle) = dlclose(lib) proc symAddr(lib: TLibHandle, name: cstring): pointer = return dlsym(lib, name) @@ -78,14 +78,14 @@ elif defined(windows) or defined(dos): proc FreeLibrary(lib: THINSTANCE) {.importc, header: "<windows.h>", stdcall.} proc winLoadLibrary(path: cstring): THINSTANCE {. importc: "LoadLibraryA", header: "<windows.h>", stdcall.} - proc GetProcAddress(lib: THINSTANCE, name: cstring): pointer {. + proc getProcAddress(lib: THINSTANCE, name: cstring): pointer {. importc: "GetProcAddress", header: "<windows.h>", stdcall.} - proc LoadLib(path: string): TLibHandle = + proc loadLib(path: string): TLibHandle = result = cast[TLibHandle](winLoadLibrary(path)) - proc LoadLib(): TLibHandle = + proc loadLib(): TLibHandle = result = cast[TLibHandle](winLoadLibrary(nil)) - proc UnloadLib(lib: TLibHandle) = FreeLibrary(cast[THINSTANCE](lib)) + proc unloadLib(lib: TLibHandle) = FreeLibrary(cast[THINSTANCE](lib)) proc symAddr(lib: TLibHandle, name: cstring): pointer = result = GetProcAddress(cast[THINSTANCE](lib), name) diff --git a/lib/system.nim b/lib/system.nim index 09e44a45a..2acb989c5 100644 --- a/lib/system.nim +++ b/lib/system.nim @@ -2333,29 +2333,29 @@ when not defined(JS): #and not defined(NimrodVM): elif defined(JS): # Stubs: - proc nimGCvisit(d: pointer, op: int) {.compilerRtl.} = nil - - proc GC_disable() = nil - proc GC_enable() = nil - proc GC_fullCollect() = nil - proc GC_setStrategy(strategy: TGC_Strategy) = nil - proc GC_enableMarkAndSweep() = nil - proc GC_disableMarkAndSweep() = nil + proc nimGCvisit(d: pointer, op: int) {.compilerRtl.} = discard + + proc GC_disable() = discard + proc GC_enable() = discard + proc GC_fullCollect() = discard + proc GC_setStrategy(strategy: TGC_Strategy) = discard + proc GC_enableMarkAndSweep() = discard + proc GC_disableMarkAndSweep() = discard proc GC_getStatistics(): string = return "" proc getOccupiedMem(): int = return -1 proc getFreeMem(): int = return -1 proc getTotalMem(): int = return -1 - proc dealloc(p: pointer) = nil - proc alloc(size: int): pointer = nil - proc alloc0(size: int): pointer = nil - proc realloc(p: Pointer, newsize: int): pointer = nil + proc dealloc(p: pointer) = discard + proc alloc(size: int): pointer = discard + proc alloc0(size: int): pointer = discard + proc realloc(p: Pointer, newsize: int): pointer = discard - proc allocShared(size: int): pointer = nil - proc allocShared0(size: int): pointer = nil - proc deallocShared(p: pointer) = nil - proc reallocShared(p: pointer, newsize: int): pointer = nil + proc allocShared(size: int): pointer = discard + proc allocShared0(size: int): pointer = discard + proc deallocShared(p: pointer) = discard + proc reallocShared(p: pointer, newsize: int): pointer = discard when defined(JS): include "system/jssys" @@ -2490,11 +2490,11 @@ proc staticRead*(filename: string): string {.magic: "Slurp".} ## ``slurp`` is an alias for ``staticRead``. proc gorge*(command: string, input = ""): string {. - magic: "StaticExec".} = nil + magic: "StaticExec".} = discard ## This is an alias for ``staticExec``. proc staticExec*(command: string, input = ""): string {. - magic: "StaticExec".} = nil + magic: "StaticExec".} = discard ## Executes an external process at compile-time. ## if `input` is not an empty string, it will be passed as a standard input ## to the executed program. @@ -2561,7 +2561,7 @@ proc instantiationInfo*(index = -1, fullPaths = false): tuple[ ## $pos.line, astToStr(code)] ## assert false, "A test expecting failure succeeded?" ## except exception: - ## nil + ## discard ## ## proc tester(pos: int): int = ## let diff --git a/lib/system/excpt.nim b/lib/system/excpt.nim index a3f6669d4..e50ba7b9f 100644 --- a/lib/system/excpt.nim +++ b/lib/system/excpt.nim @@ -23,7 +23,7 @@ else: proc MessageBoxA(hWnd: cint, lpText, lpCaption: cstring, uType: int): int32 {. header: "<windows.h>", nodecl.} - proc writeToStdErr(msg: CString) = + proc writeToStdErr(msg: cstring) = discard MessageBoxA(0, msg, nil, 0) proc showErrorMessage(data: cstring) = diff --git a/lib/system/gc_ms.nim b/lib/system/gc_ms.nim index 2e3596985..e78a4e5cd 100644 --- a/lib/system/gc_ms.nim +++ b/lib/system/gc_ms.nim @@ -1,7 +1,7 @@ # # # Nimrod's Runtime Library -# (c) Copyright 2013 Andreas Rumpf +# (c) Copyright 2014 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -59,11 +59,11 @@ var gch {.rtlThreadVar.}: TGcHeap when not defined(useNimRtl): - InstantiateForRegion(gch.region) + instantiateForRegion(gch.region) template acquire(gch: TGcHeap) = when hasThreadSupport and hasSharedHeap: - AcquireSys(HeapLock) + acquireSys(HeapLock) template release(gch: TGcHeap) = when hasThreadSupport and hasSharedHeap: @@ -90,7 +90,7 @@ proc extGetCellType(c: pointer): PNimType {.compilerproc.} = # used for code generation concerning debugging result = usrToCell(c).typ -proc unsureAsgnRef(dest: ppointer, src: pointer) {.inline.} = +proc unsureAsgnRef(dest: PPointer, src: pointer) {.inline.} = dest[] = src proc internRefcount(p: pointer): int {.exportc: "getRefcount".} = @@ -114,10 +114,10 @@ when BitsPerPage mod (sizeof(int)*8) != 0: # forward declarations: proc collectCT(gch: var TGcHeap) -proc IsOnStack*(p: pointer): bool {.noinline.} +proc isOnStack*(p: pointer): bool {.noinline.} proc forAllChildren(cell: PCell, op: TWalkOp) proc doOperation(p: pointer, op: TWalkOp) -proc forAllChildrenAux(dest: Pointer, mt: PNimType, op: TWalkOp) +proc forAllChildrenAux(dest: pointer, mt: PNimType, op: TWalkOp) # we need the prototype here for debugging purposes proc prepareDealloc(cell: PCell) = @@ -162,19 +162,19 @@ proc forAllSlotsAux(dest: pointer, n: ptr TNimNode, op: TWalkOp) = if m != nil: forAllSlotsAux(dest, m, op) of nkNone: sysAssert(false, "forAllSlotsAux") -proc forAllChildrenAux(dest: Pointer, mt: PNimType, op: TWalkOp) = +proc forAllChildrenAux(dest: pointer, mt: PNimType, op: TWalkOp) = var d = cast[TAddress](dest) if dest == nil: return # nothing to do if ntfNoRefs notin mt.flags: - case mt.Kind + case mt.kind of tyRef, tyString, tySequence: # leaf: - doOperation(cast[ppointer](d)[], op) + doOperation(cast[PPointer](d)[], op) of tyObject, tyTuple: forAllSlotsAux(dest, mt.node, op) of tyArray, tyArrayConstr, tyOpenArray: for i in 0..(mt.size div mt.base.size)-1: forAllChildrenAux(cast[pointer](d +% i *% mt.base.size), mt.base, op) - else: nil + else: discard proc forAllChildren(cell: PCell, op: TWalkOp) = gcAssert(cell != nil, "forAllChildren: 1") @@ -184,7 +184,7 @@ proc forAllChildren(cell: PCell, op: TWalkOp) = if marker != nil: marker(cellToUsr(cell), op.int) else: - case cell.typ.Kind + case cell.typ.kind of tyRef: # common case forAllChildrenAux(cellToUsr(cell), cell.typ.base, op) of tySequence: @@ -194,7 +194,7 @@ proc forAllChildren(cell: PCell, op: TWalkOp) = for i in 0..s.len-1: forAllChildrenAux(cast[pointer](d +% i *% cell.typ.base.size +% GenericSeqSize), cell.typ.base, op) - else: nil + else: discard proc rawNewObj(typ: PNimType, size: int, gch: var TGcHeap): pointer = # generates a new object and sets its reference counter to 0 @@ -466,7 +466,7 @@ else: sp = sp +% sizeof(pointer)*8 # last few entries: while sp <=% max: - gcMark(gch, cast[ppointer](sp)[]) + gcMark(gch, cast[PPointer](sp)[]) sp = sp +% sizeof(pointer) # ---------------------------------------------------------------------------- @@ -505,7 +505,7 @@ when not defined(useNimRtl): else: dec(gch.recGcLock) - proc GC_setStrategy(strategy: TGC_Strategy) = nil + proc GC_setStrategy(strategy: TGC_Strategy) = discard proc GC_enableMarkAndSweep() = gch.cycleThreshold = InitialThreshold diff --git a/readme.md b/readme.md index 8d42c66db..3eaef0b35 100644 --- a/readme.md +++ b/readme.md @@ -61,5 +61,5 @@ allowing you to create commercial applications. Read copying.txt for more details. -Copyright (c) 2004-2013 Andreas Rumpf. +Copyright (c) 2004-2014 Andreas Rumpf. All rights reserved. diff --git a/readme.txt b/readme.txt index 8d42c66db..3eaef0b35 100644 --- a/readme.txt +++ b/readme.txt @@ -61,5 +61,5 @@ allowing you to create commercial applications. Read copying.txt for more details. -Copyright (c) 2004-2013 Andreas Rumpf. +Copyright (c) 2004-2014 Andreas Rumpf. All rights reserved. diff --git a/tests/macros/tstringinterp.nim b/tests/macros/tstringinterp.nim index f030213e0..a500ed56e 100644 --- a/tests/macros/tstringinterp.nim +++ b/tests/macros/tstringinterp.nim @@ -9,7 +9,7 @@ proc concat(strings: varargs[string]): string = result = newString(0) for s in items(strings): result.add(s) -template ProcessInterpolations(e: expr) = +template processInterpolations(e: expr) = var s = e[1].strVal for f in interpolatedFragments(s): case f.kind @@ -35,7 +35,7 @@ macro formatStyleInterpolation(e: expr): expr = proc addDollar() = formatString.add("$$") - ProcessInterpolations(e) + processInterpolations(e) result = parseExpr("\"x\" % [y]") result[1].strVal = formatString @@ -50,7 +50,7 @@ macro concatStyleInterpolation(e: expr): expr = proc addExpr(e: PNimrodNode) = args.add(e) proc addDollar() = args.add(newStrLitNode"$") - ProcessInterpolations(e) + processInterpolations(e) result = newCall("concat", args) diff --git a/tests/specials.nim b/tests/specials.nim deleted file mode 100644 index 9ced66bbb..000000000 --- a/tests/specials.nim +++ /dev/null @@ -1,238 +0,0 @@ -# -# -# Nimrod Tester -# (c) Copyright 2013 Andreas Rumpf -# -# See the file "copying.txt", included in this -# distribution, for details about the copyright. -# - -## Include for the tester that contains test suites that test special features -## of the compiler. - -# included from tester.nim -# ---------------- ROD file tests --------------------------------------------- - -const - rodfilesDir = "tests/rodfiles" - nimcacheDir = rodfilesDir / "nimcache" - -proc delNimCache() = - try: - removeDir(nimcacheDir) - except EOS: - echo "[Warning] could not delete: ", nimcacheDir - -proc runRodFiles(r: var TResults, options: string) = - template test(filename: expr): stmt = - runSingleTest(r, rodfilesDir / filename, options) - - delNimCache() - - # test basic recompilation scheme: - test "hallo" - test "hallo" - # test incremental type information: - test "hallo2" - delNimCache() - - # test type converters: - test "aconv" - test "bconv" - delNimCache() - - # test G, A, B example from the documentation; test init sections: - test "deada" - test "deada2" - delNimCache() - - # test method generation: - test "bmethods" - test "bmethods2" - delNimCache() - - # test generics: - test "tgeneric1" - test "tgeneric2" - delNimCache() - -proc compileRodFiles(r: var TResults, options: string) = - template test(filename: expr): stmt = - compileSingleTest(r, rodfilesDir / filename, options) - - delNimCache() - # test DLL interfacing: - test "gtkex1" - test "gtkex2" - delNimCache() - -# --------------------- DLL generation tests ---------------------------------- - -proc safeCopyFile(src, dest: string) = - try: - copyFile(src, dest) - except EOS: - echo "[Warning] could not copy: ", src, " to ", dest - -proc runBasicDLLTest(c, r: var TResults, options: string) = - compileSingleTest c, "lib/nimrtl.nim", options & " --app:lib -d:createNimRtl" - compileSingleTest c, "tests/dll/server.nim", - options & " --app:lib -d:useNimRtl" - - when defined(Windows): - # windows looks in the dir of the exe (yay!): - var nimrtlDll = DynlibFormat % "nimrtl" - safeCopyFile("lib" / nimrtlDll, "tests/dll" / nimrtlDll) - else: - # posix relies on crappy LD_LIBRARY_PATH (ugh!): - var libpath = getenv"LD_LIBRARY_PATH".string - if peg"\i '/nimrod' (!'/')* '/lib'" notin libpath: - echo "[Warning] insufficient LD_LIBRARY_PATH" - var serverDll = DynlibFormat % "server" - safeCopyFile("tests/dll" / serverDll, "lib" / serverDll) - - runSingleTest r, "tests/dll/client.nim", options & " -d:useNimRtl" - -proc runDLLTests(r: var TResults, options: string) = - # dummy compile result: - var c = initResults() - - runBasicDLLTest c, r, options - runBasicDLLTest c, r, options & " -d:release" - runBasicDLLTest c, r, options & " --gc:boehm" - runBasicDLLTest c, r, options & " -d:release --gc:boehm" - -proc compileDLLTests(r: var TResults, options: string) = - # dummy run result: - var c = initResults() - - runBasicDLLTest r, c, options - runBasicDLLTest r, c, options & " -d:release" - runBasicDLLTest r, c, options & " --gc:boehm" - runBasicDLLTest r, c, options & " -d:release --gc:boehm" - -# ------------------------------ GC tests ------------------------------------- - -proc runGcTests(r: var TResults, options: string) = - template test(filename: expr): stmt = - runSingleTest(r, "tests/gc" / filename, options) - runSingleTest(r, "tests/gc" / filename, options & " -d:release") - runSingleTest(r, "tests/gc" / filename, options & - " -d:release -d:useRealtimeGC") - runSingleTest(r, "tests/gc" / filename, options & - " --gc:markAndSweep") - runSingleTest(r, "tests/gc" / filename, options & - " -d:release --gc:markAndSweep") - - test "gcbench" - test "gcleak" - test "gcleak2" - test "gctest" - test "gcleak3" - test "weakrefs" - test "cycleleak" - test "closureleak" - -# ------------------------- threading tests ----------------------------------- - -proc runThreadTests(r: var TResults, options: string) = - template test(filename: expr): stmt = - runSingleTest(r, "tests/threads" / filename, options) - runSingleTest(r, "tests/threads" / filename, options & " -d:release") - runSingleTest(r, "tests/threads" / filename, options & " --tlsEmulation:on") - - test "tactors" - test "tactors2" - test "threadex" - # deactivated because output capturing still causes problems sometimes: - #test "trecursive_actor" - #test "threadring" - #test "tthreadanalysis" - #test "tthreadsort" - -proc rejectThreadTests(r: var TResults, options: string) = - rejectSingleTest(r, "tests/threads/tthreadanalysis2", options) - rejectSingleTest(r, "tests/threads/tthreadanalysis3", options) - rejectSingleTest(r, "tests/threads/tthreadheapviolation1", options) - -# ------------------------- IO tests ------------------------------------------ - -proc runIOTests(r: var TResults, options: string) = - # We need readall_echo to be compiled for this test to run. - # dummy compile result: - var c = initResults() - compileSingleTest(c, "tests/system/helpers/readall_echo", options) - runSingleTest(r, "tests/system/io", options) - -# ------------------------- debugger tests ------------------------------------ - -proc compileDebuggerTests(r: var TResults, options: string) = - compileSingleTest(r, "tools/nimgrep", options & - " --debugger:on") - -# ------------------------- JS tests ------------------------------------------ - -proc runJsTests(r: var TResults, options: string) = - template test(filename: expr): stmt = - runSingleTest(r, filename, options & " -d:nodejs", targetJS) - runSingleTest(r, filename, options & " -d:nodejs -d:release", targetJS) - - for t in os.walkFiles("tests/js/t*.nim"): - test(t) - for testfile in ["texceptions", "texcpt1", "texcsub", "tfinally", - "tfinally2", "tfinally3", "tactiontable", "tmultim1", - "tmultim3", "tmultim4"]: - test "tests/run/" & testfile & ".nim" - -# ------------------------- register special tests here ----------------------- -proc runSpecialTests(r: var TResults, options: string) = - runRodFiles(r, options) - #runDLLTests(r, options) - runGCTests(r, options) - runThreadTests(r, options & " --threads:on") - runIOTests(r, options) - - for t in os.walkFiles("tests/patterns/t*.nim"): - runSingleTest(r, t, options) - for t in ["lib/packages/docutils/highlite"]: - runSingleTest(r, t, options) - -proc rejectSpecialTests(r: var TResults, options: string) = - rejectThreadTests(r, options) - -proc findMainFile(dir: string): string = - # finds the file belonging to ".nimrod.cfg"; if there is no such file - # it returns the some ".nim" file if there is only one: - const cfgExt = ".nimrod.cfg" - result = "" - var nimFiles = 0 - for kind, file in os.walkDir(dir): - if kind == pcFile: - if file.endsWith(cfgExt): return file[.. -(cfgExt.len+1)] & ".nim" - elif file.endsWith(".nim"): - if result.len == 0: result = file - inc nimFiles - if nimFiles != 1: result.setlen(0) - -proc compileManyLoc(r: var TResults, options: string) = - for kind, dir in os.walkDir("tests/manyloc"): - if kind == pcDir: - let mainfile = findMainFile(dir) - if mainfile != ".nim": - compileSingleTest(r, mainfile, options) - -proc compileSpecialTests(r: var TResults, options: string) = - compileRodFiles(r, options) - - compileSingleTest(r, "compiler/c2nim/c2nim.nim", options) - compileSingleTest(r, "compiler/pas2nim/pas2nim.nim", options) - - compileDLLTests(r, options) - compileDebuggerTests(r, options) - - compileManyLoc(r, options) - - #var given = callCompiler("nimrod i", "nimrod i", options) - #r.addResult("nimrod i", given.msg, if given.err: reFailure else: reSuccess) - #if not given.err: inc(r.passed) - diff --git a/tests/testament/backend.nim b/tests/testament/backend.nim index bc1f92eba..5199bb9d6 100644 --- a/tests/testament/backend.nim +++ b/tests/testament/backend.nim @@ -49,10 +49,10 @@ proc createDb() = # """, []) type - MachineId = distinct int64 + MachineId* = distinct int64 CommitId = distinct int64 -proc `$`(id: MachineId): string {.borrow.} +proc `$`*(id: MachineId): string {.borrow.} proc `$`(id: CommitId): string {.borrow.} var @@ -61,7 +61,7 @@ var proc `()`(cmd: string{lit}): string = cmd.execProcess.string.strip -proc getMachine: MachineId = +proc getMachine*(db: TDbConn): MachineId = var name = "hostname"() if name.len == 0: name = when defined(posix): getenv"HOSTNAME".string @@ -76,7 +76,7 @@ proc getMachine: MachineId = result = db.insertId(sql"insert into Machine(name, os, cpu) values (?,?,?)", name, system.hostOS, system.hostCPU).MachineId -proc getCommit: CommitId = +proc getCommit(db: TDbConn): CommitId = const commLen = "commit ".len let hash = "git log -n 1"()[commLen..commLen+10] let branch = "git symbolic-ref --short HEAD"() @@ -115,7 +115,7 @@ proc open*() = db = open(connection="testament.db", user="testament", password="", database="testament") createDb() - thisMachine = getMachine() - thisCommit = getCommit() + thisMachine = getMachine(db) + thisCommit = getCommit(db) proc close*() = close(db) diff --git a/tests/testament/htmlgen.nim b/tests/testament/htmlgen.nim index bc2d8bd37..eb674a171 100644 --- a/tests/testament/htmlgen.nim +++ b/tests/testament/htmlgen.nim @@ -159,3 +159,22 @@ proc generateHtml*(filename: string, commit: int) = outfile.write(HtmlEnd) close(db) close(outfile) + +proc generateJson*(filename: string, commit: int) = + const selRow = """select count(*), + sum(result = 'reSuccess'), + sum(result = 'reIgnored') + from TestResult + where [commit] = ? and machine = ? + order by category""" + var db = open(connection="testament.db", user="testament", password="", + database="testament") + let lastCommit = db.getCommit(commit) + + var outfile = open(filename, fmWrite) + + let data = db.getRow(sql(selRow), lastCommit, $backend.getMachine(db)) + + outfile.writeln("""{"total": $#, "passed": $#, "skipped": $#}""" % data) + close(db) + close(outfile) diff --git a/tests/testament/tester.nim b/tests/testament/tester.nim index 54a6de2d0..fac97cf2a 100644 --- a/tests/testament/tester.nim +++ b/tests/testament/tester.nim @@ -208,20 +208,6 @@ proc makeTest(test, options: string, cat: Category, action = actionCompile, include categories -proc toJson(res: TResults): PJsonNode = - result = newJObject() - result["total"] = newJInt(res.total) - result["passed"] = newJInt(res.passed) - result["skipped"] = newJInt(res.skipped) - -proc outputJson(reject, compile, run: TResults) = - var doc = newJObject() - doc["reject"] = toJson(reject) - doc["compile"] = toJson(compile) - doc["run"] = toJson(run) - var s = pretty(doc) - writeFile(jsonFile, s) - # proc runCaasTests(r: var TResults) = # for test, output, status, mode in caasTestsRunner(): # r.addResult(test, "", output & "-> " & $mode, @@ -259,6 +245,7 @@ proc main() = var commit = 0 discard parseInt(p.cmdLineRest.string, commit) generateHtml(resultsFile, commit) + generateJson(jsonFile, commit) else: quit usage diff --git a/tests/tester.nim b/tests/tester.nim deleted file mode 100644 index 9f9da6bfe..000000000 --- a/tests/tester.nim +++ /dev/null @@ -1,457 +0,0 @@ -# -# -# Nimrod Tester -# (c) Copyright 2013 Andreas Rumpf -# -# See the file "copying.txt", included in this -# distribution, for details about the copyright. -# - -## This program verifies Nimrod against the testcases. - -import - parseutils, strutils, pegs, os, osproc, streams, parsecfg, browsers, json, - marshal, cgi, parseopt #, caas - -const - cmdTemplate = r"nimrod cc --hints:on $# $#" - resultsFile = "testresults.html" - jsonFile = "testresults.json" - Usage = "usage: tester [--print] " & - "reject|compile|run|" & - "merge|special|rodfiles| [nimrod options]\n" & - " or: tester test|comp|rej singleTest" - -type - TTestAction = enum - actionCompile, actionRun, actionReject - TResultEnum = enum - reNimrodcCrash, # nimrod compiler seems to have crashed - reMsgsDiffer, # error messages differ - reFilesDiffer, # expected and given filenames differ - reLinesDiffer, # expected and given line numbers differ - reOutputsDiffer, - reExitcodesDiffer, - reInvalidPeg, - reCodegenFailure, - reCodeNotFound, - reExeNotFound, - reIgnored, # test is ignored - reSuccess # test was successful - - TTarget = enum - targetC, targetCpp, targetObjC, targetJS - - TSpec = object - action: TTestAction - file, cmd: string - outp: string - line, exitCode: int - msg: string - ccodeCheck: string - err: TResultEnum - substr: bool - TResults = object - total, passed, skipped: int - data: string - -# ----------------------- Spec parser ---------------------------------------- - -when not defined(parseCfgBool): - # candidate for the stdlib: - proc parseCfgBool(s: string): bool = - case normalize(s) - of "y", "yes", "true", "1", "on": result = true - of "n", "no", "false", "0", "off": result = false - else: raise newException(EInvalidValue, "cannot interpret as a bool: " & s) - -proc extractSpec(filename: string): string = - const tripleQuote = "\"\"\"" - var x = readFile(filename).string - var a = x.find(tripleQuote) - var b = x.find(tripleQuote, a+3) - # look for """ only in the first section - if a >= 0 and b > a and a < 40: - result = x.substr(a+3, b-1).replace("'''", tripleQuote) - else: - #echo "warning: file does not contain spec: " & filename - result = "" - -when not defined(nimhygiene): - {.pragma: inject.} - -template parseSpecAux(fillResult: stmt) {.immediate.} = - var ss = newStringStream(extractSpec(filename)) - var p {.inject.}: TCfgParser - open(p, ss, filename, 1) - while true: - var e {.inject.} = next(p) - case e.kind - of cfgEof: break - of cfgSectionStart, cfgOption, cfgError: - echo ignoreMsg(p, e) - of cfgKeyValuePair: - fillResult - close(p) - -proc parseSpec(filename: string): TSpec = - result.file = filename - result.msg = "" - result.outp = "" - result.ccodeCheck = "" - result.cmd = cmdTemplate - parseSpecAux: - case normalize(e.key) - of "action": - case e.value.normalize - of "compile": result.action = actionCompile - of "run": result.action = actionRun - of "reject": result.action = actionReject - else: echo ignoreMsg(p, e) - of "file": result.file = e.value - of "line": discard parseInt(e.value, result.line) - of "output": result.outp = e.value - of "outputsub": - result.outp = e.value - result.substr = true - of "exitcode": - discard parseInt(e.value, result.exitCode) - of "errormsg", "msg": result.msg = e.value - of "disabled": - if parseCfgBool(e.value): result.err = reIgnored - of "cmd": result.cmd = e.value - of "ccodecheck": result.ccodeCheck = e.value - else: echo ignoreMsg(p, e) - -# ---------------------------------------------------------------------------- - -let - pegLineError = - peg"{[^(]*} '(' {\d+} ', ' \d+ ') ' ('Error'/'Warning') ':' \s* {.*}" - pegOtherError = peg"'Error:' \s* {.*}" - pegSuccess = peg"'Hint: operation successful'.*" - pegOfInterest = pegLineError / pegOtherError - -proc callCompiler(cmdTemplate, filename, options: string): TSpec = - let c = parseCmdLine(cmdTemplate % [options, filename]) - var p = startProcess(command=c[0], args=c[1.. -1], - options={poStdErrToStdOut, poUseShell}) - let outp = p.outputStream - var suc = "" - var err = "" - var x = newStringOfCap(120) - while outp.readLine(x.TaintedString) or running(p): - if x =~ pegOfInterest: - # `err` should contain the last error/warning message - err = x - elif x =~ pegSuccess: - suc = x - close(p) - result.msg = "" - result.file = "" - result.outp = "" - result.line = -1 - if err =~ pegLineError: - result.file = extractFilename(matches[0]) - result.line = parseInt(matches[1]) - result.msg = matches[2] - elif err =~ pegOtherError: - result.msg = matches[0] - elif suc =~ pegSuccess: - result.err = reSuccess - -proc initResults: TResults = - result.total = 0 - result.passed = 0 - result.skipped = 0 - result.data = "" - -proc readResults(filename: string): TResults = - result = marshal.to[TResults](readFile(filename).string) - -proc writeResults(filename: string, r: TResults) = - writeFile(filename, $$r) - -proc `$`(x: TResults): string = - result = ("Tests passed: $1 / $3 <br />\n" & - "Tests skipped: $2 / $3 <br />\n") % - [$x.passed, $x.skipped, $x.total] - -proc colorResult(r: TResultEnum): string = - case r - of reIgnored: result = "<span style=\"color:fuchsia\">ignored</span>" - of reSuccess: result = "<span style=\"color:green\">yes</span>" - else: result = "<span style=\"color:red\">no</span>" - -const - TableHeader4 = "<table border=\"1\"><tr><td>Test</td><td>Expected</td>" & - "<td>Given</td><td>Success</td></tr>\n" - TableHeader3 = "<table border=\"1\"><tr><td>Test</td>" & - "<td>Given</td><td>Success</td></tr>\n" - TableFooter = "</table>\n" - HtmlBegin = """<html> - <head> - <title>Test results</title> - <style type="text/css"> - <!--""" & slurp("testament/css/boilerplate.css") & "\n" & - slurp("testament/css/style.css") & - """--> - </style> - - </head> - <body>""" - - HtmlEnd = "</body></html>" - -proc td(s: string): string = - result = s.substr(0, 200).XMLEncode - -proc addResult(r: var TResults, test, expected, given: string, - success: TResultEnum) = - r.data.addf("<tr><td>$#</td><td>$#</td><td>$#</td><td>$#</td></tr>\n", [ - XMLEncode(test), td(expected), td(given), success.colorResult]) - -proc addResult(r: var TResults, test, given: string, - success: TResultEnum) = - r.data.addf("<tr><td>$#</td><td>$#</td><td>$#</td></tr>\n", [ - XMLEncode(test), td(given), success.colorResult]) - -proc listResults(reject, compile, run: TResults) = - var s = HtmlBegin - s.add("<h1>Tests to Reject</h1>\n") - s.add($reject) - s.add(TableHeader4 & reject.data & TableFooter) - s.add("<br /><br /><br /><h1>Tests to Compile</h1>\n") - s.add($compile) - s.add(TableHeader3 & compile.data & TableFooter) - s.add("<br /><br /><br /><h1>Tests to Run</h1>\n") - s.add($run) - s.add(TableHeader4 & run.data & TableFooter) - s.add(HtmlEnd) - writeFile(resultsFile, s) - -proc cmpMsgs(r: var TResults, expected, given: TSpec, test: string) = - if strip(expected.msg) notin strip(given.msg): - r.addResult(test, expected.msg, given.msg, reMsgsDiffer) - elif extractFilename(expected.file) != extractFilename(given.file) and - "internal error:" notin expected.msg: - r.addResult(test, expected.file, given.file, reFilesDiffer) - elif expected.line != given.line and expected.line != 0: - r.addResult(test, $expected.line, $given.line, reLinesDiffer) - else: - r.addResult(test, expected.msg, given.msg, reSuccess) - inc(r.passed) - -proc rejectSingleTest(r: var TResults, test, options: string) = - let test = test.addFileExt(".nim") - var t = extractFilename(test) - inc(r.total) - echo t - var expected = parseSpec(test) - if expected.err == reIgnored: - r.addResult(t, "", "", reIgnored) - inc(r.skipped) - else: - var given = callCompiler(expected.cmd, test, options) - cmpMsgs(r, expected, given, t) - -proc reject(r: var TResults, dir, options: string) = - ## handle all the tests that the compiler should reject - for test in os.walkFiles(dir / "t*.nim"): rejectSingleTest(r, test, options) - -proc codegenCheck(test, check, ext: string, given: var TSpec) = - if check.len > 0: - try: - let (path, name, ext2) = test.splitFile - echo path / "nimcache" / name.changeFileExt(ext) - let contents = readFile(path / "nimcache" / name.changeFileExt(ext)).string - if contents.find(check.peg) < 0: - given.err = reCodegenFailure - except EInvalidValue: - given.err = reInvalidPeg - except EIO: - given.err = reCodeNotFound - -proc codegenChecks(test: string, expected: TSpec, given: var TSpec) = - codegenCheck(test, expected.ccodeCheck, ".c", given) - -proc compile(r: var TResults, pattern, options: string) = - for test in os.walkFiles(pattern): - let t = extractFilename(test) - echo t - inc(r.total) - let expected = parseSpec(test) - if expected.err == reIgnored: - r.addResult(t, "", reIgnored) - inc(r.skipped) - else: - var given = callCompiler(expected.cmd, test, options) - if given.err == reSuccess: - codegenChecks(test, expected, given) - r.addResult(t, given.msg, given.err) - if given.err == reSuccess: inc(r.passed) - -proc compileSingleTest(r: var TResults, test, options: string) = - # does not extract the spec because the file is not supposed to have any - let test = test.addFileExt(".nim") - let t = extractFilename(test) - inc(r.total) - echo t - let given = callCompiler(cmdTemplate, test, options) - r.addResult(t, given.msg, given.err) - if given.err == reSuccess: inc(r.passed) - -proc runSingleTest(r: var TResults, test, options: string, target: TTarget) = - var test = test.addFileExt(".nim") - var t = extractFilename(test) - echo t - inc(r.total) - var expected = parseSpec(test) - if expected.err == reIgnored: - r.addResult(t, "", "", reIgnored) - inc(r.skipped) - else: - var given = callCompiler(expected.cmd, test, options) - if given.err != reSuccess: - r.addResult(t, "", given.msg, given.err) - else: - var exeFile: string - if target == targetC: - exeFile = changeFileExt(test, ExeExt) - else: - let (dir, file, ext) = splitFile(test) - exeFile = dir / "nimcache" / file & ".js" - - if existsFile(exeFile): - var (buf, exitCode) = execCmdEx( - (if target==targetJS: "node " else: "") & exeFile) - if exitCode != expected.ExitCode: - r.addResult(t, "exitcode: " & $expected.ExitCode, - "exitcode: " & $exitCode, reExitCodesDiffer) - else: - if strip(buf.string) != strip(expected.outp): - if not (expected.substr and expected.outp in buf.string): - given.err = reOutputsDiffer - if given.err == reSuccess: - codeGenChecks(test, expected, given) - if given.err == reSuccess: inc(r.passed) - r.addResult(t, expected.outp, buf.string, given.err) - else: - r.addResult(t, expected.outp, "executable not found", reExeNotFound) - -proc runSingleTest(r: var TResults, test, options: string) = - runSingleTest(r, test, options, targetC) - -proc run(r: var TResults, dir, options: string) = - for test in os.walkFiles(dir / "t*.nim"): runSingleTest(r, test, options) - -include specials - -proc compileExample(r: var TResults, pattern, options: string) = - for test in os.walkFiles(pattern): compileSingleTest(r, test, options) - -proc toJson(res: TResults): PJsonNode = - result = newJObject() - result["total"] = newJInt(res.total) - result["passed"] = newJInt(res.passed) - result["skipped"] = newJInt(res.skipped) - -proc outputJSON(reject, compile, run: TResults) = - var doc = newJObject() - doc["reject"] = toJson(reject) - doc["compile"] = toJson(compile) - doc["run"] = toJson(run) - var s = pretty(doc) - writeFile(jsonFile, s) - -# proc runCaasTests(r: var TResults) = -# for test, output, status, mode in caasTestsRunner(): -# r.addResult(test, "", output & "-> " & $mode, -# if status: reSuccess else: reOutputsDiffer) - -proc main() = - os.putenv "NIMTEST_NO_COLOR", "1" - os.putenv "NIMTEST_OUTPUT_LVL", "PRINT_FAILURES" - - const - compileJson = "compile.json" - runJson = "run.json" - rejectJson = "reject.json" - - var optPrintResults = false - var p = initOptParser() - p.next() - if p.kind == cmdLongoption: - case p.key.string - of "print": optPrintResults = true - else: quit usage - p.next() - if p.kind != cmdArgument: quit usage - var action = p.key.string.normalize - p.next() - var r = initResults() - case action - of "reject": - reject(r, "tests/reject", p.cmdLineRest.string) - rejectSpecialTests(r, p.cmdLineRest.string) - writeResults(rejectJson, r) - of "compile": - compile(r, "tests/compile/t*.nim", p.cmdLineRest.string) - compile(r, "tests/ccg/t*.nim", p.cmdLineRest.string) - compile(r, "tests/js.nim", p.cmdLineRest.string) - compileExample(r, "lib/pure/*.nim", p.cmdLineRest.string) - compileExample(r, "examples/*.nim", p.cmdLineRest.string) - compileExample(r, "examples/gtk/*.nim", p.cmdLineRest.string) - compileExample(r, "examples/talk/*.nim", p.cmdLineRest.string) - compileSpecialTests(r, p.cmdLineRest.string) - writeResults(compileJson, r) - of "run": - run(r, "tests/run", p.cmdLineRest.string) - runSpecialTests(r, p.cmdLineRest.string) - writeResults(runJson, r) - of "special": - runSpecialTests(r, p.cmdLineRest.string) - # runCaasTests(r) - writeResults(runJson, r) - of "rodfiles": - runRodFiles(r, p.cmdLineRest.string) - writeResults(runJson, r) - of "js": - if existsFile(runJSon): - r = readResults(runJson) - runJsTests(r, p.cmdLineRest.string) - writeResults(runJson, r) - of "merge": - var rejectRes = readResults(rejectJson) - var compileRes = readResults(compileJson) - var runRes = readResults(runJson) - listResults(rejectRes, compileRes, runRes) - outputJSON(rejectRes, compileRes, runRes) - of "dll": - runDLLTests r, p.cmdLineRest.string - of "gc": - runGCTests(r, p.cmdLineRest.string) - of "test": - if p.kind != cmdArgument: quit usage - var testFile = p.key.string - p.next() - runSingleTest(r, testFile, p.cmdLineRest.string) - of "comp", "rej": - if p.kind != cmdArgument: quit usage - var testFile = p.key.string - p.next() - if peg"'/reject/'" in testFile or action == "rej": - rejectSingleTest(r, testFile, p.cmdLineRest.string) - elif peg"'/compile/'" in testFile or action == "comp": - compileSingleTest(r, testFile, p.cmdLineRest.string) - else: - runSingleTest(r, testFile, p.cmdLineRest.string) - else: - quit usage - - if optPrintResults: echo r, r.data - -if paramCount() == 0: - quit usage -main() - diff --git a/todo.txt b/todo.txt index d0aec9c8c..bad9373a1 100644 --- a/todo.txt +++ b/todo.txt @@ -1,14 +1,11 @@ version 0.9.4 ============= -- better debugging support for writes to locations -- document new templating symbol binding rules -- fix eval in macros.nim - Bugs ==== +- fix eval in macros.nim - new VM: - implement overflow checking - bug: 'type T = ref T' not recognized as illegal recursion |