signature hashing: more progress

This commit is contained in:
Araq
2016-11-11 08:58:42 +01:00
parent 72af7e6821
commit 860cbd3107
7 changed files with 301 additions and 300 deletions

View File

@@ -50,7 +50,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
of tyUInt64: result = uint64Literal(uint64(n.intVal))
else:
result = "(($1) $2)" % [getTypeDesc(p.module,
skipTypes(ty, abstractVarRange)), intLiteral(n.intVal)]
ty), intLiteral(n.intVal)]
of nkNilLit:
let t = skipTypes(ty, abstractVarRange)
if t.kind == tyProc and t.callConv == ccClosure:
@@ -61,7 +61,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
inc(p.module.labels)
addf(p.module.s[cfsData],
"static NIM_CONST $1 $2 = {NIM_NIL,NIM_NIL};$n",
[getTypeDesc(p.module, t), result])
[getTypeDesc(p.module, ty), result])
else:
result = rope("NIM_NIL")
of nkStrLit..nkTripleStrLit:
@@ -266,7 +266,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
# little HACK to support the new 'var T' as return type:
linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
return
var ty = skipTypes(dest.t, abstractRange)
let ty = skipTypes(dest.t, abstractRange)
case ty.kind
of tyRef:
genRefAssign(p, dest, src, flags)
@@ -315,8 +315,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
genGenericAsgn(p, dest, src, flags)
elif needsComplexAssignment(ty):
if ty.sons[0].isNil and asgnComplexity(ty.n) <= 4:
discard getTypeDesc(p.module, ty)
ty = getUniqueType(ty)
discard getTypeDesc(p.module, dest.t)
internalAssert ty.n != nil
genOptAsgnObject(p, dest, src, flags, ty.n)
else:
@@ -330,7 +329,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
useStringh(p.module)
linefmt(p, cpsStmts,
"memcpy((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n",
rdLoc(dest), rdLoc(src), getTypeDesc(p.module, ty))
rdLoc(dest), rdLoc(src), getTypeDesc(p.module, dest.t))
of tyOpenArray, tyVarargs:
# open arrays are always on the stack - really? What if a sequence is
# passed to an open array?
@@ -494,12 +493,12 @@ proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
# later via 'chckRange'
let t = e.typ.skipTypes(abstractRange)
if optOverflowCheck notin p.options:
let res = opr[m] % [getTypeDesc(p.module, t), rdLoc(a), rdLoc(b)]
let res = opr[m] % [getTypeDesc(p.module, e.typ), rdLoc(a), rdLoc(b)]
putIntoDest(p, d, e.typ, res)
else:
let res = binaryArithOverflowRaw(p, t, a, b,
if t.kind == tyInt64: prc64[m] else: prc[m])
putIntoDest(p, d, e.typ, "($#)($#)" % [getTypeDesc(p.module, t), res])
putIntoDest(p, d, e.typ, "($#)($#)" % [getTypeDesc(p.module, e.typ), res])
proc unaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
const
@@ -700,12 +699,11 @@ proc genAddr(p: BProc, e: PNode, d: var TLoc) =
template inheritLocation(d: var TLoc, a: TLoc) =
if d.k == locNone: d.s = a.s
proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc): PType =
proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc) =
initLocExpr(p, e.sons[0], a)
if e.sons[1].kind != nkSym: internalError(e.info, "genRecordFieldAux")
d.inheritLocation(a)
discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
result = a.t.getUniqueType
proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
var
@@ -714,13 +712,12 @@ proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
initLocExpr(p, e.sons[0], a)
d.inheritLocation(a)
discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
var ty = a.t.getUniqueType
var r = rdLoc(a)
case e.sons[1].kind
of nkIntLit..nkUInt64Lit: i = int(e.sons[1].intVal)
else: internalError(e.info, "genTupleElem")
addf(r, ".Field$1", [rope(i)])
putIntoDest(p, d, ty.sons[i], r, a.s)
putIntoDest(p, d, a.t.sons[i], r, a.s)
proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope): PSym =
var ty = ty
@@ -731,14 +728,15 @@ proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope): PSym =
result = lookupInRecord(ty.n, field.name)
if result != nil: break
if not p.module.compileToCpp: add(r, ".Sup")
ty = getUniqueType(ty.sons[0])
ty = ty.sons[0]
if result == nil: internalError(field.info, "genCheckedRecordField")
proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
var a: TLoc
var ty = genRecordFieldAux(p, e, d, a)
genRecordFieldAux(p, e, d, a)
var r = rdLoc(a)
var f = e.sons[1].sym
let ty = skipTypes(a.t, abstractInst)
if ty.kind == tyTuple:
# we found a unique tuple type which lacks field information
# so we use Field$i
@@ -746,7 +744,7 @@ proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
putIntoDest(p, d, f.typ, r, a.s)
else:
let field = lookupFieldAgain(p, ty, f, r)
if field.loc.r == nil: internalError(e.info, "genRecordField 3")
if field.loc.r == nil: internalError(e.info, "genRecordField 3 " & typeToString(ty))
addf(r, ".$1", [field.loc.r])
putIntoDest(p, d, field.typ, r, a.s)
#d.s = a.s
@@ -789,7 +787,8 @@ proc genFieldCheck(p: BProc, e: PNode, obj: Rope, field: PSym;
proc genCheckedRecordField(p: BProc, e: PNode, d: var TLoc) =
if optFieldCheck in p.options:
var a: TLoc
let ty = genRecordFieldAux(p, e.sons[0], d, a)
genRecordFieldAux(p, e.sons[0], d, a)
let ty = skipTypes(a.t, abstractInst)
var r = rdLoc(a)
let f = e.sons[0].sons[1].sym
let field = lookupFieldAgain(p, ty, f, r)
@@ -1029,10 +1028,10 @@ proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
var a, b, dest: TLoc
initLocExpr(p, e.sons[1], a)
initLocExpr(p, e.sons[2], b)
let bt = skipTypes(e.sons[2].typ, abstractVar)
let bt = skipTypes(e.sons[2].typ, {tyVar})
lineCg(p, cpsStmts, seqAppendPattern, [
rdLoc(a),
getTypeDesc(p.module, skipTypes(e.sons[1].typ, abstractVar)),
getTypeDesc(p.module, e.sons[1].typ),
getTypeDesc(p.module, bt)])
#if bt != b.t:
# echo "YES ", e.info, " new: ", typeToString(bt), " old: ", typeToString(b.t)
@@ -1046,16 +1045,17 @@ proc genReset(p: BProc, n: PNode) =
var a: TLoc
initLocExpr(p, n.sons[1], a)
linefmt(p, cpsStmts, "#genericReset((void*)$1, $2);$n",
addrLoc(a), genTypeInfo(p.module, skipTypes(a.t, abstractVarRange)))
addrLoc(a), genTypeInfo(p.module, skipTypes(a.t, {tyVar})))
proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) =
var sizeExpr = sizeExpr
let refType = skipTypes(a.t, abstractVarRange)
let refType = a.t
var b: TLoc
initLoc(b, locExpr, a.t, OnHeap)
let bt = refType.lastSon
if sizeExpr.isNil:
sizeExpr = "sizeof($1)" %
[getTypeDesc(p.module, skipTypes(refType.sons[0], abstractRange))]
[getTypeDesc(p.module, bt)]
let args = [getTypeDesc(p.module, refType),
genTypeInfo(p.module, refType),
sizeExpr]
@@ -1070,7 +1070,6 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) =
else:
b.r = ropecg(p.module, "($1) #newObj($2, $3)", args)
genAssignment(p, a, b, {}) # set the object type:
let bt = skipTypes(refType.sons[0], abstractRange)
genObjectInit(p, cpsStmts, bt, a, false)
proc genNew(p: BProc, e: PNode) =
@@ -1122,7 +1121,7 @@ proc genNewSeqOfCap(p: BProc; e: PNode; d: var TLoc) =
proc genConstExpr(p: BProc, n: PNode): Rope
proc handleConstExpr(p: BProc, n: PNode, d: var TLoc): bool =
if d.k == locNone and n.len > ord(n.kind == nkObjConstr) and n.isDeepConstExpr:
var t = getUniqueType(n.typ)
let t = n.typ
discard getTypeDesc(p.module, t) # so that any fields are initialized
let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
fillLoc(d, locData, t, p.module.tmpBase & rope(id), OnStatic)
@@ -1322,7 +1321,7 @@ proc genRepr(p: BProc, e: PNode, d: var TLoc) =
gcUsage(e)
proc genGetTypeInfo(p: BProc, e: PNode, d: var TLoc) =
var t = skipTypes(e.sons[1].typ, abstractVarRange)
let t = e.sons[1].typ
putIntoDest(p, d, e.typ, genTypeInfo(p.module, t))
proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
@@ -1336,7 +1335,7 @@ proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
var a = e.sons[1]
if a.kind == nkHiddenAddr: a = a.sons[0]
var typ = skipTypes(a.typ, abstractVar)
let typ = skipTypes(a.typ, abstractVar)
case typ.kind
of tyOpenArray, tyVarargs:
if op == mHigh: unaryExpr(p, e, d, "($1Len0-1)")
@@ -1363,7 +1362,7 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
assert(d.k == locNone)
initLocExpr(p, e.sons[1], a)
initLocExpr(p, e.sons[2], b)
var t = skipTypes(e.sons[1].typ, abstractVar)
let t = skipTypes(e.sons[1].typ, {tyVar})
let setLenPattern = if not p.module.compileToCpp:
"$1 = ($3) #setLengthSeq(&($1)->Sup, sizeof($4), $2);$n"
else:
@@ -1371,7 +1370,7 @@ 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])])
getTypeDesc(p.module, t.skipTypes(abstractInst).sons[0])])
gcUsage(e)
proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) =
@@ -1562,7 +1561,7 @@ proc genCast(p: BProc, e: PNode, d: var TLoc) =
var tmp: TLoc
tmp.r = "LOC$1.source" % [lbl]
linefmt(p, cpsLocals, "union { $1 source; $2 dest; } LOC$3;$n",
getTypeDesc(p.module, srct), getTypeDesc(p.module, destt), lbl)
getTypeDesc(p.module, e.sons[1].typ), getTypeDesc(p.module, e.typ), lbl)
tmp.k = locExpr
tmp.t = srct
tmp.s = OnStack
@@ -1796,7 +1795,7 @@ proc genSetConstr(p: BProc, e: PNode, d: var TLoc) =
proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
var rec: TLoc
if not handleConstExpr(p, n, d):
var t = getUniqueType(n.typ)
let t = n.typ
discard getTypeDesc(p.module, t) # so that any fields are initialized
if d.k == locNone: getTemp(p, t, d)
for i in countup(0, sonsLen(n) - 1):
@@ -1805,11 +1804,6 @@ proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
initLoc(rec, locExpr, it.typ, d.s)
rec.r = "$1.Field$2" % [rdLoc(d), rope(i)]
expr(p, it, rec)
when false:
initLoc(rec, locExpr, it.typ, d.s)
if (t.n.sons[i].kind != nkSym): InternalError(n.info, "genTupleConstr")
rec.r = "$1.$2" % [rdLoc(d), mangleRecFieldName(t.n.sons[i].sym, t)]
expr(p, it, rec)
proc isConstClosure(n: PNode): bool {.inline.} =
result = n.sons[0].kind == nkSym and isRoutine(n.sons[0].sym) and
@@ -1863,7 +1857,7 @@ proc genStmtListExpr(p: BProc, n: PNode, d: var TLoc) =
proc upConv(p: BProc, n: PNode, d: var TLoc) =
var a: TLoc
initLocExpr(p, n.sons[0], a)
var dest = skipTypes(n.typ, abstractPtrs)
let dest = skipTypes(n.typ, abstractPtrs)
if optObjCheck in p.options and not isObjLackingTypeField(dest):
var r = rdLoc(a)
var nilCheck: Rope = nil
@@ -1925,7 +1919,7 @@ proc downConv(p: BProc, n: PNode, d: var TLoc) =
putIntoDest(p, d, n.typ, r, a.s)
proc exprComplexConst(p: BProc, n: PNode, d: var TLoc) =
var t = getUniqueType(n.typ)
let t = n.typ
discard getTypeDesc(p.module, t) # so that any fields are initialized
let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
let tmp = p.module.tmpBase & rope(id)
@@ -2161,13 +2155,14 @@ proc genConstSeq(p: BProc, n: PNode, t: PType): Rope =
data.add("}")
result = getTempName(p.module)
let base = t.skipTypes(abstractInst).sons[0]
appcg(p.module, cfsData,
"NIM_CONST struct {$n" &
" #TGenericSeq Sup;$n" &
" $1 data[$2];$n" &
"} $3 = $4;$n", [
getTypeDesc(p.module, t.sons[0]), n.len.rope, result, data])
getTypeDesc(p.module, base), n.len.rope, result, data])
result = "(($1)&$2)" % [getTypeDesc(p.module, t), result]
@@ -2182,7 +2177,7 @@ proc genConstExpr(p: BProc, n: PNode): Rope =
of nkBracket, nkPar, nkClosure, nkObjConstr:
var t = skipTypes(n.typ, abstractInst)
if t.kind == tySequence:
result = genConstSeq(p, n, t)
result = genConstSeq(p, n, n.typ)
else:
result = genConstSimpleList(p, n)
else:

