no interval arithmetic anymore to construct implicit range types; breaking change

This commit is contained in:
Andreas Rumpf
2017-07-13 05:13:12 +02:00
parent 2b862b74e0
commit bc738d63a7
11 changed files with 46 additions and 222 deletions

View File

@@ -134,12 +134,32 @@ proc genSetNode(p: BProc, n: PNode): Rope =
else:
result = genRawSetData(cs, size)
proc getStorageLoc(n: PNode): TStorageLoc =
case n.kind
of nkSym:
case n.sym.kind
of skParam, skTemp:
result = OnStack
of skVar, skForVar, skResult, skLet:
if sfGlobal in n.sym.flags: result = OnHeap
else: result = OnStack
of skConst:
if sfGlobal in n.sym.flags: result = OnHeap
else: result = OnUnknown
else: result = OnUnknown
of nkDerefExpr, nkHiddenDeref:
case n.sons[0].typ.kind
of tyVar: result = OnUnknown
of tyPtr: result = OnStack
of tyRef: result = OnHeap
else: internalError(n.info, "getStorageLoc")
of nkBracketExpr, nkDotExpr, nkObjDownConv, nkObjUpConv:
result = getStorageLoc(n.sons[0])
else: result = OnUnknown
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))
elif dest.s == OnStackShadowDup:
linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
linefmt(p, cpsStmts, "$1 = $2;$n", dupLoc(dest), rdLoc(src))
elif dest.s == OnHeap:
# location is on heap
# now the writer barrier is inlined for performance:
@@ -166,8 +186,6 @@ proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
else:
linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, $2);$n",
addrLoc(dest), rdLoc(src))
if preciseStack():
linefmt(p, cpsStmts, "$1 = $2;$n", dupLoc(dest), rdLoc(src))
proc asgnComplexity(n: PNode): int =
if n != nil:
@@ -225,7 +243,7 @@ proc genOptAsgnObject(p: BProc, dest, src: TLoc, flags: TAssignmentFlags,
proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
# Consider:
# type MyFastString {.shallow.} = string
# type TMyFastString {.shallow.} = string
# Due to the implementation of pragmas this would end up to set the
# tfShallow flag for the built-in string type too! So we check only
# here for this flag, where it is reasonably safe to do so
@@ -243,9 +261,6 @@ proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
else:
linefmt(p, cpsStmts, "#genericAssign((void*)$1, (void*)$2, $3);$n",
addrLoc(dest), addrLoc(src), genTypeInfo(p.module, dest.t))
if dest.s == OnStackShadowDup:
linefmt(p, cpsStmts, "#genericAssignDup((void*)&$1, (void*)$2, $3);$n",
dupLoc(dest), addrLoc(src), genTypeInfo(p.module, dest.t))
proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
# This function replaces all other methods for generating
@@ -264,17 +279,12 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
else:
linefmt(p, cpsStmts, "#genericSeqAssign($1, $2, $3);$n",
addrLoc(dest), rdLoc(src), genTypeInfo(p.module, dest.t))
if dest.s == OnStackShadowDup:
linefmt(p, cpsStmts, "$1 = $2;$n", dest.dupLoc, dest.rdLoc)
of tyString:
if needToCopy notin flags and src.s != OnStatic:
genRefAssign(p, dest, src, flags)
else:
if dest.s == OnStack or not usesNativeGC():
linefmt(p, cpsStmts, "$1 = #copyString($2);$n", dest.rdLoc, src.rdLoc)
elif dest.s == OnStackShadowDup:
linefmt(p, cpsStmts, "$1 = #copyString($2);$n", dest.rdLoc, src.rdLoc)
linefmt(p, cpsStmts, "$1 = $2;$n", dest.dupLoc, dest.rdLoc)
elif dest.s == OnHeap:
# we use a temporary to care for the dreaded self assignment:
var tmp: TLoc
@@ -285,8 +295,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 preciseStack():
linefmt(p, cpsStmts, "$1 = $2;$n", dest.dupLoc, dest.rdLoc)
of tyProc:
if needsComplexAssignment(dest.t):
# optimize closure assignment:
@@ -735,9 +743,6 @@ proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
else: internalError(e.info, "genTupleElem")
addf(r, ".Field$1", [rope(i)])
putIntoDest(p, d, tupType.sons[i], r, a.s)
if a.s == OnStackShadowDup:
d.s = OnStackShadowDup
d.dup = ropef("$1[$2]", a.dup, ithRefInTuple(tupType, i))
proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope): PSym =
var ty = ty
@@ -762,18 +767,12 @@ proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
# so we use Field$i
addf(r, ".Field$1", [rope(f.position)])
putIntoDest(p, d, f.typ, r, a.s)
if a.s == OnStackShadowDup:
d.s = OnStackShadowDup
d.dup = ropef("$1[$2]", a.dup, ithRefInTuple(ty, f.position))
else:
let field = lookupFieldAgain(p, ty, f, r)
if field.loc.r == nil: fillObjectFields(p.module, ty)
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)
if a.s == OnStackShadowDup and field.loc.dup != nil:
d.s = OnStackShadowDup
d.dup = ropef("$1.$2", a.dup, field.loc.dup)
#d.s = a.s
proc genInExprAux(p: BProc, e: PNode, a, b, d: var TLoc)
@@ -825,9 +824,6 @@ proc genCheckedRecordField(p: BProc, e: PNode, d: var TLoc) =
genFieldCheck(p, e, r, field, ty)
add(r, rfmt(nil, ".$1", field.loc.r))
putIntoDest(p, d, field.typ, r, a.s)
if a.s == OnStackShadowDup and field.loc.dup != nil:
d.s = OnStackShadowDup
d.dup = ropef("$1.$2", a.dup, field.loc.dup)
else:
genRecordField(p, e.sons[0], d)
@@ -855,9 +851,6 @@ proc genArrayElem(p: BProc, x, y: PNode, d: var TLoc) =
d.inheritLocation(a)
putIntoDest(p, d, elemType(skipTypes(ty, abstractVar)),
rfmt(nil, "$1[($2)- $3]", rdLoc(a), rdCharLoc(b), first), a.s)
if a.s == OnStackShadowDup:
d.s = OnStackShadowDup
d.dup = ropef("$1[($2)- $3]", a.dup, rdCharLoc(b), first)
proc genCStringElem(p: BProc, x, y: PNode, d: var TLoc) =
var a, b: TLoc
@@ -878,9 +871,6 @@ proc genOpenArrayElem(p: BProc, x, y: PNode, d: var TLoc) =
if d.k == locNone: d.s = a.s
putIntoDest(p, d, elemType(skipTypes(a.t, abstractVar)),
rfmt(nil, "$1[$2]", rdLoc(a), rdCharLoc(b)), a.s)
if a.s == OnStackShadowDup:
d.s = OnStackShadowDup
d.dup = ropef("$1[$2]", a.dup, rdCharLoc(b))
proc genSeqElem(p: BProc, x, y: PNode, d: var TLoc) =
var a, b: TLoc
@@ -1185,7 +1175,6 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
var t = e.typ.skipTypes(abstractInst)
getTemp(p, t, tmp)
let isRef = t.kind == tyRef
let stck = stackPlacement(t)
var r = rdLoc(tmp)
if isRef:
rawGenNew(p, tmp, nil)
@@ -1209,7 +1198,7 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
add(tmp2.r, field.loc.r)
tmp2.k = locTemp
tmp2.t = field.loc.t
tmp2.s = if isRef: OnHeap else: stck
tmp2.s = if isRef: OnHeap else: OnStack
expr(p, it.sons[1], tmp2)
if d.k == locNone:

