diff options
author | Araq <rumpf_a@web.de> | 2016-08-27 20:52:26 +0200 |
---|---|---|
committer | Araq <rumpf_a@web.de> | 2016-08-27 20:52:26 +0200 |
commit | 884d5518dd824ff451caf5689624c824a73520d5 (patch) | |
tree | 1069304c1c36814b413ebd54bf4680c977e1d2df | |
parent | 68e30d7d52d84578fbe0f6f1c2041b150251e800 (diff) | |
parent | 7e643d73788fd0799cc970601bc75592e9610039 (diff) | |
download | Nim-884d5518dd824ff451caf5689624c824a73520d5.tar.gz |
Merged
91 files changed, 991 insertions, 733 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index 75491af6b..347060248 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -726,9 +726,6 @@ type flags*: TLocFlags # location's flags t*: PType # type of location r*: Rope # rope value of location (code generators) - heapRoot*: Rope # keeps track of the enclosing heap object that - # owns this location (required by GC algorithms - # employing heap snapshots or sliding views) # ---------------- end of backend information ------------------------------ @@ -857,9 +854,6 @@ type key*, val*: RootRef TPairSeq* = seq[TPair] - TTable* = object # the same as table[PObject] of PObject - counter*: int - data*: TPairSeq TIdPair* = object key*: PIdObj @@ -1103,12 +1097,6 @@ proc copyIdTable*(dest: var TIdTable, src: TIdTable) = newSeq(dest.data, len(src.data)) for i in countup(0, high(src.data)): dest.data[i] = src.data[i] -proc copyTable*(dest: var TTable, src: TTable) = - dest.counter = src.counter - if isNil(src.data): return - setLen(dest.data, len(src.data)) - for i in countup(0, high(src.data)): dest.data[i] = src.data[i] - proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) = dest.counter = src.counter if isNil(src.data): return @@ -1322,10 +1310,6 @@ proc initStrTable*(x: var TStrTable) = proc newStrTable*: TStrTable = initStrTable(result) -proc initTable(x: var TTable) = - x.counter = 0 - newSeq(x.data, StartSize) - proc initIdTable*(x: var TIdTable) = x.counter = 0 newSeq(x.data, StartSize) @@ -1506,19 +1490,9 @@ proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool = return true result = false -proc replaceSons(n: PNode, oldKind, newKind: TNodeKind) = - for i in countup(0, sonsLen(n) - 1): - if n.sons[i].kind == oldKind: n.sons[i].kind = newKind - -proc sonsNotNil(n: PNode): bool = - for i in countup(0, sonsLen(n) - 1): - if n.sons[i] == nil: - return false - result = true - proc getInt*(a: PNode): BiggestInt = case a.kind - of nkIntLit..nkUInt64Lit: result = a.intVal + of nkCharLit..nkUInt64Lit: result = a.intVal else: internalError(a.info, "getInt") result = 0 diff --git a/compiler/astalgo.nim b/compiler/astalgo.nim index 3ca44ea7e..7c07b2995 100644 --- a/compiler/astalgo.nim +++ b/compiler/astalgo.nim @@ -31,17 +31,6 @@ proc objectSetIncl*(t: var TObjectSet, obj: RootRef) proc objectSetContainsOrIncl*(t: var TObjectSet, obj: RootRef): bool # more are not needed ... -# ----------------------- (key, val)-Hashtables ---------------------------- -proc tablePut*(t: var TTable, key, val: RootRef) -proc tableGet*(t: TTable, key: RootRef): RootRef -type - TCmpProc* = proc (key, closure: RootRef): bool {.nimcall.} # true if found - -proc tableSearch*(t: TTable, key, closure: RootRef, - comparator: TCmpProc): RootRef - # return val as soon as comparator returns true; if this never happens, - # nil is returned - # ----------------------- str table ----------------------------------------- proc strTableContains*(t: TStrTable, n: PSym): bool proc strTableAdd*(t: var TStrTable, n: PSym) @@ -251,20 +240,6 @@ proc symToYamlAux(n: PSym, marker: var IntSet, indent, maxRecDepth: int): Rope proc typeToYamlAux(n: PType, marker: var IntSet, indent, maxRecDepth: int): Rope -proc strTableToYaml(n: TStrTable, marker: var IntSet, indent: int, - maxRecDepth: int): Rope = - var istr = rspaces(indent + 2) - result = rope("[") - var mycount = 0 - for i in countup(0, high(n.data)): - if n.data[i] != nil: - if mycount > 0: add(result, ",") - addf(result, "$N$1$2", - [istr, symToYamlAux(n.data[i], marker, indent + 2, maxRecDepth - 1)]) - inc(mycount) - if mycount > 0: addf(result, "$N$1", [rspaces(indent)]) - add(result, "]") - assert(mycount == n.counter) proc ropeConstr(indent: int, c: openArray[Rope]): Rope = # array of (name, value) pairs @@ -463,9 +438,6 @@ proc debug(n: PType) = proc debug(n: PNode) = echo($debugTree(n, 0, 100)) -const - EmptySeq = @[] - proc nextTry(h, maxHash: Hash): Hash = result = ((5 * h) + 1) and maxHash # For any initial h in range(maxHash), repeating that maxHash times @@ -519,55 +491,6 @@ proc objectSetContainsOrIncl(t: var TObjectSet, obj: RootRef): bool = inc(t.counter) result = false -proc tableRawGet(t: TTable, key: RootRef): int = - var h: Hash = hashNode(key) and high(t.data) # start with real hash value - while t.data[h].key != nil: - if t.data[h].key == key: - return h - h = nextTry(h, high(t.data)) - result = -1 - -proc tableSearch(t: TTable, key, closure: RootRef, - comparator: TCmpProc): RootRef = - var h: Hash = hashNode(key) and high(t.data) # start with real hash value - while t.data[h].key != nil: - if t.data[h].key == key: - if comparator(t.data[h].val, closure): - # BUGFIX 1 - return t.data[h].val - h = nextTry(h, high(t.data)) - result = nil - -proc tableGet(t: TTable, key: RootRef): RootRef = - var index = tableRawGet(t, key) - if index >= 0: result = t.data[index].val - else: result = nil - -proc tableRawInsert(data: var TPairSeq, key, val: RootRef) = - var h: Hash = hashNode(key) and high(data) - while data[h].key != nil: - assert(data[h].key != key) - h = nextTry(h, high(data)) - assert(data[h].key == nil) - data[h].key = key - data[h].val = val - -proc tableEnlarge(t: var TTable) = - var n: TPairSeq - newSeq(n, len(t.data) * GrowthFactor) - for i in countup(0, high(t.data)): - if t.data[i].key != nil: tableRawInsert(n, t.data[i].key, t.data[i].val) - swap(t.data, n) - -proc tablePut(t: var TTable, key, val: RootRef) = - var index = tableRawGet(t, key) - if index >= 0: - t.data[index].val = val - else: - if mustRehash(len(t.data), t.counter): tableEnlarge(t) - tableRawInsert(t.data, key, val) - inc(t.counter) - proc strTableContains(t: TStrTable, n: PSym): bool = var h: Hash = n.name.h and high(t.data) # start with real hash value while t.data[h] != nil: diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim index dffb8a9a5..48157925c 100644 --- a/compiler/ccgcalls.nim +++ b/compiler/ccgcalls.nim @@ -411,7 +411,7 @@ proc genPatternCall(p: BProc; ri: PNode; pat: string; typ: PType): Rope = add(result, substr(pat, start, i - 1)) proc genInfixCall(p: BProc, le, ri: PNode, d: var TLoc) = - var op, a: TLoc + var op: TLoc initLocExpr(p, ri.sons[0], op) # getUniqueType() is too expensive here: var typ = skipTypes(ri.sons[0].typ, abstractInst) @@ -458,7 +458,7 @@ proc genInfixCall(p: BProc, le, ri: PNode, d: var TLoc) = proc genNamedParamCall(p: BProc, ri: PNode, d: var TLoc) = # generates a crappy ObjC call - var op, a: TLoc + var op: TLoc initLocExpr(p, ri.sons[0], op) var pl = ~"[" # getUniqueType() is too expensive here: @@ -536,8 +536,6 @@ proc genCall(p: BProc, e: PNode, d: var TLoc) = else: genPrefixCall(p, nil, e, d) postStmtActions(p) - when false: - if d.s == onStack and containsGarbageCollectedRef(d.t): keepAlive(p, d) proc genAsgnCall(p: BProc, le, ri: PNode, d: var TLoc) = if ri.sons[0].typ.skipTypes({tyGenericInst}).callConv == ccClosure: @@ -549,6 +547,3 @@ proc genAsgnCall(p: BProc, le, ri: PNode, d: var TLoc) = else: genPrefixCall(p, le, ri, d) postStmtActions(p) - when false: - if d.s == onStack and containsGarbageCollectedRef(d.t): keepAlive(p, d) - diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index f9fa1a0f6..719bc195c 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -30,19 +30,6 @@ proc intLiteral(i: BiggestInt): Rope = else: result = ~"(IL64(-9223372036854775807) - IL64(1))" -proc int32Literal(i: int): Rope = - if i == int(low(int32)): - result = ~"(-2147483647 -1)" - else: - result = rope(i) - -proc genHexLiteral(v: PNode): Rope = - # hex literals are unsigned in C - # so we don't generate hex literals any longer. - if v.kind notin {nkIntLit..nkUInt64Lit}: - internalError(v.info, "genHexLiteral") - result = intLiteral(v.intVal) - proc getStrLit(m: BModule, s: string): Rope = discard cgsym(m, "TGenericSeq") result = getTempName(m) @@ -171,7 +158,6 @@ proc getStorageLoc(n: PNode): TStorageLoc = proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = if dest.s == OnStack or not usesNativeGC(): linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src)) - if needToKeepAlive in flags: keepAlive(p, dest) elif dest.s == OnHeap: # location is on heap # now the writer barrier is inlined for performance: @@ -198,7 +184,6 @@ proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = else: linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, $2);$n", addrLoc(dest), rdLoc(src)) - if needToKeepAlive in flags: keepAlive(p, dest) proc asgnComplexity(n: PNode): int = if n != nil: @@ -218,7 +203,6 @@ proc optAsgnLoc(a: TLoc, t: PType, field: Rope): TLoc = result.s = a.s result.t = t result.r = rdLoc(a) & "." & field - result.heapRoot = a.heapRoot proc genOptAsgnTuple(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = let newflags = @@ -268,7 +252,6 @@ proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = linefmt(p, cpsStmts, "memcpy((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n", addrLoc(dest), addrLoc(src), rdLoc(dest)) - if needToKeepAlive in flags: keepAlive(p, dest) else: linefmt(p, cpsStmts, "#genericShallowAssign((void*)$1, (void*)$2, $3);$n", addrLoc(dest), addrLoc(src), genTypeInfo(p.module, dest.t)) @@ -299,7 +282,6 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = else: if dest.s == OnStack or not usesNativeGC(): linefmt(p, cpsStmts, "$1 = #copyString($2);$n", dest.rdLoc, src.rdLoc) - if needToKeepAlive in flags: keepAlive(p, dest) elif dest.s == OnHeap: # we use a temporary to care for the dreaded self assignment: var tmp: TLoc @@ -310,7 +292,6 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) = else: linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, #copyString($2));$n", addrLoc(dest), rdLoc(src)) - if needToKeepAlive in flags: keepAlive(p, dest) of tyProc: if needsComplexAssignment(dest.t): # optimize closure assignment: @@ -400,9 +381,6 @@ proc genDeepCopy(p: BProc; dest, src: TLoc) = linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src)) else: internalError("genDeepCopy: " & $ty.kind) -proc getDestLoc(p: BProc, d: var TLoc, typ: PType) = - if d.k == locNone: getTemp(p, typ, d) - proc putLocIntoDest(p: BProc, d: var TLoc, s: TLoc) = if d.k != locNone: if lfNoDeepCopy in d.flags: genAssignment(p, d, s, {}) @@ -453,13 +431,6 @@ proc unaryStmt(p: BProc, e: PNode, d: var TLoc, frmt: string) = initLocExpr(p, e.sons[1], a) lineCg(p, cpsStmts, frmt, [rdLoc(a)]) -proc binaryStmtChar(p: BProc, e: PNode, d: var TLoc, frmt: string) = - var a, b: TLoc - if (d.k != locNone): internalError(e.info, "binaryStmtChar") - initLocExpr(p, e.sons[1], a) - initLocExpr(p, e.sons[2], b) - lineCg(p, cpsStmts, frmt, [rdCharLoc(a), rdCharLoc(b)]) - proc binaryExpr(p: BProc, e: PNode, d: var TLoc, frmt: string) = var a, b: TLoc assert(e.sons[1].typ != nil) @@ -670,6 +641,8 @@ proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = #if e[0].kind != nkBracketExpr: # message(e.info, warnUser, "CAME HERE " & renderTree(e)) expr(p, e.sons[0], d) + if e.sons[0].typ.skipTypes(abstractInst).kind == tyRef: + d.s = OnHeap else: var a: TLoc let typ = skipTypes(e.sons[0].typ, abstractInst) @@ -726,8 +699,6 @@ proc genAddr(p: BProc, e: PNode, d: var TLoc) = template inheritLocation(d: var TLoc, a: TLoc) = if d.k == locNone: d.s = a.s - if d.heapRoot == nil: - d.heapRoot = if a.heapRoot != nil: a.heapRoot else: a.r proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc): PType = initLocExpr(p, e.sons[0], a) @@ -891,7 +862,6 @@ proc genSeqElem(p: BProc, x, y: PNode, d: var TLoc) = "if ((NU)($1) >= (NU)($2->$3)) #raiseIndexError();$n", rdLoc(b), rdLoc(a), lenField(p)) if d.k == locNone: d.s = OnHeap - d.heapRoot = a.r if skipTypes(a.t, abstractVar).kind in {tyRef, tyPtr}: a.r = rfmt(nil, "(*$1)", a.r) putIntoDest(p, d, elemType(skipTypes(a.t, abstractVar)), @@ -1006,9 +976,8 @@ proc genStrConcat(p: BProc, e: PNode, d: var TLoc) = add(p.s(cpsStmts), appends) if d.k == locNone: d = tmp - keepAlive(p, tmp) else: - genAssignment(p, d, tmp, {needToKeepAlive}) # no need for deep copying + genAssignment(p, d, tmp, {}) # no need for deep copying gcUsage(e) proc genStrAppend(p: BProc, e: PNode, d: var TLoc) = @@ -1045,7 +1014,6 @@ proc genStrAppend(p: BProc, e: PNode, d: var TLoc) = rdLoc(dest), rdLoc(a))) linefmt(p, cpsStmts, "$1 = #resizeString($1, $2$3);$n", rdLoc(dest), lens, rope(L)) - keepAlive(p, dest) add(p.s(cpsStmts), appends) gcUsage(e) @@ -1065,7 +1033,6 @@ proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) = rdLoc(a), getTypeDesc(p.module, skipTypes(e.sons[1].typ, abstractVar)), getTypeDesc(p.module, bt)]) - keepAlive(p, a) #if bt != b.t: # echo "YES ", e.info, " new: ", typeToString(bt), " old: ", typeToString(b.t) initLoc(dest, locExpr, bt, OnHeap) @@ -1092,7 +1059,7 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) = genTypeInfo(p.module, refType), sizeExpr] if a.s == OnHeap and usesNativeGC(): - # use newObjRC1 as an optimization; and we don't need 'keepAlive' either + # use newObjRC1 as an optimization if canFormAcycle(a.t): linefmt(p, cpsStmts, "if ($1) #nimGCunref($1);$n", a.rdLoc) else: @@ -1101,7 +1068,7 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) = linefmt(p, cpsStmts, "$1 = $2;$n", a.rdLoc, b.rdLoc) else: b.r = ropecg(p.module, "($1) #newObj($2, $3)", args) - genAssignment(p, a, b, {needToKeepAlive}) # set the object type: + genAssignment(p, a, b, {}) # set the object type: let bt = skipTypes(refType.sons[0], abstractRange) genObjectInit(p, cpsStmts, bt, a, false) @@ -1132,7 +1099,7 @@ proc genNewSeqAux(p: BProc, dest: TLoc, length: Rope) = linefmt(p, cpsStmts, "$1 = $2;$n", dest.rdLoc, call.rdLoc) else: call.r = ropecg(p.module, "($1) #newSeq($2, $3)", args) - genAssignment(p, dest, call, {needToKeepAlive}) + genAssignment(p, dest, call, {}) proc genNewSeq(p: BProc, e: PNode) = var a, b: TLoc @@ -1197,7 +1164,6 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) = tmp2.k = locTemp tmp2.t = field.loc.t tmp2.s = if isRef: OnHeap else: OnStack - tmp2.heapRoot = tmp.r expr(p, it.sons[1], tmp2) if d.k == locNone: @@ -1244,7 +1210,6 @@ proc genNewFinalize(p: BProc, e: PNode) = a, b, f: TLoc refType, bt: PType ti: Rope - oldModule: BModule refType = skipTypes(e.sons[1].typ, abstractVarRange) initLocExpr(p, e.sons[1], a) initLocExpr(p, e.sons[2], f) @@ -1254,7 +1219,7 @@ proc genNewFinalize(p: BProc, e: PNode) = b.r = ropecg(p.module, "($1) #newObj($2, sizeof($3))", [ getTypeDesc(p.module, refType), ti, getTypeDesc(p.module, skipTypes(refType.lastSon, abstractRange))]) - genAssignment(p, a, b, {needToKeepAlive}) # set the object type: + genAssignment(p, a, b, {}) # set the object type: bt = skipTypes(refType.lastSon, abstractRange) genObjectInit(p, cpsStmts, bt, a, false) gcUsage(e) @@ -1364,7 +1329,7 @@ proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) = initLocExpr(p, n.sons[1], a) a.r = ropecg(p.module, frmt, [rdLoc(a)]) if d.k == locNone: getTemp(p, n.typ, d) - genAssignment(p, d, a, {needToKeepAlive}) + genAssignment(p, d, a, {}) gcUsage(n) proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) = @@ -1406,12 +1371,10 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) = lineCg(p, cpsStmts, setLenPattern, [ rdLoc(a), rdLoc(b), getTypeDesc(p.module, t), getTypeDesc(p.module, t.sons[0])]) - keepAlive(p, a) gcUsage(e) proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) = binaryStmt(p, e, d, "$1 = #setLengthStr($1, $2);$n") - keepAlive(p, d) gcUsage(e) proc genSwap(p: BProc, e: PNode, d: var TLoc) = @@ -1681,7 +1644,6 @@ proc binaryFloatArith(p: BProc, e: PNode, d: var TLoc, m: TMagic) = binaryArith(p, e, d, m) proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) = - var line, filen: Rope case op of mOr, mAnd: genAndOr(p, e, d, op) of mNot..mToBiggestInt: unaryArith(p, e, d, op) @@ -1719,10 +1681,7 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) = getTypeDesc(p.module, ranged), res]) of mConStrStr: genStrConcat(p, e, d) - of mAppendStrCh: - binaryStmt(p, e, d, "$1 = #addChar($1, $2);$n") - # strictly speaking we need to generate "keepAlive" here too, but this - # very likely not needed and would slow down the code too much I fear + of mAppendStrCh: binaryStmt(p, e, d, "$1 = #addChar($1, $2);$n") of mAppendStrStr: genStrAppend(p, e, d) of mAppendSeqElem: genSeqElemAppend(p, e, d) of mEqStr: genStrEquals(p, e, d) diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim index a5ce147c3..1b21e641a 100644 --- a/compiler/ccgstmts.nim +++ b/compiler/ccgstmts.nim @@ -21,7 +21,7 @@ proc registerGcRoot(p: BProc, v: PSym) = # we register a specialized marked proc here; this has the advantage # that it works out of the box for thread local storage then :-) let prc = genTraverseProcForGlobal(p.module, v) - appcg(p.module, p.module.initProc.procSec(cpsStmts), + appcg(p.module, p.module.initProc.procSec(cpsInit), "#nimRegisterGlobalMarker($1);$n", [prc]) proc isAssignedImmediately(n: PNode): bool {.inline.} = @@ -459,7 +459,6 @@ proc genWhileStmt(p: BProc, t: PNode) = # significantly worse code var a: TLoc - labl: TLabel assert(sonsLen(t) == 2) inc(p.withinLoop) genLineDir(p, t) @@ -757,16 +756,6 @@ proc genCase(p: BProc, t: PNode, d: var TLoc) = else: genOrdinalCase(p, t, d) -proc hasGeneralExceptSection(t: PNode): bool = - var length = sonsLen(t) - var i = 1 - while (i < length) and (t.sons[i].kind == nkExceptBranch): - var blen = sonsLen(t.sons[i]) - if blen == 1: - return true - inc(i) - result = false - proc genTryCpp(p: BProc, t: PNode, d: var TLoc) = # code to generate: # @@ -1089,7 +1078,6 @@ proc genDiscriminantCheck(p: BProc, a, tmp: TLoc, objtype: PType, proc asgnFieldDiscriminant(p: BProc, e: PNode) = var a, tmp: TLoc var dotExpr = e.sons[0] - var d: PSym if dotExpr.kind == nkCheckedFieldExpr: dotExpr = dotExpr.sons[0] initLocExpr(p, e.sons[0], a) getTemp(p, a.t, tmp) diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim index 3d1c2affc..e30395d2e 100644 --- a/compiler/ccgtypes.nim +++ b/compiler/ccgtypes.nim @@ -744,14 +744,6 @@ proc getClosureType(m: BModule, t: PType, kind: TClosureTypeKind): Rope = "void* ClEnv;$n} $1;$n", [result, rettype, desc]) -proc getTypeDesc(m: BModule, magic: string): Rope = - var sym = magicsys.getCompilerProc(magic) - if sym != nil: - result = getTypeDesc(m, sym.typ) - else: - rawMessage(errSystemNeeds, magic) - result = nil - proc finishTypeDescriptions(m: BModule) = var i = 0 while i < len(m.typeStack): @@ -1000,9 +992,6 @@ proc fakeClosureType(owner: PSym): PType = type TTypeInfoReason = enum ## for what do we need the type info? tiNew, ## for 'new' - tiNewSeq, ## for 'newSeq' - tiNonVariantAsgn, ## for generic assignment without variants - tiVariantAsgn ## for generic assignment with variants include ccgtrav diff --git a/compiler/cgen.nim b/compiler/cgen.nim index 810f7dfd4..42883b590 100644 --- a/compiler/cgen.nim +++ b/compiler/cgen.nim @@ -167,10 +167,6 @@ proc linefmt(p: BProc, s: TCProcSection, frmt: FormatStr, args: varargs[Rope]) = add(p.s(s), indentLine(p, ropecg(p.module, frmt, args))) -proc appLineCg(p: BProc, r: var Rope, frmt: FormatStr, - args: varargs[Rope]) = - add(r, indentLine(p, ropecg(p.module, frmt, args))) - proc safeLineNm(info: TLineInfo): int = result = toLinenumber(info) if result < 0: result = 0 # negative numbers are not allowed in #line @@ -259,8 +255,7 @@ proc genObjectInit(p: BProc, section: TCProcSection, t: PType, a: TLoc, type TAssignmentFlag = enum - needToCopy, needForSubtypeCheck, afDestIsNil, afDestIsNotNil, afSrcIsNil, - afSrcIsNotNil, needToKeepAlive + needToCopy, afDestIsNil, afDestIsNotNil, afSrcIsNil, afSrcIsNotNil TAssignmentFlags = set[TAssignmentFlag] proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) @@ -338,31 +333,6 @@ proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) = result.flags = {} constructLoc(p, result, not needsInit) -proc keepAlive(p: BProc, toKeepAlive: TLoc) = - when false: - # deactivated because of the huge slowdown this causes; GC will take care - # of interior pointers instead - if optRefcGC notin gGlobalOptions: return - var result: TLoc - var fid = rope(p.gcFrameId) - result.r = "GCFRAME.F" & fid - addf(p.gcFrameType, " $1 F$2;$n", - [getTypeDesc(p.module, toKeepAlive.t), fid]) - inc(p.gcFrameId) - result.k = locTemp - #result.a = -1 - result.t = toKeepAlive.t - result.s = OnStack - result.flags = {} - - if not isComplexValueType(skipTypes(toKeepAlive.t, abstractVarRange)): - linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(result), rdLoc(toKeepAlive)) - else: - useStringh(p.module) - linefmt(p, cpsStmts, - "memcpy((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n", - addrLoc(result), addrLoc(toKeepAlive), rdLoc(result)) - proc initGCFrame(p: BProc): Rope = if p.gcFrameId > 0: result = "struct {$1} GCFRAME;$n" % [p.gcFrameType] @@ -620,9 +590,6 @@ proc generateHeaders(m: BModule) = addf(m.s[cfsHeaders], "#include $1$N", [rope(it.data)]) it = PStrEntry(it.next) -proc retIsNotVoid(s: PSym): bool = - result = (s.typ.sons[0] != nil) and not isInvalidReturnType(s.typ.sons[0]) - proc initFrame(p: BProc, procname, filename: Rope): Rope = discard cgsym(p.module, "nimFrame") if p.maxFrameLen > 0: diff --git a/compiler/extccomp.nim b/compiler/extccomp.nim index 2dcfc0226..6f8b0b197 100644 --- a/compiler/extccomp.nim +++ b/compiler/extccomp.nim @@ -505,10 +505,6 @@ proc noAbsolutePaths: bool {.inline.} = # `optGenMapping` is included here for niminst. result = gGlobalOptions * {optGenScript, optGenMapping} != {} -const - specialFileA = 42 - specialFileB = 42 - var fileCounter: int proc add(s: var string, many: openArray[string]) = diff --git a/compiler/idgen.nim b/compiler/idgen.nim index 333772705..c6b1a4d07 100644 --- a/compiler/idgen.nim +++ b/compiler/idgen.nim @@ -54,6 +54,6 @@ proc loadMaxIds*(project: string) = if f.readLine(line): var frontEndId = parseInt(line) if f.readLine(line): - var backEndId = parseInt(line) + # var backEndId = parseInt(line) gFrontEndId = max(gFrontEndId, frontEndId) f.close() diff --git a/compiler/installer.ini b/compiler/installer.ini index b802f08f1..4fc03dd1d 100644 --- a/compiler/installer.ini +++ b/compiler/installer.ini @@ -116,7 +116,6 @@ path = r"c:\Program Files (x86)\Inno Setup 5\iscc.exe" flags = "/Q" [NSIS] -path = r"c:\Program Files (x86)\NSIS\makensis.exe" flags = "/V0" [C_Compiler] diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim index a0b54812f..80bcd2b0e 100644 --- a/compiler/jsgen.nim +++ b/compiler/jsgen.nim @@ -8,7 +8,7 @@ # # This is the JavaScript code generator. -# Soon also a PHP code generator. ;-) +# Also a PHP code generator. ;-) discard """ The JS code generator contains only 2 tricks: @@ -1280,14 +1280,15 @@ proc genInfixCall(p: PProc, n: PNode, r: var TCompRes) = assert(typ.kind == tyProc) genPatternCall(p, n, pat, typ, r) return - gen(p, n.sons[1], r) - if r.typ == etyBaseIndex: - if r.address == nil: - globalError(n.info, "cannot invoke with infix syntax") - r.res = "$1[$2]" % [r.address, r.res] - r.address = nil - r.typ = etyNone - add(r.res, "." | "->") + if n.len != 1: + gen(p, n.sons[1], r) + if r.typ == etyBaseIndex: + if r.address == nil: + globalError(n.info, "cannot invoke with infix syntax") + r.res = "$1[$2]" % [r.address, r.res] + r.address = nil + r.typ = etyNone + add(r.res, "." | "->") var op: TCompRes if p.target == targetPHP: op.kind = resCallee diff --git a/compiler/lexer.nim b/compiler/lexer.nim index 0eee5004e..9c513034b 100644 --- a/compiler/lexer.nim +++ b/compiler/lexer.nim @@ -211,9 +211,6 @@ proc closeLexer*(lex: var TLexer) = inc(gLinesCompiled, lex.lineNumber) closeBaseLexer(lex) -proc getColumn(L: TLexer): int = - result = getColNumber(L, L.bufpos) - proc getLineInfo(L: TLexer): TLineInfo = result = newLineInfo(L.fileIdx, L.lineNumber, getColNumber(L, L.bufpos)) @@ -237,12 +234,6 @@ proc lexMessagePos(L: var TLexer, msg: TMsgKind, pos: int, arg = "") = proc matchTwoChars(L: TLexer, first: char, second: set[char]): bool = result = (L.buf[L.bufpos] == first) and (L.buf[L.bufpos + 1] in second) -proc isFloatLiteral(s: string): bool = - for i in countup(0, len(s) - 1): - if s[i] in {'.', 'e', 'E'}: - return true - result = false - {.push overflowChecks: off.} # We need to parse the largest uint literal without overflow checks proc unsafeParseUInt(s: string, b: var BiggestInt, start = 0): int = diff --git a/compiler/modules.nim b/compiler/modules.nim index 9120bd1b6..aa12325f4 100644 --- a/compiler/modules.nim +++ b/compiler/modules.nim @@ -38,9 +38,6 @@ proc getModule*(fileIdx: int32): PSym = if fileIdx >= 0 and fileIdx < gCompiledModules.len: result = gCompiledModules[fileIdx] -template hash(x: PSym): untyped = - gMemCacheData[x.position].hash - proc hashChanged(fileIdx: int32): bool = internalAssert fileIdx >= 0 and fileIdx < gMemCacheData.len @@ -220,12 +217,6 @@ proc includeModule*(s: PSym, fileIdx: int32): PNode {.procvar.} = addDep(s, fileIdx) doHash(fileIdx) -proc `==^`(a, b: string): bool = - try: - result = sameFile(a, b) - except OSError: - result = false - proc compileSystemModule* = if magicsys.systemModule == nil: systemFileIdx = fileInfoIdx(options.libpath/"system.nim") diff --git a/compiler/msgs.nim b/compiler/msgs.nim index 4a9980066..c10c26ec5 100644 --- a/compiler/msgs.nim +++ b/compiler/msgs.nim @@ -65,7 +65,7 @@ type errPureTypeMismatch, errTypeMismatch, errButExpected, errButExpectedX, errAmbiguousCallXYZ, errWrongNumberOfArguments, errXCannotBePassedToProcVar, - errXCannotBeInParamDecl, errPragmaOnlyInHeaderOfProc, errImplOfXNotAllowed, + errXCannotBeInParamDecl, errPragmaOnlyInHeaderOfProcX, errImplOfXNotAllowed, errImplOfXexpected, errNoSymbolToBorrowFromFound, errDiscardValueX, errInvalidDiscard, errIllegalConvFromXtoY, errCannotBindXTwice, errInvalidOrderInArrayConstructor, @@ -274,7 +274,7 @@ const errWrongNumberOfArguments: "wrong number of arguments", errXCannotBePassedToProcVar: "\'$1\' cannot be passed to a procvar", errXCannotBeInParamDecl: "$1 cannot be declared in parameter declaration", - errPragmaOnlyInHeaderOfProc: "pragmas are only allowed in the header of a proc", + errPragmaOnlyInHeaderOfProcX: "pragmas are only allowed in the header of a proc; redefinition of $1", errImplOfXNotAllowed: "implementation of \'$1\' is not allowed", errImplOfXexpected: "implementation of \'$1\' expected", errNoSymbolToBorrowFromFound: "no symbol to borrow from found", @@ -660,8 +660,6 @@ const WarningColor = fgYellow HintTitle = "Hint: " HintColor = fgGreen - InfoTitle = "Info: " - InfoColor = fgCyan proc getInfoContextLen*(): int = return msgContext.len proc setInfoContextLen*(L: int) = setLen(msgContext, L) diff --git a/compiler/nimblecmd.nim b/compiler/nimblecmd.nim index c6c2ab058..9c5c17287 100644 --- a/compiler/nimblecmd.nim +++ b/compiler/nimblecmd.nim @@ -63,18 +63,6 @@ proc addNimblePath(p: string, info: TLineInfo) = message(info, hintPath, p) lists.prependStr(options.lazyPaths, p) -proc addPathWithNimFiles(p: string, info: TLineInfo) = - proc hasNimFile(dir: string): bool = - for kind, path in walkDir(dir): - if kind == pcFile and path.endsWith(".nim"): - result = true - break - if hasNimFile(p): - addNimblePath(p, info) - else: - for kind, p2 in walkDir(p): - if hasNimFile(p2): addNimblePath(p2, info) - proc addPathRec(dir: string, info: TLineInfo) = var packages = newStringTable(modeStyleInsensitive) var pos = dir.len-1 diff --git a/compiler/parser.nim b/compiler/parser.nim index 19ef0960a..40862eb63 100644 --- a/compiler/parser.nim +++ b/compiler/parser.nim @@ -340,26 +340,6 @@ proc parseSymbol(p: var TParser, allowNil = false): PNode = if not isKeyword(p.tok.tokType): getTok(p) result = ast.emptyNode -proc indexExpr(p: var TParser): PNode = - #| indexExpr = expr - result = parseExpr(p) - -proc indexExprList(p: var TParser, first: PNode, k: TNodeKind, - endToken: TTokType): PNode = - #| indexExprList = indexExpr ^+ comma - result = newNodeP(k, p) - addSon(result, first) - getTok(p) - optInd(p, result) - while p.tok.tokType notin {endToken, tkEof}: - var a = indexExpr(p) - addSon(result, a) - if p.tok.tokType != tkComma: break - getTok(p) - skipComment(p, a) - optPar(p) - eat(p, endToken) - proc colonOrEquals(p: var TParser, a: PNode): PNode = if p.tok.tokType == tkColon: result = newNodeP(nkExprColonExpr, p) diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim index a4c95e1b7..9a12fa7fe 100644 --- a/compiler/pragmas.nim +++ b/compiler/pragmas.nim @@ -90,43 +90,38 @@ proc pragmaAsm*(c: PContext, n: PNode): char = else: invalidPragma(it) -proc setExternName(s: PSym, extname: string) = - s.loc.r = rope(extname % s.name.s) +proc setExternName(s: PSym, extname: string, info: TLineInfo) = + # special cases to improve performance: + if extname == "$1": + s.loc.r = rope(s.name.s) + elif '$' notin extname: + s.loc.r = rope(extname) + else: + try: + s.loc.r = rope(extname % s.name.s) + except ValueError: + localError(info, "invalid extern name: '" & extname & "'. (Forgot to escape '$'?)") if gCmd == cmdPretty and '$' notin extname: # note that '{.importc.}' is transformed into '{.importc: "$1".}' s.loc.flags.incl(lfFullExternalName) -proc makeExternImport(s: PSym, extname: string) = - setExternName(s, extname) +proc makeExternImport(s: PSym, extname: string, info: TLineInfo) = + setExternName(s, extname, info) incl(s.flags, sfImportc) excl(s.flags, sfForward) -proc validateExternCName(s: PSym, info: TLineInfo) = - ## Validates that the symbol name in s.loc.r is a valid C identifier. - ## - ## Valid identifiers are those alphanumeric including the underscore not - ## starting with a number. If the check fails, a generic error will be - ## displayed to the user. - let target = $s.loc.r - if target.len < 1 or target[0] notin IdentStartChars or - not target.allCharsInSet(IdentChars): - localError(info, errGenerated, "invalid exported symbol") - proc makeExternExport(s: PSym, extname: string, info: TLineInfo) = - setExternName(s, extname) - # XXX to fix make it work with nimrtl. - #if gCmd in {cmdCompileToC, cmdCompileToCpp, cmdCompileToOC}: - # validateExternCName(s, info) + setExternName(s, extname, info) incl(s.flags, sfExportc) -proc processImportCompilerProc(s: PSym, extname: string) = - setExternName(s, extname) +proc processImportCompilerProc(s: PSym, extname: string, info: TLineInfo) = + setExternName(s, extname, info) incl(s.flags, sfImportc) excl(s.flags, sfForward) incl(s.loc.flags, lfImportCompilerProc) -proc processImportCpp(s: PSym, extname: string) = - setExternName(s, extname) +proc processImportCpp(s: PSym, extname: string, info: TLineInfo) = + setExternName(s, extname, info) incl(s.flags, sfImportc) incl(s.flags, sfInfixCall) excl(s.flags, sfForward) @@ -134,8 +129,8 @@ proc processImportCpp(s: PSym, extname: string) = incl(m.flags, sfCompileToCpp) extccomp.gMixedMode = true -proc processImportObjC(s: PSym, extname: string) = - setExternName(s, extname) +proc processImportObjC(s: PSym, extname: string, info: TLineInfo) = + setExternName(s, extname, info) incl(s.flags, sfImportc) incl(s.flags, sfNamedParamCall) excl(s.flags, sfForward) @@ -625,10 +620,10 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int, of wExportc: makeExternExport(sym, getOptionalStr(c, it, "$1"), it.info) incl(sym.flags, sfUsed) # avoid wrong hints - of wImportc: makeExternImport(sym, getOptionalStr(c, it, "$1")) + of wImportc: makeExternImport(sym, getOptionalStr(c, it, "$1"), it.info) of wImportCompilerProc: - processImportCompilerProc(sym, getOptionalStr(c, it, "$1")) - of wExtern: setExternName(sym, expectStrLit(c, it)) + processImportCompilerProc(sym, getOptionalStr(c, it, "$1"), it.info) + of wExtern: setExternName(sym, expectStrLit(c, it), it.info) of wImmediate: if sym.kind in {skTemplate, skMacro}: incl(sym.flags, sfImmediate) @@ -639,9 +634,9 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int, if sym.kind == skTemplate: incl(sym.flags, sfDirty) else: invalidPragma(it) of wImportCpp: - processImportCpp(sym, getOptionalStr(c, it, "$1")) + processImportCpp(sym, getOptionalStr(c, it, "$1"), it.info) of wImportObjC: - processImportObjC(sym, getOptionalStr(c, it, "$1")) + processImportObjC(sym, getOptionalStr(c, it, "$1"), it.info) of wAlign: if sym.typ == nil: invalidPragma(it) var align = expectIntLit(c, it) diff --git a/compiler/renderer.nim b/compiler/renderer.nim index 0e733d643..a116a8afe 100644 --- a/compiler/renderer.nim +++ b/compiler/renderer.nim @@ -146,12 +146,6 @@ proc put(g: var TSrcGen, kind: TTokType, s: string) = else: g.pendingWhitespace = s.len -proc putLong(g: var TSrcGen, kind: TTokType, s: string, lineLen: int) = - # use this for tokens over multiple lines. - addPendingNL(g) - addTok(g, kind, s) - g.lineLen = lineLen - proc toNimChar(c: char): string = case c of '\0': result = "\\0" @@ -264,9 +258,6 @@ proc pushCom(g: var TSrcGen, n: PNode) = proc popAllComs(g: var TSrcGen) = setLen(g.comStack, 0) -proc popCom(g: var TSrcGen) = - setLen(g.comStack, len(g.comStack) - 1) - const Space = " " @@ -492,7 +483,7 @@ proc fits(g: TSrcGen, x: int): bool = type TSubFlag = enum - rfLongMode, rfNoIndent, rfInConstExpr + rfLongMode, rfInConstExpr TSubFlags = set[TSubFlag] TContext = tuple[spacing: int, flags: TSubFlags] @@ -675,16 +666,6 @@ proc gfor(g: var TSrcGen, n: PNode) = gcoms(g) gstmts(g, n.sons[length - 1], c) -proc gmacro(g: var TSrcGen, n: PNode) = - var c: TContext - initContext(c) - gsub(g, n.sons[0]) - putWithSpace(g, tkColon, ":") - if longMode(n) or (lsub(n.sons[1]) + g.lineLen > MaxLineLen): - incl(c.flags, rfLongMode) - gcoms(g) - gsons(g, n, c, 1) - proc gcase(g: var TSrcGen, n: PNode) = var c: TContext initContext(c) diff --git a/compiler/ropes.nim b/compiler/ropes.nim index bfae7aaa4..d84b59f78 100644 --- a/compiler/ropes.nim +++ b/compiler/ropes.nim @@ -310,15 +310,19 @@ proc equalsFile*(r: Rope, f: File): bool = buf: array[bufSize, char] bpos = buf.len blen = buf.len + btotal = 0 + rtotal = 0 for s in leaves(r): var spos = 0 let slen = s.len + rtotal += slen while spos < slen: if bpos == blen: # Read more data bpos = 0 blen = readBuffer(f, addr(buf[0]), buf.len) + btotal += blen if blen == 0: # no more data in file result = false return @@ -330,7 +334,8 @@ proc equalsFile*(r: Rope, f: File): bool = spos += n bpos += n - result = readBuffer(f, addr(buf[0]), 1) == 0 # check that we've read all + result = readBuffer(f, addr(buf[0]), 1) == 0 and + btotal == rtotal # check that we've read all proc equalsFile*(r: Rope, filename: string): bool = ## returns true if the contents of the file `f` equal `r`. If `f` does not diff --git a/compiler/sem.nim b/compiler/sem.nim index 7db4ae47e..ccbd665e9 100644 --- a/compiler/sem.nim +++ b/compiler/sem.nim @@ -39,7 +39,6 @@ proc semStmt(c: PContext, n: PNode): PNode proc semParamList(c: PContext, n, genericParams: PNode, s: PSym) proc addParams(c: PContext, n: PNode, kind: TSymKind) proc maybeAddResult(c: PContext, s: PSym, n: PNode) -proc instGenericContainer(c: PContext, n: PNode, header: PType): PType proc tryExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode proc activate(c: PContext, n: PNode) proc semQuoteAst(c: PContext, n: PNode): PNode @@ -187,7 +186,6 @@ proc semIdentVis(c: PContext, kind: TSymKind, n: PNode, # identifier with visibility proc semIdentWithPragma(c: PContext, kind: TSymKind, n: PNode, allowed: TSymFlags): PSym -proc semStmtScope(c: PContext, n: PNode): PNode proc typeAllowedCheck(info: TLineInfo; typ: PType; kind: TSymKind) = let t = typeAllowed(typ, kind) diff --git a/compiler/semcall.nim b/compiler/semcall.nim index 97209167d..b3fc020b1 100644 --- a/compiler/semcall.nim +++ b/compiler/semcall.nim @@ -40,67 +40,49 @@ proc pickBestCandidate(c: PContext, headSymbol: PNode, filter: TSymKinds, best, alt: var TCandidate, errors: var CandidateErrors) = - var o: TOverloadIter - # thanks to the lazy semchecking for operands, we need to iterate over the - # symbol table *before* any call to 'initCandidate' which might invoke - # semExpr which might modify the symbol table in cases like - # 'init(a, 1, (var b = new(Type2); b))'. - var symx = initOverloadIter(o, c, headSymbol) - let symScope = o.lastOverloadScope - - var syms: seq[tuple[a: PSym, b: int]] = @[] - while symx != nil: - if symx.kind in filter: - syms.add((symx, o.lastOverloadScope)) - symx = nextOverloadIter(o, c, headSymbol) - if syms.len == 0: - when false: - if skIterator notin filter: - # also try iterators, but these are 2nd class: - symx = initOverloadIter(o, c, headSymbol) - while symx != nil: - if symx.kind == skIterator: - syms.add((symx, 100)) - symx = nextOverloadIter(o, c, headSymbol) - if syms.len == 0: return - else: - return - - var z: TCandidate - initCandidate(c, best, syms[0][0], initialBinding, symScope) - initCandidate(c, alt, syms[0][0], initialBinding, symScope) - best.state = csNoMatch - - for i in 0 .. <syms.len: - let sym = syms[i][0] - determineType(c, sym) - initCandidate(c, z, sym, initialBinding, syms[i][1]) - - #if sym.name.s == "*" and (n.info ?? "temp5.nim") and n.info.line == 140: - # gDebug = true - matches(c, n, orig, z) - if errors != nil: - errors.safeAdd((sym, int z.mutabilityProblem)) - if z.errors != nil: - for err in z.errors: - errors.add(err) - if z.state == csMatch: - # little hack so that iterators are preferred over everything else: - if sym.kind == skIterator: inc(z.exactMatches, 200) - case best.state - of csEmpty, csNoMatch: best = z - of csMatch: - var cmp = cmpCandidates(best, z) - if cmp < 0: best = z # x is better than the best so far - elif cmp == 0: alt = z # x is as good as the best so far - else: discard - #if sym.name.s == "cmp" and (n.info ?? "rstgen.nim") and n.info.line == 516: - # echo "Matches ", n.info, " ", typeToString(sym.typ) - # debug sym - # writeMatches(z) - # for i in 1 .. <len(z.call): - # z.call[i].typ.debug - # quit 1 + while true: + block pickAttempt: + var o: TOverloadIter + var sym = initOverloadIter(o, c, headSymbol) + # Thanks to the lazy semchecking for operands, we need to check whether + # 'initCandidate' modifies the symbol table (via semExpr). + # This can occur in cases like 'init(a, 1, (var b = new(Type2); b))' + let counterInitial = c.currentScope.symbols.counter + # Initialise 'best' and 'alt' with the first available symbol + while sym != nil: + if sym.kind in filter: + initCandidate(c, best, sym, initialBinding, o.lastOverloadScope) + initCandidate(c, alt, sym, initialBinding, o.lastOverloadScope) + best.state = csNoMatch + break + else: + sym = nextOverloadIter(o, c, headSymbol) + var z: TCandidate + while sym != nil: + if sym.kind notin filter: + sym = nextOverloadIter(o, c, headSymbol) + continue + determineType(c, sym) + initCandidate(c, z, sym, initialBinding, o.lastOverloadScope) + if c.currentScope.symbols.counter != counterInitial: break pickAttempt + matches(c, n, orig, z) + if errors != nil: + errors.safeAdd((sym, int z.mutabilityProblem)) + if z.errors != nil: + for err in z.errors: + errors.add(err) + if z.state == csMatch: + # little hack so that iterators are preferred over everything else: + if sym.kind == skIterator: inc(z.exactMatches, 200) + case best.state + of csEmpty, csNoMatch: best = z + of csMatch: + var cmp = cmpCandidates(best, z) + if cmp < 0: best = z # x is better than the best so far + elif cmp == 0: alt = z # x is as good as the best so far + else: discard + sym = nextOverloadIter(o, c, headSymbol) + break # pick attempt was successful proc notFoundError*(c: PContext, n: PNode, errors: CandidateErrors) = # Gives a detailed error message; this is separated from semOverloadedCall, @@ -462,3 +444,9 @@ proc searchForBorrowProc(c: PContext, startScope: PScope, fn: PSym): PSym = var resolved = semOverloadedCall(c, call, call, {fn.kind}) if resolved != nil: result = resolved.sons[0].sym + if not compareTypes(result.typ.sons[0], fn.typ.sons[0], dcEqIgnoreDistinct): + result = nil + elif result.magic in {mArrPut, mArrGet}: + # cannot borrow these magics for now + result = nil + diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim index fc31829ba..274bb15b9 100644 --- a/compiler/semexprs.nim +++ b/compiler/semexprs.nim @@ -414,8 +414,6 @@ proc arrayConstrType(c: PContext, n: PNode): PType = if sonsLen(n) == 0: rawAddSon(typ, newTypeS(tyEmpty, c)) # needs an empty basetype! else: - var x = n.sons[0] - var lastIndex: BiggestInt = sonsLen(n) - 1 var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyOrdinal}) addSonSkipIntLit(typ, t) typ.sons[0] = makeRangeType(c, 0, sonsLen(n) - 1, n.info) @@ -512,16 +510,6 @@ proc fixAbstractType(c: PContext, n: PNode) = #if (it.typ == nil): # InternalError(it.info, "fixAbstractType: " & renderTree(it)) -proc skipObjConv(n: PNode): PNode = - case n.kind - of nkHiddenStdConv, nkHiddenSubConv, nkConv: - if skipTypes(n.sons[1].typ, abstractPtrs).kind in {tyTuple, tyObject}: - result = n.sons[1] - else: - result = n - of nkObjUpConv, nkObjDownConv: result = n.sons[0] - else: result = n - proc isAssignable(c: PContext, n: PNode; isUnsafeAddr=false): TAssignableResult = result = parampatterns.isAssignable(c.p.owner, n, isUnsafeAddr) @@ -701,9 +689,6 @@ proc semOverloadedCallAnalyseEffects(c: PContext, n: PNode, nOrig: PNode, # error correction, prevents endless for loop elimination in transf. # See bug #2051: result.sons[0] = newSymNode(errorSym(c, n)) - if sfNoSideEffect notin callee.flags: - if {sfImportc, sfSideEffect} * callee.flags != {}: - incl(c.p.owner.flags, sfSideEffect) proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode @@ -804,9 +789,6 @@ proc semIndirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode = else: result = m.call instGenericConvertersSons(c, result, m) - # we assume that a procedure that calls something indirectly - # has side-effects: - if tfNoSideEffect notin t.flags: incl(c.p.owner.flags, sfSideEffect) elif t != nil and t.kind == tyTypeDesc: if n.len == 1: return semObjConstr(c, n, flags) return semConv(c, n) @@ -1040,9 +1022,6 @@ proc semSym(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode = markUsed(n.info, s) styleCheckUse(n.info, s) - # if a proc accesses a global variable, it is not side effect free: - if sfGlobal in s.flags: - incl(c.p.owner.flags, sfSideEffect) result = newSymNode(s, n.info) # We cannot check for access to outer vars for example because it's still # not sure the symbol really ends up being used: @@ -1421,8 +1400,9 @@ proc semAsgn(c: PContext, n: PNode; mode=asgnNormal): PNode = # a = b # both are vars, means: a[] = b[] # a = b # b no 'var T' means: a = addr(b) var le = a.typ - if skipTypes(le, {tyGenericInst}).kind != tyVar and - isAssignable(c, a) == arNone: + if (skipTypes(le, {tyGenericInst}).kind != tyVar and + isAssignable(c, a) == arNone) or + skipTypes(le, abstractVar).kind in {tyOpenArray, tyVarargs}: # Direct assignment to a discriminant is allowed! localError(a.info, errXCannotBeAssignedTo, renderTree(a, {renderNoComments})) diff --git a/compiler/semfold.nim b/compiler/semfold.nim index 02f238ae6..1cb726053 100644 --- a/compiler/semfold.nim +++ b/compiler/semfold.nim @@ -458,32 +458,6 @@ proc getConstIfExpr(c: PSym, n: PNode): PNode = if result == nil: result = getConstExpr(c, it.sons[0]) else: internalError(it.info, "getConstIfExpr()") -proc partialAndExpr(c: PSym, n: PNode): PNode = - # partial evaluation - result = n - var a = getConstExpr(c, n.sons[1]) - var b = getConstExpr(c, n.sons[2]) - if a != nil: - if getInt(a) == 0: result = a - elif b != nil: result = b - else: result = n.sons[2] - elif b != nil: - if getInt(b) == 0: result = b - else: result = n.sons[1] - -proc partialOrExpr(c: PSym, n: PNode): PNode = - # partial evaluation - result = n - var a = getConstExpr(c, n.sons[1]) - var b = getConstExpr(c, n.sons[2]) - if a != nil: - if getInt(a) != 0: result = a - elif b != nil: result = b - else: result = n.sons[2] - elif b != nil: - if getInt(b) != 0: result = b - else: result = n.sons[1] - proc leValueConv(a, b: PNode): bool = result = false case a.kind diff --git a/compiler/semgnrc.nim b/compiler/semgnrc.nim index 9ea3efd0c..b8451865e 100644 --- a/compiler/semgnrc.nim +++ b/compiler/semgnrc.nim @@ -202,24 +202,25 @@ proc semGenericStmt(c: PContext, n: PNode, if s != nil: incl(s.flags, sfUsed) mixinContext = s.magic in {mDefined, mDefinedInScope, mCompiles} - let scOption = if s.name.id in ctx.toMixin: scForceOpen else: scOpen + let sc = symChoice(c, fn, s, + if s.name.id in ctx.toMixin: scForceOpen else: scOpen) case s.kind of skMacro: - if macroToExpand(s): + if macroToExpand(s) and sc.safeLen <= 1: styleCheckUse(fn.info, s) result = semMacroExpr(c, n, n, s, {efNoSemCheck}) result = semGenericStmt(c, result, flags, ctx) else: - n.sons[0] = symChoice(c, fn, s, scOption) + n.sons[0] = sc result = n mixinContext = true of skTemplate: - if macroToExpand(s): + if macroToExpand(s) and sc.safeLen <= 1: styleCheckUse(fn.info, s) result = semTemplateExpr(c, n, s, {efNoSemCheck}) result = semGenericStmt(c, result, flags, ctx) else: - n.sons[0] = symChoice(c, fn, s, scOption) + n.sons[0] = sc result = n # BUGFIX: we must not return here, we need to do first phase of # symbol lookup. Also since templates and macros can do scope injections @@ -230,7 +231,7 @@ proc semGenericStmt(c: PContext, n: PNode, # Leave it as an identifier. discard of skProc, skMethod, skIterator, skConverter, skModule: - result.sons[0] = symChoice(c, fn, s, scOption) + result.sons[0] = sc # do not check of 's.magic==mRoof' here because it might be some # other '^' but after overload resolution the proper one: if ctx.bracketExpr != nil and n.len == 2 and s.name.s == "^": diff --git a/compiler/seminst.nim b/compiler/seminst.nim index 460db4f7c..498ebc3fb 100644 --- a/compiler/seminst.nim +++ b/compiler/seminst.nim @@ -97,22 +97,6 @@ proc genericCacheGet(genericSym: PSym, entry: TInstantiation; if inst.compilesId == id and sameInstantiation(entry, inst[]): return inst.sym -proc removeDefaultParamValues(n: PNode) = - # we remove default params, because they cannot be instantiated properly - # and they are not needed anyway for instantiation (each param is already - # provided). - when false: - for i in countup(1, sonsLen(n)-1): - var a = n.sons[i] - if a.kind != nkIdentDefs: IllFormedAst(a) - var L = a.len - if a.sons[L-1].kind != nkEmpty and a.sons[L-2].kind != nkEmpty: - # ``param: typ = defaultVal``. - # We don't need defaultVal for semantic checking and it's wrong for - # ``cmp: proc (a, b: T): int = cmp``. Hm, for ``cmp = cmp`` that is - # not possible... XXX We don't solve this issue here. - a.sons[L-1] = ast.emptyNode - proc freshGenSyms(n: PNode, owner, orig: PSym, symMap: var TIdTable) = # we need to create a fresh set of gensym'ed symbols: if n.kind == nkSym and sfGenSym in n.sym.flags and n.sym.owner == orig: @@ -128,17 +112,6 @@ proc freshGenSyms(n: PNode, owner, orig: PSym, symMap: var TIdTable) = proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind) -proc addProcDecls(c: PContext, fn: PSym) = - # get the proc itself in scope (e.g. for recursion) - addDecl(c, fn) - - for i in 1 .. <fn.typ.n.len: - var param = fn.typ.n.sons[i].sym - param.owner = fn - addParamOrResult(c, param, fn.kind) - - maybeAddResult(c, fn, fn.ast) - proc instantiateBody(c: PContext, n, params: PNode, result, orig: PSym) = if n.sons[bodyPos].kind != nkEmpty: inc c.inGenericInst @@ -172,9 +145,10 @@ proc fixupInstantiatedSymbols(c: PContext, s: PSym) = popInfoContext() proc sideEffectsCheck(c: PContext, s: PSym) = - if {sfNoSideEffect, sfSideEffect} * s.flags == - {sfNoSideEffect, sfSideEffect}: - localError(s.info, errXhasSideEffects, s.name.s) + when false: + if {sfNoSideEffect, sfSideEffect} * s.flags == + {sfNoSideEffect, sfSideEffect}: + localError(s.info, errXhasSideEffects, s.name.s) proc instGenericContainer(c: PContext, info: TLineInfo, header: PType, allowMetaTypes = false): PType = @@ -187,9 +161,6 @@ proc instGenericContainer(c: PContext, info: TLineInfo, header: PType, cl.allowMetaTypes = allowMetaTypes result = replaceTypeVarsT(cl, header) -proc instGenericContainer(c: PContext, n: PNode, header: PType): PType = - result = instGenericContainer(c, n.info, header) - proc instantiateProcType(c: PContext, pt: TIdTable, prc: PSym, info: TLineInfo) = # XXX: Instantiates a generic proc signature, while at the same diff --git a/compiler/semmagic.nim b/compiler/semmagic.nim index cbe9bc176..806b00db6 100644 --- a/compiler/semmagic.nim +++ b/compiler/semmagic.nim @@ -151,13 +151,6 @@ proc isStrangeArray(t: PType): bool = let t = t.skipTypes(abstractInst) result = t.kind == tyArray and t.firstOrd != 0 -proc isNegative(n: PNode): bool = - let n = n.skipConv - if n.kind in {nkCharLit..nkUInt64Lit}: - result = n.intVal < 0 - elif n.kind in nkCallKinds and n.sons[0].kind == nkSym: - result = n.sons[0].sym.magic in {mUnaryMinusI, mUnaryMinusI64} - proc magicsAfterOverloadResolution(c: PContext, n: PNode, flags: TExprFlags): PNode = case n[0].sym.magic diff --git a/compiler/sempass2.nim b/compiler/sempass2.nim index b12ab5e96..3908fa26e 100644 --- a/compiler/sempass2.nim +++ b/compiler/sempass2.nim @@ -59,7 +59,7 @@ type init: seq[int] # list of initialized variables guards: TModel # nested guards locked: seq[PNode] # locked locations - gcUnsafe, isRecursive, isToplevel: bool + gcUnsafe, isRecursive, isToplevel, hasSideEffect: bool maxLockLevel, currLockLevel: TLockLevel PEffects = var TEffects @@ -192,6 +192,14 @@ proc markGcUnsafe(a: PEffects; reason: PNode) = a.owner.gcUnsafetyReason = newSym(skUnknown, getIdent("<unknown>"), a.owner, reason.info) +when true: + template markSideEffect(a: PEffects; reason: typed) = + a.hasSideEffect = true +else: + template markSideEffect(a: PEffects; reason: typed) = + a.hasSideEffect = true + markGcUnsafe(a, reason) + proc listGcUnsafety(s: PSym; onlyWarning: bool; cycleCheck: var IntSet) = let u = s.gcUnsafetyReason if u != nil and not cycleCheck.containsOrIncl(u.id): @@ -226,12 +234,16 @@ proc useVar(a: PEffects, n: PNode) = message(n.info, warnUninit, s.name.s) # prevent superfluous warnings about the same variable: a.init.add s.id - if {sfGlobal, sfThread} * s.flags != {} and s.kind in {skVar, skLet}: + if {sfGlobal, sfThread} * s.flags != {} and s.kind in {skVar, skLet} and + s.magic != mNimVm: if s.guard != nil: guardGlobal(a, n, s.guard) if {sfGlobal, sfThread} * s.flags == {sfGlobal} and (tfHasGCedMem in s.typ.flags or s.typ.isGCedMem): #if warnGcUnsafe in gNotes: warnAboutGcUnsafe(n) markGcUnsafe(a, s) + else: + markSideEffect(a, s) + type TIntersection = seq[tuple[id, count: int]] # a simple count table @@ -268,10 +280,6 @@ proc createTag(n: PNode): PNode = result.typ = sysTypeFromName"TEffect" if not n.isNil: result.info = n.info -proc createAnyGlobal(n: PNode): PNode = - result = newSymNode(anyGlobal) - result.info = n.info - proc addEffect(a: PEffects, e: PNode, useLineInfo=true) = assert e.kind != nkRaiseStmt var aa = a.exc @@ -495,6 +503,8 @@ proc propagateEffects(tracked: PEffects, n: PNode, s: PSym) = if notGcSafe(s.typ) and sfImportc notin s.flags: if warnGcUnsafe in gNotes: warnAboutGcUnsafe(n) markGcUnsafe(tracked, s) + if tfNoSideEffect notin s.typ.flags: + markSideEffect(tracked, s) mergeLockLevels(tracked, n, s.getLockLevel) proc notNilCheck(tracked: PEffects, n: PNode, paramType: PType) = @@ -550,12 +560,16 @@ proc trackOperand(tracked: PEffects, n: PNode, paramType: PType) = if notGcSafe(op) and not isOwnedProcVar(a, tracked.owner): if warnGcUnsafe in gNotes: warnAboutGcUnsafe(n) markGcUnsafe(tracked, a) + elif tfNoSideEffect notin op.flags and not isOwnedProcVar(a, tracked.owner): + markSideEffect(tracked, a) else: mergeEffects(tracked, effectList.sons[exceptionEffects], n) mergeTags(tracked, effectList.sons[tagEffects], n) if notGcSafe(op): if warnGcUnsafe in gNotes: warnAboutGcUnsafe(n) markGcUnsafe(tracked, a) + elif tfNoSideEffect notin op.flags: + markSideEffect(tracked, a) notNilCheck(tracked, n, paramType) proc breaksBlock(n: PNode): bool = @@ -684,6 +698,7 @@ proc track(tracked: PEffects, n: PNode) = if a.sym == tracked.owner: tracked.isRecursive = true # even for recursive calls we need to check the lock levels (!): mergeLockLevels(tracked, n, a.sym.getLockLevel) + if sfSideEffect in a.sym.flags: markSideEffect(tracked, a) else: mergeLockLevels(tracked, n, op.lockLevel) var effectList = op.n.sons[0] @@ -702,6 +717,10 @@ proc track(tracked: PEffects, n: PNode) = if not (a.kind == nkSym and a.sym == tracked.owner): if warnGcUnsafe in gNotes: warnAboutGcUnsafe(n) markGcUnsafe(tracked, a) + if tfNoSideEffect notin op.flags and not importedFromC(a): + # and it's not a recursive call: + if not (a.kind == nkSym and a.sym == tracked.owner): + markSideEffect(tracked, a) for i in 1 .. <len(n): trackOperand(tracked, n.sons[i], paramType(op, i)) if a.kind == nkSym and a.sym.magic in {mNew, mNewFinalize, mNewSeq}: # may not look like an assignment, but it is: @@ -793,9 +812,6 @@ proc track(tracked: PEffects, n: PNode) = proc subtypeRelation(spec, real: PNode): bool = result = safeInheritanceDiff(real.excType, spec.typ) <= 0 -proc symbolPredicate(spec, real: PNode): bool = - result = real.sym.id == spec.sym.id - proc checkRaisesSpec(spec, real: PNode, msg: string, hints: bool; effectPredicate: proc (a, b: PNode): bool {.nimcall.}) = # check that any real exception is listed in 'spec'; mark those as used; @@ -912,8 +928,15 @@ proc trackProc*(s: PSym, body: PNode) = else: listGcUnsafety(s, onlyWarning=true) #localError(s.info, warnGcUnsafe2, s.name.s) + if sfNoSideEffect in s.flags and t.hasSideEffect: + when false: + listGcUnsafety(s, onlyWarning=false) + else: + localError(s.info, errXhasSideEffects, s.name.s) if not t.gcUnsafe: s.typ.flags.incl tfGcSafe + if not t.hasSideEffect and sfSideEffect notin s.flags: + s.typ.flags.incl tfNoSideEffect if s.typ.lockLevel == UnspecifiedLockLevel: s.typ.lockLevel = t.maxLockLevel elif t.maxLockLevel > s.typ.lockLevel: diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim index 5d1770a32..cd96600ec 100644 --- a/compiler/semstmts.nim +++ b/compiler/semstmts.nim @@ -304,8 +304,14 @@ proc semTry(c: PContext, n: PNode): PNode = proc fitRemoveHiddenConv(c: PContext, typ: PType, n: PNode): PNode = result = fitNode(c, typ, n) if result.kind in {nkHiddenStdConv, nkHiddenSubConv}: - changeType(result.sons[1], typ, check=true) - result = result.sons[1] + let r1 = result.sons[1] + if r1.kind in {nkCharLit..nkUInt64Lit} and typ.skipTypes(abstractRange).kind in {tyFloat..tyFloat128}: + result = newFloatNode(nkFloatLit, BiggestFloat r1.intVal) + result.info = n.info + result.typ = typ + else: + changeType(r1, typ, check=true) + result = r1 elif not sameType(result.typ, typ): changeType(result, typ, check=false) @@ -1135,11 +1141,6 @@ type TProcCompilationSteps = enum stepRegisterSymbol, stepDetermineType, - stepCompileBody - -proc isForwardDecl(s: PSym): bool = - internalAssert s.kind == skProc - result = s.ast[bodyPos].kind != nkEmpty proc semProcAux(c: PContext, n: PNode, kind: TSymKind, validPragmas: TSpecialWords, @@ -1177,8 +1178,6 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind, s.ast = n #s.scope = c.currentScope - # if typeIsDetermined: assert phase == stepCompileBody - # else: assert phase == stepDetermineType # before compiling the proc body, set as current the scope # where the proc was declared let oldScope = c.currentScope @@ -1228,7 +1227,8 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind, implicitPragmas(c, s, n, validPragmas) else: if n.sons[pragmasPos].kind != nkEmpty: - localError(n.sons[pragmasPos].info, errPragmaOnlyInHeaderOfProc) + localError(n.sons[pragmasPos].info, errPragmaOnlyInHeaderOfProcX, + "'" & proto.name.s & "' from " & $proto.info) if sfForward notin proto.flags: wrongRedefinition(n.info, proto.name.s) excl(proto.flags, sfForward) @@ -1397,6 +1397,11 @@ proc semMacroDef(c: PContext, n: PNode): PNode = if namePos >= result.safeLen: return result var s = result.sons[namePos].sym var t = s.typ + var allUntyped = true + for i in 1 .. t.n.len-1: + let param = t.n.sons[i].sym + if param.typ.kind != tyExpr: allUntyped = false + if allUntyped: incl(s.flags, sfAllUntyped) if t.sons[0] == nil: localError(n.info, errXNeedsReturnType, "macro") if n.sons[bodyPos].kind == nkEmpty: localError(n.info, errImplOfXexpected, s.name.s) @@ -1560,8 +1565,3 @@ proc semStmtList(c: PContext, n: PNode, flags: TExprFlags): PNode = proc semStmt(c: PContext, n: PNode): PNode = # now: simply an alias: result = semExprNoType(c, n) - -proc semStmtScope(c: PContext, n: PNode): PNode = - openScope(c) - result = semStmt(c, n) - closeScope(c) diff --git a/compiler/semtempl.nim b/compiler/semtempl.nim index 20b5071ac..dfe3ded0d 100644 --- a/compiler/semtempl.nim +++ b/compiler/semtempl.nim @@ -287,35 +287,6 @@ proc semTemplBodySons(c: var TemplCtx, n: PNode): PNode = for i in 0.. < n.len: result.sons[i] = semTemplBody(c, n.sons[i]) -proc wrapInBind(c: var TemplCtx; n: PNode; opr: string): PNode = - let ident = getIdent(opr) - if ident.id in c.toInject: return n - - let s = searchInScopes(c.c, ident) - if s != nil: - var callee: PNode - if contains(c.toBind, s.id): - callee = symChoice(c.c, n, s, scClosed) - elif contains(c.toMixin, s.name.id): - callee = symChoice(c.c, n, s, scForceOpen) - elif s.owner == c.owner and sfGenSym in s.flags: - # template tmp[T](x: var seq[T]) = - # var yz: T - incl(s.flags, sfUsed) - callee = newSymNode(s, n.info) - styleCheckUse(n.info, s) - else: - callee = semTemplSymbol(c.c, n, s) - - let call = newNodeI(nkCall, n.info) - call.add(callee) - for i in 0 .. n.len-1: call.add(n[i]) - result = newNodeI(nkBind, n.info, 2) - result.sons[0] = n - result.sons[1] = call - else: - result = n - proc oprIsRoof(n: PNode): bool = const roof = "^" case n.kind diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim index 9d00c06ca..3834d0b51 100644 --- a/compiler/semtypes.nim +++ b/compiler/semtypes.nim @@ -110,6 +110,8 @@ proc semContainer(c: PContext, n: PNode, kind: TTypeKind, kindStr: string, result = newOrPrevType(kind, prev, c) if sonsLen(n) == 2: var base = semTypeNode(c, n.sons[1], nil) + if base.kind == tyVoid: + localError(n.info, errTIsNotAConcreteType, typeToString(base)) addSonSkipIntLit(result, base) else: localError(n.info, errXExpectsOneTypeParam, kindStr) diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim index ce4f893ea..7cdaa197d 100644 --- a/compiler/sigmatch.nim +++ b/compiler/sigmatch.nim @@ -221,13 +221,14 @@ proc cmpCandidates*(a, b: TCandidate): int = if result != 0: return result = a.convMatches - b.convMatches if result != 0: return - result = a.calleeScope - b.calleeScope - if result != 0: return # the other way round because of other semantics: result = b.inheritancePenalty - a.inheritancePenalty if result != 0: return # prefer more specialized generic over more general generic: result = complexDisambiguation(a.callee, b.callee) + # only as a last resort, consider scoping: + if result != 0: return + result = a.calleeScope - b.calleeScope proc writeMatches*(c: TCandidate) = writeLine(stdout, "exact matches: " & $c.exactMatches) @@ -1309,8 +1310,9 @@ proc localConvMatch(c: PContext, m: var TCandidate, f, a: PType, var call = newNodeI(nkCall, arg.info) call.add(f.n.copyTree) call.add(arg.copyTree) - result = c.semOverloadedCall(c, call, call, routineKinds) + result = c.semExpr(c, call) if result != nil: + if result.typ == nil: return nil # resulting type must be consistent with the other arguments: var r = typeRel(m, f.sons[0], result.typ) if r < isGeneric: return nil @@ -1319,13 +1321,6 @@ proc localConvMatch(c: PContext, m: var TCandidate, f, a: PType, if r == isGeneric: result.typ = getInstantiatedType(c, arg, m, base(f)) m.baseTypeMatch = true - # bug #4545: allow the call to go through a 'var T': - let vt = result.sons[0].typ.sons[1] - if vt.kind == tyVar: - let x = result.sons[1] - let va = newNodeIT(nkHiddenAddr, x.info, vt) - va.add x - result.sons[1] = va proc incMatches(m: var TCandidate; r: TTypeRelation; convMatch = 1) = case r diff --git a/compiler/transf.nim b/compiler/transf.nim index d64276cfb..5cd5e298b 100644 --- a/compiler/transf.nim +++ b/compiler/transf.nim @@ -474,12 +474,14 @@ proc transformConv(c: PTransf, n: PNode): PTransNode = type TPutArgInto = enum - paDirectMapping, paFastAsgn, paVarAsgn + paDirectMapping, paFastAsgn, paVarAsgn, paComplexOpenarray proc putArgInto(arg: PNode, formal: PType): TPutArgInto = # This analyses how to treat the mapping "formal <-> arg" in an # inline context. if skipTypes(formal, abstractInst).kind in {tyOpenArray, tyVarargs}: + if arg.kind == nkStmtListExpr: + return paComplexOpenarray return paDirectMapping # XXX really correct? # what if ``arg`` has side-effects? case arg.kind @@ -569,6 +571,14 @@ proc transformFor(c: PTransf, n: PNode): PTransNode = assert(skipTypes(formal.typ, abstractInst).kind == tyVar) idNodeTablePut(newC.mapping, formal, arg) # XXX BUG still not correct if the arg has a side effect! + of paComplexOpenarray: + let typ = newType(tySequence, formal.owner) + addSonSkipIntLit(typ, formal.typ.sons[0]) + var temp = newTemp(c, typ, formal.info) + addVar(v, temp) + add(stmtList, newAsgnStmt(c, temp, arg.PTransNode)) + idNodeTablePut(newC.mapping, formal, temp) + var body = iter.getBody.copyTree pushInfoContext(n.info) # XXX optimize this somehow. But the check "c.inlining" is not correct: @@ -584,13 +594,6 @@ proc transformFor(c: PTransf, n: PNode): PTransNode = popTransCon(c) # echo "transformed: ", stmtList.PNode.renderTree -proc getMagicOp(call: PNode): TMagic = - if call.sons[0].kind == nkSym and - call.sons[0].sym.kind in {skProc, skMethod, skConverter}: - result = call.sons[0].sym.magic - else: - result = mNone - proc transformCase(c: PTransf, n: PNode): PTransNode = # removes `elif` branches of a case stmt # adds ``else: nil`` if needed for the code generator diff --git a/compiler/types.nim b/compiler/types.nim index ff60730f0..4690d5a1f 100644 --- a/compiler/types.nim +++ b/compiler/types.nim @@ -48,6 +48,8 @@ proc isOrdinalType*(t: PType): bool proc enumHasHoles*(t: PType): bool const + # TODO: Remove tyTypeDesc from each abstractX and (where necessary) + # replace with typedescX abstractPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyDistinct, tyOrdinal, tyConst, tyMutable, tyTypeDesc} abstractVar* = {tyVar, tyGenericInst, tyDistinct, tyOrdinal, @@ -61,6 +63,7 @@ const skipPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyConst, tyMutable, tyTypeDesc} + # typedescX is used if we're sure tyTypeDesc should be included (or skipped) typedescPtrs* = abstractPtrs + {tyTypeDesc} typedescInst* = abstractInst + {tyTypeDesc} @@ -142,10 +145,6 @@ proc elemType*(t: PType): PType = else: result = t.lastSon assert(result != nil) -proc skipGeneric(t: PType): PType = - result = t - while result.kind == tyGenericInst: result = lastSon(result) - proc isOrdinalType(t: PType): bool = assert(t != nil) const @@ -575,10 +574,6 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string = result = typeToStr[t.kind] result.addTypeFlags(t) -proc resultType(t: PType): PType = - assert(t.kind == tyProc) - result = t.sons[0] # nil is allowed - proc base(t: PType): PType = result = t.sons[0] @@ -658,7 +653,14 @@ proc lengthOrd(t: PType): BiggestInt = case t.kind of tyInt64, tyInt32, tyInt: result = lastOrd(t) of tyDistinct, tyConst, tyMutable: result = lengthOrd(t.sons[0]) - else: result = lastOrd(t) - firstOrd(t) + 1 + else: + let last = lastOrd t + let first = firstOrd t + # XXX use a better overflow check here: + if last == high(BiggestInt) and first <= 0: + result = last + else: + result = lastOrd(t) - firstOrd(t) + 1 # -------------- type equality ----------------------------------------------- @@ -769,18 +771,6 @@ proc equalParams(a, b: PNode): TParamsEquality = result = paramsIncompatible # overloading by different # result types does not work -proc sameLiteral(x, y: PNode): bool = - if x.kind == y.kind: - case x.kind - of nkCharLit..nkInt64Lit: result = x.intVal == y.intVal - of nkFloatLit..nkFloat64Lit: result = x.floatVal == y.floatVal - of nkNilLit: result = true - else: assert(false) - -proc sameRanges(a, b: PNode): bool = - result = sameLiteral(a.sons[0], b.sons[0]) and - sameLiteral(a.sons[1], b.sons[1]) - proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool = # two tuples are equivalent iff the names, types and positions are the same; # however, both types may not have any field names (t.n may be nil) which @@ -1067,10 +1057,10 @@ proc typeAllowedNode(marker: var IntSet, n: PNode, kind: TSymKind, of nkNone..nkNilLit: discard else: + if n.kind == nkRecCase and kind in {skProc, skConst}: + return n[0].typ for i in countup(0, sonsLen(n) - 1): let it = n.sons[i] - if it.kind == nkRecCase and kind in {skProc, skConst}: - return n.typ result = typeAllowedNode(marker, it, kind, flags) if result != nil: break diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim index 7dbf6f801..b40ca1058 100644 --- a/compiler/vmdeps.nim +++ b/compiler/vmdeps.nim @@ -109,10 +109,6 @@ proc mapTypeToAstX(t: PType; info: TLineInfo; mapTypeToBracketX(name, m, t, info, inst) template newNodeX(kind): untyped = newNodeIT(kind, if t.n.isNil: info else: t.n.info, t) - template newIdent(s): untyped = - var r = newNodeX(nkIdent) - r.add !s - r template newIdentDefs(n,t): untyped = var id = newNodeX(nkIdentDefs) id.add n # name diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim index 61ab65360..6bfc33f00 100644 --- a/compiler/vmgen.nim +++ b/compiler/vmgen.nim @@ -748,7 +748,7 @@ proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) = let tmp = c.genx(arg) if dest < 0: dest = c.getTemp(n.typ) c.gABC(n, opc, dest, tmp) - c.gABx(n, opc, 0, genType(c, n.typ)) + c.gABx(n, opc, 0, genType(c, n.typ.skipTypes({tyStatic}))) c.gABx(n, opc, 0, genType(c, arg.typ.skipTypes({tyStatic}))) c.freeTemp(tmp) @@ -1127,14 +1127,6 @@ proc fitsRegister*(t: PType): bool = t.skipTypes(abstractInst-{tyTypeDesc}).kind in { tyRange, tyEnum, tyBool, tyInt..tyUInt64, tyChar} -proc requiresCopy(n: PNode): bool = - if n.typ.skipTypes(abstractInst-{tyTypeDesc}).kind in atomicTypes: - result = false - elif n.kind in ({nkCurly, nkBracket, nkPar, nkObjConstr}+nkCallKinds): - result = false - else: - result = true - proc unneededIndirection(n: PNode): bool = n.typ.skipTypes(abstractInst-{tyTypeDesc}).kind == tyRef @@ -1215,8 +1207,6 @@ proc whichAsgnOpc(n: PNode): TOpcode = else: opcAsgnComplex -proc isRef(t: PType): bool = t.skipTypes(abstractRange-{tyTypeDesc}).kind == tyRef - proc whichAsgnOpc(n: PNode; opc: TOpcode): TOpcode = opc proc genAsgn(c: PCtx; dest: TDest; ri: PNode; requiresCopy: bool) = @@ -1268,9 +1258,6 @@ proc isTemp(c: PCtx; dest: TDest): bool = template needsAdditionalCopy(n): untyped = not c.isTemp(dest) and not fitsRegister(n.typ) -proc skipDeref(n: PNode): PNode = - result = if n.kind in {nkDerefExpr, nkHiddenDeref}: n.sons[0] else: n - proc preventFalseAlias(c: PCtx; n: PNode; opc: TOpcode; dest, idx, value: TRegister) = # opcLdObj et al really means "load address". We sometimes have to create a @@ -1848,7 +1835,6 @@ proc genParams(c: PCtx; params: PNode) = # res.sym.position is already 0 c.prc.slots[0] = (inUse: true, kind: slotFixedVar) for i in 1.. <params.len: - let param = params.sons[i].sym c.prc.slots[i] = (inUse: true, kind: slotFixedLet) c.prc.maxSlots = max(params.len, 1) diff --git a/doc/manual/ffi.txt b/doc/manual/ffi.txt index 5055f18af..d7d9596d2 100644 --- a/doc/manual/ffi.txt +++ b/doc/manual/ffi.txt @@ -16,12 +16,20 @@ spelled*: .. code-block:: proc printf(formatstr: cstring) {.header: "<stdio.h>", importc: "printf", varargs.} -Note that this pragma is somewhat of a misnomer: Other backends will provide +Note that this pragma is somewhat of a misnomer: Other backends do provide the same feature under the same name. Also, if one is interfacing with C++ the `ImportCpp pragma <manual.html#implementation-specific-pragmas-importcpp-pragma>`_ and interfacing with Objective-C the `ImportObjC pragma <manual.html#implementation-specific-pragmas-importobjc-pragma>`_ can be used. +The string literal passed to ``importc`` can be a format string: + +.. code-block:: Nim + proc p(s: cstring) {.importc: "prefix$1".} + +In the example the external name of ``p`` is set to ``prefixp``. Only ``$1`` +is available and a literal dollar sign must be written as ``$$``. + Exportc pragma -------------- @@ -33,9 +41,19 @@ name is the Nim identifier *exactly as spelled*: .. code-block:: Nim proc callme(formatstr: cstring) {.exportc: "callMe", varargs.} -Note that this pragma is somewhat of a misnomer: Other backends will provide +Note that this pragma is somewhat of a misnomer: Other backends do provide the same feature under the same name. +The string literal passed to ``exportc`` can be a format string: + +.. code-block:: Nim + proc p(s: string) {.exportc: "prefix$1".} = + echo s + +In the example the external name of ``p`` is set to ``prefixp``. Only ``$1`` +is available and a literal dollar sign must be written as ``$$``. + + Extern pragma ------------- @@ -46,7 +64,9 @@ mangling. The string literal passed to ``extern`` can be a format string: proc p(s: string) {.extern: "prefix$1".} = echo s -In the example the external name of ``p`` is set to ``prefixp``. +In the example the external name of ``p`` is set to ``prefixp``. Only ``$1`` +is available and a literal dollar sign must be written as ``$$``. + Bycopy pragma diff --git a/koch.nim b/koch.nim index 04f6a4e4e..eb25a7480 100644 --- a/koch.nim +++ b/koch.nim @@ -244,11 +244,13 @@ proc boot(args: string) = var finalDest = "bin" / "nim".exe # default to use the 'c' command: let bootOptions = if args.len == 0 or args.startsWith("-"): "c" else: "" + let smartNimcache = if "release" in args: "rnimcache" else: "dnimcache" copyExe(findStartNim(), 0.thVersion) for i in 0..2: echo "iteration: ", i+1 - exec i.thVersion & " $# $# compiler" / "nim.nim" % [bootOptions, args] + exec i.thVersion & " $# $# --nimcache:$# compiler" / "nim.nim" % [bootOptions, args, + smartNimcache] if sameFileContent(output, i.thVersion): copyExe(output, finalDest) echo "executables are equal: SUCCESS!" diff --git a/lib/core/macros.nim b/lib/core/macros.nim index 4296cb0ae..19452b4a8 100644 --- a/lib/core/macros.nim +++ b/lib/core/macros.nim @@ -333,7 +333,7 @@ proc parseStmt*(s: string): NimNode {.noSideEffect, compileTime.} = let x = internalErrorFlag() if x.len > 0: raise newException(ValueError, x) -proc getAst*(macroOrTemplate: expr): NimNode {.magic: "ExpandToAst", noSideEffect.} +proc getAst*(macroOrTemplate: untyped): NimNode {.magic: "ExpandToAst", noSideEffect.} ## Obtains the AST nodes returned from a macro or template invocation. ## Example: ## @@ -342,7 +342,7 @@ proc getAst*(macroOrTemplate: expr): NimNode {.magic: "ExpandToAst", noSideEffec ## macro FooMacro() = ## var ast = getAst(BarTemplate()) -proc quote*(bl: stmt, op = "``"): NimNode {.magic: "QuoteAst", noSideEffect.} +proc quote*(bl: typed, op = "``"): NimNode {.magic: "QuoteAst", noSideEffect.} ## Quasi-quoting operator. ## Accepts an expression or a block and returns the AST that represents it. ## Within the quoted AST, you are able to interpolate NimNode expressions @@ -663,7 +663,7 @@ proc copyChildrenTo*(src, dest: NimNode) {.compileTime.}= for i in 0 .. < src.len: dest.add src[i].copyNimTree -template expectRoutine(node: NimNode): stmt = +template expectRoutine(node: NimNode) = expectKind(node, RoutineNodes) proc name*(someProc: NimNode): NimNode {.compileTime.} = @@ -870,7 +870,7 @@ proc hasArgOfName* (params: NimNode; name: string): bool {.compiletime.}= ## Search nnkFormalParams for an argument. assert params.kind == nnkFormalParams for i in 1 .. <params.len: - template node: expr = params[i] + template node: untyped = params[i] if name.eqIdent( $ node[0]): return true @@ -891,7 +891,7 @@ proc boolVal*(n: NimNode): bool {.compileTime, noSideEffect.} = else: n == bindSym"true" # hacky solution for now when not defined(booting): - template emit*(e: static[string]): stmt {.deprecated.} = + template emit*(e: static[string]): untyped {.deprecated.} = ## accepts a single string argument and treats it as nim code ## that should be inserted verbatim in the program ## Example: @@ -900,6 +900,6 @@ when not defined(booting): ## emit("echo " & '"' & "hello world".toUpper & '"') ## ## Deprecated since version 0.15 since it's so rarely useful. - macro payload: stmt {.gensym.} = + macro payload: untyped {.gensym.} = result = parseStmt(e) payload() diff --git a/lib/deprecated/pure/ftpclient.nim b/lib/deprecated/pure/ftpclient.nim index 1188c0795..ed2f14450 100644 --- a/lib/deprecated/pure/ftpclient.nim +++ b/lib/deprecated/pure/ftpclient.nim @@ -129,10 +129,10 @@ proc ftpClient*(address: string, port = Port(21), result.csock = socket() if result.csock == invalidSocket: raiseOSError(osLastError()) -template blockingOperation(sock: Socket, body: stmt) {.immediate.} = +template blockingOperation(sock: Socket, body: untyped) = body -template blockingOperation(sock: asyncio.AsyncSocket, body: stmt) {.immediate.} = +template blockingOperation(sock: asyncio.AsyncSocket, body: untyped) = sock.setBlocking(true) body sock.setBlocking(false) diff --git a/lib/pure/algorithm.nim b/lib/pure/algorithm.nim index eee4fab22..b83daf245 100644 --- a/lib/pure/algorithm.nim +++ b/lib/pure/algorithm.nim @@ -231,7 +231,7 @@ template sortedByIt*(seq1, op: untyped): untyped = ## ## echo people.sortedByIt((it.age, it.name)) ## - var result {.gensym.} = sorted(seq1, proc(x, y: type(seq1[0])): int = + var result = sorted(seq1, proc(x, y: type(seq1[0])): int = var it {.inject.} = x let a = op it = y diff --git a/lib/pure/collections/sequtils.nim b/lib/pure/collections/sequtils.nim index e277ee9e8..f458b7636 100644 --- a/lib/pure/collections/sequtils.nim +++ b/lib/pure/collections/sequtils.nim @@ -371,7 +371,7 @@ template filterIt*(seq1, pred: untyped): untyped = ## notAcceptable = filterIt(temperatures, it > 50 or it < -10) ## assert acceptable == @[-2.0, 24.5, 44.31] ## assert notAcceptable == @[-272.15, 99.9, -113.44] - var result {.gensym.} = newSeq[type(seq1[0])]() + var result = newSeq[type(seq1[0])]() for it {.inject.} in items(seq1): if pred: result.add(it) result @@ -420,7 +420,7 @@ template allIt*(seq1, pred: untyped): bool = ## let numbers = @[1, 4, 5, 8, 9, 7, 4] ## assert allIt(numbers, it < 10) == true ## assert allIt(numbers, it < 9) == false - var result {.gensym.} = true + var result = true for it {.inject.} in items(seq1): if not pred: result = false @@ -451,7 +451,7 @@ template anyIt*(seq1, pred: untyped): bool = ## let numbers = @[1, 4, 5, 8, 9, 7, 4] ## assert anyIt(numbers, it > 8) == true ## assert anyIt(numbers, it > 9) == false - var result {.gensym.} = false + var result = false for it {.inject.} in items(seq1): if pred: result = true @@ -512,7 +512,7 @@ template foldl*(sequence, operation: untyped): untyped = ## assert concatenation == "nimiscool" let s = sequence assert s.len > 0, "Can't fold empty sequences" - var result {.gensym.}: type(s[0]) + var result: type(s[0]) result = s[0] for i in 1..<s.len: let @@ -537,7 +537,7 @@ template foldl*(sequence, operation, first): untyped = ## numbers = @[0, 8, 1, 5] ## digits = foldl(numbers, a & (chr(b + ord('0'))), "") ## assert digits == "0815" - var result {.gensym.}: type(first) + var result: type(first) result = first for x in items(sequence): let @@ -574,7 +574,7 @@ template foldr*(sequence, operation: untyped): untyped = ## assert concatenation == "nimiscool" let s = sequence assert s.len > 0, "Can't fold empty sequences" - var result {.gensym.}: type(s[0]) + var result: type(s[0]) result = sequence[s.len - 1] for i in countdown(s.len - 2, 0): let @@ -598,7 +598,7 @@ template mapIt*(seq1, typ, op: untyped): untyped = ## assert strings == @["4", "8", "12", "16"] ## **Deprecated since version 0.12.0:** Use the ``mapIt(seq1, op)`` ## template instead. - var result {.gensym.}: seq[typ] = @[] + var result: seq[typ] = @[] for it {.inject.} in items(seq1): result.add(op) result @@ -662,7 +662,7 @@ template newSeqWith*(len: int, init: untyped): untyped = ## import random ## var seqRand = newSeqWith(20, random(10)) ## echo seqRand - var result {.gensym.} = newSeq[type(init)](len) + var result = newSeq[type(init)](len) for i in 0 .. <len: result[i] = init result diff --git a/lib/pure/collections/tableimpl.nim b/lib/pure/collections/tableimpl.nim index be3507137..a3dfd43a1 100644 --- a/lib/pure/collections/tableimpl.nim +++ b/lib/pure/collections/tableimpl.nim @@ -142,7 +142,8 @@ template delImpl() {.dirty.} = template clearImpl() {.dirty.} = for i in 0 .. <t.data.len: - t.data[i].hcode = 0 + when compiles(t.data[i].hcode): # CountTable records don't contain a hcode + t.data[i].hcode = 0 t.data[i].key = default(type(t.data[i].key)) t.data[i].val = default(type(t.data[i].val)) t.counter = 0 diff --git a/lib/pure/collections/tables.nim b/lib/pure/collections/tables.nim index 9308095aa..3f06762ae 100644 --- a/lib/pure/collections/tables.nim +++ b/lib/pure/collections/tables.nim @@ -118,7 +118,7 @@ template dataLen(t): untyped = len(t.data) include tableimpl -proc clear*[A, B](t: Table[A, B] | TableRef[A, B]) = +proc clear*[A, B](t: var Table[A, B] | TableRef[A, B]) = ## Resets the table so that it is empty. clearImpl() @@ -457,7 +457,7 @@ proc len*[A, B](t: OrderedTable[A, B]): int {.inline.} = ## returns the number of keys in `t`. result = t.counter -proc clear*[A, B](t: OrderedTable[A, B] | OrderedTableRef[A, B]) = +proc clear*[A, B](t: var OrderedTable[A, B] | OrderedTableRef[A, B]) = ## Resets the table so that it is empty. clearImpl() t.first = -1 @@ -786,7 +786,7 @@ proc len*[A](t: CountTable[A]): int = ## returns the number of keys in `t`. result = t.counter -proc clear*[A](t: CountTable[A] | CountTableRef[A]) = +proc clear*[A](t: var CountTable[A] | CountTableRef[A]) = ## Resets the table so that it is empty. clearImpl() t.counter = 0 diff --git a/lib/pure/concurrency/threadpool.nim b/lib/pure/concurrency/threadpool.nim index 9490dbbd5..8cdb83e19 100644 --- a/lib/pure/concurrency/threadpool.nim +++ b/lib/pure/concurrency/threadpool.nim @@ -297,9 +297,20 @@ var gSomeReady : Semaphore readyWorker: ptr Worker +# A workaround for recursion deadlock issue +# https://github.com/nim-lang/Nim/issues/4597 +var + numSlavesLock: Lock + numSlavesRunning {.guard: numSlavesLock}: int + numSlavesWaiting {.guard: numSlavesLock}: int + isSlave {.threadvar.}: bool + +numSlavesLock.initLock + gSomeReady.initSemaphore() proc slave(w: ptr Worker) {.thread.} = + isSlave = true while true: when declared(atomicStoreN): atomicStoreN(addr(w.ready), true, ATOMIC_SEQ_CST) @@ -311,7 +322,15 @@ proc slave(w: ptr Worker) {.thread.} = # XXX Somebody needs to look into this (why does this assertion fail # in Visual Studio?) when not defined(vcc): assert(not w.ready) + + withLock numSlavesLock: + inc numSlavesRunning + w.f(w, w.data) + + withLock numSlavesLock: + dec numSlavesRunning + if w.q.len != 0: w.cleanFlowVars if w.shutdown: w.shutdown = false @@ -464,10 +483,34 @@ proc nimSpawn3(fn: WorkerProc; data: pointer) {.compilerProc.} = fn(self, data) await(self.taskStarted) return - else: - await(gSomeReady) - else: - await(gSomeReady) + + if isSlave: + # Run under lock until `numSlavesWaiting` increment to avoid a + # race (otherwise two last threads might start waiting together) + withLock numSlavesLock: + if numSlavesRunning <= numSlavesWaiting + 1: + # All the other slaves are waiting + # If we wait now, we-re deadlocked until + # an external spawn happens ! + if currentPoolSize < maxPoolSize: + if not workersData[currentPoolSize].initialized: + activateWorkerThread(currentPoolSize) + let w = addr(workersData[currentPoolSize]) + atomicInc currentPoolSize + if selectWorker(w, fn, data): + return + else: + # There is no place in the pool. We're deadlocked. + # echo "Deadlock!" + discard + + inc numSlavesWaiting + + await(gSomeReady) + + if isSlave: + withLock numSlavesLock: + dec numSlavesWaiting var distinguishedLock: Lock diff --git a/lib/pure/ioselects/ioselectors_kqueue.nim b/lib/pure/ioselects/ioselectors_kqueue.nim index 29a201863..3e86f19aa 100644 --- a/lib/pure/ioselects/ioselectors_kqueue.nim +++ b/lib/pure/ioselects/ioselectors_kqueue.nim @@ -16,6 +16,10 @@ const MAX_KQUEUE_CHANGE_EVENTS = 64 # Maximum number of events that can be returned. MAX_KQUEUE_RESULT_EVENTS = 64 + # SIG_IGN and SIG_DFL declared in posix.nim as variables, but we need them + # to be constants and GC-safe. + SIG_DFL = cast[proc(x: cint) {.noconv,gcsafe.}](0) + SIG_IGN = cast[proc(x: cint) {.noconv,gcsafe.}](1) when defined(macosx) or defined(freebsd): when defined(macosx): diff --git a/lib/pure/json.nim b/lib/pure/json.nim index 19947fbc2..c76bbc3b5 100644 --- a/lib/pure/json.nim +++ b/lib/pure/json.nim @@ -580,7 +580,7 @@ type of JNull: nil of JObject: - fields*: Table[string, JsonNode] + fields*: OrderedTable[string, JsonNode] of JArray: elems*: seq[JsonNode] @@ -630,7 +630,7 @@ proc newJObject*(): JsonNode = ## Creates a new `JObject JsonNode` new(result) result.kind = JObject - result.fields = initTable[string, JsonNode](4) + result.fields = initOrderedTable[string, JsonNode](4) proc newJArray*(): JsonNode = ## Creates a new `JArray JsonNode` @@ -670,8 +670,8 @@ proc getBVal*(n: JsonNode, default: bool = false): bool = else: return n.bval proc getFields*(n: JsonNode, - default = initTable[string, JsonNode](4)): - Table[string, JsonNode] = + default = initOrderedTable[string, JsonNode](4)): + OrderedTable[string, JsonNode] = ## Retrieves the key, value pairs of a `JObject JsonNode`. ## ## Returns ``default`` if ``n`` is not a ``JObject``, or if ``n`` is nil. @@ -760,12 +760,12 @@ proc toJson(x: NimNode): NimNode {.compiletime.} = result = prefix(result, "%") -macro `%*`*(x: expr): expr = +macro `%*`*(x: untyped): untyped = ## Convert an expression to a JsonNode directly, without having to specify ## `%` for every element. result = toJson(x) -proc `==`* (a,b: JsonNode): bool = +proc `==`* (a, b: JsonNode): bool = ## Check two nodes for equality if a.isNil: if b.isNil: return true @@ -773,23 +773,29 @@ proc `==`* (a,b: JsonNode): bool = elif b.isNil or a.kind != b.kind: return false else: - return case a.kind + case a.kind of JString: - a.str == b.str + result = a.str == b.str of JInt: - a.num == b.num + result = a.num == b.num of JFloat: - a.fnum == b.fnum + result = a.fnum == b.fnum of JBool: - a.bval == b.bval + result = a.bval == b.bval of JNull: - true + result = true of JArray: - a.elems == b.elems + result = a.elems == b.elems of JObject: - a.fields == b.fields + # we cannot use OrderedTable's equality here as + # the order does not matter for equality here. + if a.fields.len != b.fields.len: return false + for key, val in a.fields: + if not b.fields.hasKey(key): return false + if b.fields[key] != val: return false + result = true -proc hash*(n: Table[string, JsonNode]): Hash {.noSideEffect.} +proc hash*(n: OrderedTable[string, JsonNode]): Hash {.noSideEffect.} proc hash*(n: JsonNode): Hash = ## Compute the hash for a JSON node @@ -807,9 +813,9 @@ proc hash*(n: JsonNode): Hash = of JString: result = hash(n.str) of JNull: - result = hash(0) + result = Hash(0) -proc hash*(n: Table[string, JsonNode]): Hash = +proc hash*(n: OrderedTable[string, JsonNode]): Hash = for key, val in n: result = result xor (hash(key) !& hash(val)) result = !$result diff --git a/lib/pure/net.nim b/lib/pure/net.nim index 9501f6dc7..bd208761b 100644 --- a/lib/pure/net.nim +++ b/lib/pure/net.nim @@ -205,6 +205,10 @@ proc newSocket*(fd: SocketHandle, domain: Domain = AF_INET, if buffered: result.currPos = 0 + # Set SO_NOSIGPIPE on OS X. + when defined(macosx): + setSockOptInt(fd, SOL_SOCKET, SO_NOSIGPIPE, 1) + proc newSocket*(domain, sockType, protocol: cint, buffered = true): Socket = ## Creates a new socket. ## @@ -342,8 +346,6 @@ when defineSsl: result = SSLContext(context: newCTX, extraInternalIndex: 0, referencedData: initSet[int]()) result.extraInternalIndex = getExtraDataIndex(result) - # The PSK callback functions assume the internal index is 0. - assert result.extraInternalIndex == 0 let extraInternal = new(SslContextExtraInternal) result.setExtraData(result.extraInternalIndex, extraInternal) @@ -392,6 +394,8 @@ when defineSsl: ## ## Only used in PSK ciphersuites. ctx.getExtraInternal().clientGetPskFunc = fun + assert ctx.extraInternalIndex == 0, + "The pskClientCallback assumes the extraInternalIndex is 0" ctx.context.SSL_CTX_set_psk_client_callback( if fun == nil: nil else: pskClientCallback) diff --git a/lib/pure/oids.nim b/lib/pure/oids.nim index fca10dab6..e4c97b260 100644 --- a/lib/pure/oids.nim +++ b/lib/pure/oids.nim @@ -74,8 +74,7 @@ proc genOid*(): Oid = var t = gettime(nil) - var i = int32(incr) - atomicInc(incr) + var i = int32(atomicInc(incr)) if fuzz == 0: # racy, but fine semantically: diff --git a/lib/pure/times.nim b/lib/pure/times.nim index d6eb29e1c..b78a2b966 100644 --- a/lib/pure/times.nim +++ b/lib/pure/times.nim @@ -1248,8 +1248,11 @@ proc parse*(value, layout: string): TimeInfo = else: parseToken(info, token, value, j) token = "" - # Reset weekday as it might not have been provided and the default may be wrong - info.weekday = getLocalTime(toTime(info)).weekday + # Reset weekday (might not have been provided and the default may be wrong) + # and yearday (is never provided directly and therefore probably wrong) + let processed = getLocalTime(toTime(info)) + info.weekday = processed.weekday + info.yearday = processed.yearday return info # Leap year calculations are adapted from: diff --git a/lib/pure/unicode.nim b/lib/pure/unicode.nim index 0cbe8de7a..6ba966816 100644 --- a/lib/pure/unicode.nim +++ b/lib/pure/unicode.nim @@ -24,7 +24,7 @@ proc `<=%`*(a, b: Rune): bool = return int(a) <=% int(b) proc `<%`*(a, b: Rune): bool = return int(a) <% int(b) proc `==`*(a, b: Rune): bool = return int(a) == int(b) -template ones(n: expr): expr = ((1 shl n)-1) +template ones(n: untyped): untyped = ((1 shl n)-1) proc runeLen*(s: string): int {.rtl, extern: "nuc$1".} = ## Returns the number of Unicode characters of the string ``s`` @@ -49,7 +49,7 @@ proc runeLenAt*(s: string, i: Natural): int = elif ord(s[i]) shr 1 == 0b1111110: result = 6 else: result = 1 -template fastRuneAt*(s: string, i: int, result: expr, doInc = true) = +template fastRuneAt*(s: string, i: int, result: untyped, doInc = true) = ## Returns the Unicode character ``s[i]`` in ``result``. If ``doInc == true`` ## ``i`` is incremented by the number of bytes that have been processed. bind ones @@ -1628,7 +1628,7 @@ proc reversed*(s: string): string = blockPos = 0 r: Rune - template reverseUntil(pos): stmt = + template reverseUntil(pos) = var j = pos - 1 while j > blockPos: result[newPos] = s[j] diff --git a/lib/pure/unittest.nim b/lib/pure/unittest.nim index 92ddc3e75..0fc2e441e 100644 --- a/lib/pure/unittest.nim +++ b/lib/pure/unittest.nim @@ -77,6 +77,15 @@ checkpoints = @[] proc shouldRun(testName: string): bool = result = true +proc startSuite(name: string) = + template rawPrint() = echo("\n[Suite] ", name) + when not defined(ECMAScript): + if colorOutput: + styledEcho styleBright, fgBlue, "\n[Suite] ", fgWhite, name + else: rawPrint() + else: rawPrint() + + template suite*(name, body) {.dirty.} = ## Declare a test suite identified by `name` with optional ``setup`` ## and/or ``teardown`` section. @@ -103,9 +112,11 @@ template suite*(name, body) {.dirty.} = ## ## .. code-block:: ## - ## [OK] 2 + 2 = 4 - ## [OK] (2 + -2) != 4 + ## [Suite] test suite for addition + ## [OK] 2 + 2 = 4 + ## [OK] (2 + -2) != 4 block: + bind startSuite template setup(setupBody: untyped) {.dirty.} = var testSetupIMPLFlag = true template testSetupIMPL: untyped {.dirty.} = setupBody @@ -114,14 +125,16 @@ template suite*(name, body) {.dirty.} = var testTeardownIMPLFlag = true template testTeardownIMPL: untyped {.dirty.} = teardownBody + let testInSuiteImplFlag = true + startSuite name body -proc testDone(name: string, s: TestStatus) = +proc testDone(name: string, s: TestStatus, indent: bool) = if s == FAILED: programResult += 1 - + let prefix = if indent: " " else: "" if outputLevel != PRINT_NONE and (outputLevel == PRINT_ALL or s == FAILED): - template rawPrint() = echo("[", $s, "] ", name) + template rawPrint() = echo(prefix, "[", $s, "] ", name) when not defined(ECMAScript): if colorOutput and not defined(ECMAScript): var color = case s @@ -129,7 +142,7 @@ proc testDone(name: string, s: TestStatus) = of FAILED: fgRed of SKIPPED: fgYellow else: fgWhite - styledEcho styleBright, color, "[", $s, "] ", fgWhite, name + styledEcho styleBright, color, prefix, "[", $s, "] ", fgWhite, name else: rawPrint() else: @@ -168,7 +181,7 @@ template test*(name, body) {.dirty.} = fail() finally: - testDone name, testStatusIMPL + testDone name, testStatusIMPL, declared(testInSuiteImplFlag) proc checkpoint*(msg: string) = ## Set a checkpoint identified by `msg`. Upon test failure all @@ -198,8 +211,9 @@ template fail* = ## ## outputs "Checkpoint A" before quitting. bind checkpoints + let prefix = if declared(testInSuiteImplFlag): " " else: "" for msg in items(checkpoints): - echo msg + echo prefix, msg when not defined(ECMAScript): if abortOnError: quit(1) diff --git a/lib/system.nim b/lib/system.nim index 62405e521..28536b89b 100644 --- a/lib/system.nim +++ b/lib/system.nim @@ -3229,7 +3229,7 @@ proc `[]`*[Idx, T](a: array[Idx, T], x: Slice[int]): seq[T] = when low(a) < 0: {.error: "Slicing for arrays with negative indices is unsupported.".} var L = x.b - x.a + 1 - newSeq(result, L) + result = newSeq[T](L) for i in 0.. <L: result[i] = a[i + x.a] proc `[]=`*[Idx, T](a: var array[Idx, T], x: Slice[int], b: openArray[T]) = diff --git a/lib/upcoming/asyncdispatch.nim b/lib/upcoming/asyncdispatch.nim index 162ac5e08..19c9815d2 100644 --- a/lib/upcoming/asyncdispatch.nim +++ b/lib/upcoming/asyncdispatch.nim @@ -1233,7 +1233,7 @@ when defined(windows) or defined(nimdoc): registerWaitableHandle(p, hProcess, flags, pcd, proccb) - proc newEvent*(): AsyncEvent = + proc newAsyncEvent*(): AsyncEvent = ## Creates new ``AsyncEvent`` object. var sa = SECURITY_ATTRIBUTES( nLength: sizeof(SECURITY_ATTRIBUTES).cint, @@ -1314,7 +1314,7 @@ else: readCB: Callback writeCB: Callback - AsyncEvent = SelectEvent + AsyncEvent* = SelectEvent PDispatcher* = ref object of PDispatcherBase selector: Selector[AsyncData] @@ -1419,7 +1419,7 @@ else: if adata.writeCB == cb: adata.writeCB = nil update = true - + when supportedPlatform: if (customSet * events) != {}: let cb = keys[i].data.readCB @@ -1686,11 +1686,11 @@ else: proc setEvent*(ev: AsyncEvent) = ## Sets new ``AsyncEvent`` to signaled state. - setEvent(SelectEvent(ev)) + ioselectors.setEvent(SelectEvent(ev)) proc close*(ev: AsyncEvent) = ## Closes ``AsyncEvent`` - close(SelectEvent(ev)) + ioselectors.close(SelectEvent(ev)) proc addEvent*(ev: AsyncEvent, cb: Callback) = ## Start watching for event ``ev``, and call callback ``cb``, when diff --git a/tests/array/troof2.nim b/tests/array/troof2.nim index d4c1a4982..e4b4f4b3c 100644 --- a/tests/array/troof2.nim +++ b/tests/array/troof2.nim @@ -2,8 +2,8 @@ discard """ errormsg: "invalid context for '^' as 'foo()' has side effects" line: "9" """ - -proc foo(): seq[int] = +# XXX This needs to be fixed properly! +proc foo(): seq[int] {.sideEffect.} = echo "ha" let f = foo()[^1] diff --git a/tests/async/tioselectors.nim b/tests/async/tioselectors.nim index ed2fea84f..2237de01a 100644 --- a/tests/async/tioselectors.nim +++ b/tests/async/tioselectors.nim @@ -79,7 +79,7 @@ when not defined(windows): var rc2 = selector.select(100) assert(len(rc2) == 1) - var read_count = posix.recv(server2_socket, addr (buffer[0]), 128, 0) + var read_count = posix.recv(server2_socket, addr buffer[0], 128, 0) if read_count == -1: raiseOSError(osLastError()) @@ -233,7 +233,7 @@ when not defined(windows): proc mt_event_test(): bool = var - thr: array [0..7, Thread[SelectEvent]] + thr: array[0..7, Thread[SelectEvent]] var selector = newSelector[int]() var sock = newNativeSocket() var event = newSelectEvent() @@ -317,7 +317,7 @@ else: var rc2 = selector.select(100) assert(len(rc2) == 1) - var read_count = recv(server2_socket, addr (buffer[0]), 128, 0) + var read_count = recv(server2_socket, addr buffer[0], 128, 0) if read_count == -1: raiseOSError(osLastError()) @@ -391,7 +391,7 @@ else: assert(selector.isEmpty()) proc mt_event_test(): bool = - var thr: array [0..7, Thread[SelectEvent]] + var thr: array[0..7, Thread[SelectEvent]] var event = newSelectEvent() for i in 0..high(thr): createThread(thr[i], event_wait_thread, event) diff --git a/tests/bind/tnicerrorforsymchoice.nim b/tests/bind/tnicerrorforsymchoice.nim index 5145fdcff..bd00188fa 100644 --- a/tests/bind/tnicerrorforsymchoice.nim +++ b/tests/bind/tnicerrorforsymchoice.nim @@ -1,6 +1,6 @@ discard """ line: 18 - errormsg: "type mismatch: got (proc (s: TScgi) | proc (client: AsyncSocket, headers: StringTableRef, input: string){.gcsafe, locks: 0.}" + errormsg: "type mismatch: got (proc (s: TScgi) | proc (client: AsyncSocket, headers: StringTableRef, input: string){.noSideEffect, gcsafe, locks: 0.}" """ #bug #442 diff --git a/tests/ccgbugs/twrong_rc_for_refarray.nim b/tests/ccgbugs/twrong_rc_for_refarray.nim new file mode 100644 index 000000000..99bdac5e1 --- /dev/null +++ b/tests/ccgbugs/twrong_rc_for_refarray.nim @@ -0,0 +1,26 @@ +discard """ + output: '''m[0][0] = 1.0 +m[0][0] = 2.0''' +""" +# bug #4653 +type + Vector = ref array[2, float64] + Matrix = ref array[2, Vector] + +proc newVector(): Vector = + new(result) + +proc newMatrix(): Matrix = + new(result) + for ix in 0 .. 1: + result[ix] = newVector() + +let m = newMatrix() + +m[0][0] = 1.0 +echo "m[0][0] = ", m[0][0] + +GC_fullCollect() + +m[0][0] = 2.0 +echo "m[0][0] = ", m[0][0] diff --git a/tests/closure/tclosure4.nim b/tests/closure/tclosure4.nim index 69c076cd5..bc134ded6 100644 --- a/tests/closure/tclosure4.nim +++ b/tests/closure/tclosure4.nim @@ -1,7 +1,7 @@ import json, tables, sequtils -proc run(json_params: Table) = +proc run(json_params: OrderedTable) = let json_elems = json_params["files"].elems # These fail compilation. var files = map(json_elems, proc (x: JsonNode): string = x.str) diff --git a/tests/collections/ttables.nim b/tests/collections/ttables.nim index a8a182a78..59fef4920 100644 --- a/tests/collections/ttables.nim +++ b/tests/collections/ttables.nim @@ -134,6 +134,29 @@ block mpairsTableTest1: block SyntaxTest: var x = toTable[int, string]({:}) +# Until #4448 is fixed, these tests will fail +when false: + block clearTableTest: + var t = data.toTable + assert t.len() != 0 + t.clear() + assert t.len() == 0 + + block clearOrderedTableTest: + var t = data.toOrderedTable + assert t.len() != 0 + t.clear() + assert t.len() == 0 + + block clearCountTableTest: + var t = initCountTable[string]() + t.inc("90", 3) + t.inc("12", 2) + t.inc("34", 1) + assert t.len() != 0 + t.clear() + assert t.len() == 0 + proc orderedTableSortTest() = var t = initOrderedTable[string, int](2) for key, val in items(data): t[key] = val diff --git a/tests/collections/ttablesref.nim b/tests/collections/ttablesref.nim index 32494f1f2..12af1ccbb 100644 --- a/tests/collections/ttablesref.nim +++ b/tests/collections/ttablesref.nim @@ -141,6 +141,31 @@ block anonZipTest: let values = @[1, 2, 3] doAssert "{a: 1, b: 2, c: 3}" == $ toTable zip(keys, values) +block clearTableTest: + var t = newTable[string, float]() + t["test"] = 1.2345 + t["111"] = 1.000043 + t["123"] = 1.23 + assert t.len() != 0 + t.clear() + assert t.len() == 0 + +block clearOrderedTableTest: + var t = newOrderedTable[string, int](2) + for key, val in items(data): t[key] = val + assert t.len() != 0 + t.clear() + assert t.len() == 0 + +block clearCountTableTest: + var t = newCountTable[string]() + t.inc("90", 3) + t.inc("12", 2) + t.inc("34", 1) + assert t.len() != 0 + t.clear() + assert t.len() == 0 + orderedTableSortTest() echo "true" diff --git a/tests/distinct/tcurrncy.nim b/tests/distinct/tcurrncy.nim index 7ad4caea4..2675de739 100644 --- a/tests/distinct/tcurrncy.nim +++ b/tests/distinct/tcurrncy.nim @@ -2,7 +2,7 @@ discard """ file: "tcurrncy.nim" output: "25" """ -template Additive(typ: typeDesc): stmt = +template Additive(typ: untyped) = proc `+` *(x, y: typ): typ {.borrow.} proc `-` *(x, y: typ): typ {.borrow.} @@ -10,18 +10,18 @@ template Additive(typ: typeDesc): stmt = proc `+` *(x: typ): typ {.borrow.} proc `-` *(x: typ): typ {.borrow.} -template Multiplicative(typ, base: typeDesc): stmt {.immediate.} = +template Multiplicative(typ, base: untyped) = 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: untyped) = proc `<` * (x, y: typ): bool {.borrow.} proc `<=` * (x, y: typ): bool {.borrow.} proc `==` * (x, y: typ): bool {.borrow.} -template DefineCurrency(typ, base: expr): stmt {.immediate.} = +template DefineCurrency(typ, base: untyped) = type typ* = distinct base Additive(typ) diff --git a/tests/effects/tsidee4.nim b/tests/effects/tsidee4.nim index 2cb88a23e..ecc79580c 100644 --- a/tests/effects/tsidee4.nim +++ b/tests/effects/tsidee4.nim @@ -1,13 +1,13 @@ discard """ file: "tsidee4.nim" - line: 15 - errormsg: "type mismatch" + line: 12 + errormsg: "'noSideEffect' can have side effects" """ var global: int -proc dontcare(x: int): int = return x +proc dontcare(x: int): int = return global proc noSideEffect(x, y: int, p: proc (a: int): int {.noSideEffect.}): int {.noSideEffect.} = return x + y + dontcare(x) diff --git a/tests/generics/tlamba_in_generic.nim b/tests/generics/tlamba_in_generic.nim new file mode 100644 index 000000000..91d417b5e --- /dev/null +++ b/tests/generics/tlamba_in_generic.nim @@ -0,0 +1,13 @@ +discard """ + output: '''!!Hi!!''' +""" +# bug #4658 +import future + +var x = 123 + +proc twice[T](f: T -> T): T -> T = (x: T) => f(f(x)) + +proc quote(s: string): string = "!" & s & "!" + +echo twice(quote)("Hi") diff --git a/tests/generics/ttempl_in_generic.nim b/tests/generics/ttempl_in_generic.nim new file mode 100644 index 000000000..f04b9d216 --- /dev/null +++ b/tests/generics/ttempl_in_generic.nim @@ -0,0 +1,8 @@ + +# bug #4600 +template foo(x: untyped): untyped = echo 1 +template foo(x,y: untyped): untyped = echo 2 + +proc bar1[T](x: T) = foo(x) +proc bar2(x: float) = foo(x,x) +proc bar3[T](x: T) = foo(x,x) diff --git a/tests/iter/tcomplex_openarray.nim b/tests/iter/tcomplex_openarray.nim new file mode 100644 index 000000000..6fc191e90 --- /dev/null +++ b/tests/iter/tcomplex_openarray.nim @@ -0,0 +1,33 @@ + +# bug #3221 + +import algorithm, math, sequtils + + +iterator permutations[T](ys: openarray[T]): seq[T] = + var + d = 1 + c = newSeq[int](ys.len) + xs = newSeq[T](ys.len) + for i, y in ys: xs[i] = y + yield xs + block outer: + while true: + while d > 1: + dec d + c[d] = 0 + while c[d] >= d: + inc d + if d >= ys.len: break outer + let i = if (d and 1) == 1: c[d] else: 0 + swap xs[i], xs[d] + yield xs + inc c[d] + +proc dig_vectors(): void = + var v_nums: seq[int] + v_nums = newSeq[int](1) + for perm in permutations(toSeq(0 .. 1)): + v_nums[0] = 1 + +dig_vectors() diff --git a/tests/js/tunittests.nim b/tests/js/tunittests.nim index 4b09c99a9..7c2e70563 100644 --- a/tests/js/tunittests.nim +++ b/tests/js/tunittests.nim @@ -1,5 +1,7 @@ discard """ - output: '''[OK] >:)''' + output: ''' +[Suite] Bacon + [OK] >:)''' """ import unittest diff --git a/tests/macros/tgettype2.nim b/tests/macros/tgettype2.nim new file mode 100644 index 000000000..f129e6e1b --- /dev/null +++ b/tests/macros/tgettype2.nim @@ -0,0 +1,67 @@ + +import macros, typetraits + +type Foo = distinct int +type Bar = distinct int +type Baz = int + +let foo = 0.Foo +let bar = 1.Bar +let baz = 2.Baz + +type MyType[T] = distinct tuple[a,b:T] +type MySimpleType = distinct tuple[a,b: int] + +var v: seq[int] +var vv: seq[float] +var t: MyType[int] +var tt: MyType[float] +var s: MySimpleType + +echo "############" +echo "#### gt ####" +echo "############" + +macro gt(a: typed): string = + let b = a.getType + var str = "gt(" & $a & "):\t" & b.repr + if b.kind == nnkSym: # bad predicat to check weather the type has an implementation + str = str & ", " & b.getType.repr # append the implementation to the result + result = newLit(str) + +echo gt(Foo) # typeDesc[Foo] +echo gt(Bar) # typeDesc[Bar] +echo gt(Baz) # typeDesc[int] shouldn't it be typeDesc[Baz]? +echo gt(foo) # distinct[int] I would prefer Foo, distinct[int] +echo gt(bar) # distinct[int] I would prefer Bar, distinct[int] +echo gt(baz) # int, int I would prefer Baz, int + +echo gt(v) # seq[int], ok +echo gt(vv) # seq[float], ok +echo gt(t) # MyType, distinct[tuple[int, int]] I would prefer MyType[int], distinct[tuple[int, int]] +echo gt(tt) # MyType, distinct[tuple[float, float]] I would prefer MyType[float], distinct[tuple[int, int]] +echo gt(s) # distinct[tuple[int, int]] I would prefer MySimpleType, distinct[tuple[int,int]] + +echo "#############" +echo "#### gt2 ####" +echo "#############" + +# get type name via typetraits + +macro gt2(a: typed): string = + let prefix = "gt2(" & $a & "): \t" + result = quote do: + `prefix` & `a`.type.name + +echo gt2(Foo) # Foo shouldn't this be typeDesc[Foo] ? +echo gt2(Bar) # Bar shouldn't this be typeDesc[Bar] ? +echo gt2(Baz) # Baz shouldn't this be typeDesc[Baz] ? +echo gt2(foo) # Foo +echo gt2(bar) # Bar +echo gt2(baz) # Baz + +echo gt2(v) # seq[int] +echo gt2(vv) # seq[float] +echo gt2(t) # MyType[system.int] why is it system.int and not just int like in seq? +echo gt2(tt) # MyType[system.float] why is it system.float and not just float like in seq? +echo gt2(s) # MySimpleType diff --git a/tests/metatype/twildtypedesc.nim b/tests/metatype/twildtypedesc.nim new file mode 100644 index 000000000..268bff0d8 --- /dev/null +++ b/tests/metatype/twildtypedesc.nim @@ -0,0 +1,43 @@ +discard """ + output: '''123 +123 +123 +123 +123 +123''' +""" + +import strutils + +proc unpack(t: typedesc[string], v: string): string = $v +proc unpack(t: typedesc[int], v: string): int = parseInt(v) + +proc unpack[T](v: string): T = + unpack T, v + +var s = "123" + +assert(unpack[string](s) is string) +assert(unpack[int](s) is int) + +echo unpack[int](s) +echo unpack[string](s) + +echo unpack(int,s) +echo unpack(string,s) + +template `as`*(x: untyped, t: typedesc): untyped = unpack(t,x) + +echo s as int +echo s as string + +# bug #4534 + +proc unit(t: typedesc[int]): t = 0 +proc unit(t: typedesc[string]): t = "" +proc unit(t: typedesc[float]): t = 0.0 + +assert unit(int) == 0 +assert unit(string) == "" +assert unit(float) == 0.0 + diff --git a/tests/stdlib/tnet_ll.nim b/tests/stdlib/tnet_ll.nim index 4d4df7c13..2ac272fd1 100644 --- a/tests/stdlib/tnet_ll.nim +++ b/tests/stdlib/tnet_ll.nim @@ -1,5 +1,8 @@ discard """ action: run + output: ''' +[Suite] inet_ntop tests +''' """ when defined(windows): diff --git a/tests/stdlib/tparseuints.nim b/tests/stdlib/tparseuints.nim index 5be3bcbd0..6b228d933 100644 --- a/tests/stdlib/tparseuints.nim +++ b/tests/stdlib/tparseuints.nim @@ -1,5 +1,7 @@ discard """ action: run + output: ''' +[Suite] parseutils''' """ import unittest, strutils diff --git a/tests/stdlib/ttime.nim b/tests/stdlib/ttime.nim index ac37196fb..3ab287c4e 100644 --- a/tests/stdlib/ttime.nim +++ b/tests/stdlib/ttime.nim @@ -39,55 +39,49 @@ doAssert t4.format("M MM MMM MMMM") == "10 10 Oct October" doAssert((t4 - initInterval(years = 2)).format("yyyy") == "1995") doAssert((t4 - initInterval(years = 7, minutes = 34, seconds = 24)).format("yyyy mm ss") == "1990 24 10") -var s = "Tuesday at 09:04am on Dec 15, 2015" -var f = "dddd at hh:mmtt on MMM d, yyyy" -doAssert($s.parse(f) == "Tue Dec 15 09:04:00 2015") +proc parseTest(s, f, sExpected: string, ydExpected: int) = + let parsed = s.parse(f) + doAssert($parsed == sExpected) + doAssert(parsed.yearday == ydExpected) +proc parseTestTimeOnly(s, f, sExpected: string) = + doAssert(sExpected in $s.parse(f)) + +parseTest("Tuesday at 09:04am on Dec 15, 2015", + "dddd at hh:mmtt on MMM d, yyyy", "Tue Dec 15 09:04:00 2015", 348) # ANSIC = "Mon Jan _2 15:04:05 2006" -s = "Thu Jan 12 15:04:05 2006" -f = "ddd MMM dd HH:mm:ss yyyy" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Thu Jan 12 15:04:05 2006", "ddd MMM dd HH:mm:ss yyyy", + "Thu Jan 12 15:04:05 2006", 11) # UnixDate = "Mon Jan _2 15:04:05 MST 2006" -s = "Thu Jan 12 15:04:05 MST 2006" -f = "ddd MMM dd HH:mm:ss ZZZ yyyy" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Thu Jan 12 15:04:05 MST 2006", "ddd MMM dd HH:mm:ss ZZZ yyyy", + "Thu Jan 12 15:04:05 2006", 11) # RubyDate = "Mon Jan 02 15:04:05 -0700 2006" -s = "Thu Jan 12 15:04:05 -07:00 2006" -f = "ddd MMM dd HH:mm:ss zzz yyyy" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Mon Feb 29 15:04:05 -07:00 2016", "ddd MMM dd HH:mm:ss zzz yyyy", + "Mon Feb 29 15:04:05 2016", 59) # leap day # RFC822 = "02 Jan 06 15:04 MST" -s = "12 Jan 16 15:04 MST" -f = "dd MMM yy HH:mm ZZZ" -doAssert($s.parse(f) == "Tue Jan 12 15:04:00 2016") +parseTest("12 Jan 16 15:04 MST", "dd MMM yy HH:mm ZZZ", + "Tue Jan 12 15:04:00 2016", 11) # RFC822Z = "02 Jan 06 15:04 -0700" # RFC822 with numeric zone -s = "12 Jan 16 15:04 -07:00" -f = "dd MMM yy HH:mm zzz" -doAssert($s.parse(f) == "Tue Jan 12 15:04:00 2016") +parseTest("01 Mar 16 15:04 -07:00", "dd MMM yy HH:mm zzz", + "Tue Mar 1 15:04:00 2016", 60) # day after february in leap year # RFC850 = "Monday, 02-Jan-06 15:04:05 MST" -s = "Monday, 12-Jan-06 15:04:05 MST" -f = "dddd, dd-MMM-yy HH:mm:ss ZZZ" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Monday, 12-Jan-06 15:04:05 MST", "dddd, dd-MMM-yy HH:mm:ss ZZZ", + "Thu Jan 12 15:04:05 2006", 11) # RFC1123 = "Mon, 02 Jan 2006 15:04:05 MST" -s = "Thu, 12 Jan 2006 15:04:05 MST" -f = "ddd, dd MMM yyyy HH:mm:ss ZZZ" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Sun, 01 Mar 2015 15:04:05 MST", "ddd, dd MMM yyyy HH:mm:ss ZZZ", + "Sun Mar 1 15:04:05 2015", 59) # day after february in non-leap year # RFC1123Z = "Mon, 02 Jan 2006 15:04:05 -0700" # RFC1123 with numeric zone -s = "Thu, 12 Jan 2006 15:04:05 -07:00" -f = "ddd, dd MMM yyyy HH:mm:ss zzz" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("Thu, 12 Jan 2006 15:04:05 -07:00", "ddd, dd MMM yyyy HH:mm:ss zzz", + "Thu Jan 12 15:04:05 2006", 11) # RFC3339 = "2006-01-02T15:04:05Z07:00" -s = "2006-01-12T15:04:05Z-07:00" -f = "yyyy-MM-ddTHH:mm:ssZzzz" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") -f = "yyyy-MM-dd'T'HH:mm:ss'Z'zzz" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("2006-01-12T15:04:05Z-07:00", "yyyy-MM-ddTHH:mm:ssZzzz", + "Thu Jan 12 15:04:05 2006", 11) +parseTest("2006-01-12T15:04:05Z-07:00", "yyyy-MM-dd'T'HH:mm:ss'Z'zzz", + "Thu Jan 12 15:04:05 2006", 11) # RFC3339Nano = "2006-01-02T15:04:05.999999999Z07:00" -s = "2006-01-12T15:04:05.999999999Z-07:00" -f = "yyyy-MM-ddTHH:mm:ss.999999999Zzzz" -doAssert($s.parse(f) == "Thu Jan 12 15:04:05 2006") +parseTest("2006-01-12T15:04:05.999999999Z-07:00", + "yyyy-MM-ddTHH:mm:ss.999999999Zzzz", "Thu Jan 12 15:04:05 2006", 11) # Kitchen = "3:04PM" -s = "3:04PM" -f = "h:mmtt" -doAssert "15:04:00" in $s.parse(f) +parseTestTimeOnly("3:04PM", "h:mmtt", "15:04:00") #when not defined(testing): # echo "Kitchen: " & $s.parse(f) # var ti = timeToTimeInfo(getTime()) diff --git a/tests/template/ttemp_in_varargs.nim b/tests/template/ttemp_in_varargs.nim new file mode 100644 index 000000000..be78e6ef2 --- /dev/null +++ b/tests/template/ttemp_in_varargs.nim @@ -0,0 +1,9 @@ +discard """ + output: '''a''' +""" + +# bug #4292 + +template foo(s: string): string = s +proc variadicProc*(v: varargs[string, foo]) = echo v[0] +variadicProc("a") diff --git a/tests/vm/tconst_float_as_int.nim b/tests/vm/tconst_float_as_int.nim new file mode 100644 index 000000000..ed84ec194 --- /dev/null +++ b/tests/vm/tconst_float_as_int.nim @@ -0,0 +1,3 @@ + +# bug #4619 +const x: float = 0 diff --git a/todo.txt b/todo.txt index 86bffcc3d..106f2bb34 100644 --- a/todo.txt +++ b/todo.txt @@ -1,6 +1,7 @@ version 1.0 battle plan ======================= +- iters for js - fix "high priority" bugs - try to fix as many compiler crashes as reasonable diff --git a/web/assets/news/images/survey/dev_os.png b/web/assets/news/images/survey/dev_os.png new file mode 100644 index 000000000..088918dc3 --- /dev/null +++ b/web/assets/news/images/survey/dev_os.png Binary files differdiff --git a/web/assets/news/images/survey/do_you_use_nim.png b/web/assets/news/images/survey/do_you_use_nim.png new file mode 100644 index 000000000..257148325 --- /dev/null +++ b/web/assets/news/images/survey/do_you_use_nim.png Binary files differdiff --git a/web/assets/news/images/survey/editors.png b/web/assets/news/images/survey/editors.png new file mode 100644 index 000000000..816ad515f --- /dev/null +++ b/web/assets/news/images/survey/editors.png Binary files differdiff --git a/web/assets/news/images/survey/nim_at_work.png b/web/assets/news/images/survey/nim_at_work.png new file mode 100644 index 000000000..f00ab1a94 --- /dev/null +++ b/web/assets/news/images/survey/nim_at_work.png Binary files differdiff --git a/web/assets/news/images/survey/nim_found.png b/web/assets/news/images/survey/nim_found.png new file mode 100644 index 000000000..a0a65b813 --- /dev/null +++ b/web/assets/news/images/survey/nim_found.png Binary files differdiff --git a/web/assets/news/images/survey/nim_time.png b/web/assets/news/images/survey/nim_time.png new file mode 100644 index 000000000..23bc4a136 --- /dev/null +++ b/web/assets/news/images/survey/nim_time.png Binary files differdiff --git a/web/assets/news/images/survey/nim_time_rust.png b/web/assets/news/images/survey/nim_time_rust.png new file mode 100644 index 000000000..9b861608a --- /dev/null +++ b/web/assets/news/images/survey/nim_time_rust.png Binary files differdiff --git a/web/assets/news/images/survey/nim_versions.png b/web/assets/news/images/survey/nim_versions.png new file mode 100644 index 000000000..ba382c93d --- /dev/null +++ b/web/assets/news/images/survey/nim_versions.png Binary files differdiff --git a/web/assets/news/images/survey/planning_to_use_at_work.png b/web/assets/news/images/survey/planning_to_use_at_work.png new file mode 100644 index 000000000..be3a50467 --- /dev/null +++ b/web/assets/news/images/survey/planning_to_use_at_work.png Binary files differdiff --git a/web/assets/news/images/survey/project_size.png b/web/assets/news/images/survey/project_size.png new file mode 100644 index 000000000..ad1359d0c --- /dev/null +++ b/web/assets/news/images/survey/project_size.png Binary files differdiff --git a/web/assets/news/images/survey/project_size_nim_rust.png b/web/assets/news/images/survey/project_size_nim_rust.png new file mode 100644 index 000000000..41e3ec8b1 --- /dev/null +++ b/web/assets/news/images/survey/project_size_nim_rust.png Binary files differdiff --git a/web/assets/news/images/survey/project_size_work.png b/web/assets/news/images/survey/project_size_work.png new file mode 100644 index 000000000..fab6e52f2 --- /dev/null +++ b/web/assets/news/images/survey/project_size_work.png Binary files differdiff --git a/web/assets/news/images/survey/reliability.png b/web/assets/news/images/survey/reliability.png new file mode 100644 index 000000000..1767e9803 --- /dev/null +++ b/web/assets/news/images/survey/reliability.png Binary files differdiff --git a/web/assets/news/images/survey/target_os.png b/web/assets/news/images/survey/target_os.png new file mode 100644 index 000000000..a36915af1 --- /dev/null +++ b/web/assets/news/images/survey/target_os.png Binary files differdiff --git a/web/assets/news/images/survey/upgrades_broke_things.png b/web/assets/news/images/survey/upgrades_broke_things.png new file mode 100644 index 000000000..28a8ee3f0 --- /dev/null +++ b/web/assets/news/images/survey/upgrades_broke_things.png Binary files differdiff --git a/web/news/nim_community_survey_results.rst b/web/news/nim_community_survey_results.rst new file mode 100644 index 000000000..49656f20a --- /dev/null +++ b/web/news/nim_community_survey_results.rst @@ -0,0 +1,317 @@ +Nim Community Survey Results +============================ + +.. container:: metadata + + Posted by Dominik Picheta on 20/08/2016 + +We have recently closed the 2016 Nim Community Survey. I am happy to +say that we have received exactly 790 responses, huge thanks go to the people +that took the time to respond. We're very thankful for this very valuable +feedback. + +This survey was inspired in part by the +`2016 State of Rust <https://blog.rust-lang.org/2016/06/30/State-of-Rust-Survey-2016.html>`_ +survey. You will note that many of the questions were modelled after +Rust's survey. One of the reasons for doing this was to allow us to easily +compare our results against the results obtained in the Rust survey. In +addition, we of course also liked many of their questions. + +Our survey ran from the 23rd of June 2016 until the 8th of August 2016. The +response numbers are impressive considering Nim's community size; at 790 they +make up just over 25% of the Rust survey's responses. + +The goal of this survey was to primarily determine how our community is using +Nim, in order to better understand how we should be improving it. In particular, +we wanted to know what people feel is missing from Nim in the lead up to +version 1.0. We have also asked our respondents about how well the Nim tools +worked, the challenges of adopting Nim, the resources that they used to learn +Nim and more. + +It is my hope that we will be able to run a similar survey in a years time, +doing so should give us an idea of whether we are improving. +With these general facts in mind, let's begin looking at specific questions. + +How did you find out about Nim? +------------------------------- + +The rationale for the first question was simple, we wanted to know where our +respondents found out about Nim. This is an interesting question for us, as +we do occassionally get users asking us why it took so long for them to hear +about Nim. It allows us to see how effective each website is at spreading the +word about Nim. + +.. raw::html + + <a href="../assets/news/images/survey/nim_found.png"> + <img src="../assets/news/images/survey/nim_found.png" alt="How did you find out about Nim?" style="width:100%"/> + </a> + +The majority of our respondents found Nim via Reddit, HackerNews or a search +engine such as Google. These results are not altogether surprising. There were +also a lot of "Other" responses, some of which were a bit more +interesting. These included multiple mentions of habrahabr.ru, Dr. Dobb's, +and lobste.rs. + +Do you use Nim? +--------------- + +Just like the Rust survey creators, we wanted to ensure that our survey was +open to both Nim users as well people who never used Nim. In addition to +those two groups, we have also included a third group of people: ex-Nim +users. All three are interesting, for many different reasons. +Nim users can tell us how they are using Nim and also how Nim's +tooling can improve. Ex-Nim users give us an +idea of why they stopped using Nim. Finally, respondents who never used Nim +can tell us the reasons for not adopting it. + +.. raw::html + + <a href="../assets/news/images/survey/do_you_use_nim.png"> + <img src="../assets/news/images/survey/do_you_use_nim.png" alt="Do you use Nim?" style="width:100%"/> + </a> + +It's nice to see that we have such a good range of respondents. The Rust survey +had a much larger number of Rust users amongst their respondents, with +no distinction between users that never used Rust and users that stopped using +Rust. + +.. raw::html + + <a href="https://blog.rust-lang.org/images/2016-06-Survey/do_you_use_rust.png"> + <img src="https://blog.rust-lang.org/images/2016-06-Survey/do_you_use_rust.png" alt="Do you use Rust?" style="width:100%"/> + </a> + +Should we consider your answers to be invalid? +---------------------------------------------- + +This was something I thought would be interesting to have, after I saw it +being used in another survey. While it does pinpoint possibly +invalid respondents, I have opted against filtering those out. Mainly because +that would require re-creating each of the charts generated by Google Forms +manually. + +.. raw::html + + <a href="../assets/news/images/survey/reliability.png"> + <img src="../assets/news/images/survey/reliability.png" alt="Should we consider your answers to be invalid?" style="width:100%"/> + </a> + +According to the responses to this question, around 94% of our responses +can be considered reliable. + +Nim users +--------- + +The following questions were answered only by the 38.9% of our respondents +who identified themselves as Nim users. + +How long have you been using Nim? +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +.. raw::html + + <a href="../assets/news/images/survey/nim_time.png"> + <img src="../assets/news/images/survey/nim_time.png" alt="How long have you been using Nim?" style="width:100%"/> + </a> + +A large proportion of our Nim users were new. This is good news as it means that +our community is growing, with a large proportion of new Nim users that could +become long-term Nimians. In total, more than 35% of Nim users can be considered +new having used Nim for less than 3 months. With 18% of Nim users that can +be considered very new having used Nim for less than a month. +This could suggest that 18% of our users have only just found out about Nim in +the last week or so and have not yet got the chance to use it extensively. + +The high percentages of long term Nim users are encouraging. +They suggest +that many users are continuing to use Nim after making it through the first +few months. The sharp drop at 7-9 months is interesting, but may simply be +due to the fact that there were fewer newcomers during that period, or it +could be because our respondents are more likely to estimate that they have +been using Nim for a year or half a year rather than the awkward 7-9 months. + +.. raw::html + + <a href="../assets/news/images/survey/nim_time_rust.png"> + <img src="../assets/news/images/survey/nim_time_rust.png" alt="Time using Nim and Rust" style="width:100%"/> + </a> + +The results for Nim and Rust are actually remarkably similar. They both show a +drop at 7-9 months, although Rust's isn't as dramatic. Nim on the other hand +has a significantly higher percentage of new Nim users. + +Do you use Nim at work? +~~~~~~~~~~~~~~~~~~~~~~~ + +An important aspect of a language's adoption is whether it is being used for +"real" work. We wanted to know how many people are using Nim in their day +jobs and under what circumstances it is used. + +.. raw::html + + <a href="../assets/news/images/survey/nim_at_work.png"> + <img src="../assets/news/images/survey/nim_at_work.png" alt="Do you use Nim at work?" style="width:100%"/> + </a> + +While a vast majority of our users are not using Nim at work, more than 25% +of them are. It's encouraging to see such a high number already, even before +we have released version 1.0. In fact, this percentage is likely close to 30%, +because many of the "Other" responses mention using Nim for the likes of +internal tools or small scripts to help with the respondent's work. + +.. raw::html + + <a href="https://blog.rust-lang.org/images/2016-06-Survey/rust_at_work.png"> + <img src="https://blog.rust-lang.org/images/2016-06-Survey/rust_at_work.png" alt="Do you use Rust at work?" style="width:100%"/> + </a> + +Interestingly, a larger percentage of Nim users are using Nim at work than +Rust users. The sample sizes are of course vastly different, but it's still an +interesting result. Combined, nearly 1/5th of Rust users are using Rust +commercially whereas more than a quarter of Nim users are using Nim +commercially. + +Approximately how large are all the Nim projects that you work on? +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Finding out how large the Nim projects worked on by Nim users are is also +very valuable. + +.. raw::html + + <a href="../assets/news/images/survey/project_size.png"> + <img src="../assets/news/images/survey/project_size.png" alt="Nim project size for all users" style="width:100%"/> + </a> + +This shows us that currently Nim is primarily being used for small scripts and +applications, with nearly 60% of the projects consisting of less than 1,000 +lines of code. This makes sense as many of our users are not using Nim +professionally, but are doing so in their spare time. + +.. raw::html + + <a href="../assets/news/images/survey/project_size_work.png"> + <img src="../assets/news/images/survey/project_size_work.png" alt="Nim project size for work users" style="width:100%"/> + </a> + +The numbers for part-time and full-time work users of Nim tell a different +story. Over 70% of the projects written by full-time users are between 10,001 +and 100,000 lines of code. Part-time users show a slightly different trend, +with many more small projects, the majority being between 1,000 and +10,000 lines of code. + +Overall it's good to see that there is a few large projects out there which are +composed of more than 100,000 lines of code. We expect to see the amount of +large projects to grow with time, especially with version 1.0 on the way. + +.. raw::html + + <a href="../assets/news/images/survey/project_size_nim_rust.png"> + <img src="../assets/news/images/survey/project_size_nim_rust.png" alt="Nim project size for work users (Nim vs. Rust)" style="width:100%"/> + </a> + +In comparison to Rust the proportion of project sizes for full-time users is +vastly different. This is likely due to our small sample size. Project sizes for +part-time users between Rust and Nim are somewhat similar, with differences of +around 10% for each project size. + +Do you plan to try to use Nim at work? +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +.. raw::html + + <a href="../assets/news/images/survey/planning_to_use_at_work.png"> + <img src="../assets/news/images/survey/planning_to_use_at_work.png" alt="Planning to use Nim at work?" style="width:100%"/> + </a> + +It's also encouraging to see that over 50% of Nim users are planning to use +Nim at work! This is slightly more than Rust's 40% and should help Nim's +adoption into even more areas. + +Nim and its tools +~~~~~~~~~~~~~~~~~ + +In this section of the survey, we wanted to find out the tools that Nim +users are utilising when developing Nim applications. + +What editor(s) do you use when writing Nim? +___________________________________________ + +Programmers are very specific when it comes to their editor of choice, because +of that it's good to know which editor is most popular among our community. + +.. raw::html + + <a href="../assets/news/images/survey/editors.png"> + <img src="../assets/news/images/survey/editors.png" alt="Editors used by Nim users" style="width:100%"/> + </a> + +Looks like Vim is the winner with almost 30%. Followed by Sublime Text and +Visual Studio Code. Aporia, the Nim IDE, gets a respectable 15.5%. There was +also more than +17% of answers which included "Other" editors, such as: Notepad++, Geany, gedit, +and Kate. + +What operating system(s) do you compile for and run your Nim projects on? +_________________________________________________________________________ + +This question gave us information about the most popular target operating +systems, as well as some of the more obscure ones. We have asked this question +to find out the platforms on which Nim applications run on most frequently. + +.. raw::html + + <a href="../assets/news/images/survey/target_os.png"> + <img src="../assets/news/images/survey/target_os.png" alt="Target operating systems" style="width:100%"/> + </a> + +This question allowed multiple choices, so each percentage is out of the total +number of respondents for this question. For example, 80.7% of the +respondents selected "Linux" but only 26.6% selected OS X. + +This makes Linux by far the most popular target for Nim applications. +Some "Other" targets included: BSD (OpenBSD, FreeBSD), iOS, Android, and +JavaScript. +It's great to see Nim being used on such a wide variety of platforms. + +What operating system(s) do you develop Nim projects on? +________________________________________________________ + +With this question, we wanted to know what operating systems are used for +development. + +.. raw::html + + <a href="../assets/news/images/survey/dev_os.png"> + <img src="../assets/news/images/survey/dev_os.png" alt="Development operating systems" style="width:100%"/> + </a> + +This question also allowed multiple choices and ended up with very similar +results. + +You can see that Linux is also the most popular developmental +platform for Nim. But it's more popular as a target platform. + +Which version(s) of Nim do you use for your applications? +_________________________________________________________ + +.. raw::html + + <a href="../assets/news/images/survey/nim_versions.png"> + <img src="../assets/news/images/survey/nim_versions.png" alt="Version use" style="width:100%"/> + </a> + +At the time of this survey, version 0.14.2 was the latest stable release. +It's no wonder that it is the most commonly used release of Nim. It's good to +see that the older versions are not used as often. The high use of ``Git HEAD (devel)`` +(nightly builds) isn't surprising, Nim is still evolving rapidly and our +release schedule is not regular or frequent. + +Once we go past the 1.0 release, we expect to see much less use of the unstable +``devel`` branch. + + + + + diff --git a/web/news/version_0_15_released.rst b/web/news/version_0_15_released.rst index 1e35fb627..2b1b216b8 100644 --- a/web/news/version_0_15_released.rst +++ b/web/news/version_0_15_released.rst @@ -10,6 +10,8 @@ Some text here. Changes affecting backwards compatibility ----------------------------------------- +- The ``json`` module uses an ``OrderedTable`` rather than a ``Table`` + for JSON objects. - De-deprecated ``re.nim`` because we have too much code using it and it got the basic API right. |