View File

@@ -12,7 +12,7 @@
import
ast, astalgo, ropes, options, strutils, nimlexbase, msgs, cgendata, rodutils,
intsets, platform, llstream
intsets, platform, llstream, tables, sighashes
# Careful! Section marks need to contain a tabulator so that they cannot
# be part of C string literals.
@@ -69,7 +69,7 @@ proc genSectionEnd*(ps: TCProcSection): Rope =
if compilationCachePresent:
result = rope(NimMergeEndMark & tnl)
proc writeTypeCache(a: TIdTable, s: var string) =
proc writeTypeCache(a: TypeCache, s: var string) =
var i = 0
for id, value in pairs(a):
if i == 10:
@@ -77,9 +77,9 @@ proc writeTypeCache(a: TIdTable, s: var string) =
s.add(tnl)
else:
s.add(' ')
encodeVInt(id, s)
encodeStr($id, s)
s.add(':')
encodeStr($Rope(value), s)
encodeStr($value, s)
inc i
s.add('}')
@@ -103,8 +103,9 @@ proc genMergeInfo*(m: BModule): Rope =
writeTypeCache(m.typeCache, s)
s.add("declared:{")
writeIntSet(m.declaredThings, s)
s.add("typeInfo:{")
writeIntSet(m.typeInfoMarker, s)
when false:
s.add("typeInfo:{")
writeIntSet(m.typeInfoMarker, s)
s.add("labels:")
encodeVInt(m.labels, s)
s.add(" flags:")
@@ -185,19 +186,18 @@ proc newFakeType(id: int): PType =
new(result)
result.id = id
proc readTypeCache(L: var TBaseLexer, result: var TIdTable) =
proc readTypeCache(L: var TBaseLexer, result: var TypeCache) =
if ^L.bufpos != '{': internalError("ccgmerge: '{' expected")
inc L.bufpos
while ^L.bufpos != '}':
skipWhite(L)
var key = decodeVInt(L.buf, L.bufpos)
var key = decodeStr(L.buf, L.bufpos)
if ^L.bufpos != ':': internalError("ccgmerge: ':' expected")
inc L.bufpos
var value = decodeStr(L.buf, L.bufpos)
# XXX little hack: we create a "fake" type object with the correct Id
# better would be to adapt the data structure to not even store the
# object as key, but only the Id
idTablePut(result, newFakeType(key), value.rope)
# XXX implement me
when false:
idTablePut(result, newFakeType(key), value.rope)
inc L.bufpos
proc readIntSet(L: var TBaseLexer, result: var IntSet) =
@@ -220,7 +220,8 @@ proc processMergeInfo(L: var TBaseLexer, m: BModule) =
case k
of "typeCache": readTypeCache(L, m.typeCache)
of "declared": readIntSet(L, m.declaredThings)
of "typeInfo": readIntSet(L, m.typeInfoMarker)
of "typeInfo":
when false: readIntSet(L, m.typeInfoMarker)
of "labels": m.labels = decodeVInt(L.buf, L.bufpos)
of "flags":
m.flags = cast[set[CodegenFlag]](decodeVInt(L.buf, L.bufpos) != 0)