View File

@@ -802,8 +802,6 @@ proc genTryCpp(p: BProc, t: PNode, d: var TLoc) =
endBlock(p, ropecg(p.module, "} catch (NimException& $1) {$n", [exc]))
if optStackTrace in p.options:
linefmt(p, cpsStmts, "#setFrame((TFrame*)&FR_);$n")
if p.gcFrameLen > 0:
linefmt(p, cpsStmts, "#setGcFrame((#GcFrameBase*)&GCF_);$n")
inc p.inExceptBlock
var i = 1
var catchAllPresent = false
@@ -912,9 +910,6 @@ proc genTry(p: BProc, t: PNode, d: var TLoc) =
linefmt(p, cpsStmts, "#popSafePoint();$n")
if optStackTrace in p.options:
linefmt(p, cpsStmts, "#setFrame((TFrame*)&FR_);$n")
if p.gcFrameLen > 0:
linefmt(p, cpsStmts, "#setGcFrame((#GcFrameBase*)&GCF_);$n")
inc p.inExceptBlock
var i = 1
while (i < length) and (t.sons[i].kind == nkExceptBranch):

View File

@@ -282,7 +282,7 @@ proc ccgIntroducedPtr(s: PSym): bool =
proc fillResult(param: PSym) =
fillLoc(param.loc, locParam, param.typ, ~"Result",
stackPlacement(param.typ))
OnStack)
if mapReturnType(param.typ) != ctArray and isInvalidReturnType(param.typ):
incl(param.loc.flags, lfIndirect)
param.loc.s = OnUnknown
@@ -376,9 +376,9 @@ proc getTypeDescWeak(m: BModule; t: PType; check: var IntSet): Rope =
result = getTypeDescAux(m, t, check)
proc paramStorageLoc(param: PSym): TStorageLoc =
let t = param.typ.skipTypes({tyVar, tyTypeDesc})
if t.kind notin {tyArray, tyOpenArray, tyVarargs}:
result = stackPlacement(t)
if param.typ.skipTypes({tyVar, tyTypeDesc}).kind notin {
tyArray, tyOpenArray, tyVarargs}:
result = OnStack
else:
result = OnUnknown

