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 /compiler | |
parent | 68e30d7d52d84578fbe0f6f1c2041b150251e800 (diff) | |
parent | 7e643d73788fd0799cc970601bc75592e9610039 (diff) | |
download | Nim-884d5518dd824ff451caf5689624c824a73520d5.tar.gz |
Merged
Diffstat (limited to 'compiler')
35 files changed, 201 insertions, 610 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) |