View File

@@ -43,15 +43,9 @@ proc idOrSig(m: BModule; s: PSym): Rope =
# signatures for exported routines are reliable enough to
# produce a unique name and this means produced C++ is more stable wrt
# Nim changes:
when false:
let h = hashType(s.typ, {considerParamNames})
if m.hashConflicts.containsOrIncl(cast[int](h)):
result = s.id
else:
result = BiggestInt(h)
result = rope($hashProc(s))
else:
result = rope s.id
result = "_" & rope s.id
proc mangleName(m: BModule; s: PSym): Rope =
result = s.loc.r
@@ -102,7 +96,6 @@ proc mangleName(m: BModule; s: PSym): Rope =
if keepOrigName:
result.add "0"
else:
add(result, ~"_")
add(result, m.idOrSig(s))
#add(result, ~"_")
#add(result, rope(hashOwner(s).BiggestInt))
@@ -112,24 +105,12 @@ proc typeName(typ: PType): Rope =
result = if typ.sym != nil: typ.sym.name.s.mangle.rope
else: ~"TY"
proc getTypeName(m: BModule; typ: PType): Rope =
proc getTypeName(m: BModule; typ: PType; sig: SigHash): Rope =
if typ.sym != nil and {sfImportc, sfExportc} * typ.sym.flags != {}:
result = typ.sym.loc.r
else:
if typ.loc.r == nil:
when false:
# doesn't work yet and would require bigger rewritings
let h = hashType(typ, {considerParamNames})# and 0x0fff_ffffu32
let sig =
if m.hashConflicts.containsOrIncl(cast[int](h)) and false:
BiggestInt typ.id
else:
BiggestInt h
else:
let sig = BiggestInt typ.id
typ.loc.r = typ.typeName & sig.rope #& ("_" & m.module.name.s)
#if typ.kind != tySet:
# typ.loc.r.add "_" & m.module.name.s
typ.loc.r = typ.typeName & $sig
result = typ.loc.r
if result == nil: internalError("getTypeName: " & $typ.kind)
@@ -196,7 +177,7 @@ proc isImportedType(t: PType): bool =
proc isImportedCppType(t: PType): bool =
result = t.sym != nil and sfInfixCall in t.sym.flags
proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope
proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope
proc needsComplexAssignment(typ: PType): bool =
result = containsGarbageCollectedRef(typ)
@@ -229,11 +210,11 @@ const
# but one can #define it to what one wants
"N_INLINE", "N_NOINLINE", "N_FASTCALL", "N_CLOSURE", "N_NOCONV"]
proc cacheGetType(tab: TIdTable, key: PType): Rope =
proc cacheGetType(tab: TypeCache; sig: SigHash): Rope =
# returns nil if we need to declare this type
# since types are now unique via the ``getUniqueType`` mechanism, this slow
# linear search is not necessary anymore:
result = Rope(idTableGet(tab, key))
result = tab.getOrDefault(sig)
proc getTempName(m: BModule): Rope =
result = m.tmpBase & rope(m.labels)
@@ -266,7 +247,7 @@ proc fillResult(param: PSym) =
proc typeNameOrLiteral(m: BModule; t: PType, literal: string): Rope =
if t.sym != nil and sfImportc in t.sym.flags and t.sym.magic == mNone:
result = getTypeName(m, t)
result = t.sym.loc.r
else:
result = rope(literal)
@@ -299,11 +280,11 @@ proc getSimpleTypeDesc(m: BModule, typ: PType): Rope =
proc pushType(m: BModule, typ: PType) =
add(m.typeStack, typ)
proc getTypePre(m: BModule, typ: PType): Rope =
proc getTypePre(m: BModule, typ: PType; sig: SigHash): Rope =
if typ == nil: result = rope("void")
else:
result = getSimpleTypeDesc(m, typ)
if result == nil: result = cacheGetType(m.typeCache, typ)
if result == nil: result = cacheGetType(m.typeCache, sig)
proc structOrUnion(t: PType): Rope =
(if tfUnion in t.flags: rope("union") else: rope("struct"))
@@ -312,42 +293,44 @@ proc getForwardStructFormat(m: BModule): string =
if m.compileToCpp: result = "$1 $2;$n"
else: result = "typedef $1 $2 $2;$n"
proc getTypeForward(m: BModule, typ: PType): Rope =
result = cacheGetType(m.forwTypeCache, typ)
proc getTypeForward(m: BModule, typ: PType; sig: SigHash): Rope =
result = cacheGetType(m.forwTypeCache, sig)
if result != nil: return
result = getTypePre(m, typ)
result = getTypePre(m, typ, sig)
if result != nil: return
case typ.kind
case typ.skipTypes(abstractInst).kind
of tySequence, tyTuple, tyObject:
result = getTypeName(m, typ)
result = getTypeName(m, typ, sig)
m.forwTypeCache[sig] = result
if not isImportedType(typ):
addf(m.s[cfsForwardTypes], "/* getTypeForward: $1 $2 $3 */", [rope typeToString typ,
rope typ.id, rope m.module.id])
addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
[structOrUnion(typ), result])
idTablePut(m.forwTypeCache, typ, result)
doAssert m.forwTypeCache[sig] == result
else: internalError("getTypeForward(" & $typ.kind & ')')
proc getTypeDescWeak(m: BModule; t: PType; check: var IntSet): Rope =
## like getTypeDescAux but creates only a *weak* dependency. In other words
## we know we only need a pointer to it so we only generate a struct forward
## declaration:
var etB = t.skipTypes(abstractInst)
let etB = t.skipTypes(abstractInst)
case etB.kind
of tyObject, tyTuple:
if isImportedCppType(etB) and t.kind == tyGenericInst:
result = getTypeDescAux(m, t, check)
else:
let x = getUniqueType(etB)
result = getTypeForward(m, x)
pushType(m, x)
result = getTypeForward(m, t, hashType(t))
pushType(m, t)
of tySequence:
let x = getUniqueType(etB)
result = getTypeForward(m, x) & "*"
pushType(m, x)
result = getTypeForward(m, t, hashType(t)) & "*"
pushType(m, t)
else:
result = getTypeDescAux(m, t, check)
proc paramStorageLoc(param: PSym): TStorageLoc =
if param.typ.skipTypes({tyVar, tyTypeDesc}).kind notin {tyArray, tyOpenArray, tyVarargs, tyArrayConstr}:
if param.typ.skipTypes({tyVar, tyTypeDesc}).kind notin {
tyArray, tyOpenArray, tyVarargs, tyArrayConstr}:
result = OnStack
else:
result = OnUnknown
@@ -419,10 +402,6 @@ proc mangleRecFieldName(field: PSym, rectype: PType): Rope =
proc genRecordFieldsAux(m: BModule, n: PNode,
accessExpr: Rope, rectype: PType,
check: var IntSet): Rope =
var
ae, uname, sname, a: Rope
k: PNode
field: PSym
result = nil
case n.kind
of nkRecList:
@@ -431,18 +410,18 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
of nkRecCase:
if n.sons[0].kind != nkSym: internalError(n.info, "genRecordFieldsAux")
add(result, genRecordFieldsAux(m, n.sons[0], accessExpr, rectype, check))
uname = rope(mangle(n.sons[0].sym.name.s) & 'U')
if accessExpr != nil: ae = "$1.$2" % [accessExpr, uname]
else: ae = uname
let uname = rope(mangle(n.sons[0].sym.name.s) & 'U')
let ae = if accessExpr != nil: "$1.$2" % [accessExpr, uname]
else: uname
var unionBody: Rope = nil
for i in countup(1, sonsLen(n) - 1):
case n.sons[i].kind
of nkOfBranch, nkElse:
k = lastSon(n.sons[i])
let k = lastSon(n.sons[i])
if k.kind != nkSym:
sname = "S" & rope(i)
a = genRecordFieldsAux(m, k, "$1.$2" % [ae, sname], rectype,
check)
let sname = "S" & rope(i)
let a = genRecordFieldsAux(m, k, "$1.$2" % [ae, sname], rectype,
check)
if a != nil:
add(unionBody, "struct {")
add(unionBody, a)
@@ -453,12 +432,12 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
if unionBody != nil:
addf(result, "union{$n$1} $2;$n", [unionBody, uname])
of nkSym:
field = n.sym
let field = n.sym
if field.typ.kind == tyVoid: return
#assert(field.ast == nil)
sname = mangleRecFieldName(field, rectype)
if accessExpr != nil: ae = "$1.$2" % [accessExpr, sname]
else: ae = sname
let sname = mangleRecFieldName(field, rectype)
let ae = if accessExpr != nil: "$1.$2" % [accessExpr, sname]
else: sname
fillLoc(field.loc, locField, field.typ, ae, OnUnknown)
# for importcpp'ed objects, we only need to set field.loc, but don't
# have to recurse via 'getTypeDescAux'. And not doing so prevents problems
@@ -558,24 +537,29 @@ proc resolveStarsInCppType(typ: PType, idx, stars: int): PType =
result = if result.kind == tyGenericInst: result.sons[1]
else: result.elemType
proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
const
irrelevantForBackend = {tyGenericBody, tyGenericInst, tyGenericInvocation,
tyDistinct, tyRange, tyStatic}
proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope =
# returns only the type's name
var t = getUniqueType(typ)
if t == nil: internalError("getTypeDescAux: t == nil")
var t = origTyp.skipTypes(irrelevantForBackend)
if t.sym != nil: useHeader(m, t.sym)
result = getTypePre(m, t)
if t != origTyp and origTyp.sym != nil: useHeader(m, origTyp.sym)
let sig = hashType(origTyp)
result = getTypePre(m, t, sig)
if result != nil: return
if containsOrIncl(check, t.id):
if not (isImportedCppType(typ) or isImportedCppType(t)):
internalError("cannot generate C type for: " & typeToString(typ))
if not (isImportedCppType(origTyp) or isImportedCppType(t)):
internalError("cannot generate C type for: " & typeToString(origTyp))
# XXX: this BUG is hard to fix -> we need to introduce helper structs,
# but determining when this needs to be done is hard. We should split
# C type generation into an analysis and a code generation phase somehow.
case t.kind
of tyRef, tyPtr, tyVar:
var star = if t.kind == tyVar and tfVarIsPtr notin typ.flags and
var star = if t.kind == tyVar and tfVarIsPtr notin origTyp.flags and
compileToCpp(m): "&" else: "*"
var et = typ.skipTypes(abstractInst).lastSon
var et = origTyp.skipTypes(abstractInst).lastSon
var etB = et.skipTypes(abstractInst)
if etB.kind in {tyArrayConstr, tyArray, tyOpenArray, tyVarargs}:
# this is correct! sets have no proper base type, so we treat
@@ -589,33 +573,30 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
result = getTypeDescAux(m, et, check) & star
else:
# no restriction! We have a forward declaration for structs
let x = getUniqueType(etB)
let name = getTypeForward(m, x)
let name = getTypeForward(m, et, hashType et)
result = name & star
idTablePut(m.typeCache, t, result)
pushType(m, x)
m.typeCache[sig] = result
pushType(m, et)
of tySequence:
# no restriction! We have a forward declaration for structs
let x = getUniqueType(etB)
let name = getTypeForward(m, x)
let name = getTypeForward(m, et, hashType et)
result = name & "*" & star
idTablePut(m.typeCache, t, result)
pushType(m, x)
m.typeCache[sig] = result
pushType(m, et)
else:
# else we have a strong dependency :-(
result = getTypeDescAux(m, et, check) & star
idTablePut(m.typeCache, t, result)
m.typeCache[sig] = result
of tyOpenArray, tyVarargs:
result = getTypeDescWeak(m, t.sons[0], check) & "*"
idTablePut(m.typeCache, t, result)
of tyRange, tyEnum:
let t = if t.kind == tyRange: t.lastSon else: t
result = cacheGetType(m.typeCache, t)
m.typeCache[sig] = result
of tyEnum:
result = cacheGetType(m.typeCache, sig)
if result == nil:
result = getTypeName(m, t)
result = getTypeName(m, t, sig)
if not (isImportedCppType(t) or
(sfImportc in t.sym.flags and t.sym.magic == mNone)):
idTablePut(m.typeCache, t, result)
m.typeCache[sig] = result
var size: int
if firstOrd(t) < 0:
addf(m.s[cfsTypes], "typedef NI32 $1;$n", [result])
@@ -639,8 +620,8 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
gDebugInfo.registerEnum(EnumDesc(size: size, owner: owner, id: t.sym.id,
name: t.sym.name.s, values: vals))
of tyProc:
result = getTypeName(m, t)
idTablePut(m.typeCache, t, result)
result = getTypeName(m, origTyp, sig)
m.typeCache[sig] = result
var rettype, desc: Rope
genProcParams(m, t, rettype, desc, check, true, true)
if not isImportedType(t):
@@ -655,15 +636,15 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
of tySequence:
# we cannot use getTypeForward here because then t would be associated
# with the name of the struct, not with the pointer to the struct:
result = cacheGetType(m.forwTypeCache, t)
result = cacheGetType(m.forwTypeCache, sig)
if result == nil:
result = getTypeName(m, t)
result = getTypeName(m, origTyp, sig)
if not isImportedType(t):
addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
[structOrUnion(t), result])
idTablePut(m.forwTypeCache, t, result)
assert(cacheGetType(m.typeCache, t) == nil)
idTablePut(m.typeCache, t, result & "*")
m.forwTypeCache[sig] = result
assert(cacheGetType(m.typeCache, sig) == nil)
m.typeCache[sig] = result & "*"
if not isImportedType(t):
if skipTypes(t.sons[0], typedescInst).kind != tyEmpty:
const
@@ -677,20 +658,20 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
else:
result = rope("TGenericSeq")
add(result, "*")
of tyArrayConstr, tyArray:
of tyArray:
var n: BiggestInt = lengthOrd(t)
if n <= 0: n = 1 # make an array of at least one element
result = getTypeName(m, t)
idTablePut(m.typeCache, t, result)
result = getTypeName(m, origTyp, sig)
m.typeCache[sig] = result
if not isImportedType(t):
let foo = getTypeDescAux(m, t.sons[1], check)
addf(m.s[cfsTypes], "typedef $1 $2[$3];$n",
[foo, result, rope(n)])
of tyObject, tyTuple:
if isImportedCppType(t) and typ.kind == tyGenericInst:
if isImportedCppType(t) and origTyp.kind == tyGenericInst:
# for instantiated templates we do not go through the type cache as the
# the type cache is not aware of 'tyGenericInst'.
let cppName = getTypeName(m, t)
let cppName = getTypeName(m, t, sig)
var i = 0
var chunkStart = 0
while i < cppName.data.len:
@@ -701,7 +682,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
result.add cppName.data.substr(chunkStart, chunkEnd)
chunkStart = i
let typeInSlot = resolveStarsInCppType(typ, idx + 1, stars)
let typeInSlot = resolveStarsInCppType(origTyp, idx + 1, stars)
if typeInSlot == nil or typeInSlot.kind == tyVoid:
result.add(~"void")
else:
@@ -713,28 +694,44 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
result.add cppName.data.substr(chunkStart)
else:
result = cppName & "<"
for i in 1 .. typ.len-2:
for i in 1 .. origTyp.len-2:
if i > 1: result.add(" COMMA ")
result.add(getTypeDescAux(m, typ.sons[i], check))
result.add(getTypeDescAux(m, origTyp.sons[i], check))
result.add("> ")
# always call for sideeffects:
assert t.kind != tyTuple
discard getRecordDesc(m, t, result, check)
else:
result = cacheGetType(m.forwTypeCache, t)
when false:
if t.sym != nil and t.sym.name.s == "KeyValuePair":
if t == origTyp:
echo "wtf: came here"
writeStackTrace()
quit 1
result = cacheGetType(m.forwTypeCache, sig)
if result == nil:
result = getTypeName(m, t)
when false:
if t.sym != nil and t.sym.name.s == "KeyValuePair":
# or {sfImportc, sfExportc} * t.sym.flags == {}:
if t.loc.r != nil:
echo t.kind, " ", hashType t
echo origTyp.kind, " ", sig
assert t.loc.r == nil
result = getTypeName(m, origTyp, sig)
m.forwTypeCache[sig] = result
if not isImportedType(t):
addf(m.s[cfsForwardTypes], "/* tyObject: $1 $2 $3 */", [rope typeToString t,
rope t.id, rope m.module.id])
addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
[structOrUnion(t), result])
idTablePut(m.forwTypeCache, t, result)
idTablePut(m.typeCache, t, result) # always call for sideeffects:
doAssert m.forwTypeCache[sig] == result
m.typeCache[sig] = result # always call for sideeffects:
let recdesc = if t.kind != tyTuple: getRecordDesc(m, t, result, check)
else: getTupleDesc(m, t, result, check)
if not isImportedType(t): add(m.s[cfsTypes], recdesc)
of tySet:
result = getTypeName(m, t.lastSon) & "Set"
idTablePut(m.typeCache, t, result)
result = getTypeName(m, t.lastSon, hashType t.lastSon) & "Set"
m.typeCache[sig] = result
if not isImportedType(t):
let s = int(getSize(t))
case s
@@ -822,8 +819,7 @@ proc genTypeInfoAuxBase(m: BModule; typ, origType: PType; name, base: Rope) =
var size: Rope
if tfIncompleteStruct in typ.flags: size = rope"void*"
elif m.compileToCpp: size = getTypeDesc(m, origType)
else: size = getTypeDesc(m, typ)
else: size = getTypeDesc(m, origType)
addf(m.s[cfsTypeInit3],
"$1.size = sizeof($2);$n" & "$1.kind = $3;$n" & "$1.base = $4;$n",
[name, size, rope(nimtypeKind), base])
@@ -855,26 +851,26 @@ proc discriminatorTableName(m: BModule, objtype: PType, d: PSym): Rope =
objtype = objtype.sons[0]
if objtype.sym == nil:
internalError(d.info, "anonymous obj with discriminator")
result = "NimDT_$1_$2" % [rope(objtype.id), rope(d.name.s.mangle)]
result = "NimDT_$1_$2" % [rope($hashType(objtype)), rope(d.name.s.mangle)]
proc discriminatorTableDecl(m: BModule, objtype: PType, d: PSym): Rope =
discard cgsym(m, "TNimNode")
var tmp = discriminatorTableName(m, objtype, d)
result = "TNimNode* $1[$2];$n" % [tmp, rope(lengthOrd(d.typ)+1)]
proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
proc genObjectFields(m: BModule, typ, origType: PType, n: PNode, expr: Rope) =
case n.kind
of nkRecList:
var L = sonsLen(n)
if L == 1:
genObjectFields(m, typ, n.sons[0], expr)
genObjectFields(m, typ, origType, n.sons[0], expr)
elif L > 0:
var tmp = getTempName(m)
addf(m.s[cfsTypeInit1], "static TNimNode* $1[$2];$n", [tmp, rope(L)])
for i in countup(0, L-1):
var tmp2 = getNimNode(m)
addf(m.s[cfsTypeInit3], "$1[$2] = &$3;$n", [tmp, rope(i), tmp2])
genObjectFields(m, typ, n.sons[i], tmp2)
genObjectFields(m, typ, origType, n.sons[i], tmp2)
addf(m.s[cfsTypeInit3], "$1.len = $2; $1.kind = 2; $1.sons = &$3[0];$n",
[expr, rope(L), tmp])
else:
@@ -888,7 +884,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
addf(m.s[cfsTypeInit3], "$1.kind = 3;$n" &
"$1.offset = offsetof($2, $3);$n" & "$1.typ = $4;$n" &
"$1.name = $5;$n" & "$1.sons = &$6[0];$n" &
"$1.len = $7;$n", [expr, getTypeDesc(m, typ), field.loc.r,
"$1.len = $7;$n", [expr, getTypeDesc(m, origType), field.loc.r,
genTypeInfo(m, field.typ),
makeCString(field.name.s),
tmp, rope(L)])
@@ -896,7 +892,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
for i in countup(1, sonsLen(n)-1):
var b = n.sons[i] # branch
var tmp2 = getNimNode(m)
genObjectFields(m, typ, lastSon(b), tmp2)
genObjectFields(m, typ, origType, lastSon(b), tmp2)
case b.kind
of nkOfBranch:
if sonsLen(b) < 2:
@@ -920,7 +916,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
if field.bitsize == 0:
addf(m.s[cfsTypeInit3], "$1.kind = 1;$n" &
"$1.offset = offsetof($2, $3);$n" & "$1.typ = $4;$n" &
"$1.name = $5;$n", [expr, getTypeDesc(m, typ),
"$1.name = $5;$n", [expr, getTypeDesc(m, origType),
field.loc.r, genTypeInfo(m, field.typ), makeCString(field.name.s)])
else: internalError(n.info, "genObjectFields")
@@ -929,7 +925,7 @@ proc genObjectInfo(m: BModule, typ, origType: PType, name: Rope) =
else: genTypeInfoAuxBase(m, typ, origType, name, rope("0"))
var tmp = getNimNode(m)
if not isImportedCppType(typ):
genObjectFields(m, typ, typ.n, tmp)
genObjectFields(m, typ, origType, typ.n, tmp)
addf(m.s[cfsTypeInit3], "$1.node = &$2;$n", [name, tmp])
var t = typ.sons[0]
while t != nil:
@@ -937,7 +933,7 @@ proc genObjectInfo(m: BModule, typ, origType: PType, name: Rope) =
t.flags.incl tfObjHasKids
t = t.sons[0]
proc genTupleInfo(m: BModule, typ: PType, name: Rope) =
proc genTupleInfo(m: BModule, typ, origType: PType, name: Rope) =
genTypeInfoAuxBase(m, typ, typ, name, rope("0"))
var expr = getNimNode(m)
var length = sonsLen(typ)
@@ -952,7 +948,7 @@ proc genTupleInfo(m: BModule, typ: PType, name: Rope) =
"$1.offset = offsetof($2, Field$3);$n" &
"$1.typ = $4;$n" &
"$1.name = \"Field$3\";$n",
[tmp2, getTypeDesc(m, typ), rope(i), genTypeInfo(m, a)])
[tmp2, getTypeDesc(m, origType), rope(i), genTypeInfo(m, a)])
addf(m.s[cfsTypeInit3], "$1.len = $2; $1.kind = 2; $1.sons = &$3[0];$n",
[expr, rope(length), tmp])
else:
@@ -1034,27 +1030,20 @@ proc genDeepCopyProc(m: BModule; s: PSym; result: Rope) =
proc genTypeInfo(m: BModule, t: PType): Rope =
let origType = t
var t = getUniqueType(t)
var t = skipTypes(origType, irrelevantForBackend)
when false:
let h = hashType(t, {considerParamNames})
let tid = if m.hashConflicts.containsOrIncl(cast[int](h)):
BiggestInt t.id
else:
BiggestInt h
else:
let tid = t.id
result = "NTI$1" % [rope(tid)]
if containsOrIncl(m.typeInfoMarker, t.id):
let sig = hashType(origType)
result = m.typeInfoMarker.getOrDefault(sig)
if result != nil:
return "(&".rope & result & ")".rope
# getUniqueType doesn't skip tyDistinct when that has an overriden operation:
while t.kind == tyDistinct: t = t.lastSon
result = "NTI$1" % [rope($sig)]
m.typeInfoMarker[sig] = result
let owner = t.skipTypes(typedescPtrs).owner.getModule
if owner != m.module:
# make sure the type info is created in the owner module
discard genTypeInfo(owner.bmod, t)
discard genTypeInfo(owner.bmod, origType)
# reference the type info as extern here
discard cgsym(m, "TNimType")
discard cgsym(m, "TNimNode")
@@ -1072,7 +1061,8 @@ proc genTypeInfo(m: BModule, t: PType): Rope =
if t.callConv != ccClosure:
genTypeInfoAuxBase(m, t, t, result, rope"0")
else:
genTupleInfo(m, fakeClosureType(t.owner), result)
let x = fakeClosureType(t.owner)
genTupleInfo(m, x, x, result)
of tySequence, tyRef:
genTypeInfoAux(m, t, t, result)
if gSelectedGC >= gcMarkAndSweep:
@@ -1088,7 +1078,7 @@ proc genTypeInfo(m: BModule, t: PType): Rope =
# else:
# BUGFIX: use consistently RTTI without proper field names; otherwise
# results are not deterministic!
genTupleInfo(m, t, result)
genTupleInfo(m, t, origType, result)
else: internalError("genTypeInfo(" & $t.kind & ')')
if t.deepCopy != nil:
genDeepCopyProc(m, t.deepCopy, result)