View File

@@ -242,10 +242,6 @@ proc addrLoc(a: TLoc): Rope =
if lfIndirect notin a.flags and mapType(a.t) != ctArray:
result = "(&" & result & ")"
proc dupLoc(a: TLoc): Rope =
result = a.dup
assert result != nil
proc rdCharLoc(a: TLoc): Rope =
# read a location that may need a char-cast:
result = rdLoc(a)
@@ -290,13 +286,12 @@ proc resetLoc(p: BProc, loc: var TLoc) =
if not isComplexValueType(typ):
if containsGcRef:
var nilLoc: TLoc
initLoc(nilLoc, locTemp, loc.t, stackPlacement(typ))
initLoc(nilLoc, locTemp, loc.t, OnStack)
nilLoc.r = rope("NIM_NIL")
genRefAssign(p, loc, nilLoc, {afSrcIsNil})
else:
linefmt(p, cpsStmts, "$1 = 0;$n", rdLoc(loc))
else:
# XXX use stackPlacement here?
if optNilCheck in p.options:
linefmt(p, cpsStmts, "#chckNil((void*)$1);$n", addrLoc(loc))
if loc.s != OnStack:
@@ -346,21 +341,17 @@ proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) =
linefmt(p, cpsLocals, "$1 $2;$n", getTypeDesc(p.module, t), result.r)
result.k = locTemp
result.t = t
result.s = stackPlacement(t)
result.s = OnStack
result.flags = {}
constructLoc(p, result, not needsInit)
proc initGCFrame(p: BProc): Rope =
if p.gcFrameLen > 0:
result = ropegc(p.module, """
struct {#GcFrameBase b_; $1} GCF_;$n
GCF_.b_.L=$2;$n
#pushGcFrame((GcFrameBase*)&GCF_);$n""" % [
p.gcFrameType, rope(p.gcFrameLen)])
if p.gcFrameId > 0: result = "struct {$1} GCFRAME_;$n" % [p.gcFrameType]
proc deinitGCFrame(p: BProc): Rope =
if p.gcFrameLen > 0:
result = ropecg(p.module, "#popGcFrame();$n")
if p.gcFrameId > 0:
result = ropecg(p.module,
"if (((NU)&GCFRAME_) < 4096) #nimGCFrame(&GCFRAME_);$n")
proc localDebugInfo(p: BProc, s: PSym) =
if {optStackTrace, optEndb} * p.options != {optStackTrace, optEndb}: return
@@ -377,7 +368,7 @@ proc localDebugInfo(p: BProc, s: PSym) =
proc localVarDecl(p: BProc; s: PSym): Rope =
if s.loc.k == locNone:
fillLoc(s.loc, locLocalVar, s.typ, mangleLocalName(p, s), stackPlacement(s.typ))
fillLoc(s.loc, locLocalVar, s.typ, mangleLocalName(p, s), OnStack)
if s.kind == skLet: incl(s.loc.flags, lfNoDeepCopy)
result = getTypeDesc(p.module, s.typ)
if s.constraint.isNil:

View File

@@ -90,7 +90,7 @@ type
splitDecls*: int # > 0 if we are in some context for C++ that
# requires 'T x = T()' to become 'T x; x = T()'
# (yes, C++ is weird like that)
gcFrameLen*: int # the number of slots in the GC-Frame
gcFrameId*: Natural # for the GC stack marking
gcFrameType*: Rope # the struct {} we put the GC markers into
sigConflicts*: CountTable[string]

View File

@@ -588,7 +588,6 @@ proc evalAtCompileTime(c: PContext, n: PNode): PNode =
result = semfold.getConstExpr(c.module, call)
if result.isNil: result = n
else: return result
result.typ = semfold.getIntervalType(callee.magic, call)
block maybeLabelAsStatic:
# XXX: temporary work-around needed for tlateboundstatic.

View File

