diff options
59 files changed, 799 insertions, 346 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index 39d33bb7c..1b14a8f79 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -296,6 +296,7 @@ const sfCompileToCpp* = sfInfixCall # compile the module as C++ code sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code sfExperimental* = sfOverriden # module uses the .experimental switch + sfGoto* = sfOverriden # var is used for 'goto' code generation const # getting ready for the future expr/stmt merge @@ -795,8 +796,8 @@ type # for enum types a list of symbols # for tyInt it can be the int literal # for procs and tyGenericBody, it's the - # the body of the user-defined type class # formal param list + # for concepts, the concept body # else: unused owner*: PSym # the 'owner' of the type sym*: PSym # types have the sym associated with them @@ -1170,7 +1171,9 @@ proc newType*(kind: TTypeKind, owner: PSym): PType = result.lockLevel = UnspecifiedLockLevel when debugIds: registerId(result) - #if result.id < 2000: + #if result.id == 92231: + # echo "KNID ", kind + # writeStackTrace() # messageOut(typeKindToStr[kind] & ' has id: ' & toString(result.id)) proc mergeLoc(a: var TLoc, b: TLoc) = @@ -1317,6 +1320,13 @@ proc skipTypes*(t: PType, kinds: TTypeKinds): PType = result = t while result.kind in kinds: result = lastSon(result) +proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType = + ## same as skipTypes but handles 'nil' + result = t + while result != nil and result.kind in kinds: + if result.len == 0: return nil + result = lastSon(result) + proc isGCedMem*(t: PType): bool {.inline.} = result = t.kind in {tyString, tyRef, tySequence} or t.kind == tyProc and t.callConv == ccClosure diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim index 8f354d457..2dacc25e9 100644 --- a/compiler/ccgcalls.nim +++ b/compiler/ccgcalls.nim @@ -385,18 +385,11 @@ proc genPatternCall(p: BProc; ri: PNode; pat: string; typ: PType): Rope = inc j inc i of '\'': - inc i - let stars = i - while pat[i] == '*': inc i - if pat[i] in Digits: - let j = pat[i].ord - '0'.ord - var t = typ.sons[j] - for k in 1..i-stars: - if t != nil and t.len > 0: - t = if t.kind == tyGenericInst: t.sons[1] else: t.elemType + var idx, stars: int + if scanCppGenericSlot(pat, i, idx, stars): + var t = resolveStarsInCppType(typ, idx, stars) if t == nil: result.add(~"void") else: result.add(getTypeDesc(p.module, t)) - inc i else: let start = i while i < pat.len: diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index 4123be7b9..a468de6e5 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -676,7 +676,7 @@ proc isCppRef(p: BProc; typ: PType): bool {.inline.} = proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = let mt = mapType(e.sons[0].typ) - if (mt in {ctArray, ctPtrToArray} and not enforceDeref): + if mt in {ctArray, ctPtrToArray} and not enforceDeref: # XXX the amount of hacks for C's arrays is incredible, maybe we should # simply wrap them in a struct? --> Losing auto vectorization then? #if e[0].kind != nkBracketExpr: @@ -685,19 +685,29 @@ proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = else: var a: TLoc initLocExprSingleUse(p, e.sons[0], a) - let typ = skipTypes(a.t, abstractInst) - case typ.kind - of tyRef: - d.s = OnHeap - of tyVar: - d.s = OnUnknown - if tfVarIsPtr notin typ.flags and p.module.compileToCpp and - e.kind == nkHiddenDeref: + if d.k == locNone: + let typ = skipTypes(a.t, abstractInst) + # dest = *a; <-- We do not know that 'dest' is on the heap! + # It is completely wrong to set 'd.s' here, unless it's not yet + # been assigned to. + case typ.kind + of tyRef: + d.s = OnHeap + of tyVar: + d.s = OnUnknown + if tfVarIsPtr notin typ.flags and p.module.compileToCpp and + e.kind == nkHiddenDeref: + putIntoDest(p, d, e.typ, rdLoc(a)) + return + of tyPtr: + d.s = OnUnknown # BUGFIX! + else: internalError(e.info, "genDeref " & $a.t.kind) + elif p.module.compileToCpp: + let typ = skipTypes(a.t, abstractInst) + if typ.kind == tyVar and tfVarIsPtr notin typ.flags and + e.kind == nkHiddenDeref: putIntoDest(p, d, e.typ, rdLoc(a)) return - of tyPtr: - d.s = OnUnknown # BUGFIX! - else: internalError(e.info, "genDeref " & $a.t.kind) if enforceDeref and mt == ctPtrToArray: # we lie about the type for better C interop: 'ptr array[3,T]' is # translated to 'ptr T', but for deref'ing this produces wrong code. @@ -1587,8 +1597,6 @@ proc genRangeChck(p: BProc, n: PNode, d: var TLoc, magic: string) = [getTypeDesc(p.module, dest), rdCharLoc(a)]) else: initLocExpr(p, n.sons[0], a) - if not leValue(n.sons[1], n.sons[2]): - internalError(n.info, "range check will always fail; empty range") putIntoDest(p, d, dest, ropecg(p.module, "(($1)#$5($2, $3, $4))", [ getTypeDesc(p.module, dest), rdCharLoc(a), genLiteral(p, n.sons[1], dest), genLiteral(p, n.sons[2], dest), diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim index 1277f7154..c1e6b01ae 100644 --- a/compiler/ccgstmts.nim +++ b/compiler/ccgstmts.nim @@ -175,9 +175,18 @@ proc genBreakState(p: BProc, n: PNode) = proc genVarPrototypeAux(m: BModule, sym: PSym) +proc genGotoVar(p: BProc; value: PNode) = + if value.kind notin {nkCharLit..nkUInt64Lit}: + localError(value.info, "'goto' target must be a literal value") + else: + lineF(p, cpsStmts, "goto NIMSTATE_$#;$n", [value.intVal.rope]) + proc genSingleVar(p: BProc, a: PNode) = var v = a.sons[0].sym - if sfCompileTime in v.flags: return + if {sfCompileTime, sfGoto} * v.flags != {}: + # translate 'var state {.goto.} = X' into 'goto LX': + if sfGoto in v.flags: genGotoVar(p, a.sons[2]) + return var targetProc = p if sfGlobal in v.flags: if v.flags * {sfImportc, sfExportc} == {sfImportc} and @@ -365,6 +374,19 @@ proc genReturnStmt(p: BProc, t: PNode) = linefmt(p, cpsStmts, "if ($1.status != 0) #popCurrentException();$n", safePoint) lineF(p, cpsStmts, "goto BeforeRet;$n", []) +proc genGotoForCase(p: BProc; caseStmt: PNode) = + for i in 1 .. <caseStmt.len: + startBlock(p) + let it = caseStmt.sons[i] + for j in 0 .. it.len-2: + if it.sons[j].kind == nkRange: + localError(it.info, "range notation not available for computed goto") + return + let val = getOrdValue(it.sons[j]) + lineF(p, cpsStmts, "NIMSTATE_$#:$n", [val.rope]) + genStmts(p, it.lastSon) + endBlock(p) + proc genComputedGoto(p: BProc; n: PNode) = # first pass: Generate array of computed labels: var casePos = -1 @@ -737,7 +759,10 @@ proc genCase(p: BProc, t: PNode, d: var TLoc) = genCaseGeneric(p, t, d, "if ($1 >= $2 && $1 <= $3) goto $4;$n", "if ($1 == $2) goto $3;$n") else: - genOrdinalCase(p, t, d) + if t.sons[0].kind == nkSym and sfGoto in t.sons[0].sym.flags: + genGotoForCase(p, t) + else: + genOrdinalCase(p, t, d) proc hasGeneralExceptSection(t: PNode): bool = var length = sonsLen(t) @@ -1065,7 +1090,9 @@ proc asgnFieldDiscriminant(p: BProc, e: PNode) = proc genAsgn(p: BProc, e: PNode, fastAsgn: bool) = genLineDir(p, e) - if not fieldDiscriminantCheckNeeded(p, e): + if e.sons[0].kind == nkSym and sfGoto in e.sons[0].sym.flags: + genGotoVar(p, e.sons[1]) + elif not fieldDiscriminantCheckNeeded(p, e): var a: TLoc initLocExpr(p, e.sons[0], a) if fastAsgn: incl(a.flags, lfNoDeepCopy) diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim index 8fdabd6cc..60ebf591b 100644 --- a/compiler/ccgtypes.nim +++ b/compiler/ccgtypes.nim @@ -495,6 +495,33 @@ proc getTupleDesc(m: BModule, typ: PType, name: Rope, else: add(result, desc) add(result, "};" & tnl) +proc scanCppGenericSlot(pat: string, cursor, outIdx, outStars: var int): bool = + # A helper proc for handling cppimport patterns, involving numeric + # placeholders for generic types (e.g. '0, '**2, etc). + # pre: the cursor must be placed at the ' symbol + # post: the cursor will be placed after the final digit + # false will returned if the input is not recognized as a placeholder + inc cursor + let begin = cursor + while pat[cursor] == '*': inc cursor + if pat[cursor] in Digits: + outIdx = pat[cursor].ord - '0'.ord + outStars = cursor - begin + inc cursor + return true + else: + return false + +proc resolveStarsInCppType(typ: PType, idx, stars: int): PType = + # XXX: we should catch this earlier and report it as a semantic error + if idx >= typ.len: internalError "invalid apostrophe type parameter index" + + result = typ.sons[idx] + for i in 1..stars: + if result != nil and result.len > 0: + result = if result.kind == tyGenericInst: result.sons[1] + else: result.elemType + proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope = # returns only the type's name var t = getUniqueType(typ) @@ -597,11 +624,33 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope = if isImportedCppType(t) and typ.kind == tyGenericInst: # for instantiated templates we do not go through the type cache as the # the type cache is not aware of 'tyGenericInst'. - result = getTypeName(t) & "<" - for i in 1 .. typ.len-2: - if i > 1: result.add(", ") - result.add(getTypeDescAux(m, typ.sons[i], check)) - result.add("> ") + let cppName = getTypeName(t) + var i = 0 + var chunkStart = 0 + while i < cppName.data.len: + if cppName.data[i] == '\'': + var chunkEnd = <i + var idx, stars: int + if scanCppGenericSlot(cppName.data, i, idx, stars): + result.add cppName.data.substr(chunkStart, chunkEnd) + chunkStart = i + + let typeInSlot = resolveStarsInCppType(typ, idx + 1, stars) + if typeInSlot == nil or typeInSlot.kind == tyEmpty: + result.add(~"void") + else: + result.add getTypeDescAux(m, typeInSlot, check) + else: + inc i + + if chunkStart != 0: + result.add cppName.data.substr(chunkStart) + else: + result = cppName & "<" + for i in 1 .. typ.len-2: + if i > 1: result.add(", ") + result.add(getTypeDescAux(m, typ.sons[i], check)) + result.add("> ") # always call for sideeffects: assert t.kind != tyTuple discard getRecordDesc(m, t, result, check) diff --git a/compiler/commands.nim b/compiler/commands.nim index 69b1c1f1a..5b5f461ef 100644 --- a/compiler/commands.nim +++ b/compiler/commands.nim @@ -80,9 +80,9 @@ proc writeVersionInfo(pass: TCmdLinePass) = platform.OS[platform.hostOS].name, CPU[platform.hostCPU].name])) - discard """const gitHash = gorge("git log -n 1 --format=%H") - if gitHash.strip.len == 40: - msgWriteln("git hash: " & gitHash)""" + const gitHash = gorge("git log -n 1 --format=%H").strip + when gitHash.len == 40: + msgWriteln("git hash: " & gitHash) msgWriteln("active boot switches:" & usedRelease & usedAvoidTimeMachine & usedTinyC & usedGnuReadline & usedNativeStacktrace & usedNoCaas & diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim index 6c667a3a7..c3f01774e 100644 --- a/compiler/jsgen.nim +++ b/compiler/jsgen.nim @@ -124,7 +124,7 @@ proc newProc(globals: PGlobals, module: BModule, procDef: PNode, const MappedToObject = {tyObject, tyArray, tyArrayConstr, tyTuple, tyOpenArray, - tySet, tyVar, tyRef, tyPtr, tyBigNum, tyVarargs} + tySet, tyBigNum, tyVarargs} proc mapType(typ: PType): TJSTypeKind = let t = skipTypes(typ, abstractInst) @@ -163,7 +163,8 @@ proc mangleName(s: PSym): Rope = add(result, rope(s.id)) s.loc.r = result -proc makeJSString(s: string): Rope = strutils.escape(s).rope +proc makeJSString(s: string): Rope = + (if s.isNil: "null".rope else: strutils.escape(s).rope) include jstypes @@ -937,6 +938,12 @@ proc genArrayAccess(p: PProc, n: PNode, r: var TCompRes) = r.address = nil r.kind = resExpr +proc isIndirect(v: PSym): bool = + result = {sfAddrTaken, sfGlobal} * v.flags != {} and + #(mapType(v.typ) != etyObject) and + {sfImportc, sfVolatile, sfExportc} * v.flags == {} and + v.kind notin {skProc, skConverter, skMethod, skIterator, skClosureIterator} + proc genAddr(p: PProc, n: PNode, r: var TCompRes) = case n.sons[0].kind of nkSym: @@ -945,12 +952,16 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) = case s.kind of skVar, skLet, skResult: r.kind = resExpr - if mapType(n.sons[0].typ) == etyObject: + let jsType = mapType(n.typ) + if jsType == etyObject: # make addr() a no-op: r.typ = etyNone - r.res = s.loc.r + if isIndirect(s): + r.res = s.loc.r & "[0]" + else: + r.res = s.loc.r r.address = nil - elif {sfGlobal, sfAddrTaken} * s.flags != {}: + elif {sfGlobal, sfAddrTaken} * s.flags != {} or jsType == etyBaseIndex: # for ease of code generation, we do not distinguish between # sfAddrTaken and sfGlobal. r.typ = etyBaseIndex @@ -992,7 +1003,7 @@ proc genSym(p: PProc, n: PNode, r: var TCompRes) = else: r.address = s.loc.r r.res = s.loc.r & "_Idx" - elif k != etyObject and {sfAddrTaken, sfGlobal} * s.flags != {}: + elif isIndirect(s): r.res = "$1[0]" % [s.loc.r] else: r.res = s.loc.r @@ -1124,7 +1135,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = of tyRange, tyGenericInst: result = createVar(p, lastSon(typ), indirect) of tySet: - result = rope("{}") + result = putToSeq("{}", indirect) of tyBool: result = putToSeq("false", indirect) of tyArray, tyArrayConstr: @@ -1144,6 +1155,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = add(result, createVar(p, e, false)) inc(i) add(result, "]") + if indirect: result = "[$1]" % [result] of tyTuple: result = rope("{") for i in 0.. <t.sonsLen: @@ -1151,6 +1163,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = addf(result, "Field$1: $2" | "Field$# = $#", [i.rope, createVar(p, t.sons[i], false)]) add(result, "}") + if indirect: result = "[$1]" % [result] of tyObject: result = rope("{") var c = 0 @@ -1161,6 +1174,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = add(result, createRecordVarAux(p, t.n, c)) t = t.sons[0] add(result, "}") + if indirect: result = "[$1]" % [result] of tyVar, tyPtr, tyRef: if mapType(t) == etyBaseIndex: result = putToSeq("[null, 0]" | "{nil, 0}", indirect) @@ -1172,11 +1186,6 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = internalError("createVar: " & $t.kind) result = nil -proc isIndirect(v: PSym): bool = - result = {sfAddrTaken, sfGlobal} * v.flags != {} and - (mapType(v.typ) != etyObject) and - v.kind notin {skProc, skConverter, skMethod, skIterator, skClosureIterator} - proc genVarInit(p: PProc, v: PSym, n: PNode) = var a: TCompRes @@ -1239,7 +1248,7 @@ proc genNew(p: PProc, n: PNode) = var a: TCompRes gen(p, n.sons[1], a) var t = skipTypes(n.sons[1].typ, abstractVar).sons[0] - addf(p.body, "$1 = $2;$n", [a.res, createVar(p, t, true)]) + addf(p.body, "$1 = $2;$n", [a.res, createVar(p, t, false)]) proc genNewSeq(p: PProc, n: PNode) = var x, y: TCompRes diff --git a/compiler/msgs.nim b/compiler/msgs.nim index 3f5c4763e..778b839f3 100644 --- a/compiler/msgs.nim +++ b/compiler/msgs.nim @@ -827,6 +827,9 @@ proc localError*(info: TLineInfo, msg: TMsgKind, arg = "") = proc localError*(info: TLineInfo, arg: string) = liMessage(info, errGenerated, arg, doNothing) +proc localError*(info: TLineInfo, format: string, params: openarray[string]) = + localError(info, format % params) + proc message*(info: TLineInfo, msg: TMsgKind, arg = "") = liMessage(info, msg, arg, doNothing) diff --git a/compiler/parser.nim b/compiler/parser.nim index d2831ea46..7da2f0d22 100644 --- a/compiler/parser.nim +++ b/compiler/parser.nim @@ -212,7 +212,8 @@ proc getPrecedence(tok: TToken, strongSpaces: bool): int = let relevantChar = tok.ident.s[0] # arrow like? - if L > 1 and tok.ident.s[L-1] == '>': return considerStrongSpaces(1) + if L > 1 and tok.ident.s[L-1] == '>' and + tok.ident.s[L-2] in {'-', '~', '='}: return considerStrongSpaces(1) template considerAsgn(value: expr) = result = if tok.ident.s[L-1] == '=': 1 else: value @@ -1139,9 +1140,11 @@ proc parseMacroColon(p: var TParser, x: PNode): PNode = result = makeCall(result) getTok(p) skipComment(p, result) + let stmtList = newNodeP(nkStmtList, p) if p.tok.tokType notin {tkOf, tkElif, tkElse, tkExcept}: let body = parseStmt(p) - addSon(result, makeStmtList(body)) + stmtList.add body + #addSon(result, makeStmtList(body)) while sameInd(p): var b: PNode case p.tok.tokType @@ -1164,8 +1167,13 @@ proc parseMacroColon(p: var TParser, x: PNode): PNode = eat(p, tkColon) else: break addSon(b, parseStmt(p)) - addSon(result, b) + addSon(stmtList, b) if b.kind == nkElse: break + if stmtList.len == 1 and stmtList[0].kind == nkStmtList: + # to keep backwards compatibility (see tests/vm/tstringnil) + result.add stmtList[0] + else: + result.add stmtList proc parseExprStmt(p: var TParser): PNode = #| exprStmt = simpleExpr diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim index ec594069e..c048d78e9 100644 --- a/compiler/pragmas.nim +++ b/compiler/pragmas.nim @@ -60,7 +60,7 @@ const varPragmas* = {wImportc, wExportc, wVolatile, wRegister, wThreadVar, wNodecl, wMagic, wHeader, wDeprecated, wCompilerproc, wDynlib, wExtern, wImportCpp, wImportObjC, wError, wNoInit, wCompileTime, wGlobal, - wGensym, wInject, wCodegenDecl, wGuard} + wGensym, wInject, wCodegenDecl, wGuard, wGoto} constPragmas* = {wImportc, wExportc, wHeader, wDeprecated, wMagic, wNodecl, wExtern, wImportCpp, wImportObjC, wError, wGensym, wInject} letPragmas* = varPragmas @@ -843,6 +843,11 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int, invalidPragma(it) else: sym.guard = pragmaGuard(c, it, sym.kind) + of wGoto: + if sym == nil or sym.kind notin {skVar, skLet}: + invalidPragma(it) + else: + sym.flags.incl sfGoto of wInjectStmt: if it.kind != nkExprColonExpr: localError(it.info, errExprExpected) diff --git a/compiler/renderer.nim b/compiler/renderer.nim index ce818e3cd..ffdb60696 100644 --- a/compiler/renderer.nim +++ b/compiler/renderer.nim @@ -503,6 +503,7 @@ proc gsub(g: var TSrcGen, n: PNode) = proc hasCom(n: PNode): bool = result = false + if n.isNil: return false if n.comment != nil: return true case n.kind of nkEmpty..nkNilLit: discard diff --git a/compiler/semdata.nim b/compiler/semdata.nim index cf7a52ff5..1c2720006 100644 --- a/compiler/semdata.nim +++ b/compiler/semdata.nim @@ -247,6 +247,7 @@ proc makeAndType*(c: PContext, t1, t2: PType): PType = propagateToOwner(result, t1) propagateToOwner(result, t2) result.flags.incl((t1.flags + t2.flags) * {tfHasStatic}) + result.flags.incl tfHasMeta proc makeOrType*(c: PContext, t1, t2: PType): PType = result = newTypeS(tyOr, c) @@ -254,12 +255,14 @@ proc makeOrType*(c: PContext, t1, t2: PType): PType = propagateToOwner(result, t1) propagateToOwner(result, t2) result.flags.incl((t1.flags + t2.flags) * {tfHasStatic}) + result.flags.incl tfHasMeta proc makeNotType*(c: PContext, t1: PType): PType = result = newTypeS(tyNot, c) result.sons = @[t1] propagateToOwner(result, t1) result.flags.incl(t1.flags * {tfHasStatic}) + result.flags.incl tfHasMeta proc nMinusOne*(n: PNode): PNode = result = newNode(nkCall, n.info, @[ diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim index c5bfbfa92..eb8d0c561 100644 --- a/compiler/semexprs.nim +++ b/compiler/semexprs.nim @@ -389,7 +389,7 @@ proc isOpImpl(c: PContext, n: PNode): PNode = maybeLiftType(t2, c, n.info) var m: TCandidate initCandidate(c, m, t2) - let match = typeRel(m, t2, t1) != isNone + let match = typeRel(m, t2, t1) >= isSubtype # isNone result = newIntNode(nkIntLit, ord(match)) result.typ = n.typ diff --git a/compiler/semfold.nim b/compiler/semfold.nim index 2e7179673..52931bc2b 100644 --- a/compiler/semfold.nim +++ b/compiler/semfold.nim @@ -170,13 +170,19 @@ proc getIntervalType*(m: TMagic, n: PNode): PType = let a = n.sons[1].typ if isFloatRange(a): # abs(-5.. 1) == (1..5) - result = makeRangeF(a, abs(getFloat(a.n.sons[1])), - abs(getFloat(a.n.sons[0]))) + if a.n[0].floatVal <= 0.0: + result = makeRangeF(a, 0.0, abs(getFloat(a.n.sons[0]))) + else: + result = makeRangeF(a, abs(getFloat(a.n.sons[1])), + abs(getFloat(a.n.sons[0]))) of mAbsI, mAbsI64: let a = n.sons[1].typ if isIntRange(a): - result = makeRange(a, `|abs|`(getInt(a.n.sons[1])), - `|abs|`(getInt(a.n.sons[0]))) + if a.n[0].intVal <= 0: + result = makeRange(a, 0, `|abs|`(getInt(a.n.sons[0]))) + else: + result = makeRange(a, `|abs|`(getInt(a.n.sons[1])), + `|abs|`(getInt(a.n.sons[0]))) of mSucc: let a = n.sons[1].typ let b = n.sons[2].typ diff --git a/compiler/seminst.nim b/compiler/seminst.nim index dc36ecf34..f72e2dc5b 100644 --- a/compiler/seminst.nim +++ b/compiler/seminst.nim @@ -176,7 +176,9 @@ proc instantiateProcType(c: PContext, pt: TIdTable, for i in 1 .. <result.len: # twrong_field_caching requires these 'resetIdTable' calls: - if i > 1: resetIdTable(cl.symMap) + if i > 1: + resetIdTable(cl.symMap) + resetIdTable(cl.localCache) result.sons[i] = replaceTypeVarsT(cl, result.sons[i]) propagateToOwner(result, result.sons[i]) internalAssert originalParams[i].kind == nkSym @@ -196,6 +198,7 @@ proc instantiateProcType(c: PContext, pt: TIdTable, addDecl(c, result.n.sons[i].sym) resetIdTable(cl.symMap) + resetIdTable(cl.localCache) result.sons[0] = replaceTypeVarsT(cl, result.sons[0]) result.n.sons[0] = originalParams[0].copyTree diff --git a/compiler/sempass2.nim b/compiler/sempass2.nim index 6928dbaf4..5a243afa0 100644 --- a/compiler/sempass2.nim +++ b/compiler/sempass2.nim @@ -764,7 +764,7 @@ proc track(tracked: PEffects, n: PNode) = setLen(tracked.locked, oldLocked) tracked.currLockLevel = oldLockLevel of nkTypeSection, nkProcDef, nkConverterDef, nkMethodDef, nkIteratorDef, - nkMacroDef, nkTemplateDef: + nkMacroDef, nkTemplateDef, nkLambda, nkDo: discard else: for i in 0 .. <safeLen(n): track(tracked, n.sons[i]) diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim index 50bcca9eb..a8463cbed 100644 --- a/compiler/semstmts.nim +++ b/compiler/semstmts.nim @@ -687,6 +687,16 @@ proc typeSectionRightSidePass(c: PContext, n: PNode) = #debug s.typ s.ast = a popOwner() + let aa = a.sons[2] + if aa.kind in {nkRefTy, nkPtrTy} and aa.len == 1 and + aa.sons[0].kind == nkObjectTy: + # give anonymous object a dummy symbol: + var st = s.typ + if st.kind == tyGenericBody: st = st.lastSon + internalAssert st.kind in {tyPtr, tyRef} + internalAssert st.lastSon.sym == nil + st.lastSon.sym = newSym(skType, getIdent(s.name.s & ":ObjectType"), + getCurrOwner(), s.info) proc checkForMetaFields(n: PNode) = template checkMeta(t) = @@ -730,16 +740,6 @@ proc typeSectionFinalPass(c: PContext, n: PNode) = checkConstructedType(s.info, s.typ) if s.typ.kind in {tyObject, tyTuple} and not s.typ.n.isNil: checkForMetaFields(s.typ.n) - let aa = a.sons[2] - if aa.kind in {nkRefTy, nkPtrTy} and aa.len == 1 and - aa.sons[0].kind == nkObjectTy: - # give anonymous object a dummy symbol: - var st = s.typ - if st.kind == tyGenericBody: st = st.lastSon - internalAssert st.kind in {tyPtr, tyRef} - internalAssert st.lastSon.sym == nil - st.lastSon.sym = newSym(skType, getIdent(s.name.s & ":ObjectType"), - getCurrOwner(), s.info) proc semTypeSection(c: PContext, n: PNode): PNode = ## Processes a type section. This must be done in separate passes, in order diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim index 757cfb878..9e36341bb 100644 --- a/compiler/semtypes.nim +++ b/compiler/semtypes.nim @@ -646,14 +646,17 @@ proc semObjectNode(c: PContext, n: PNode, prev: PType): PType = # n.sons[0] contains the pragmas (if any). We process these later... checkSonsLen(n, 3) if n.sons[1].kind != nkEmpty: - base = skipTypes(semTypeNode(c, n.sons[1].sons[0], nil), skipPtrs) - var concreteBase = skipGenericInvocation(base).skipTypes(skipPtrs) - if concreteBase.kind == tyObject and tfFinal notin concreteBase.flags: - addInheritedFields(c, check, pos, concreteBase) + base = skipTypesOrNil(semTypeNode(c, n.sons[1].sons[0], nil), skipPtrs) + if base.isNil: + localError(n.info, errIllegalRecursionInTypeX, "object") else: - if concreteBase.kind != tyError: - localError(n.sons[1].info, errInheritanceOnlyWithNonFinalObjects) - base = nil + var concreteBase = skipGenericInvocation(base).skipTypes(skipPtrs) + if concreteBase.kind == tyObject and tfFinal notin concreteBase.flags: + addInheritedFields(c, check, pos, concreteBase) + else: + if concreteBase.kind != tyError: + localError(n.sons[1].info, errInheritanceOnlyWithNonFinalObjects) + base = nil if n.kind != nkObjectTy: internalError(n.info, "semObjectNode") result = newOrPrevType(tyObject, prev, c) rawAddSon(result, base) @@ -786,7 +789,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, @[newTypeS(paramType.kind, c)]) result = addImplicitGeneric(typ) else: - for i in 0 .. <paramType.sons.len: + for i in 0 .. <paramType.len: if paramType.sons[i] == paramType: globalError(info, errIllegalRecursionInTypeX, typeToString(paramType)) var lifted = liftingWalk(paramType.sons[i]) @@ -831,7 +834,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, cp.kind = tyUserTypeClassInst return addImplicitGeneric(cp) - for i in 1 .. (paramType.sons.len - 2): + for i in 1 .. paramType.len-2: var lifted = liftingWalk(paramType.sons[i]) if lifted != nil: paramType.sons[i] = lifted @@ -844,7 +847,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, result.shouldHaveMeta of tyGenericInvocation: - for i in 1 .. <paramType.sonsLen: + for i in 1 .. <paramType.len: let lifted = liftingWalk(paramType.sons[i]) if lifted != nil: paramType.sons[i] = lifted when false: diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim index cbd7999c7..c5caf8b92 100644 --- a/compiler/semtypinst.nim +++ b/compiler/semtypinst.nim @@ -233,7 +233,9 @@ proc instCopyType*(cl: var TReplTypeVars, t: PType): PType = # XXX: relying on allowMetaTypes is a kludge result = copyType(t, t.owner, cl.allowMetaTypes) result.flags.incl tfFromGeneric - result.flags.excl tfInstClearedFlags + if not (t.kind in tyMetaTypes or + (t.kind == tyStatic and t.n == nil)): + result.flags.excl tfInstClearedFlags proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = # tyGenericInvocation[A, tyGenericInvocation[A, B]] @@ -418,15 +420,23 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = result = t of tyGenericInst: + result = PType(idTableGet(cl.localCache, t)) + if result != nil: return result result = instCopyType(cl, t) + idTablePut(cl.localCache, t, result) for i in 1 .. <result.sonsLen: result.sons[i] = replaceTypeVarsT(cl, result.sons[i]) propagateToOwner(result, result.lastSon) else: if containsGenericType(t): + #if not cl.allowMetaTypes: + result = PType(idTableGet(cl.localCache, t)) + if result != nil: return result result = instCopyType(cl, t) result.size = -1 # needs to be recomputed + #if not cl.allowMetaTypes: + idTablePut(cl.localCache, t, result) for i in countup(0, sonsLen(result) - 1): if result.sons[i] != nil: diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim index faa84de15..5c8a3bc58 100644 --- a/compiler/sigmatch.nim +++ b/compiler/sigmatch.nim @@ -1108,8 +1108,10 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation = localError(f.n.info, errTypeExpected) result = isNone + of tyNone: + if a.kind == tyNone: result = isEqual else: - internalAssert false + internalError " unknown type kind " & $f.kind proc cmpTypes*(c: PContext, f, a: PType): TTypeRelation = var m: TCandidate diff --git a/compiler/trees.nim b/compiler/trees.nim index 86a1139a0..2c631af99 100644 --- a/compiler/trees.nim +++ b/compiler/trees.nim @@ -9,40 +9,40 @@ # tree helper routines -import +import ast, astalgo, lexer, msgs, strutils, wordrecg -proc hasSon(father, son: PNode): bool = - for i in countup(0, sonsLen(father) - 1): - if father.sons[i] == son: +proc hasSon(father, son: PNode): bool = + for i in countup(0, sonsLen(father) - 1): + if father.sons[i] == son: return true result = false -proc cyclicTreeAux(n, s: PNode): bool = - if n == nil: +proc cyclicTreeAux(n, s: PNode): bool = + if n == nil: return false - if hasSon(s, n): + if hasSon(s, n): return true var m = sonsLen(s) addSon(s, n) - if not (n.kind in {nkEmpty..nkNilLit}): - for i in countup(0, sonsLen(n) - 1): - if cyclicTreeAux(n.sons[i], s): + if not (n.kind in {nkEmpty..nkNilLit}): + for i in countup(0, sonsLen(n) - 1): + if cyclicTreeAux(n.sons[i], s): return true result = false delSon(s, m) -proc cyclicTree*(n: PNode): bool = +proc cyclicTree*(n: PNode): bool = var s = newNodeI(nkEmpty, n.info) result = cyclicTreeAux(n, s) -proc exprStructuralEquivalent*(a, b: PNode): bool = +proc exprStructuralEquivalent*(a, b: PNode): bool = result = false - if a == b: + if a == b: result = true - elif (a != nil) and (b != nil) and (a.kind == b.kind): + elif (a != nil) and (b != nil) and (a.kind == b.kind): case a.kind - of nkSym: + of nkSym: # don't go nuts here: same symbol as string is enough: result = a.sym.name.id == b.sym.name.id of nkIdent: result = a.ident.id == b.ident.id @@ -50,12 +50,12 @@ proc exprStructuralEquivalent*(a, b: PNode): bool = of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal of nkEmpty, nkNilLit, nkType: result = true - else: - if sonsLen(a) == sonsLen(b): - for i in countup(0, sonsLen(a) - 1): - if not exprStructuralEquivalent(a.sons[i], b.sons[i]): return + else: + if sonsLen(a) == sonsLen(b): + for i in countup(0, sonsLen(a) - 1): + if not exprStructuralEquivalent(a.sons[i], b.sons[i]): return result = true - + proc sameTree*(a, b: PNode): bool = result = false if a == b: @@ -66,7 +66,7 @@ proc sameTree*(a, b: PNode): bool = if a.info.col != b.info.col: return #if a.info.fileIndex <> b.info.fileIndex then exit; case a.kind - of nkSym: + of nkSym: # don't go nuts here: same symbol as string is enough: result = a.sym.name.id == b.sym.name.id of nkIdent: result = a.ident.id == b.ident.id @@ -75,15 +75,15 @@ proc sameTree*(a, b: PNode): bool = of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal of nkEmpty, nkNilLit, nkType: result = true else: - if sonsLen(a) == sonsLen(b): - for i in countup(0, sonsLen(a) - 1): - if not sameTree(a.sons[i], b.sons[i]): return + if sonsLen(a) == sonsLen(b): + for i in countup(0, sonsLen(a) - 1): + if not sameTree(a.sons[i], b.sons[i]): return result = true - -proc getProcSym*(call: PNode): PSym = + +proc getProcSym*(call: PNode): PSym = result = call.sons[0].sym -proc getOpSym*(op: PNode): PSym = +proc getOpSym*(op: PNode): PSym = if op.kind notin {nkCall, nkHiddenCallConv, nkCommand, nkCallStrLit}: result = nil else: @@ -91,25 +91,25 @@ proc getOpSym*(op: PNode): PSym = elif op.sons[0].kind == nkSym: result = op.sons[0].sym else: result = nil -proc getMagic*(op: PNode): TMagic = +proc getMagic*(op: PNode): TMagic = case op.kind of nkCallKinds: case op.sons[0].kind of nkSym: result = op.sons[0].sym.magic else: result = mNone else: result = mNone - -proc treeToSym*(t: PNode): PSym = + +proc treeToSym*(t: PNode): PSym = result = t.sym -proc isConstExpr*(n: PNode): bool = +proc isConstExpr*(n: PNode): bool = result = (n.kind in - {nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, + {nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, nkFloatLit..nkFloat64Lit, nkNilLit}) or (nfAllConst in n.flags) proc isDeepConstExpr*(n: PNode): bool = case n.kind - of nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, + of nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, nkFloatLit..nkFloat64Lit, nkNilLit: result = true of nkExprEqExpr, nkExprColonExpr, nkHiddenStdConv, nkHiddenSubConv: @@ -122,33 +122,33 @@ proc isDeepConstExpr*(n: PNode): bool = result = n.typ.isNil or n.typ.skipTypes({tyGenericInst, tyDistinct}).kind != tyObject else: discard -proc flattenTreeAux(d, a: PNode, op: TMagic) = +proc flattenTreeAux(d, a: PNode, op: TMagic) = if (getMagic(a) == op): # a is a "leaf", so add it: for i in countup(1, sonsLen(a) - 1): # BUGFIX flattenTreeAux(d, a.sons[i], op) - else: + else: addSon(d, copyTree(a)) - -proc flattenTree*(root: PNode, op: TMagic): PNode = + +proc flattenTree*(root: PNode, op: TMagic): PNode = result = copyNode(root) if getMagic(root) == op: # BUGFIX: forget to copy prc addSon(result, copyNode(root.sons[0])) flattenTreeAux(result, root, op) -proc swapOperands*(op: PNode) = +proc swapOperands*(op: PNode) = var tmp = op.sons[1] op.sons[1] = op.sons[2] op.sons[2] = tmp -proc isRange*(n: PNode): bool {.inline.} = - if n.kind == nkInfix: +proc isRange*(n: PNode): bool {.inline.} = + if n.kind in nkCallKinds: if n[0].kind == nkIdent and n[0].ident.id == ord(wDotDot) or - n[0].kind in {nkClosedSymChoice, nkOpenSymChoice} and + n[0].kind in {nkClosedSymChoice, nkOpenSymChoice} and n[0][1].sym.name.id == ord(wDotDot): result = true -proc whichPragma*(n: PNode): TSpecialWord = +proc whichPragma*(n: PNode): TSpecialWord = let key = if n.kind == nkExprColonExpr: n.sons[0] else: n if key.kind == nkIdent: result = whichKeyword(key.ident) diff --git a/compiler/types.nim b/compiler/types.nim index 153c26a42..7f05e7051 100644 --- a/compiler/types.nim +++ b/compiler/types.nim @@ -541,6 +541,9 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string = of tyProc: result = if tfIterator in t.flags: "iterator (" else: "proc (" for i in countup(1, sonsLen(t) - 1): + if t.n != nil and i < t.n.len and t.n[i].kind == nkSym: + add(result, t.n[i].sym.name.s) + add(result, ": ") add(result, typeToString(t.sons[i])) if i < sonsLen(t) - 1: add(result, ", ") add(result, ')') diff --git a/compiler/vm.nim b/compiler/vm.nim index 3b5c8e7f3..6fae5a8b7 100644 --- a/compiler/vm.nim +++ b/compiler/vm.nim @@ -1043,7 +1043,14 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg = decodeB(rkNode) let newLen = regs[rb].intVal.int if regs[ra].node.isNil: stackTrace(c, tos, pc, errNilAccess) - else: setLen(regs[ra].node.sons, newLen) + else: + let oldLen = regs[ra].node.len + setLen(regs[ra].node.sons, newLen) + if oldLen < newLen: + # XXX This is still not entirely correct + # set to default value: + for i in oldLen .. <newLen: + regs[ra].node.sons[i] = newNodeI(nkEmpty, c.debug[pc]) of opcSwap: let rb = instr.regB if regs[ra].kind == regs[rb].kind: diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim index 90b9f2517..b4892d010 100644 --- a/compiler/vmdef.nim +++ b/compiler/vmdef.nim @@ -16,7 +16,7 @@ const byteExcess* = 128 # we use excess-K for immediates wordExcess* = 32768 - MaxLoopIterations* = 500_000 # max iterations of all loops + MaxLoopIterations* = 1500_000 # max iterations of all loops type @@ -29,7 +29,7 @@ type opcRet, # return opcYldYoid, # yield with no value opcYldVal, # yield with a value - + opcAsgnInt, opcAsgnStr, opcAsgnFloat, @@ -48,8 +48,8 @@ type opcWrDeref, opcWrStrIdx, opcLdStrIdx, # a = b[c] - - opcAddInt, + + opcAddInt, opcAddImmInt, opcSubInt, opcSubImmInt, @@ -58,36 +58,36 @@ type opcIncl, opcInclRange, opcExcl, opcCard, opcMulInt, opcDivInt, opcModInt, opcAddFloat, opcSubFloat, opcMulFloat, opcDivFloat, opcShrInt, opcShlInt, - opcBitandInt, opcBitorInt, opcBitxorInt, opcAddu, opcSubu, opcMulu, - opcDivu, opcModu, opcEqInt, opcLeInt, opcLtInt, opcEqFloat, - opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcEqNimrodNode, opcXor, - opcNot, opcUnaryMinusInt, opcUnaryMinusFloat, opcBitnotInt, + opcBitandInt, opcBitorInt, opcBitxorInt, opcAddu, opcSubu, opcMulu, + opcDivu, opcModu, opcEqInt, opcLeInt, opcLtInt, opcEqFloat, + opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcEqNimrodNode, opcXor, + opcNot, opcUnaryMinusInt, opcUnaryMinusFloat, opcBitnotInt, opcEqStr, opcLeStr, opcLtStr, opcEqSet, opcLeSet, opcLtSet, opcMulSet, opcPlusSet, opcMinusSet, opcSymdiffSet, opcConcatStr, opcContainsSet, opcRepr, opcSetLenStr, opcSetLenSeq, opcSwap, opcIsNil, opcOf, opcIs, opcSubStr, opcParseFloat, opcConv, opcCast, opcQuit, opcReset, opcNarrowS, opcNarrowU, - + opcAddStrCh, opcAddStrStr, opcAddSeqElem, opcRangeChck, - + opcNAdd, opcNAddMultiple, - opcNKind, - opcNIntVal, - opcNFloatVal, - opcNSymbol, + opcNKind, + opcNIntVal, + opcNFloatVal, + opcNSymbol, opcNIdent, opcNGetType, opcNStrVal, - + opcNSetIntVal, opcNSetFloatVal, opcNSetSymbol, opcNSetIdent, opcNSetType, opcNSetStrVal, opcNNewNimNode, opcNCopyNimNode, opcNCopyNimTree, opcNDel, opcGenSym, - + opcSlurp, opcGorge, opcParseExprToAst, @@ -100,7 +100,7 @@ type opcEqIdent, opcStrToIdent, opcIdentToStr, - + opcEcho, opcIndCall, # dest = call regStart, n; where regStart = fn, arg1, ... opcIndCallAsgn, # dest = call regStart, n; where regStart = fn, arg1, ... @@ -110,7 +110,7 @@ type opcNSetChild, opcCallSite, opcNewStr, - + opcTJmp, # jump Bx if A != 0 opcFJmp, # jump Bx if A == 0 opcJmp, # jump Bx @@ -178,13 +178,13 @@ type slots*: pointer currentException*: PNode VmCallback* = proc (args: VmArgs) {.closure.} - + PCtx* = ref TCtx TCtx* = object of passes.TPassContext # code gen context code*: seq[TInstr] debug*: seq[TLineInfo] # line info for every instruction; kept separate # to not slow down interpretation - globals*: PNode # + globals*: PNode # constants*: PNode # constant data types*: seq[PType] # some instructions reference types (e.g. 'except') currentExceptionA*, currentExceptionB*: PNode @@ -203,7 +203,7 @@ type TPosition* = distinct int PEvalContext* = PCtx - + proc newCtx*(module: PSym): PCtx = PCtx(code: @[], debug: @[], globals: newNode(nkStmtListExpr), constants: newNode(nkStmtList), types: @[], diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim index 6148ed319..21ee4967b 100644 --- a/compiler/vmdeps.nim +++ b/compiler/vmdeps.nim @@ -144,7 +144,9 @@ proc mapTypeToAst(t: PType, info: TLineInfo; allowRecursion=false): PNode = of tyIter: result = mapTypeToBracket("iter", t, info) of tyProxy: result = atomicType"error" of tyBuiltInTypeClass: result = mapTypeToBracket("builtinTypeClass", t, info) - of tyUserTypeClass: result = mapTypeToBracket("userTypeClass", t, info) + of tyUserTypeClass: + result = mapTypeToBracket("concept", t, info) + result.add t.n.copyTree of tyCompositeTypeClass: result = mapTypeToBracket("compositeTypeClass", t, info) of tyAnd: result = mapTypeToBracket("and", t, info) of tyOr: result = mapTypeToBracket("or", t, info) diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim index c3013852d..4526687c9 100644 --- a/compiler/vmgen.nim +++ b/compiler/vmgen.nim @@ -1364,7 +1364,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = of tyCString, tyString: result = newNodeIT(nkStrLit, info, t) of tyVar, tyPointer, tyPtr, tySequence, tyExpr, - tyStmt, tyTypeDesc, tyStatic, tyRef: + tyStmt, tyTypeDesc, tyStatic, tyRef, tyNil: result = newNodeIT(nkNilLit, info, t) of tyProc: if t.callConv != ccClosure: @@ -1391,7 +1391,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = addSon(result, getNullValue(t.sons[i], info)) of tySet: result = newNodeIT(nkCurly, info, t) - else: internalError("getNullValue: " & $t.kind) + else: internalError(info, "getNullValue: " & $t.kind) proc ldNullOpcode(t: PType): TOpcode = if fitsRegister(t): opcLdNullReg else: opcLdNull @@ -1610,7 +1610,8 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = genBreak(c, n) of nkTryStmt: genTry(c, n, dest) of nkStmtList: - unused(n, dest) + #unused(n, dest) + # XXX Fix this bug properly, lexim triggers it for x in n: gen(c, x) of nkStmtListExpr: let L = n.len-1 diff --git a/doc/manual/lexing.txt b/doc/manual/lexing.txt index e2f006f04..df6d85636 100644 --- a/doc/manual/lexing.txt +++ b/doc/manual/lexing.txt @@ -289,7 +289,7 @@ Numerical constants are of a single type and have the form:: INT32_LIT = INT_LIT ['\''] ('i' | 'I') '32' INT64_LIT = INT_LIT ['\''] ('i' | 'I') '64' - UINT8_LIT = INT_LIT ['\''] ('u' | 'U') + UINT_LIT = INT_LIT ['\''] ('u' | 'U') UINT8_LIT = INT_LIT ['\''] ('u' | 'U') '8' UINT16_LIT = INT_LIT ['\''] ('u' | 'U') '16' UINT32_LIT = INT_LIT ['\''] ('u' | 'U') '32' diff --git a/doc/manual/pragmas.txt b/doc/manual/pragmas.txt index 46fd89b13..39aebd826 100644 --- a/doc/manual/pragmas.txt +++ b/doc/manual/pragmas.txt @@ -71,10 +71,9 @@ procedural variable. compileTime pragma ------------------ -The ``compileTime`` pragma is used to mark a proc to be used at compile -time only. No code will be generated for it. Compile time procs are useful -as helpers for macros. - +The ``compileTime`` pragma is used to mark a proc or variable to be used at +compile time only. No code will be generated for it. Compile time procs are +useful as helpers for macros. noReturn pragma --------------- diff --git a/doc/manual/syntax.txt b/doc/manual/syntax.txt index cf44eb588..24644bce2 100644 --- a/doc/manual/syntax.txt +++ b/doc/manual/syntax.txt @@ -15,8 +15,6 @@ Associativity Binary operators whose first character is ``^`` are right-associative, all other binary operators are left-associative. -Operators ending in ``>`` but longer than a single character are -called `arrow like`:idx:. Precedence @@ -33,9 +31,12 @@ as ``(@x).abc`` whereas ``$x.abc`` is parsed as ``$(x.abc)``. For binary operators that are not keywords the precedence is determined by the following rules: +Operators ending in either ``->``, ``~>`` or ``=>`` are called +`arrow like`:idx:, and have the lowest precedence of all operators. + If the operator ends with ``=`` and its first character is none of ``<``, ``>``, ``!``, ``=``, ``~``, ``?``, it is an *assignment operator* which -has the lowest precedence. +has the second lowest precedence. Otherwise precedence is determined by the first character. @@ -43,14 +44,14 @@ Otherwise precedence is determined by the first character. Precedence level Operators First character Terminal symbol ================ =============================================== ================== =============== 10 (highest) ``$ ^`` OP10 - 9 ``* / div mod shl shr %`` ``* % \ /`` OP9 - 8 ``+ -`` ``+ ~ |`` OP8 + 9 ``* / div mod shl shr %`` ``* % \ /`` OP9 + 8 ``+ -`` ``+ - ~ |`` OP8 7 ``&`` ``&`` OP7 6 ``..`` ``.`` OP6 - 5 ``== <= < >= > != in notin is isnot not of`` ``= < > !`` OP5 + 5 ``== <= < >= > != in notin is isnot not of`` ``= < > !`` OP5 4 ``and`` OP4 3 ``or xor`` OP3 - 2 ``@ : ?`` OP2 + 2 ``@ : ?`` OP2 1 *assignment operator* (like ``+=``, ``*=``) OP1 0 (lowest) *arrow like operator* (like ``->``, ``=>``) OP0 ================ =============================================== ================== =============== @@ -67,7 +68,7 @@ is still parsed as ``1 + (3 * 4)``, but ``1+3 * 4`` is parsed as ``(1+3) * 4``: .. code-block:: nim #! strongSpaces - if foo+4 * 4 == 8 and b&c | 9 ++ + if foo+4 * 4 == 8 and b&c | 9 ++ bar: echo "" # is parsed as diff --git a/doc/manual/type_bound_ops.txt b/doc/manual/type_bound_ops.txt index efa5578d4..c707979fe 100644 --- a/doc/manual/type_bound_ops.txt +++ b/doc/manual/type_bound_ops.txt @@ -127,8 +127,8 @@ The signature has to be: .. code-block:: nim proc `=deepCopy`(x: T): T -This mechanism is used by most data structures that support shared memory like -channels to implement thread safe automatic memory management. +This mechanism will be used by most data structures that support shared memory +like channels to implement thread safe automatic memory management. The builtin ``deepCopy`` can even clone closures and their environments. See the documentation of `spawn`_ for details. diff --git a/doc/nimc.txt b/doc/nimc.txt index 831fce567..cfbccc479 100644 --- a/doc/nimc.txt +++ b/doc/nimc.txt @@ -506,7 +506,7 @@ For example: .. code-block:: nim type Input {.importcpp: "System::Input".} = object - proc getSubsystem*[T](): ptr T {.importcpp: "SystemManager::getSubsystem<'*0>()".} + proc getSubsystem*[T](): ptr T {.importcpp: "SystemManager::getSubsystem<'*0>()", nodecl.} let x: ptr Input = getSubsystem[Input]() @@ -596,6 +596,25 @@ Produces: x[6] = 91.4; +- If more precise control is needed, the apostrophe ``'`` can be used in the + supplied pattern to denote the concrete type parameters of the generic type. + See the usage of the apostrophe operator in proc patterns for more details. + +.. code-block:: nim + + type + VectorIterator {.importcpp: "std::vector<'0>::iterator".} [T] = object + + var x: VectorIterator[cint] + + +Produces: + +.. code-block:: C + + std::vector<int>::iterator x; + + ImportObjC pragma ----------------- Similar to the `importc pragma for C <manual.html#importc-pragma>`_, the diff --git a/lib/core/macros.nim b/lib/core/macros.nim index 5583748e0..35f0f61c1 100644 --- a/lib/core/macros.nim +++ b/lib/core/macros.nim @@ -88,7 +88,9 @@ type ntyBigNum, ntyConst, ntyMutable, ntyVarargs, ntyIter, - ntyError + ntyError, + ntyBuiltinTypeClass, ntyConcept, ntyConceptInst, ntyComposite, + ntyAnd, ntyOr, ntyNot TNimTypeKinds* {.deprecated.} = set[NimTypeKind] NimSymKind* = enum @@ -162,6 +164,7 @@ proc kind*(n: NimNode): NimNodeKind {.magic: "NKind", noSideEffect.} ## returns the `kind` of the node `n`. proc intVal*(n: NimNode): BiggestInt {.magic: "NIntVal", noSideEffect.} +proc boolVal*(n: NimNode): bool {.compileTime, noSideEffect.} = n.intVal != 0 proc floatVal*(n: NimNode): BiggestFloat {.magic: "NFloatVal", noSideEffect.} proc symbol*(n: NimNode): NimSym {.magic: "NSymbol", noSideEffect.} proc ident*(n: NimNode): NimIdent {.magic: "NIdent", noSideEffect.} @@ -355,6 +358,12 @@ proc expectLen*(n: NimNode, len: int) {.compileTime.} = ## macros that check its number of arguments. if n.len != len: error("macro expects a node with " & $len & " children") +proc newTree*(kind: NimNodeKind, + children: varargs[NimNode]): NimNode {.compileTime.} = + ## produces a new node with children. + result = newNimNode(kind) + result.add(children) + proc newCall*(theProc: NimNode, args: varargs[NimNode]): NimNode {.compileTime.} = ## produces a new call node. `theProc` is the proc that is called with @@ -389,6 +398,11 @@ proc newLit*(i: BiggestInt): NimNode {.compileTime.} = result = newNimNode(nnkIntLit) result.intVal = i +proc newLit*(b: bool): NimNode {.compileTime.} = + ## produces a new boolean literal node. + result = newNimNode(nnkIntLit) + result.intVal = ord(b) + proc newLit*(f: BiggestFloat): NimNode {.compileTime.} = ## produces a new float literal node. result = newNimNode(nnkFloatLit) diff --git a/lib/impure/re.nim b/lib/impure/re.nim index e6fc93c7a..fb95610f6 100644 --- a/lib/impure/re.nim +++ b/lib/impure/re.nim @@ -7,8 +7,11 @@ # distribution, for details about the copyright. # -## Regular expression support for Nim. Consider using the pegs module -## instead. +## Regular expression support for Nim. Consider using the pegs module instead. +## +## There is an alternative regular expressions library with a more unified API: +## `nre <https://github.com/flaviut/nre>`_. It may be added to the standard +## library in the future, instead of `re`. ## ## **Note:** The 're' proc defaults to the **extended regular expression ## syntax** which lets you use whitespace freely to make your regexes readable. @@ -413,22 +416,28 @@ proc escapeRe*(s: string): string = result.add(toHex(ord(c), 2)) const ## common regular expressions - reIdentifier* = r"\b[a-zA-Z_]+[a-zA-Z_0-9]*\b" ## describes an identifier - reNatural* = r"\b\d+\b" ## describes a natural number - reInteger* = r"\b[-+]?\d+\b" ## describes an integer - reHex* = r"\b0[xX][0-9a-fA-F]+\b" ## describes a hexadecimal number - reBinary* = r"\b0[bB][01]+\b" ## describes a binary number (example: 0b11101) - reOctal* = r"\b0[oO][0-7]+\b" ## describes an octal number (example: 0o777) - reFloat* = r"\b[-+]?[0-9]*\.?[0-9]+([eE][-+]?[0-9]+)?\b" + reIdentifier* {.deprecated.} = r"\b[a-zA-Z_]+[a-zA-Z_0-9]*\b" + ## describes an identifier + reNatural* {.deprecated.} = r"\b\d+\b" + ## describes a natural number + reInteger* {.deprecated.} = r"\b[-+]?\d+\b" + ## describes an integer + reHex* {.deprecated.} = r"\b0[xX][0-9a-fA-F]+\b" + ## describes a hexadecimal number + reBinary* {.deprecated.} = r"\b0[bB][01]+\b" + ## describes a binary number (example: 0b11101) + reOctal* {.deprecated.} = r"\b0[oO][0-7]+\b" + ## describes an octal number (example: 0o777) + reFloat* {.deprecated.} = r"\b[-+]?[0-9]*\.?[0-9]+([eE][-+]?[0-9]+)?\b" ## describes a floating point number - reEmail* = r"\b[a-zA-Z0-9!#$%&'*+/=?^_`{|}~\-]+(?:\. &" & - r"[a-zA-Z0-9!#$%&'*+/=?^_`{|}~-]+)" & - r"*@(?:[a-zA-Z0-9](?:[a-zA-Z0-9-]*[a-zA-Z0-9])?\.)+" & - r"(?:[a-zA-Z]{2}|com|org|" & - r"net|gov|mil|biz|info|mobi|name|aero|jobs|museum)\b" + reEmail* {.deprecated.} = r"\b[a-zA-Z0-9!#$%&'*+/=?^_`{|}~\-]+(?:\. &" & + r"[a-zA-Z0-9!#$%&'*+/=?^_`{|}~-]+)*@" & + r"(?:[a-zA-Z0-9](?:[a-zA-Z0-9-]*[a-zA-Z0-9])?\.)+" & + r"(?:[a-zA-Z]{2}|com|org|net|gov|mil|biz|" & + r"info|mobi|name|aero|jobs|museum)\b" ## describes a common email address - reURL* = r"\b(http(s)?|ftp|gopher|telnet|file|notes|ms\-help):" & - r"((//)|(\\\\))+[\w\d:#@%/;$()~_?\+\-\=\\\.\&]*\b" + reURL* {.deprecated.} = r"\b(http(s)?|ftp|gopher|telnet|file|notes|ms-help)" & + r":((//)|(\\\\))+[\w\d:#@%/;$()~_?\+\-\=\\\.\&]*\b" ## describes an URL when isMainModule: diff --git a/lib/packages/docutils/rst.nim b/lib/packages/docutils/rst.nim index a4d095e68..2ee94ba13 100644 --- a/lib/packages/docutils/rst.nim +++ b/lib/packages/docutils/rst.nim @@ -564,7 +564,7 @@ proc fixupEmbeddedRef(n, a, b: PRstNode) = proc parsePostfix(p: var TRstParser, n: PRstNode): PRstNode = result = n - if isInlineMarkupEnd(p, "_"): + if isInlineMarkupEnd(p, "_") or isInlineMarkupEnd(p, "__"): inc(p.idx) if p.tok[p.idx-2].symbol == "`" and p.tok[p.idx-3].symbol == ">": var a = newRstNode(rnInner) diff --git a/lib/packages/docutils/rstgen.nim b/lib/packages/docutils/rstgen.nim index da05be9bf..a44740bcf 100644 --- a/lib/packages/docutils/rstgen.nim +++ b/lib/packages/docutils/rstgen.nim @@ -34,14 +34,14 @@ type TOutputTarget* = enum ## which document type to generate outHtml, # output is HTML outLatex # output is Latex - - TTocEntry = object + + TTocEntry = object n*: PRstNode refname*, header*: string - TMetaEnum* = enum + TMetaEnum* = enum metaNone, metaTitle, metaSubtitle, metaAuthor, metaVersion - + TRstGenerator* = object of RootObj target*: TOutputTarget config*: StringTableRef @@ -60,7 +60,7 @@ type seenIndexTerms: Table[string, int] ## \ ## Keeps count of same text index terms to generate different identifiers ## for hyperlinks. See renderIndexTerm proc for details. - + PDoc = var TRstGenerator ## Alias to type less. CodeBlockParams = object ## Stores code block params. @@ -136,7 +136,7 @@ proc initRstGenerator*(g: var TRstGenerator, target: TOutputTarget, g.currentSection = "Module " & fileParts.name g.seenIndexTerms = initTable[string, int]() g.msgHandler = msgHandler - + let s = config["split.item.toc"] if s != "": g.splitAfter = parseInt(s) for i in low(g.meta)..high(g.meta): g.meta[i] = "" @@ -147,23 +147,23 @@ proc writeIndexFile*(g: var TRstGenerator, outfile: string) = ## You previously need to add entries to the index with the `setIndexTerm() ## <#setIndexTerm>`_ proc. If the index is empty the file won't be created. if g.theIndex.len > 0: writeFile(outfile, g.theIndex) - -proc addXmlChar(dest: var string, c: char) = + +proc addXmlChar(dest: var string, c: char) = case c of '&': add(dest, "&") of '<': add(dest, "<") of '>': add(dest, ">") of '\"': add(dest, """) else: add(dest, c) - -proc addRtfChar(dest: var string, c: char) = + +proc addRtfChar(dest: var string, c: char) = case c of '{': add(dest, "\\{") of '}': add(dest, "\\}") of '\\': add(dest, "\\\\") else: add(dest, c) - -proc addTexChar(dest: var string, c: char) = + +proc addTexChar(dest: var string, c: char) = case c of '_': add(dest, "\\_") of '{': add(dest, "\\symbol{123}") @@ -183,54 +183,54 @@ proc addTexChar(dest: var string, c: char) = var splitter*: string = "<wbr />" -proc escChar*(target: TOutputTarget, dest: var string, c: char) {.inline.} = +proc escChar*(target: TOutputTarget, dest: var string, c: char) {.inline.} = case target of outHtml: addXmlChar(dest, c) of outLatex: addTexChar(dest, c) - -proc nextSplitPoint*(s: string, start: int): int = + +proc nextSplitPoint*(s: string, start: int): int = result = start - while result < len(s) + 0: + while result < len(s) + 0: case s[result] - of '_': return - of 'a'..'z': - if result + 1 < len(s) + 0: - if s[result + 1] in {'A'..'Z'}: return + of '_': return + of 'a'..'z': + if result + 1 < len(s) + 0: + if s[result + 1] in {'A'..'Z'}: return else: discard inc(result) dec(result) # last valid index - -proc esc*(target: TOutputTarget, s: string, splitAfter = -1): string = + +proc esc*(target: TOutputTarget, s: string, splitAfter = -1): string = result = "" - if splitAfter >= 0: + if splitAfter >= 0: var partLen = 0 var j = 0 - while j < len(s): + while j < len(s): var k = nextSplitPoint(s, j) - if (splitter != " ") or (partLen + k - j + 1 > splitAfter): + if (splitter != " ") or (partLen + k - j + 1 > splitAfter): partLen = 0 add(result, splitter) for i in countup(j, k): escChar(target, result, s[i]) inc(partLen, k - j + 1) j = k + 1 - else: + else: for i in countup(0, len(s) - 1): escChar(target, result, s[i]) proc disp(target: TOutputTarget, xml, tex: string): string = - if target != outLatex: result = xml + if target != outLatex: result = xml else: result = tex - -proc dispF(target: TOutputTarget, xml, tex: string, - args: varargs[string]): string = - if target != outLatex: result = xml % args + +proc dispF(target: TOutputTarget, xml, tex: string, + args: varargs[string]): string = + if target != outLatex: result = xml % args else: result = tex % args - -proc dispA(target: TOutputTarget, dest: var string, + +proc dispA(target: TOutputTarget, dest: var string, xml, tex: string, args: varargs[string]) = if target != outLatex: addf(dest, xml, args) else: addf(dest, tex, args) - + proc `or`(x, y: string): string {.inline.} = result = if x.isNil: y else: x @@ -248,7 +248,7 @@ proc renderRstToOut*(d: var TRstGenerator, n: PRstNode, result: var string) ## renderRstToOut(gen, rst, generatedHTML) ## echo generatedHTML -proc renderAux(d: PDoc, n: PRstNode, result: var string) = +proc renderAux(d: PDoc, n: PRstNode, result: var string) = for i in countup(0, len(n)-1): renderRstToOut(d, n.sons[i], result) proc renderAux(d: PDoc, n: PRstNode, frmtA, frmtB: string, result: var string) = @@ -347,7 +347,7 @@ proc renderIndexTerm*(d: PDoc, n: PRstNode, result: var string) = var term = "" renderAux(d, n, term) setIndexTerm(d, id, term, d.currentSection) - dispA(d.target, result, "<span id=\"$1\">$2</span>", "$2\\label{$1}", + dispA(d.target, result, "<span id=\"$1\">$2</span>", "$2\\label{$1}", [id, term]) type @@ -656,7 +656,7 @@ proc mergeIndexes*(dir: string): string = result.add("<h2>API symbols</h2>\n") result.add(generateSymbolIndex(symbols)) - + # ---------------------------------------------------------------------------- proc stripTOCHTML(s: string): string = @@ -677,7 +677,7 @@ proc stripTOCHTML(s: string): string = result.delete(first, last) first = result.find('<', first) -proc renderHeadline(d: PDoc, n: PRstNode, result: var string) = +proc renderHeadline(d: PDoc, n: PRstNode, result: var string) = var tmp = "" for i in countup(0, len(n) - 1): renderRstToOut(d, n.sons[i], tmp) d.currentSection = tmp @@ -700,9 +700,9 @@ proc renderHeadline(d: PDoc, n: PRstNode, result: var string) = "id=\"$2\" href=\"#$2\">$3</a></h$1>", "\\rsth$4{$3}\\label{$2}\n", [$n.level, d.tocPart[length].refname, tmp, $chr(n.level - 1 + ord('A'))]) else: - dispA(d.target, result, "\n<h$1 id=\"$2\">$3</h$1>", + dispA(d.target, result, "\n<h$1 id=\"$2\">$3</h$1>", "\\rsth$4{$3}\\label{$2}\n", [ - $n.level, refname, tmp, + $n.level, refname, tmp, $chr(n.level - 1 + ord('A'))]) # Generate index entry using spaces to indicate TOC level for the output HTML. @@ -710,7 +710,7 @@ proc renderHeadline(d: PDoc, n: PRstNode, result: var string) = setIndexTerm(d, refname, tmp.stripTOCHTML, spaces(max(0, n.level)) & tmp) -proc renderOverline(d: PDoc, n: PRstNode, result: var string) = +proc renderOverline(d: PDoc, n: PRstNode, result: var string) = if d.meta[metaTitle].len == 0: for i in countup(0, len(n)-1): renderRstToOut(d, n.sons[i], d.meta[metaTitle]) @@ -723,14 +723,14 @@ proc renderOverline(d: PDoc, n: PRstNode, result: var string) = var tmp = "" for i in countup(0, len(n) - 1): renderRstToOut(d, n.sons[i], tmp) d.currentSection = tmp - dispA(d.target, result, "<h$1 id=\"$2\"><center>$3</center></h$1>", + dispA(d.target, result, "<h$1 id=\"$2\"><center>$3</center></h$1>", "\\rstov$4{$3}\\label{$2}\n", [$n.level, rstnodeToRefname(n), tmp, $chr(n.level - 1 + ord('A'))]) - -proc renderTocEntry(d: PDoc, e: TTocEntry, result: var string) = + +proc renderTocEntry(d: PDoc, e: TTocEntry, result: var string) = dispA(d.target, result, - "<li><a class=\"reference\" id=\"$1_toc\" href=\"#$1\">$2</a></li>\n", + "<li><a class=\"reference\" id=\"$1_toc\" href=\"#$1\">$2</a></li>\n", "\\item\\label{$1_toc} $2\\ref{$1}\n", [e.refname, e.header]) proc renderTocEntries*(d: var TRstGenerator, j: var int, lvl: int, @@ -759,33 +759,33 @@ proc renderImage(d: PDoc, n: PRstNode, result: var string) = var options = "" var s = getFieldValue(n, "scale") if s.valid: dispA(d.target, options, " scale=\"$1\"", " scale=$1", [strip(s)]) - + s = getFieldValue(n, "height") if s.valid: dispA(d.target, options, " height=\"$1\"", " height=$1", [strip(s)]) - + s = getFieldValue(n, "width") if s.valid: dispA(d.target, options, " width=\"$1\"", " width=$1", [strip(s)]) - + s = getFieldValue(n, "alt") if s.valid: dispA(d.target, options, " alt=\"$1\"", "", [strip(s)]) - + s = getFieldValue(n, "align") if s.valid: dispA(d.target, options, " align=\"$1\"", "", [strip(s)]) - + if options.len > 0: options = dispF(d.target, "$1", "[$1]", [options]) let arg = getArgument(n) if arg.valid: - dispA(d.target, result, "<img src=\"$1\"$2 />", "\\includegraphics$2{$1}", + dispA(d.target, result, "<img src=\"$1\"$2 />", "\\includegraphics$2{$1}", [arg, options]) if len(n) >= 3: renderRstToOut(d, n.sons[2], result) - + proc renderSmiley(d: PDoc, n: PRstNode, result: var string) = dispA(d.target, result, - """<img src="$1" width="15" + """<img src="$1" width="15" height="17" hspace="2" vspace="2" class="smiley" />""", "\\includegraphics{$1}", [d.config["doc.smiley_format"] % n.text]) - + proc parseCodeBlockField(d: PDoc, n: PRstNode, params: var CodeBlockParams) = ## Parses useful fields which can appear before a code block. ## @@ -880,11 +880,11 @@ proc renderCodeBlock(d: PDoc, n: PRstNode, result: var string) = else: var g: TGeneralTokenizer initGeneralTokenizer(g, m.text) - while true: + while true: getNextToken(g, params.lang) case g.kind - of gtEof: break - of gtNone, gtWhitespace: + of gtEof: break + of gtNone, gtWhitespace: add(result, substr(m.text, g.start, g.length + g.start - 1)) else: dispA(d.target, result, "<span class=\"$2\">$1</span>", "\\span$2{$1}", [ @@ -893,36 +893,36 @@ proc renderCodeBlock(d: PDoc, n: PRstNode, result: var string) = deinitGeneralTokenizer(g) dispA(d.target, result, blockEnd, "\n\\end{rstpre}\n") -proc renderContainer(d: PDoc, n: PRstNode, result: var string) = +proc renderContainer(d: PDoc, n: PRstNode, result: var string) = var tmp = "" renderRstToOut(d, n.sons[2], tmp) var arg = strip(getArgument(n)) - if arg == "": + if arg == "": dispA(d.target, result, "<div>$1</div>", "$1", [tmp]) else: dispA(d.target, result, "<div class=\"$1\">$2</div>", "$2", [arg, tmp]) - -proc texColumns(n: PRstNode): string = + +proc texColumns(n: PRstNode): string = result = "" for i in countup(1, len(n)): add(result, "|X") - -proc renderField(d: PDoc, n: PRstNode, result: var string) = + +proc renderField(d: PDoc, n: PRstNode, result: var string) = var b = false - if d.target == outLatex: + if d.target == outLatex: var fieldname = addNodes(n.sons[0]) var fieldval = esc(d.target, strip(addNodes(n.sons[1]))) - if cmpIgnoreStyle(fieldname, "author") == 0 or + if cmpIgnoreStyle(fieldname, "author") == 0 or cmpIgnoreStyle(fieldname, "authors") == 0: if d.meta[metaAuthor].len == 0: d.meta[metaAuthor] = fieldval b = true - elif cmpIgnoreStyle(fieldname, "version") == 0: + elif cmpIgnoreStyle(fieldname, "version") == 0: if d.meta[metaVersion].len == 0: d.meta[metaVersion] = fieldval b = true if not b: renderAux(d, n, "<tr>$1</tr>\n", "$1", result) - + proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = if n == nil: return case n.kind @@ -947,54 +947,54 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = of rnDefBody: renderAux(d, n, "<dd>$1</dd>\n", "$1\n", result) of rnFieldList: var tmp = "" - for i in countup(0, len(n) - 1): + for i in countup(0, len(n) - 1): renderRstToOut(d, n.sons[i], tmp) - if tmp.len != 0: + if tmp.len != 0: dispA(d.target, result, "<table class=\"docinfo\" frame=\"void\" rules=\"none\">" & "<col class=\"docinfo-name\" />" & - "<col class=\"docinfo-content\" />" & + "<col class=\"docinfo-content\" />" & "<tbody valign=\"top\">$1" & - "</tbody></table>", - "\\begin{description}$1\\end{description}\n", + "</tbody></table>", + "\\begin{description}$1\\end{description}\n", [tmp]) of rnField: renderField(d, n, result) - of rnFieldName: + of rnFieldName: renderAux(d, n, "<th class=\"docinfo-name\">$1:</th>", "\\item[$1:]", result) - of rnFieldBody: + of rnFieldBody: renderAux(d, n, "<td>$1</td>", " $1\n", result) - of rnIndex: + of rnIndex: renderRstToOut(d, n.sons[2], result) - of rnOptionList: - renderAux(d, n, "<table frame=\"void\">$1</table>", + of rnOptionList: + renderAux(d, n, "<table frame=\"void\">$1</table>", "\\begin{description}\n$1\\end{description}\n", result) - of rnOptionListItem: + of rnOptionListItem: renderAux(d, n, "<tr>$1</tr>\n", "$1", result) - of rnOptionGroup: + of rnOptionGroup: renderAux(d, n, "<th align=\"left\">$1</th>", "\\item[$1]", result) - of rnDescription: + of rnDescription: renderAux(d, n, "<td align=\"left\">$1</td>\n", " $1\n", result) - of rnOption, rnOptionString, rnOptionArgument: + of rnOption, rnOptionString, rnOptionArgument: doAssert false, "renderRstToOut" of rnLiteralBlock: - renderAux(d, n, "<pre>$1</pre>\n", + renderAux(d, n, "<pre>$1</pre>\n", "\\begin{rstpre}\n$1\n\\end{rstpre}\n", result) - of rnQuotedLiteralBlock: + of rnQuotedLiteralBlock: doAssert false, "renderRstToOut" - of rnLineBlock: + of rnLineBlock: renderAux(d, n, "<p>$1</p>", "$1\n\n", result) - of rnLineBlockItem: + of rnLineBlockItem: renderAux(d, n, "$1<br />", "$1\\\\\n", result) - of rnBlockQuote: - renderAux(d, n, "<blockquote><p>$1</p></blockquote>\n", + of rnBlockQuote: + renderAux(d, n, "<blockquote><p>$1</p></blockquote>\n", "\\begin{quote}$1\\end{quote}\n", result) - of rnTable, rnGridTable: - renderAux(d, n, - "<table border=\"1\" class=\"docutils\">$1</table>", + of rnTable, rnGridTable: + renderAux(d, n, + "<table border=\"1\" class=\"docutils\">$1</table>", "\\begin{table}\\begin{rsttab}{" & texColumns(n) & "|}\n\\hline\n$1\\end{rsttab}\\end{table}", result) - of rnTableRow: + of rnTableRow: if len(n) >= 1: if d.target == outLatex: #var tmp = "" @@ -1007,25 +1007,25 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = result.add("<tr>") renderAux(d, n, result) result.add("</tr>\n") - of rnTableDataCell: + of rnTableDataCell: renderAux(d, n, "<td>$1</td>", "$1", result) - of rnTableHeaderCell: + of rnTableHeaderCell: renderAux(d, n, "<th>$1</th>", "\\textbf{$1}", result) - of rnLabel: + of rnLabel: doAssert false, "renderRstToOut" # used for footnotes and other - of rnFootnote: + of rnFootnote: doAssert false, "renderRstToOut" # a footnote - of rnCitation: + of rnCitation: doAssert false, "renderRstToOut" # similar to footnote - of rnRef: + of rnRef: var tmp = "" renderAux(d, n, tmp) dispA(d.target, result, "<a class=\"reference external\" href=\"#$2\">$1</a>", "$1\\ref{$2}", [tmp, rstnodeToRefname(n)]) - of rnStandaloneHyperlink: - renderAux(d, n, - "<a class=\"reference external\" href=\"$1\">$1</a>", + of rnStandaloneHyperlink: + renderAux(d, n, + "<a class=\"reference external\" href=\"$1\">$1</a>", "\\href{$1}{$1}", result) of rnHyperlink: var tmp0 = "" @@ -1042,11 +1042,11 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = of rnRawLatex: if d.target == outLatex: result.add addNodes(lastSon(n)) - + of rnImage, rnFigure: renderImage(d, n, result) of rnCodeBlock: renderCodeBlock(d, n, result) of rnContainer: renderContainer(d, n, result) - of rnSubstitutionReferences, rnSubstitutionDef: + of rnSubstitutionReferences, rnSubstitutionDef: renderAux(d, n, "|$1|", "|$1|", result) of rnDirective: renderAux(d, n, "", "", result) @@ -1063,15 +1063,15 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = of rnStrongEmphasis: renderAux(d, n, "<strong>$1</strong>", "\\textbf{$1}", result) of rnTripleEmphasis: - renderAux(d, n, "<strong><em>$1</em></strong>", + renderAux(d, n, "<strong><em>$1</em></strong>", "\\textbf{emph{$1}}", result) of rnInterpretedText: renderAux(d, n, "<cite>$1</cite>", "\\emph{$1}", result) of rnIdx: renderIndexTerm(d, n, result) - of rnInlineLiteral: - renderAux(d, n, - "<tt class=\"docutils literal\"><span class=\"pre\">$1</span></tt>", + of rnInlineLiteral: + renderAux(d, n, + "<tt class=\"docutils literal\"><span class=\"pre\">$1</span></tt>", "\\texttt{$1}", result) of rnSmiley: renderSmiley(d, n, result) of rnLeaf: result.add(esc(d.target, n.text)) @@ -1082,55 +1082,55 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = # ----------------------------------------------------------------------------- -proc getVarIdx(varnames: openArray[string], id: string): int = - for i in countup(0, high(varnames)): - if cmpIgnoreStyle(varnames[i], id) == 0: +proc getVarIdx(varnames: openArray[string], id: string): int = + for i in countup(0, high(varnames)): + if cmpIgnoreStyle(varnames[i], id) == 0: return i result = -1 -proc formatNamedVars*(frmt: string, varnames: openArray[string], - varvalues: openArray[string]): string = +proc formatNamedVars*(frmt: string, varnames: openArray[string], + varvalues: openArray[string]): string = var i = 0 var L = len(frmt) result = "" var num = 0 - while i < L: - if frmt[i] == '$': + while i < L: + if frmt[i] == '$': inc(i) # skip '$' case frmt[i] - of '#': + of '#': add(result, varvalues[num]) inc(num) inc(i) - of '$': + of '$': add(result, "$") inc(i) - of '0'..'9': + of '0'..'9': var j = 0 - while true: + while true: j = (j * 10) + ord(frmt[i]) - ord('0') inc(i) - if i > L-1 or frmt[i] notin {'0'..'9'}: break + if i > L-1 or frmt[i] notin {'0'..'9'}: break if j > high(varvalues) + 1: raise newException(ValueError, "invalid index: " & $j) num = j add(result, varvalues[j - 1]) - of 'A'..'Z', 'a'..'z', '\x80'..'\xFF': + of 'A'..'Z', 'a'..'z', '\x80'..'\xFF': var id = "" - while true: + while true: add(id, frmt[i]) inc(i) - if frmt[i] notin {'A'..'Z', '_', 'a'..'z', '\x80'..'\xFF'}: break + if frmt[i] notin {'A'..'Z', '_', 'a'..'z', '\x80'..'\xFF'}: break var idx = getVarIdx(varnames, id) - if idx >= 0: + if idx >= 0: add(result, varvalues[idx]) else: raise newException(ValueError, "unknown substitution var: " & id) - of '{': + of '{': var id = "" inc(i) - while frmt[i] != '}': - if frmt[i] == '\0': + while frmt[i] != '}': + if frmt[i] == '\0': raise newException(ValueError, "'}' expected") add(id, frmt[i]) inc(i) @@ -1138,12 +1138,12 @@ proc formatNamedVars*(frmt: string, varnames: openArray[string], # search for the variable: var idx = getVarIdx(varnames, id) if idx >= 0: add(result, varvalues[idx]) - else: + else: raise newException(ValueError, "unknown substitution var: " & id) else: raise newException(ValueError, "unknown substitution: $" & $frmt[i]) var start = i - while i < L: + while i < L: if frmt[i] != '$': inc(i) else: break if i-1 >= start: add(result, substr(frmt, start, i - 1)) @@ -1163,10 +1163,10 @@ proc defaultConfig*(): StringTableRef = ## pages, while this proc returns just the content for procs like ## ``rstToHtml`` to generate the bare minimum HTML. result = newStringTable(modeStyleInsensitive) - + template setConfigVar(key, val: expr) = result[key] = val - + # If you need to modify these values, it might be worth updating the template # file in config/nimdoc.cfg. setConfigVar("split.item.toc", "20") @@ -1214,7 +1214,7 @@ $content # ---------- forum --------------------------------------------------------- -proc rstToHtml*(s: string, options: TRstParseOptions, +proc rstToHtml*(s: string, options: TRstParseOptions, config: StringTableRef): string = ## Converts an input rst string into embeddable HTML. ## @@ -1236,13 +1236,13 @@ proc rstToHtml*(s: string, options: TRstParseOptions, ## output you have to create your own ``TRstGenerator`` with ## ``initRstGenerator`` and related procs. - proc myFindFile(filename: string): string = + proc myFindFile(filename: string): string = # we don't find any files in online mode: result = "" const filen = "input" var d: TRstGenerator - initRstGenerator(d, outHtml, config, filen, options, myFindFile, + initRstGenerator(d, outHtml, config, filen, options, myFindFile, rst.defaultMsgHandler) var dummyHasToc = false var rst = rstParse(s, filen, 0, 1, dummyHasToc, options) diff --git a/lib/pure/algorithm.nim b/lib/pure/algorithm.nim index 68960e2e8..f7ccb9234 100644 --- a/lib/pure/algorithm.nim +++ b/lib/pure/algorithm.nim @@ -40,8 +40,8 @@ proc reverse*[T](a: var openArray[T]) = proc reversed*[T](a: openArray[T], first, last: Natural): seq[T] = ## returns the reverse of the array `a[first..last]`. result = newSeq[T](last - first + 1) - var x = first - var y = last + var x = first.int + var y = last.int while x <= last: result[x] = a[y] dec(y) diff --git a/lib/pure/osproc.nim b/lib/pure/osproc.nim index eb7ad64bb..dce0673ba 100644 --- a/lib/pure/osproc.nim +++ b/lib/pure/osproc.nim @@ -174,7 +174,7 @@ proc terminate*(p: Process) {.rtl, extern: "nosp$1", tags: [].} proc kill*(p: Process) {.rtl, extern: "nosp$1", tags: [].} ## Kill the process `p`. On Posix OSes the procedure sends ``SIGKILL`` to ## the process. On Windows ``kill()`` is simply an alias for ``terminate()``. - + proc running*(p: Process): bool {.rtl, extern: "nosp$1", tags: [].} ## Returns true iff the process `p` is still running. Returns immediately. @@ -666,7 +666,7 @@ elif not defined(useNimRtl): data.workingDir = workingDir - when declared(posix_spawn) and not defined(useFork) and + when declared(posix_spawn) and not defined(useFork) and not defined(useClone) and not defined(linux): pid = startProcessAuxSpawn(data) else: @@ -823,7 +823,7 @@ elif not defined(useNimRtl): discard execvp(data.sysCommand, data.sysArgs) else: when defined(uClibc): - # uClibc environment (OpenWrt included) doesn't have the full execvpe + # uClibc environment (OpenWrt included) doesn't have the full execvpe discard execve(data.sysCommand, data.sysArgs, data.sysEnv) else: discard execvpe(data.sysCommand, data.sysArgs, data.sysEnv) @@ -864,9 +864,9 @@ elif not defined(useNimRtl): raiseOsError(osLastError()) proc kill(p: Process) = - if kill(p.id, SIGKILL) != 0'i32: + if kill(p.id, SIGKILL) != 0'i32: raiseOsError(osLastError()) - + proc waitForExit(p: Process, timeout: int = -1): int = #if waitPid(p.id, p.exitCode, 0) == int(p.id): # ``waitPid`` fails if the process is not running anymore. But then @@ -883,7 +883,7 @@ elif not defined(useNimRtl): var ret = waitpid(p.id, p.exitCode, WNOHANG) var b = ret == int(p.id) if b: result = -1 - if p.exitCode == -3: result = -1 + if not WIFEXITED(p.exitCode): result = -1 else: result = p.exitCode.int shr 8 proc createStream(stream: var Stream, handle: var FileHandle, @@ -907,7 +907,7 @@ elif not defined(useNimRtl): createStream(p.errStream, p.errHandle, fmRead) return p.errStream - proc csystem(cmd: cstring): cint {.nodecl, importc: "system", + proc csystem(cmd: cstring): cint {.nodecl, importc: "system", header: "<stdlib.h>".} proc execCmd(command: string): int = diff --git a/lib/system.nim b/lib/system.nim index 83f071717..ac6c3a38f 100644 --- a/lib/system.nim +++ b/lib/system.nim @@ -1744,6 +1744,12 @@ iterator items*(E: typedesc[enum]): E = for v in low(E)..high(E): yield v +iterator items*[T](s: Slice[T]): T = + ## iterates over the slice `s`, yielding each value between `s.a` and `s.b` + ## (inclusively). + for x in s.a..s.b: + yield x + iterator pairs*[T](a: openArray[T]): tuple[key: int, val: T] {.inline.} = ## iterates over each item of `a`. Yields ``(index, a[index])`` pairs. var i = 0 diff --git a/lib/system/atomics.nim b/lib/system/atomics.nim index 300fa85f3..c97d2fc7f 100644 --- a/lib/system/atomics.nim +++ b/lib/system/atomics.nim @@ -87,7 +87,7 @@ when someGcc and hasThreadSupport: proc atomicCompareExchange*[T: TAtomType](p, expected, desired: ptr T, weak: bool, success_memmodel: AtomMemModel, failure_memmodel: AtomMemModel): bool {. - importc: "__atomic_compare_exchange_n ", nodecl.} + importc: "__atomic_compare_exchange", nodecl.} ## This proc implements the generic version of atomic_compare_exchange. ## The proc is virtually identical to atomic_compare_exchange_n, except the desired ## value is also a pointer. diff --git a/tests/ccgbugs/tarray_equality.nim b/tests/ccgbugs/tarray_equality.nim index 1d4465477..66a953439 100644 --- a/tests/ccgbugs/tarray_equality.nim +++ b/tests/ccgbugs/tarray_equality.nim @@ -1,5 +1,6 @@ discard """ - output: '''true''' + output: '''true +true''' """ # bug #2489 @@ -7,3 +8,8 @@ discard """ let a = [1] let b = [1] echo a == b + +# bug #2498 +var x: array[0, int] +var y: array[0, int] +echo x == y diff --git a/tests/cpp/tget_subsystem.nim b/tests/cpp/tget_subsystem.nim new file mode 100644 index 000000000..461914739 --- /dev/null +++ b/tests/cpp/tget_subsystem.nim @@ -0,0 +1,23 @@ +discard """ + cmd: "nim cpp $file" +""" + +{.emit: """ + +namespace System { + struct Input {}; +} + +struct SystemManager { + template <class T> + static T* getSubsystem() { return new T; } +}; + +""".} + +type Input {.importcpp: "System::Input".} = object +proc getSubsystem*[T](): ptr T {. + importcpp: "SystemManager::getSubsystem<'*0>()", nodecl.} + +let input: ptr Input = getSubsystem[Input]() + diff --git a/tests/cpp/tvector_iterator.nim b/tests/cpp/tvector_iterator.nim new file mode 100644 index 000000000..cb5ab33af --- /dev/null +++ b/tests/cpp/tvector_iterator.nim @@ -0,0 +1,19 @@ +discard """ + cmd: "nim cpp $file" +""" + +{.emit: """ + +template <class T> +struct Vector { + struct Iterator {}; +}; + +""".} + +type + Vector {.importcpp: "Vector".} [T] = object + VectorIterator {.importcpp: "Vector<'0>::Iterator".} [T] = object + +var x: VectorIterator[void] + diff --git a/tests/effects/tgcsafe.nim b/tests/effects/tgcsafe.nim index 0d5109439..d146794b6 100644 --- a/tests/effects/tgcsafe.nim +++ b/tests/effects/tgcsafe.nim @@ -1,5 +1,5 @@ discard """ - line: 16 + line: 17 errormsg: "'mainUnsafe' is not GC-safe" cmd: "nim $target --hints:on --threads:on $options $file" """ diff --git a/tests/exception/texceptions.nim b/tests/exception/texceptions.nim index 69b2d0f6a..bdf338599 100644 --- a/tests/exception/texceptions.nim +++ b/tests/exception/texceptions.nim @@ -35,9 +35,9 @@ echo "" proc reraise_in_except = try: echo "BEFORE" - raise newException(EIO, "") + raise newException(IOError, "") - except EIO: + except IOError: echo "EXCEPT" raise @@ -52,7 +52,7 @@ echo "" proc return_in_except = try: echo "BEFORE" - raise newException(EIO, "") + raise newException(IOError, "") except: echo "EXCEPT" diff --git a/tests/exception/treraise.nim b/tests/exception/treraise.nim index cbd0b5f8a..b2a11d34f 100644 --- a/tests/exception/treraise.nim +++ b/tests/exception/treraise.nim @@ -4,8 +4,8 @@ discard """ exitcode: "1" """ type - ESomething = object of E_Base - ESomeOtherErr = object of E_Base + ESomething = object of Exception + ESomeOtherErr = object of Exception proc genErrors(s: string) = if s == "error!": diff --git a/tests/generics/twrong_generic_object.nim b/tests/generics/twrong_generic_object.nim new file mode 100644 index 000000000..00d90c55e --- /dev/null +++ b/tests/generics/twrong_generic_object.nim @@ -0,0 +1,21 @@ +discard """ + errormsg: "cannot instantiate: 'GenericNodeObj'" + line: 21 +""" +# bug #2509 +type + GenericNodeObj[T] = ref object + obj: T + + Node* = ref object + children*: seq[Node] + parent*: Node + + nodeObj*: GenericNodeObj # [int] + +proc newNode*(nodeObj: GenericNodeObj): Node = + result = Node(nodeObj: nodeObj) + newSeq(result.children, 10) + +var genericObj = GenericNodeObj[int]() +var myNode = newNode(genericObj) diff --git a/tests/js/tunittests.nim b/tests/js/tunittests.nim index af38cd9b9..8a264a5e0 100644 --- a/tests/js/tunittests.nim +++ b/tests/js/tunittests.nim @@ -1,3 +1,10 @@ +discard """ + disabled: "true" +""" + +# Unittest uses lambdalifting at compile-time which we disable for the JS +# codegen! So this cannot and will not work for quite some time. + import unittest suite "Bacon": diff --git a/tests/macros/tlexerex.nim b/tests/macros/tlexerex.nim new file mode 100644 index 000000000..d348a4bcc --- /dev/null +++ b/tests/macros/tlexerex.nim @@ -0,0 +1,16 @@ + +import macros + +macro match*(s: cstring|string; pos: int; sections: untyped): untyped = + for sec in sections.children: + expectKind sec, nnkOfBranch + expectLen sec, 2 + result = newStmtList() + +when isMainModule: + var input = "the input" + var pos = 0 + match input, pos: + of r"[a-zA-Z_]\w+": echo "an identifier" + of r"\d+": echo "an integer" + of r".": echo "something else" diff --git a/tests/macros/typesapi2.nim b/tests/macros/typesapi2.nim index 016295ba4..2e59d2154 100644 --- a/tests/macros/typesapi2.nim +++ b/tests/macros/typesapi2.nim @@ -1,4 +1,4 @@ -# tests to see if a symbol returned from macros.getType() can +# tests to see if a symbol returned from macros.getType() can # be used as a type import macros @@ -20,7 +20,7 @@ static: assert iii is TestFN proc foo11 : testTypesym(void) = echo "HI!" -static: assert foo11 is proc():void +static: assert foo11 is (proc():void {.nimcall.}) var sss: testTypesym(seq[int]) static: assert sss is seq[int] diff --git a/tests/metatype/tautoproc.nim b/tests/metatype/tautoproc.nim index 562f508fc..ef5377096 100644 --- a/tests/metatype/tautoproc.nim +++ b/tests/metatype/tautoproc.nim @@ -1,11 +1,13 @@ discard """ - errormsg: "expression 'generate(builder)' has no type (or is ambiguous)" + output: "empty" """ # bug #898 +import typetraits + proc measureTime(e: auto) = - discard + echo e.type.name proc generate(a: int): void = discard diff --git a/tests/objects/tillegal_recursion.nim b/tests/objects/tillegal_recursion.nim new file mode 100644 index 000000000..171a04f87 --- /dev/null +++ b/tests/objects/tillegal_recursion.nim @@ -0,0 +1,7 @@ +discard """ + errormsg: "illegal recursion in type 'object'" + line: 7 +""" +# bug #1691 +type + Foo = ref object of Foo diff --git a/tests/objects/tobjloop.nim b/tests/objects/tobjloop.nim new file mode 100644 index 000000000..9fea1e2fb --- /dev/null +++ b/tests/objects/tobjloop.nim @@ -0,0 +1,15 @@ +discard """ + output: "is Nil false" +""" +# bug #1658 + +type + Loop* = ref object + onBeforeSelect*: proc (L: Loop) + +var L: Loop +new L +L.onBeforeSelect = proc (bar: Loop) = + echo "is Nil ", bar.isNil + +L.onBeforeSelect(L) diff --git a/tests/objects/trefobjsyntax2.nim b/tests/objects/trefobjsyntax2.nim new file mode 100644 index 000000000..8ee209cc7 --- /dev/null +++ b/tests/objects/trefobjsyntax2.nim @@ -0,0 +1,19 @@ +# bug #2508 + +type + GenericNodeObj[T] = ref object + obj: T + + Node* = ref object + children*: seq[Node] + parent*: Node + + nodeObj*: GenericNodeObj[int] + +proc newNode*(nodeObj: GenericNodeObj): Node = + result = Node(nodeObj: nodeObj) + newSeq(result.children, 10) + +var genericObj = GenericNodeObj[int]() + +var myNode = newNode(genericObj) diff --git a/tests/parallel/twrong_refcounts.nim b/tests/parallel/twrong_refcounts.nim new file mode 100644 index 000000000..db32a96d8 --- /dev/null +++ b/tests/parallel/twrong_refcounts.nim @@ -0,0 +1,53 @@ +discard """ + output: "Success" +""" + +import math, threadPool + +# --- + +type + Person = object + age: int + friend: ref Person + +var + people: seq[ref Person] = @[] + +proc newPerson(age:int): ref Person = + result.new() + result.age = age + +proc greet(p:Person) = + #echo p.age, ", ", p.friend.age + p.friend.age += 1 + +# --- + +proc setup = + for i in 0 .. <20: + people.add newPerson(i + 1) + for i in 0 .. <20: + people[i].friend = people[random(20)] + +proc update = + var countA: array[20, int] + var countB: array[20, int] + + for i, p in people: + countA[i] = getRefCount(p) + parallel: + for i in 0 .. people.high: + spawn greet(people[i][]) + for i, p in people: + countB[i] = getRefCount(p) + + for i in 0 .. <20: + doAssert countA[i] == countB[i] + echo "Success" + +# --- + +when isMainModule: + setup() + update() diff --git a/tests/parser/tstrongspaces.nim b/tests/parser/tstrongspaces.nim index 568abda4c..e70b91988 100644 --- a/tests/parser/tstrongspaces.nim +++ b/tests/parser/tstrongspaces.nim @@ -15,6 +15,10 @@ true tester args all all args +19 +-3 +false +-2 ''' """ @@ -67,3 +71,13 @@ const echo tester & " " & args|"all" echo "all" | tester & " " & args echo "all"|tester & " " & args + +# Test arrow like operators. See also tests/macros/tclosuremacro.nim +proc `+->`(a, b: int): int = a + b*4 +template `===>`(a, b: int): expr = a - b shr 1 + +echo 3 +-> 2 + 2 and 4 +var arrowed = 3+->2 + 2 and 4 # arrowed = 4 +echo arrowed ===> 15 +echo (2 * 3+->2) == (2*3 +-> 2) +echo arrowed ===> 2 + 3+->2 diff --git a/tests/testament/specs.nim b/tests/testament/specs.nim index 2a8a4ea24..8bf1a4ad7 100644 --- a/tests/testament/specs.nim +++ b/tests/testament/specs.nim @@ -42,7 +42,8 @@ type action*: TTestAction file*, cmd*: string outp*: string - line*, exitCode*: int + line*, column*: int + exitCode*: int msg*: string ccodeCheck*: string err*: TResultEnum @@ -98,6 +99,8 @@ proc parseSpec*(filename: string): TSpec = result.nimout = "" result.ccodeCheck = "" result.cmd = cmdTemplate + result.line = 0 + result.column = 0 parseSpecAux: case normalize(e.key) of "action": @@ -108,6 +111,7 @@ proc parseSpec*(filename: string): TSpec = else: echo ignoreMsg(p, e) of "file": result.file = e.value of "line": discard parseInt(e.value, result.line) + of "column": discard parseInt(e.value, result.column) of "output": result.action = actionRun result.outp = e.value diff --git a/tests/testament/tester.nim b/tests/testament/tester.nim index 7391b105e..ed39109ad 100644 --- a/tests/testament/tester.nim +++ b/tests/testament/tester.nim @@ -50,7 +50,7 @@ type let pegLineError = - peg"{[^(]*} '(' {\d+} ', ' \d+ ') ' ('Error') ':' \s* {.*}" + peg"{[^(]*} '(' {\d+} ', ' {\d+} ') ' ('Error') ':' \s* {.*}" pegOtherError = peg"'Error:' \s* {.*}" pegSuccess = peg"'Hint: operation successful'.*" pegOfInterest = pegLineError / pegOtherError @@ -77,11 +77,13 @@ proc callCompiler(cmdTemplate, filename, options: string, result.msg = "" result.file = "" result.outp = "" - result.line = -1 + result.line = 0 + result.column = 0 if err =~ pegLineError: result.file = extractFilename(matches[0]) result.line = parseInt(matches[1]) - result.msg = matches[2] + result.column = parseInt(matches[2]) + result.msg = matches[3] elif err =~ pegOtherError: result.msg = matches[0] elif suc =~ pegSuccess: @@ -130,8 +132,11 @@ proc cmpMsgs(r: var TResults, expected, given: TSpec, test: TTest) = 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) + elif expected.line != given.line and expected.line != 0 or + expected.column != given.column and expected.column != 0: + r.addResult(test, $expected.line & ':' & $expected.column, + $given.line & ':' & $given.column, + reLinesDiffer) else: r.addResult(test, expected.msg, given.msg, reSuccess) inc(r.passed) diff --git a/tests/types/tisopr.nim b/tests/types/tisopr.nim index 8b7fe4e46..b9acfa5fb 100644 --- a/tests/types/tisopr.nim +++ b/tests/types/tisopr.nim @@ -1,5 +1,11 @@ discard """ - output: '''true true false yes''' + output: '''true true false yes +false +false +false +true +true +no''' """ proc IsVoid[T](): string = @@ -28,7 +34,7 @@ no s.items is iterator: float yes s.items is iterator: TNumber no s.items is iterator: object -type +type Iter[T] = iterator: T yes s.items is Iter[TNumber] @@ -51,3 +57,34 @@ yes Foo[4, int] is Bar[int] no Foo[4, int] is Baz[4] yes Foo[4, float] is Baz[4] + +# bug #2505 + +echo(8'i8 is int32) + +# bug #1853 +type SeqOrSet[E] = seq[E] or set[E] +type SeqOfInt = seq[int] +type SeqOrSetOfInt = SeqOrSet[int] + +# This prints "false", which seems less correct that (1) printing "true" or (2) +# raising a compiler error. +echo seq is SeqOrSet + +# This prints "false", as expected. +echo seq is SeqOrSetOfInt + +# This prints "true", as expected. +echo SeqOfInt is SeqOrSet + +# This causes an internal error (filename: compiler/semtypes.nim, line: 685). +echo SeqOfInt is SeqOrSetOfInt + +# bug #2522 +proc test[T](x: T) = + when T is typedesc: + echo "yes" + else: + echo "no" + +test(7) diff --git a/web/news.txt b/web/news.txt index af44f91a1..6b109aa1c 100644 --- a/web/news.txt +++ b/web/news.txt @@ -34,6 +34,10 @@ News should be used instead. - ``nim idetools`` has been replaced by a separate tool `nimsuggest`_. - *arrow like* operators are not right associative anymore. + - *arrow like* operators are now required to end with either ``->``, ``~>`` or + ``=>``, not just ``>``. Examples of operators still considered arrow like: + ``->``, ``==>``, ``+=>``. On the other hand, the following operators are now + considered regular operators again: ``|>``, ``-+>``, etc. - Typeless parameters are now only allowed in templates and macros. The old way turned out to be too error-prone. - The 'addr' and 'type' operators are now parsed as unary function |