View File

@@ -85,87 +85,77 @@ proc slowSearch(key: PType; k: TTypeKind): PType =
proc getUniqueType*(key: PType): PType =
# this is a hotspot in the compiler!
if key == nil: return
var k = key.kind
case k
of tyBool, tyChar, tyInt..tyUInt64:
# no canonicalization for integral types, so that e.g. ``pid_t`` is
# produced instead of ``NI``.
result = key
of tyEmpty, tyNil, tyExpr, tyStmt, tyPointer, tyString,
tyCString, tyNone, tyVoid:
result = gCanonicalTypes[k]
if result == nil:
gCanonicalTypes[k] = key
result = key
when false:
if key == nil: return
var k = key.kind
case k
of tyBool, tyChar, tyInt..tyUInt64:
# no canonicalization for integral types, so that e.g. ``pid_t`` is
# produced instead of ``NI``.
result = key
of tyTypeDesc, tyTypeClasses, tyGenericParam, tyFromExpr, tyFieldAccessor:
if key.sym != nil:
internalError(key.sym.info, "metatype not eliminated")
else:
internalError("metatype not eliminated")
of tyDistinct:
if key.deepCopy != nil: result = key
else: result = getUniqueType(lastSon(key))
of tyGenericInst, tyOrdinal, tyStatic:
result = getUniqueType(lastSon(key))
#let obj = lastSon(key)
#if obj.sym != nil and obj.sym.name.s == "TOption":
# echo "for ", typeToString(key), " I returned "
# debug result
of tyPtr, tyRef, tyVar:
let elemType = lastSon(key)
if elemType.kind in {tyBool, tyChar, tyInt..tyUInt64}:
# no canonicalization for integral types, so that e.g. ``ptr pid_t`` is
# produced instead of ``ptr NI``.
result = key
else:
of tyEmpty, tyNil, tyExpr, tyStmt, tyPointer, tyString,
tyCString, tyNone, tyVoid:
result = gCanonicalTypes[k]
if result == nil:
gCanonicalTypes[k] = key
result = key
of tyTypeDesc, tyTypeClasses, tyGenericParam, tyFromExpr, tyFieldAccessor:
if key.sym != nil:
internalError(key.sym.info, "metatype not eliminated")
else:
internalError("metatype not eliminated")
of tyDistinct:
if key.deepCopy != nil: result = key
else: result = getUniqueType(lastSon(key))
of tyGenericInst, tyOrdinal, tyStatic:
result = getUniqueType(lastSon(key))
#let obj = lastSon(key)
#if obj.sym != nil and obj.sym.name.s == "TOption":
# echo "for ", typeToString(key), " I returned "
# debug result
of tyPtr, tyRef, tyVar:
let elemType = lastSon(key)
if elemType.kind in {tyBool, tyChar, tyInt..tyUInt64}:
# no canonicalization for integral types, so that e.g. ``ptr pid_t`` is
# produced instead of ``ptr NI``.
result = key
else:
result = slowSearch(key, k)
of tyArrayConstr, tyGenericInvocation, tyGenericBody,
tyOpenArray, tyArray, tySet, tyRange, tyTuple,
tySequence, tyForward, tyVarargs, tyProxy:
# we have to do a slow linear search because types may need
# to be compared by their structure:
result = slowSearch(key, k)
of tyArrayConstr, tyGenericInvocation, tyGenericBody,
tyOpenArray, tyArray, tySet, tyRange, tyTuple,
tySequence, tyForward, tyVarargs, tyProxy:
# we have to do a slow linear search because types may need
# to be compared by their structure:
result = slowSearch(key, k)
of tyObject:
if tfFromGeneric notin key.flags:
# fast case; lookup per id suffices:
of tyObject:
if tfFromGeneric notin key.flags:
# fast case; lookup per id suffices:
result = PType(idTableGet(gTypeTable[k], key))
if result == nil:
idTablePut(gTypeTable[k], key, key)
result = key
else:
# ugly slow case: need to compare by structure
if idTableHasObjectAsKey(gTypeTable[k], key): return key
for h in countup(0, high(gTypeTable[k].data)):
var t = PType(gTypeTable[k].data[h].key)
if t != nil and sameBackendType(t, key):
return t
idTablePut(gTypeTable[k], key, key)
result = key
of tyEnum:
result = PType(idTableGet(gTypeTable[k], key))
if result == nil:
idTablePut(gTypeTable[k], key, key)
result = key
else:
# ugly slow case: need to compare by structure
if idTableHasObjectAsKey(gTypeTable[k], key): return key
for h in countup(0, high(gTypeTable[k].data)):
var t = PType(gTypeTable[k].data[h].key)
if t != nil and sameBackendType(t, key):
return t
idTablePut(gTypeTable[k], key, key)
result = key
of tyEnum:
result = PType(idTableGet(gTypeTable[k], key))
if result == nil:
idTablePut(gTypeTable[k], key, key)
result = key
of tyProc:
if key.callConv != ccClosure:
result = key
else:
# ugh, we need the canon here:
result = slowSearch(key, k)
of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("getUniqueType")
proc tableGetType*(tab: TIdTable, key: PType): RootRef =
# returns nil if we need to declare this type
result = idTableGet(tab, key)
if (result == nil) and (tab.counter > 0):
# we have to do a slow linear search because types may need
# to be compared by their structure:
for h in countup(0, high(tab.data)):
var t = PType(tab.data[h].key)
if t != nil:
if sameType(t, key):
return tab.data[h].val
of tyProc:
if key.callConv != ccClosure:
result = key
else:
# ugh, we need the canon here:
result = slowSearch(key, k)
of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("getUniqueType")
proc makeSingleLineCString*(s: string): string =
result = "\""