@@ -92,26 +92,6 @@ proc pickIntRange(a, b: PType): PType =
proc isIntRangeOrLit(t: PType): bool =
result = isIntRange(t) or isIntLit(t)
proc pickMinInt(n: PNode): BiggestInt =
if n.kind in {nkIntLit..nkUInt64Lit}:
result = n.intVal
elif isIntLit(n.typ):
result = n.typ.n.intVal
elif isIntRange(n.typ):
result = firstOrd(n.typ)
else:
internalError(n.info, "pickMinInt")
proc pickMaxInt(n: PNode): BiggestInt =
if n.kind in {nkIntLit..nkUInt64Lit}:
result = n.intVal
elif isIntLit(n.typ):
result = n.typ.n.intVal
elif isIntRange(n.typ):
result = lastOrd(n.typ)
else:
internalError(n.info, "pickMaxInt")
proc makeRange(typ: PType, first, last: BiggestInt): PType =
let minA = min(first, last)
let maxA = max(first, last)
@@ -137,116 +117,6 @@ proc makeRangeF(typ: PType, first, last: BiggestFloat): PType =
result.n = n
addSonSkipIntLit(result, skipTypes(typ, {tyRange}))
proc getIntervalType*(m: TMagic, n: PNode): PType =
# Nim requires interval arithmetic for ``range`` types. Lots of tedious
# work but the feature is very nice for reducing explicit conversions.
const ordIntLit = {nkIntLit..nkUInt64Lit}
result = n.typ
template commutativeOp(opr: untyped) =
let a = n.sons[1]
let b = n.sons[2]
if isIntRangeOrLit(a.typ) and isIntRangeOrLit(b.typ):
result = makeRange(pickIntRange(a.typ, b.typ),
opr(pickMinInt(a), pickMinInt(b)),
opr(pickMaxInt(a), pickMaxInt(b)))
template binaryOp(opr: untyped) =
let a = n.sons[1]
let b = n.sons[2]
if isIntRange(a.typ) and b.kind in {nkIntLit..nkUInt64Lit}:
result = makeRange(a.typ,
opr(pickMinInt(a), pickMinInt(b)),
opr(pickMaxInt(a), pickMaxInt(b)))
case m
of mUnaryMinusI, mUnaryMinusI64:
let a = n.sons[1].typ
if isIntRange(a):
# (1..3) * (-1) == (-3.. -1)
result = makeRange(a, 0|-|lastOrd(a), 0|-|firstOrd(a))
of mUnaryMinusF64:
let a = n.sons[1].typ
if isFloatRange(a):
result = makeRangeF(a, -getFloat(a.n.sons[1]),
-getFloat(a.n.sons[0]))
of mAbsF64:
let a = n.sons[1].typ
if isFloatRange(a):
# abs(-5.. 1) == (1..5)
if a.n[0].floatVal <= 0.0:
result = makeRangeF(a, 0.0, abs(getFloat(a.n.sons[0])))
else:
result = makeRangeF(a, abs(getFloat(a.n.sons[1])),
abs(getFloat(a.n.sons[0])))
of mAbsI:
let a = n.sons[1].typ
if isIntRange(a):
if a.n[0].intVal <= 0:
result = makeRange(a, 0, `|abs|`(getInt(a.n.sons[0])))
else:
result = makeRange(a, `|abs|`(getInt(a.n.sons[1])),
`|abs|`(getInt(a.n.sons[0])))
of mSucc:
let a = n.sons[1].typ
let b = n.sons[2].typ
if isIntRange(a) and isIntLit(b):
# (-5.. 1) + 6 == (-5 + 6)..(-1 + 6)
result = makeRange(a, pickMinInt(n.sons[1]) |+| pickMinInt(n.sons[2]),
pickMaxInt(n.sons[1]) |+| pickMaxInt(n.sons[2]))
of mPred:
let a = n.sons[1].typ
let b = n.sons[2].typ
if isIntRange(a) and isIntLit(b):
result = makeRange(a, pickMinInt(n.sons[1]) |-| pickMinInt(n.sons[2]),
pickMaxInt(n.sons[1]) |-| pickMaxInt(n.sons[2]))
of mAddI, mAddU:
commutativeOp(`|+|`)
of mMulI, mMulU:
commutativeOp(`|*|`)
of mSubI, mSubU:
binaryOp(`|-|`)
of mBitandI:
# since uint64 is still not even valid for 'range' (since it's no ordinal
# yet), we exclude it from the list (see bug #1638) for now:
var a = n.sons[1]
var b = n.sons[2]
# symmetrical:
if b.kind notin ordIntLit: swap(a, b)
if b.kind in ordIntLit:
let x = b.intVal|+|1
if (x and -x) == x and x >= 0:
result = makeRange(n.typ, 0, b.intVal)
of mModU:
let a = n.sons[1]
let b = n.sons[2]
if b.kind in ordIntLit:
if b.intVal >= 0:
result = makeRange(n.typ, 0, b.intVal-1)
else:
result = makeRange(n.typ, b.intVal+1, 0)
of mModI:
# so ... if you ever wondered about modulo's signedness; this defines it:
let a = n.sons[1]
let b = n.sons[2]
if b.kind in {nkIntLit..nkUInt64Lit}:
if b.intVal >= 0:
result = makeRange(n.typ, -(b.intVal-1), b.intVal-1)
else:
result = makeRange(n.typ, b.intVal+1, -(b.intVal+1))
of mDivI, mDivU:
binaryOp(`|div|`)
of mMinI:
commutativeOp(min)
of mMaxI:
commutativeOp(max)
else: discard
discard """
mShlI,
mShrI, mAddF64, mSubF64, mMulF64, mDivF64, mMaxF64, mMinF64
"""
proc evalIs(n, a: PNode): PNode =
# XXX: This should use the standard isOpImpl
internalAssert a.kind == nkSym and a.sym.kind == skType

View File

@@ -136,26 +136,6 @@ determined). Assignments from the base type to one of its subrange types
A subrange type has the same size as its base type (``int`` in the example).
Nim requires `interval arithmetic`:idx: for subrange types over a set
of built-in operators that involve constants: ``x %% 3`` is of
type ``range[0..2]``. The following built-in operators for integers are
affected by this rule: ``-``, ``+``, ``*``, ``min``, ``max``, ``succ``,
``pred``, ``mod``, ``div``, ``%%``, ``and`` (bitwise ``and``).
Bitwise ``and`` only produces a ``range`` if one of its operands is a
constant *x* so that (x+1) is a power of two.
(Bitwise ``and`` is then a ``%%`` operation.)
This means that the following code is accepted:
.. code-block:: nim
case (x and 3) + 7
of 7: echo "A"
of 8: echo "B"
of 9: echo "C"
of 10: echo "D"
# note: no ``else`` required as (x and 3) + 7 has the type: range[7..10]
Pre-defined floating point types
--------------------------------

View File

@@ -78,10 +78,10 @@ proc encode(dest: var MD5Block, src: cstring) =
proc decode(dest: var openArray[uint8], src: openArray[uint32]) =
var i = 0
for j in 0..high(src):
dest[i] = src[j] and 0xff'u32
dest[i+1] = src[j] shr 8 and 0xff'u32
dest[i+2] = src[j] shr 16 and 0xff'u32
dest[i+3] = src[j] shr 24 and 0xff'u32
dest[i] = uint8(src[j] and 0xff'u32)
dest[i+1] = uint8(src[j] shr 8 and 0xff'u32)
dest[i+2] = uint8(src[j] shr 16 and 0xff'u32)
dest[i+3] = uint8(src[j] shr 24 and 0xff'u32)
inc(i, 4)
proc transform(buffer: pointer, state: var MD5State) =
@@ -216,8 +216,8 @@ proc `$`*(d: MD5Digest): string =
const digits = "0123456789abcdef"
result = ""
for i in 0..15:
add(result, digits[(d[i] shr 4) and 0xF])
add(result, digits[d[i] and 0xF])
add(result, digits[(d[i].int shr 4) and 0xF])
add(result, digits[d[i].int and 0xF])
proc getMD5*(s: string): string =
## computes an MD5 value of `s` and returns its string representation

View File

@@ -148,13 +148,13 @@ proc sha1(src: cstring; len: int): Sha1Digest =
while lastBlockBytes < endCurrentBlock:
var value = uint32(src[lastBlockBytes + currentBlock]) shl
((3'u32 - (lastBlockBytes and 3)) shl 3)
((3'u32 - uint32(lastBlockBytes and 3)) shl 3)
w[lastBlockBytes shr 2] = w[lastBlockBytes shr 2] or value
inc(lastBlockBytes)
w[lastBlockBytes shr 2] = w[lastBlockBytes shr 2] or (
0x80'u32 shl ((3'u32 - (lastBlockBytes and 3)) shl 3)
0x80'u32 shl ((3'u32 - uint32(lastBlockBytes and 3)) shl 3)
)
if endCurrentBlock >= 56:

View File

@@ -887,7 +887,7 @@ proc toHex*(x: BiggestInt, len: Positive): string {.noSideEffect,
n = x
result = newString(len)
for j in countdown(len-1, 0):
result[j] = HexChars[n and 0xF]
result[j] = HexChars[(n and 0xF).int]
n = n shr 4
# handle negative overflow
if n == 0 and x < 0: n = -1