View File

@@ -14,7 +14,7 @@ import
nversion, nimsets, msgs, securehash, bitsets, idents, lists, types,
ccgutils, os, ropes, math, passes, rodread, wordrecg, treetab, cgmeth,
condsyms, rodutils, renderer, idgen, cgendata, ccgmerge, semfold, aliases,
lowerings, semparallel
lowerings, semparallel, tables
from modulegraphs import ModuleGraph
@@ -263,6 +263,7 @@ type
proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags)
proc isComplexValueType(t: PType): bool {.inline.} =
let t = t.skipTypes(abstractInst)
result = t.kind in {tyArray, tyArrayConstr, tySet, tyTuple, tyObject} or
(t.kind == tyProc and t.callConv == ccClosure)
@@ -296,7 +297,7 @@ proc resetLoc(p: BProc, loc: var TLoc) =
genObjectInit(p, cpsStmts, loc.t, loc, true)
proc constructLoc(p: BProc, loc: TLoc, isTemp = false) =
let typ = skipTypes(loc.t, abstractRange)
let typ = loc.t
if not isComplexValueType(typ):
linefmt(p, cpsStmts, "$1 = ($2)0;$n", rdLoc(loc),
getTypeDesc(p.module, typ))
@@ -325,13 +326,9 @@ proc initLocalVar(p: BProc, v: PSym, immediateAsgn: bool) =
proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) =
inc(p.labels)
result.r = "LOC" & rope(p.labels)
#addf(p.blocks[0].sections[cpsLocals],
# "$1 $2;$n", [getTypeDesc(p.module, t), result.r])
linefmt(p, cpsLocals, "$1 $2;$n", getTypeDesc(p.module, t), result.r)
result.k = locTemp
#result.a = - 1
result.t = t
#result.t = getUniqueType(t)
result.s = OnStack
result.flags = {}
constructLoc(p, result, not needsInit)
@@ -1094,10 +1091,10 @@ proc rawNewModule(module: PSym, filename: string): BModule =
result.declaredProtos = initIntSet()
result.cfilename = filename
result.filename = filename
initIdTable(result.typeCache)
initIdTable(result.forwTypeCache)
result.typeCache = initTable[SigHash, Rope]()
result.forwTypeCache = initTable[SigHash, Rope]()
result.module = module
result.typeInfoMarker = initIntSet()
result.typeInfoMarker = initTable[SigHash, Rope]()
result.initProc = newProc(nil, result)
result.initProc.options = initProcOptions(result)
result.preInitProc = newPreInitProc(result)
@@ -1107,7 +1104,6 @@ proc rawNewModule(module: PSym, filename: string): BModule =
result.forwardedProcs = @[]
result.typeNodesName = getTempName(result)
result.nimTypesName = getTempName(result)
result.hashConflicts = initIntSet()
# no line tracing for the init sections of the system module so that we
# don't generate a TFrame which can confuse the stack botton initialization:
if sfSystemModule in module.flags:
@@ -1124,7 +1120,7 @@ proc resetModule*(m: BModule) =
# away all the data that was written to disk
initLinkedList(m.headerFiles)
m.declaredProtos = initIntSet()
initIdTable(m.forwTypeCache)
m.forwTypeCache = initTable[SigHash, Rope]()
m.initProc = newProc(nil, m)
m.initProc.options = initProcOptions(m)
m.preInitProc = newPreInitProc(m)
@@ -1141,7 +1137,6 @@ proc resetModule*(m: BModule) =
nullify m.s
m.typeNodes = 0
m.nimTypes = 0
m.hashConflicts = initIntSet()
nullify m.extensionLoaders
# indicate that this is now cached module

View File

@@ -10,7 +10,8 @@
## This module contains the data structures for the C code generation phase.
import
ast, astalgo, ropes, passes, options, intsets, lists, platform
ast, astalgo, ropes, passes, options, intsets, lists, platform, sighashes,
tables
from msgs import TLineInfo
@@ -92,6 +93,7 @@ type
gcFrameType*: Rope # the struct {} we put the GC markers into
TTypeSeq* = seq[PType]
TypeCache* = Table[SigHash, Rope]
Codegenflag* = enum
preventStackTrace, # true if stack traces need to be prevented
@@ -109,12 +111,12 @@ type
cfilename*: string # filename of the module (including path,
# without extension)
tmpBase*: Rope # base for temp identifier generation
typeCache*: TIdTable # cache the generated types
forwTypeCache*: TIdTable # cache for forward declarations of types
typeCache*: TypeCache # cache the generated types
forwTypeCache*: TypeCache # cache for forward declarations of types
declaredThings*: IntSet # things we have declared in this .c file
declaredProtos*: IntSet # prototypes we have declared in this .c file
headerFiles*: TLinkedList # needed headers to include
typeInfoMarker*: IntSet # needed for generating type information
typeInfoMarker*: TypeCache # needed for generating type information
initProc*: BProc # code for init procedure
postInitProc*: BProc # code to be executed after the init proc
preInitProc*: BProc # code executed before the init proc
@@ -127,7 +129,6 @@ type
extensionLoaders*: array['0'..'9', Rope] # special procs for the
# OpenGL wrapper
injectStmt*: Rope
hashConflicts*: IntSet
var
mainModProcs*, mainModInit*, otherModsInit*, mainDatInit*: Rope

View File

@@ -10,7 +10,10 @@
## Computes hash values for routine (proc, method etc) signatures.
import ast, md5
export md5.`==`
from hashes import Hash
from astalgo import debug
from types import typeToString
from strutils import startsWith
when false:
type
@@ -25,7 +28,7 @@ when false:
else:
type
SigHash* = Md5Digest
SigHash* = distinct Md5Digest
const
cb64 = [
@@ -39,6 +42,7 @@ else:
proc toBase64a(s: cstring, len: int): string =
## encodes `s` into base64 representation.
result = newStringOfCap(((len + 2) div 3) * 4)
result.add '_'
var i = 0
while i < len - 2:
let a = ord(s[i])
@@ -65,6 +69,15 @@ else:
proc `&=`(c: var MD5Context, s: string) = md5Update(c, s, s.len)
proc `&=`(c: var MD5Context, ch: char) = md5Update(c, unsafeAddr ch, 1)
proc `==`*(a, b: SigHash): bool =
# {.borrow.}
result = equalMem(unsafeAddr a, unsafeAddr b, sizeof(a))
proc hash*(u: SigHash): Hash =
result = 0
for x in 0..3:
result = (result shl 8) or u.MD5Digest[x].int
proc hashSym(c: var MD5Context, s: PSym) =
if sfAnon in s.flags or s.kind == skGenericParam:
c &= ":anon"
@@ -105,28 +118,46 @@ proc hashTree(c: var MD5Context, n: PNode) =
type
ConsiderFlag* = enum
considerParamNames
CoProc
CoType
proc hashType(c: var MD5Context, t: PType; flags: set[ConsiderFlag]) =
# modelled after 'typeToString'
if t == nil:
c &= "\254"
return
c &= char(t.kind)
# Every cyclic type in Nim need to be constructed via some 't.sym', so this
# is actually safe without an infinite recursion check:
if t.sym != nil and sfAnon notin t.sym.flags:
# t.n for literals, but not for e.g. objects!
if t.kind in {tyFloat, tyInt}: c.hashTree(t.n)
c.hashSym(t.sym)
case t.kind
of tyGenericInst:
var x = t.lastSon
if x.kind == tyGenericBody: x = x.lastSon
if x.kind == tyTuple:
c.hashType x, flags
return
for i in countup(0, sonsLen(t) - 2):
c.hashType t.sons[i], flags
return
of tyGenericInvocation:
for i in countup(0, sonsLen(t) - 1):
c.hashType t.sons[i], flags
return
of tyDistinct:
if CoType in flags:
c.hashType t.lastSon, flags
else:
c.hashSym(t.sym)
return
else:
discard
case t.kind
of tyGenericBody, tyGenericInst, tyGenericInvocation:
for i in countup(0, sonsLen(t) - 1 - ord(t.kind != tyGenericInvocation)):
c.hashType t.sons[i], flags
of tyObject, tyEnum:
# Every cyclic type in Nim need to be constructed via some 't.sym', so this
# is actually safe without an infinite recursion check:
c.hashSym(t.sym)
of tyRef, tyPtr, tyGenericBody:
c.hashType t.lastSon, flags
of tyUserTypeClass:
if t.sym != nil and t.sym.owner != nil:
c &= t.sym.owner.name.s
@@ -139,11 +170,8 @@ proc hashType(c: var MD5Context, t: PType; flags: set[ConsiderFlag]) =
c.hashType t.sons[i], flags
of tyFromExpr, tyFieldAccessor:
c.hashTree(t.n)
of tyArrayConstr:
c.hashTree(t.sons[0].n)
c.hashType(t.sons[1], flags)
of tyTuple:
if t.n != nil:
if t.n != nil and CoType notin flags:
assert(sonsLen(t.n) == sonsLen(t))
for i in countup(0, sonsLen(t.n) - 1):
assert(t.n.sons[i].kind == nkSym)
@@ -154,11 +182,11 @@ proc hashType(c: var MD5Context, t: PType; flags: set[ConsiderFlag]) =
else:
for i in countup(0, sonsLen(t) - 1): c.hashType t.sons[i], flags
of tyRange:
c.hashTree(t.n)
if CoType notin flags: c.hashTree(t.n)
c.hashType(t.sons[0], flags)
of tyProc:
c &= (if tfIterator in t.flags: "iterator " else: "proc ")
if considerParamNames in flags and t.n != nil:
if CoProc in flags and t.n != nil:
let params = t.n
for i in 1..<params.len:
let param = params[i].sym
@@ -170,22 +198,23 @@ proc hashType(c: var MD5Context, t: PType; flags: set[ConsiderFlag]) =
else:
for i in 0.. <t.len: c.hashType(t.sons[i], flags)
c &= char(t.callConv)
if tfNoSideEffect in t.flags: c &= ".noSideEffect"
if tfThread in t.flags: c &= ".thread"
if CoType notin flags:
if tfNoSideEffect in t.flags: c &= ".noSideEffect"
if tfThread in t.flags: c &= ".thread"
else:
for i in 0.. <t.len: c.hashType(t.sons[i], flags)
if tfNotNil in t.flags: c &= "not nil"
if tfNotNil in t.flags and CoType notin flags: c &= "not nil"
proc hashType*(t: PType; flags: set[ConsiderFlag]): SigHash =
proc hashType*(t: PType; flags: set[ConsiderFlag] = {CoType}): SigHash =
var c: MD5Context
md5Init c
hashType c, t, flags
md5Final c, result
md5Final c, result.Md5Digest
proc hashProc*(s: PSym): SigHash =
var c: MD5Context
md5Init c
hashType c, s.typ, {considerParamNames}
hashType c, s.typ, {CoProc}
var m = s
while m.kind != skModule: m = m.owner
@@ -195,7 +224,7 @@ proc hashProc*(s: PSym): SigHash =
c &= "."
c &= m.name.s
md5Final c, result
md5Final c, result.Md5Digest
proc hashOwner*(s: PSym): SigHash =
var c: MD5Context
@@ -208,4 +237,4 @@ proc hashOwner*(s: PSym): SigHash =
c &= "."
c &= m.name.s
md5Final c, result
md5Final c, result.Md5Digest