Merge branch 'vm2_2' into devel

This commit is contained in:
Araq
2014-02-25 01:21:00 +01:00
21 changed files with 976 additions and 577 deletions

View File

@@ -62,7 +62,7 @@ type
nkTripleStrLit, # a triple string literal """
nkNilLit, # the nil literal
# end of atoms
nkMetaNode, # difficult to explain; represents itself
nkMetaNode_Obsolete, # difficult to explain; represents itself
# (used for macros)
nkDotCall, # used to temporarily flag a nkCall node;
# this is used
@@ -1112,10 +1112,6 @@ proc newNodeIT(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
result.info = info
result.typ = typ
proc newMetaNodeIT*(tree: PNode, info: TLineInfo, typ: PType): PNode =
result = newNodeIT(nkMetaNode, info, typ)
result.add(tree)
var emptyParams = newNode(nkFormalParams)
emptyParams.addSon(emptyNode)

View File

@@ -337,7 +337,10 @@ proc treeToYamlAux(n: PNode, marker: var TIntSet, indent: int,
appf(result, ",$N$1\"floatVal\": $2",
[istr, toRope(n.floatVal.toStrMaxPrecision)])
of nkStrLit..nkTripleStrLit:
appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
if n.strVal.isNil:
appf(result, ",$N$1\"strVal\": null", [istr])
else:
appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
of nkSym:
appf(result, ",$N$1\"sym\": $2",
[istr, symToYamlAux(n.sym, marker, indent + 2, maxRecDepth)])
@@ -407,7 +410,10 @@ proc debugTree(n: PNode, indent: int, maxRecDepth: int): PRope =
appf(result, ",$N$1\"floatVal\": $2",
[istr, toRope(n.floatVal.toStrMaxPrecision)])
of nkStrLit..nkTripleStrLit:
appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
if n.strVal.isNil:
appf(result, ",$N$1\"strVal\": null", [istr])
else:
appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
of nkSym:
appf(result, ",$N$1\"sym\": $2_$3",
[istr, toRope(n.sym.name.s), toRope(n.sym.id)])

288
compiler/canonicalizer.nim Normal file
View File

@@ -0,0 +1,288 @@
#
#
# The Nimrod Compiler
# (c) Copyright 2014 Andreas Rumpf
#
# See the file "copying.txt", included in this
# distribution, for details about the copyright.
#
## This module implements the canonalization for the various caching mechanisms.
import strutils, db_sqlite, md5
var db: TDbConn
# We *hash* the relevant information into 128 bit hashes. This should be good enough
# to prevent any collisions.
type
TUid = distinct MD5Digest
# For name mangling we encode these hashes via a variant of base64 (called
# 'base64a') and prepend the *primary* identifier to ease the debugging pain.
# So a signature like:
#
# proc gABI(c: PCtx; n: PNode; opc: TOpcode; a, b: TRegister; imm: BiggestInt)
#
# is mangled into:
# gABI_MTdmOWY5MTQ1MDcyNGQ3ZA
#
# This is a good compromise between correctness and brevity. ;-)
const
cb64 = [
"A", "B", "C", "D", "E", "F", "G", "H", "I", "J", "K", "L", "M", "N",
"O", "P", "Q", "R", "S", "T" "U", "V", "W", "X", "Y", "Z",
"a", "b", "c", "d", "e", "f", "g", "h", "i", "j", "k", "l", "m", "n",
"o", "p", "q", "r", "s", "t", "u", "v", "w", "x", "y", "z",
"0", "1", "2", "3", "4", "5", "6", "7", "8", "9",
"_A", "_B"]
proc toBase64a(s: cstring, len: int): string =
## encodes `s` into base64 representation. After `lineLen` characters, a
## `newline` is added.
var total = ((len + 2) div 3) * 4
result = newStringOfCap(total)
var i = 0
while i < s.len - 2:
let a = ord(s[i])
let b = ord(s[i+1])
let c = ord(s[i+2])
result.add cb64[a shr 2]
result.add cb64[((a and 3) shl 4) or ((b and 0xF0) shr 4)]
result.add cb64[((b and 0x0F) shl 2) or ((c and 0xC0) shr 6)]
result.add cb64[c and 0x3F]
inc(i, 3)
if i < s.len-1:
let a = ord(s[i])
let b = ord(s[i+1])
result.add cb64[a shr 2]
result.add cb64[((a and 3) shl 4) or ((b and 0xF0) shr 4)]
result.add cb64[((b and 0x0F) shl 2)]
elif i < s.len:
let a = ord(s[i])
result.add cb64[a shr 2]
result.add cb64[(a and 3) shl 4]
proc toBase64a(u: TUid): string = toBase64a(cast[cstring](u), sizeof(u))
proc `&=`(c: var MD5Context, s: string) = md5Update(c, s, s.len)
proc hashSym(c: var MD5Context, s: PSym) =
if sfAnon in s.flags or s.kind == skGenericParam:
c &= ":anon"
else:
var it = s.owner
while it != nil:
hashSym(c, it)
c &= "."
it = s.owner
c &= s.name.s
proc hashTree(c: var MD5Context, n: PNode) =
if n == nil:
c &= "null"
return
var k = n.kind
md5Update(c, cast[cstring](addr(k)), 1)
# we really must not hash line information. 'n.typ' is debatable but
# shouldn't be necessary for now and avoids potential infinite recursions.
case n.kind
of nkEmpty, nkNilLit, nkType: discard
of nkIdent:
c &= n.ident.s
of nkSym:
hashSym(c, n.sym)
of nkCharLit..nkUInt64Lit:
var v = n.intVal
md5Update(c, cast[cstring](addr(v)), sizeof(v))
of nkFloatLit..nkFloat64Lit:
var v = n.floatVal
md5Update(c, cast[cstring](addr(v)), sizeof(v))
of nkStrLit..nkTripleStrLit:
c &= n.strVal
else:
for i in 0.. <n.len: hashTree(c, n.sons[i])
const
typeToStr: array[TTypeKind, string] = ["None", "bool", "Char", "empty",
"Array Constructor [$1]", "nil", "expr", "stmt", "typeDesc",
"GenericInvokation", "GenericBody", "GenericInst", "GenericParam",
"distinct $1", "enum", "ordinal[$1]", "array[$1, $2]", "object", "tuple",
"set[$1]", "range[$1]", "ptr ", "ref ", "var ", "seq[$1]", "proc",
"pointer", "OpenArray[$1]", "string", "CString", "Forward",
"int", "int8", "int16", "int32", "int64",
"float", "float32", "float64", "float128",
"uint", "uint8", "uint16", "uint32", "uint64",
"bignum", "const ",
"!", "varargs[$1]", "iter[$1]", "Error Type",
"BuiltInTypeClass", "UserTypeClass",
"UserTypeClassInst", "CompositeTypeClass",
"and", "or", "not", "any", "static", "TypeFromExpr", "FieldAccessor"]
proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
var t = typ
result = ""
if t == nil: return
if prefer == preferName and t.sym != nil and sfAnon notin t.sym.flags:
if t.kind == tyInt and isIntLit(t):
return t.sym.name.s & " literal(" & $t.n.intVal & ")"
return t.sym.name.s
case t.kind
of tyInt:
if not isIntLit(t) or prefer == preferExported:
result = typeToStr[t.kind]
else:
result = "int literal(" & $t.n.intVal & ")"
of tyGenericBody, tyGenericInst, tyGenericInvokation:
result = typeToString(t.sons[0]) & '['
for i in countup(1, sonsLen(t) -1 -ord(t.kind != tyGenericInvokation)):
if i > 1: add(result, ", ")
add(result, typeToString(t.sons[i]))
add(result, ']')
of tyTypeDesc:
if t.base.kind == tyNone: result = "typedesc"
else: result = "typedesc[" & typeToString(t.base) & "]"
of tyStatic:
internalAssert t.len > 0
result = "static[" & typeToString(t.sons[0]) & "]"
of tyUserTypeClass:
internalAssert t.sym != nil and t.sym.owner != nil
return t.sym.owner.name.s
of tyBuiltInTypeClass:
result = case t.base.kind:
of tyVar: "var"
of tyRef: "ref"
of tyPtr: "ptr"
of tySequence: "seq"
of tyArray: "array"
of tySet: "set"
of tyRange: "range"
of tyDistinct: "distinct"
of tyProc: "proc"
of tyObject: "object"
of tyTuple: "tuple"
else: (internalAssert(false); "")
of tyUserTypeClassInst:
let body = t.base
result = body.sym.name.s & "["
for i in countup(1, sonsLen(t) - 2):
if i > 1: add(result, ", ")
add(result, typeToString(t.sons[i]))
result.add "]"
of tyAnd:
result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
of tyOr:
result = typeToString(t.sons[0]) & " or " & typeToString(t.sons[1])
of tyNot:
result = "not " & typeToString(t.sons[0])
of tyExpr:
internalAssert t.len == 0
result = "expr"
of tyFromExpr, tyFieldAccessor:
result = renderTree(t.n)
of tyArray:
if t.sons[0].kind == tyRange:
result = "array[" & hashTree(t.sons[0].n) & ", " &
typeToString(t.sons[1]) & ']'
else:
result = "array[" & typeToString(t.sons[0]) & ", " &
typeToString(t.sons[1]) & ']'
of tyArrayConstr:
result = "Array constructor[" & hashTree(t.sons[0].n) & ", " &
typeToString(t.sons[1]) & ']'
of tySequence:
result = "seq[" & typeToString(t.sons[0]) & ']'
of tyOrdinal:
result = "ordinal[" & typeToString(t.sons[0]) & ']'
of tySet:
result = "set[" & typeToString(t.sons[0]) & ']'
of tyOpenArray:
result = "openarray[" & typeToString(t.sons[0]) & ']'
of tyDistinct:
result = "distinct " & typeToString(t.sons[0], preferName)
of tyTuple:
# we iterate over t.sons here, because t.n may be nil
result = "tuple["
if t.n != nil:
assert(sonsLen(t.n) == sonsLen(t))
for i in countup(0, sonsLen(t.n) - 1):
assert(t.n.sons[i].kind == nkSym)
add(result, t.n.sons[i].sym.name.s & ": " & typeToString(t.sons[i]))
if i < sonsLen(t.n) - 1: add(result, ", ")
else:
for i in countup(0, sonsLen(t) - 1):
add(result, typeToString(t.sons[i]))
if i < sonsLen(t) - 1: add(result, ", ")
add(result, ']')
of tyPtr, tyRef, tyVar, tyMutable, tyConst:
result = typeToStr[t.kind] & typeToString(t.sons[0])
of tyRange:
result = "range " & hashTree(t.n)
if prefer != preferExported:
result.add("(" & typeToString(t.sons[0]) & ")")
of tyProc:
result = if tfIterator in t.flags: "iterator (" else: "proc ("
for i in countup(1, sonsLen(t) - 1):
add(result, typeToString(t.sons[i]))
if i < sonsLen(t) - 1: add(result, ", ")
add(result, ')')
if t.sons[0] != nil: add(result, ": " & typeToString(t.sons[0]))
var prag: string
if t.callConv != ccDefault: prag = CallingConvToStr[t.callConv]
else: prag = ""
if tfNoSideEffect in t.flags:
addSep(prag)
add(prag, "noSideEffect")
if tfThread in t.flags:
addSep(prag)
add(prag, "thread")
if len(prag) != 0: add(result, "{." & prag & ".}")
of tyVarargs, tyIter:
result = typeToStr[t.kind] % typeToString(t.sons[0])
else:
result = typeToStr[t.kind]
if tfShared in t.flags: result = "shared " & result
if tfNotNil in t.flags: result.add(" not nil")
proc createDb() =
db.exec(sql"""
create table if not exists Module(
id integer primary key,
name varchar(256) not null,
fullpath varchar(256) not null,
interfHash varchar(256) not null,
fullHash varchar(256) not null,
created timestamp not null default (DATETIME('now')),
);""")
db.exec(sql"""
create table if not exists Symbol(
id integer primary key,
module integer not null,
name varchar(max) not null,
data varchar(max) not null,
created timestamp not null default (DATETIME('now')),
foreign key (module) references module(id)
);""")
db.exec(sql"""
create table if not exists Type(
id integer primary key,
module integer not null,
name varchar(max) not null,
data varchar(max) not null,
created timestamp not null default (DATETIME('now')),
foreign key (module) references module(id)
);""")
#db.exec(sql"""
# --create unique index if not exists TsstNameIx on TestResult(name);
# """, [])

View File

@@ -1915,7 +1915,6 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
internalError(n.info, "expr: proc not init " & sym.name.s)
putLocIntoDest(p, d, sym.loc)
of nkClosure: genClosure(p, n, d)
of nkMetaNode: expr(p, n.sons[0], d)
of nkEmpty: discard
of nkWhileStmt: genWhileStmt(p, n)

View File

@@ -1600,7 +1600,6 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
if lfNoDecl in s.loc.flags or s.magic != mNone: discard
elif not p.g.generatedSyms.containsOrIncl(s.id):
app(p.locals, genProc(p, s))
of nkMetaNode: gen(p, n.sons[0], r)
of nkType: r.res = genTypeInfo(p, n.typ)
of nkStmtList, nkStmtListExpr:
# this shows the distinction is nice for backends and should be kept

View File

@@ -67,7 +67,7 @@ type
errAmbiguousCallXYZ, errWrongNumberOfArguments,
errXCannotBePassedToProcVar,
errXCannotBeInParamDecl, errPragmaOnlyInHeaderOfProc, errImplOfXNotAllowed,
errImplOfXexpected, errNoSymbolToBorrowFromFound, errDiscardValue,
errImplOfXexpected, errNoSymbolToBorrowFromFound, errDiscardValueX,
errInvalidDiscard, errIllegalConvFromXtoY, errCannotBindXTwice,
errInvalidOrderInArrayConstructor,
errInvalidOrderInEnumX, errEnumXHasHoles, errExceptExpected, errInvalidTry,
@@ -266,7 +266,7 @@ const
errImplOfXNotAllowed: "implementation of \'$1\' is not allowed",
errImplOfXexpected: "implementation of \'$1\' expected",
errNoSymbolToBorrowFromFound: "no symbol to borrow from found",
errDiscardValue: "value returned by statement has to be discarded",
errDiscardValueX: "value of type '$1' has to be discarded",
errInvalidDiscard: "statement returns no value that can be discarded",
errIllegalConvFromXtoY: "conversion from $1 to $2 is invalid",
errCannotBindXTwice: "cannot bind parameter \'$1\' twice",

View File

@@ -1268,7 +1268,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
put(g, tkBracketLe, "[")
gcomma(g, n)
put(g, tkBracketRi, "]")
of nkMetaNode:
of nkMetaNode_Obsolete:
put(g, tkParLe, "(META|")
gsub(g, n.sons[0])
put(g, tkParRi, ")")

View File

@@ -890,7 +890,7 @@ proc loadStub*(s: PSym) =
# deactivate the GC here because we do a deep recursion and generate no
# garbage when restoring parts of the object graph anyway.
# Since we die with internal errors if this fails, so no try-finally is
# Since we die with internal errors if this fails, no try-finally is
# necessary.
GC_disable()
rawLoadStub(s)

View File

@@ -220,7 +220,7 @@ proc tryConstExpr(c: PContext, n: PNode): PNode =
return nil
result = fixupTypeAfterEval(c, result, e)
except:
except ERecoverableError:
return nil
proc semConstExpr(c: PContext, n: PNode): PNode =

View File

@@ -641,9 +641,11 @@ proc evalAtCompileTime(c: PContext, n: PNode): PNode =
result = evalStaticExpr(c.module, call, c.p.owner)
if result.isNil:
localError(n.info, errCannotInterpretNodeX, renderTree(call))
else: result = fixupTypeAfterEval(c, result, n)
else:
result = evalConstExpr(c.module, call)
if result.isNil: result = n
else: result = fixupTypeAfterEval(c, result, n)
#if result != n:
# echo "SUCCESS evaluated at compile time: ", call.renderTree
@@ -653,6 +655,8 @@ proc semStaticExpr(c: PContext, n: PNode): PNode =
if result.isNil:
localError(n.info, errCannotInterpretNodeX, renderTree(n))
result = emptyNode
else:
result = fixupTypeAfterEval(c, result, a)
proc semOverloadedCallAnalyseEffects(c: PContext, n: PNode, nOrig: PNode,
flags: TExprFlags): PNode =

View File

@@ -537,7 +537,7 @@ proc foldArrayAccess(m: PSym, n: PNode): PNode =
if result.kind == nkExprColonExpr: result = result.sons[1]
else:
localError(n.info, errIndexOutOfBounds)
of nkBracket, nkMetaNode:
of nkBracket:
if (idx >= 0) and (idx < sonsLen(x)): result = x.sons[int(idx)]
else: localError(n.info, errIndexOutOfBounds)
of nkStrLit..nkTripleStrLit:

View File

@@ -126,7 +126,7 @@ proc implicitlyDiscardable(n: PNode): bool =
proc fixNilType(n: PNode) =
if isAtom(n):
if n.kind != nkNilLit and n.typ != nil:
localError(n.info, errDiscardValue)
localError(n.info, errDiscardValueX, n.typ.typeToString)
elif n.kind in {nkStmtList, nkStmtListExpr}:
n.kind = nkStmtList
for it in n: fixNilType(it)
@@ -155,7 +155,7 @@ proc discardCheck(c: PContext, result: PNode) =
else:
var n = result
while n.kind in skipForDiscardable: n = n.lastSon
localError(n.info, errDiscardValue)
localError(n.info, errDiscardValueX, result.typ.typeToString)
proc semIf(c: PContext, n: PNode): PNode =
result = n
@@ -332,6 +332,7 @@ proc checkNilable(v: PSym) =
proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
var b: PNode
result = copyNode(n)
var hasCompileTime = false
for i in countup(0, sonsLen(n)-1):
var a = n.sons[i]
if gCmd == cmdIdeTools: suggestStmt(c, a)
@@ -411,7 +412,9 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
v.typ = tup.sons[j]
b.sons[j] = newSymNode(v)
checkNilable(v)
if sfCompileTime in v.flags: hasCompileTime = true
if hasCompileTime: vm.setupCompileTimeVar(c.module, result)
proc semConst(c: PContext, n: PNode): PNode =
result = copyNode(n)
for i in countup(0, sonsLen(n) - 1):

View File

@@ -463,7 +463,7 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
of tyAnd:
result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
of tyOr:
result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
result = typeToString(t.sons[0]) & " or " & typeToString(t.sons[1])
of tyNot:
result = "not " & typeToString(t.sons[0])
of tyExpr:

File diff suppressed because it is too large Load Diff

View File

@@ -8,7 +8,7 @@
#
## This module contains the type definitions for the new evaluation engine.
## An instruction is 1-2 int32s in memory, it is a register based VM.
## An instruction is 1-3 int32s in memory, it is a register based VM.
import ast, passes, msgs, intsets
@@ -32,17 +32,17 @@ type
opcAsgnFloat,
opcAsgnRef,
opcAsgnComplex,
opcRegToNode,
opcNodeToReg,
opcLdArr, # a = b[c]
opcLdArrRef,
opcWrArr, # a[b] = c
opcWrArrRef,
opcLdObj, # a = b.c
opcLdObjRef,
opcWrObj, # a.b = c
opcWrObjRef,
opcAddr,
opcDeref,
opcAddrReg,
opcAddrNode,
opcLdDeref,
opcWrDeref,
opcWrStrIdx,
opcLdStrIdx, # a = b[c]
@@ -117,15 +117,13 @@ type
opcNew,
opcNewSeq,
opcLdNull, # dest = nullvalue(types[Bx])
opcLdNullReg,
opcLdConst, # dest = constants[Bx]
opcAsgnConst, # dest = copy(constants[Bx])
opcLdGlobal, # dest = globals[Bx]
opcLdImmInt, # dest = immediate value
opcNBindSym,
opcWrGlobal,
opcWrGlobalRef,
opcGlobalAlias, # load an alias to a global into a register
opcGlobalOnce, # used to introduce an assignment to a global once
opcSetType, # dest.typ = types[Bx]
opcTypeTrait
@@ -165,8 +163,6 @@ type
blocks*: seq[TBlock] # blocks; temp data structure
slots*: array[TRegister, tuple[inUse: bool, kind: TSlotKind]]
maxSlots*: int
globals*: array[TRegister, int] # hack: to support passing globals byref
# we map a slot persistently to a global
PCtx* = ref TCtx
TCtx* = object of passes.TPassContext # code gen context
@@ -183,6 +179,7 @@ type
callsite*: PNode
mode*: TEvalMode
features*: TSandboxFlags
traceActive*: bool
TPosition* = distinct int

View File

@@ -139,25 +139,12 @@ proc getTemp(c: PCtx; typ: PType): TRegister =
if not c.slots[i].inUse:
c.slots[i] = (inUse: true, kind: k)
return TRegister(i)
if c.maxSlots >= high(TRegister):
internalError("cannot generate code; too many registers required")
result = TRegister(c.maxSlots)
c.slots[c.maxSlots] = (inUse: true, kind: k)
inc c.maxSlots
proc getGlobalSlot(c: PCtx; n: PNode; s: PSym): TRegister =
let p = c.prc
for i in 0 .. p.maxSlots-1:
if p.globals[i] == s.id: return TRegister(i)
result = TRegister(p.maxSlots)
p.slots[p.maxSlots] = (inUse: true, kind: slotFixedVar)
p.globals[p.maxSlots] = s.id
inc p.maxSlots
# XXX this is still not correct! We need to load the global in a proc init
# section, otherwise control flow could lead to a usage before it's been
# loaded.
c.gABx(n, opcGlobalAlias, result, s.position)
# XXX add some internal asserts here
proc freeTemp(c: PCtx; r: TRegister) =
let c = c.prc
if c.slots[r].kind >= slotSomeTemp: c.slots[r].inUse = false
@@ -322,13 +309,7 @@ proc genAndOr(c: PCtx; n: PNode; opc: TOpcode; dest: var TDest) =
c.patch(L1)
proc nilLiteral(n: PNode): PNode =
if n.kind == nkNilLit and n.typ.sym != nil and
n.typ.sym.magic == mPNimrodNode:
let nilo = newNodeIT(nkNilLit, n.info, n.typ)
result = newNodeIT(nkMetaNode, n.info, n.typ)
result.add nilo
else:
result = n
result = n
proc rawGenLiteral(c: PCtx; n: PNode): int =
result = c.constants.len
@@ -470,21 +451,37 @@ proc genCall(c: PCtx; n: PNode; dest: var TDest) =
c.gABC(n, opcIndCallAsgn, dest, x, n.len)
c.freeTempRange(x, n.len)
template isGlobal(s: PSym): bool = sfGlobal in s.flags and s.kind != skForVar
proc needsAsgnPatch(n: PNode): bool =
n.kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr}
n.kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr,
nkDerefExpr, nkHiddenDeref} or (n.kind == nkSym and n.sym.isGlobal)
proc genAsgnPatch(c: PCtx; le: PNode, value: TRegister) =
case le.kind
of nkBracketExpr:
let dest = c.genx(le.sons[0])
let dest = c.genx(le.sons[0], {gfAddrOf})
let idx = c.genx(le.sons[1])
c.gABC(le, opcWrArrRef, dest, idx, value)
c.gABC(le, opcWrArr, dest, idx, value)
c.freeTemp(dest)
c.freeTemp(idx)
of nkDotExpr, nkCheckedFieldExpr:
# XXX field checks here
let left = if le.kind == nkDotExpr: le else: le.sons[0]
let dest = c.genx(left.sons[0])
let dest = c.genx(left.sons[0], {gfAddrOf})
let idx = c.genx(left.sons[1])
c.gABC(left, opcWrObjRef, dest, idx, value)
c.gABC(left, opcWrObj, dest, idx, value)
c.freeTemp(dest)
c.freeTemp(idx)
of nkDerefExpr, nkHiddenDeref:
let dest = c.genx(le.sons[0], {gfAddrOf})
c.gABC(le, opcWrDeref, dest, value)
c.freeTemp(dest)
of nkSym:
if le.sym.isGlobal:
let dest = c.genx(le, {gfAddrOf})
c.gABC(le, opcWrDeref, dest, value)
c.freeTemp(dest)
else:
discard
@@ -594,10 +591,10 @@ proc genAddSubInt(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) =
let tmp = c.genx(arg)
c.gABx(n, opcSetType, tmp, genType(c, arg.typ))
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, arg.typ))
c.freeTemp(tmp)
proc genCard(c: PCtx; n: PNode; dest: var TDest) =
@@ -623,6 +620,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
c.genAddSubInt(n, dest, opcAddInt)
of mInc, mDec:
unused(n, dest)
# XXX generates inefficient code for globals
var d = c.genx(n.sons[1]).TDest
c.genAddSubInt(n, d, if m == mInc: opcAddInt else: opcSubInt)
c.genAsgnPatch(n.sons[1], d)
@@ -636,6 +634,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
c.genNewSeq(n)
of mNewString:
genUnaryABC(c, n, dest, opcNewStr)
# XXX buggy
of mNewStringOfCap:
# we ignore the 'cap' argument and translate it as 'newString(0)'.
# eval n.sons[1] for possible side effects:
@@ -644,6 +643,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
if dest < 0: dest = c.getTemp(n.typ)
c.gABC(n, opcNewStr, dest, tmp)
c.freeTemp(tmp)
# XXX buggy
of mLengthOpenArray, mLengthArray, mLengthSeq:
genUnaryABI(c, n, dest, opcLenSeq)
of mLengthStr:
@@ -905,6 +905,10 @@ const
tyFloat, tyFloat32, tyFloat64, tyFloat128,
tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64}
proc fitsRegister*(t: PType): bool =
t.skipTypes(abstractInst-{tyTypeDesc}).kind in {
tyRange, tyEnum, tyBool, tyInt..tyUInt64}
proc requiresCopy(n: PNode): bool =
if n.typ.skipTypes(abstractInst-{tyTypeDesc}).kind in atomicTypes:
result = false
@@ -919,7 +923,8 @@ proc unneededIndirection(n: PNode): bool =
proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode;
flags: TGenFlags) =
# a nop for certain types
let flags = if opc == opcAddr: flags+{gfAddrOf} else: flags
let isAddr = opc in {opcAddrNode, opcAddrReg}
let flags = if isAddr: flags+{gfAddrOf} else: flags
# consider:
# proc foo(f: var ref int) =
# f = new(int)
@@ -929,12 +934,17 @@ proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode;
#
# The type of 'f' is 'var ref int' and of 'x' is 'ref int'. Hence for
# nkAddr we must not use 'unneededIndirection', but for deref we use it.
if opc != opcAddr and unneededIndirection(n.sons[0]):
if not isAddr and unneededIndirection(n.sons[0]):
gen(c, n.sons[0], dest, flags)
else:
let tmp = c.genx(n.sons[0], flags)
if dest < 0: dest = c.getTemp(n.typ)
gABC(c, n, opc, dest, tmp)
if not isAddr:
gABC(c, n, opc, dest, tmp)
elif c.prc.slots[tmp].kind >= slotTempUnknown:
gABC(c, n, opcAddrReg, dest, tmp)
else:
gABC(c, n, opcAddrNode, dest, tmp)
c.freeTemp(tmp)
proc whichAsgnOpc(n: PNode): TOpcode =
@@ -952,8 +962,7 @@ proc whichAsgnOpc(n: PNode): TOpcode =
proc isRef(t: PType): bool = t.skipTypes(abstractRange-{tyTypeDesc}).kind == tyRef
proc whichAsgnOpc(n: PNode; opc: TOpcode): TOpcode =
if isRef(n.typ): succ(opc) else: opc
proc whichAsgnOpc(n: PNode; opc: TOpcode): TOpcode = opc
proc genAsgn(c: PCtx; dest: TDest; ri: PNode; requiresCopy: bool) =
let tmp = c.genx(ri)
@@ -961,8 +970,6 @@ proc genAsgn(c: PCtx; dest: TDest; ri: PNode; requiresCopy: bool) =
gABC(c, ri, whichAsgnOpc(ri), dest, tmp)
c.freeTemp(tmp)
template isGlobal(s: PSym): bool = sfGlobal in s.flags and s.kind != skForVar
proc setSlot(c: PCtx; v: PSym) =
# XXX generate type initialization here?
if v.position == 0:
@@ -974,29 +981,36 @@ proc setSlot(c: PCtx; v: PSym) =
proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
case le.kind
of nkBracketExpr:
let dest = c.genx(le.sons[0])
let dest = c.genx(le.sons[0], {gfAddrOf})
let idx = c.genx(le.sons[1])
let tmp = c.genx(ri)
if le.sons[0].typ.skipTypes(abstractVarRange-{tyTypeDesc}).kind in {
tyString, tyCString}:
c.gABC(le, opcWrStrIdx, dest, idx, tmp)
else:
c.gABC(le, whichAsgnOpc(le, opcWrArr), dest, idx, tmp)
c.gABC(le, opcWrArr, dest, idx, tmp)
c.freeTemp(tmp)
of nkDotExpr, nkCheckedFieldExpr:
# XXX field checks here
let left = if le.kind == nkDotExpr: le else: le.sons[0]
let dest = c.genx(left.sons[0])
let dest = c.genx(left.sons[0], {gfAddrOf})
let idx = c.genx(left.sons[1])
let tmp = c.genx(ri)
c.gABC(left, whichAsgnOpc(left, opcWrObj), dest, idx, tmp)
c.gABC(left, opcWrObj, dest, idx, tmp)
c.freeTemp(tmp)
of nkDerefExpr, nkHiddenDeref:
let dest = c.genx(le, {gfAddrOf})
let tmp = c.genx(ri)
c.gABC(le, opcWrDeref, dest, tmp)
c.freeTemp(tmp)
of nkSym:
let s = le.sym
if s.isGlobal:
withTemp(tmp, le.typ):
gen(c, ri, tmp)
c.gABx(le, whichAsgnOpc(le, opcWrGlobal), tmp, s.position)
c.gen(le, tmp, {gfAddrOf})
let val = c.genx(ri)
c.gABC(le, opcWrDeref, tmp, val)
c.freeTemp(val)
else:
if s.kind == skForVar and c.mode == emRepl: c.setSlot s
internalAssert s.position > 0 or (s.position == 0 and
@@ -1004,7 +1018,7 @@ proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
var dest: TRegister = s.position + ord(s.kind == skParam)
gen(c, ri, dest)
else:
let dest = c.genx(le)
let dest = c.genx(le, {gfAddrOf})
genAsgn(c, dest, ri, requiresCopy)
proc genLit(c: PCtx; n: PNode; dest: var TDest) =
@@ -1034,18 +1048,22 @@ proc cannotEval(n: PNode) {.noinline.} =
globalError(n.info, errGenerated, "cannot evaluate at compile time: " &
n.renderTree)
proc getNullValue*(typ: PType, info: TLineInfo): PNode
proc genGlobalInit(c: PCtx; n: PNode; s: PSym) =
c.globals.add(emptyNode.copyNode)
c.globals.add(getNullValue(s.typ, n.info))
s.position = c.globals.len
# This is rather hard to support, due to the laziness of the VM code
# generator. See tests/compile/tmacro2 for why this is necesary:
# var decls{.compileTime.}: seq[PNimrodNode] = @[]
c.gABx(n, opcGlobalOnce, 0, s.position)
let dest = c.getTemp(s.typ)
c.gABx(n, opcLdGlobal, dest, s.position)
let tmp = c.genx(s.ast)
c.gABx(n, whichAsgnOpc(n, opcWrGlobal), tmp, s.position)
c.gABC(n, opcWrDeref, dest, tmp)
c.freeTemp(dest)
c.freeTemp(tmp)
proc genRdVar(c: PCtx; n: PNode; dest: var TDest) =
proc genRdVar(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
let s = n.sym
if s.isGlobal:
if sfCompileTime in s.flags or c.mode == emRepl:
@@ -1055,9 +1073,12 @@ proc genRdVar(c: PCtx; n: PNode; dest: var TDest) =
if s.position == 0:
if sfImportc in s.flags: c.importcSym(n.info, s)
else: genGlobalInit(c, n, s)
if dest < 0:
dest = c.getGlobalSlot(n, s)
#c.gABx(n, opcAliasGlobal, dest, s.position)
if dest < 0: dest = c.getTemp(n.typ)
if gfAddrOf notin flags and fitsRegister(s.typ):
var cc = c.getTemp(n.typ)
c.gABx(n, opcLdGlobal, cc, s.position)
c.gABC(n, opcNodeToReg, dest, cc)
c.freeTemp(cc)
else:
c.gABx(n, opcLdGlobal, dest, s.position)
else:
@@ -1078,7 +1099,13 @@ proc genAccess(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode;
let a = c.genx(n.sons[0], flags)
let b = c.genx(n.sons[1], {})
if dest < 0: dest = c.getTemp(n.typ)
c.gABC(n, (if gfAddrOf in flags: succ(opc) else: opc), dest, a, b)
if gfAddrOf notin flags and fitsRegister(n.typ):
var cc = c.getTemp(n.typ)
c.gABC(n, opc, cc, a, b)
c.gABC(n, opcNodeToReg, dest, cc)
c.freeTemp(cc)
else:
c.gABC(n, opc, dest, a, b)
c.freeTemp(a)
c.freeTemp(b)
@@ -1096,7 +1123,6 @@ proc genArrAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
else:
genAccess(c, n, dest, opcLdArr, flags)
proc getNullValue*(typ: PType, info: TLineInfo): PNode
proc getNullValueAux(obj: PNode, result: PNode) =
case obj.kind
of nkRecList:
@@ -1121,12 +1147,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
result = newNodeIT(nkFloatLit, info, t)
of tyVar, tyPointer, tyPtr, tyCString, tySequence, tyString, tyExpr,
tyStmt, tyTypeDesc, tyStatic, tyRef:
if t.sym != nil and t.sym.magic == mPNimrodNode:
let nilo = newNodeIT(nkNilLit, info, t)
result = newNodeIT(nkMetaNode, info, t)
result.add nilo
else:
result = newNodeIT(nkNilLit, info, t)
result = newNodeIT(nkNilLit, info, t)
of tyProc:
if t.callConv != ccClosure:
result = newNodeIT(nkNilLit, info, t)
@@ -1154,6 +1175,9 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
result = newNodeIT(nkCurly, info, t)
else: internalError("getNullValue: " & $t.kind)
proc ldNullOpcode(t: PType): TOpcode =
if fitsRegister(t): opcLdNullReg else: opcLdNull
proc genVarSection(c: PCtx; n: PNode) =
for a in n:
if a.kind == nkCommentStmt: continue
@@ -1164,8 +1188,8 @@ proc genVarSection(c: PCtx; n: PNode) =
setSlot(c, a[i].sym)
# v = t[i]
var v: TDest = -1
genRdVar(c, a[i], v)
c.gABC(n, opcLdObj, v, tmp, i)
genRdVar(c, a[i], v, {gfAddrOf})
c.gABC(n, opcWrObj, v, tmp, i)
# XXX globals?
c.freeTemp(tmp)
elif a.sons[0].kind == nkSym:
@@ -1177,27 +1201,28 @@ proc genVarSection(c: PCtx; n: PNode) =
let sa = if s.ast.isNil: getNullValue(s.typ, a.info) else: s.ast
c.globals.add(sa)
s.position = c.globals.len
# "Once support" is unnecessary here
if a.sons[2].kind == nkEmpty:
when false:
withTemp(tmp, s.typ):
c.gABx(a, opcLdNull, tmp, c.genType(s.typ))
c.gABx(a, whichAsgnOpc(a.sons[0], opcWrGlobal), tmp, s.position)
else:
let tmp = genx(c, a.sons[2])
c.gABx(a, whichAsgnOpc(a.sons[0], opcWrGlobal), tmp, s.position)
let tmp = c.genx(a.sons[0], {gfAddrOf})
let val = c.genx(a.sons[2])
c.gABC(a, opcWrDeref, tmp, val)
c.freeTemp(val)
c.freeTemp(tmp)
else:
setSlot(c, s)
if a.sons[2].kind == nkEmpty:
c.gABx(a, opcLdNull, s.position, c.genType(s.typ))
c.gABx(a, ldNullOpcode(s.typ), s.position, c.genType(s.typ))
else:
gen(c, a.sons[2], s.position.TRegister)
else:
# assign to a.sons[0]; happens for closures
if a.sons[2].kind == nkEmpty:
let tmp = genx(c, a.sons[0])
c.gABx(a, opcLdNull, tmp, c.genType(a.sons[0].typ))
c.gABx(a, ldNullOpcode(a[0].typ), tmp, c.genType(a.sons[0].typ))
c.freeTemp(tmp)
else:
genAsgn(c, a.sons[0], a.sons[2], true)
@@ -1205,10 +1230,19 @@ proc genVarSection(c: PCtx; n: PNode) =
proc genArrayConstr(c: PCtx, n: PNode, dest: var TDest) =
if dest < 0: dest = c.getTemp(n.typ)
c.gABx(n, opcLdNull, dest, c.genType(n.typ))
let intType = getSysType(tyInt)
let seqType = n.typ.skipTypes(abstractVar-{tyTypeDesc})
if seqType.kind == tySequence:
var tmp = c.getTemp(intType)
c.gABx(n, opcLdImmInt, tmp, n.len)
c.gABx(n, opcNewSeq, dest, c.genType(seqType))
c.gABx(n, opcNewSeq, tmp, 0)
c.freeTemp(tmp)
if n.len > 0:
let intType = getSysType(tyInt)
var tmp = getTemp(c, intType)
c.gABx(n, opcLdNull, tmp, c.genType(intType))
c.gABx(n, opcLdNullReg, tmp, c.genType(intType))
for x in n:
let a = c.genx(x)
c.gABC(n, whichAsgnOpc(x, opcWrArr), dest, tmp, a)
@@ -1274,7 +1308,7 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) =
let s = n.sym
case s.kind
of skVar, skForVar, skTemp, skLet, skParam, skResult:
genRdVar(c, n, dest)
genRdVar(c, n, dest, flags)
of skProc, skConverter, skMacro, skTemplate, skMethod, skIterator:
# 'skTemplate' is only allowed for 'getAst' support:
if sfImportc in s.flags: c.importcSym(n.info, s)
@@ -1320,8 +1354,8 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) =
of nkDotExpr: genObjAccess(c, n, dest, flags)
of nkCheckedFieldExpr: genCheckedObjAccess(c, n, dest, flags)
of nkBracketExpr: genArrAccess(c, n, dest, flags)
of nkDerefExpr, nkHiddenDeref: genAddrDeref(c, n, dest, opcDeref, flags)
of nkAddr, nkHiddenAddr: genAddrDeref(c, n, dest, opcAddr, flags)
of nkDerefExpr, nkHiddenDeref: genAddrDeref(c, n, dest, opcLdDeref, flags)
of nkAddr, nkHiddenAddr: genAddrDeref(c, n, dest, opcAddrNode, flags)
of nkWhenStmt, nkIfStmt, nkIfExpr: genIf(c, n, dest)
of nkCaseStmt: genCase(c, n, dest)
of nkWhileStmt:
@@ -1506,7 +1540,7 @@ proc genProc(c: PCtx; s: PSym): int =
c.gABC(body, opcEof, eofInstr.regA)
c.optimizeJumps(result)
s.offset = c.prc.maxSlots
#if s.name.s == "concatStyleInterpolation":
#if s.name.s == "importImpl_forward" or s.name.s == "importImpl":
# c.echoCode(result)
# echo renderTree(body)
c.prc = oldPrc

View File

@@ -51,7 +51,7 @@ macro okayy:stmt =
for node in decls: result.add node
for node in impls: result.add node
importimpl(Item, int):
importImpl(Item, int):
echo 42
importImpl(Foo, int16):
echo 77

View File

@@ -18,10 +18,9 @@
# OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
# SOFTWARE.
#
when defined(Linux):
const Lib = "libchipmunk.so.6.1.1"
else:
{.error: "Platform unsupported".}
const Lib = "libchipmunk.so.6.1.1"
when defined(MoreNimrod):
{.hint: "MoreNimrod defined; some Chipmunk functions replaced in Nimrod".}
{.deadCodeElim: on.}

View File

@@ -17,10 +17,9 @@ COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER
IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN
CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
"""
when defined(Linux):
const Lib = "libenet.so.1(|.0.3)"
else:
{.error: "Your platform has not been accounted for."}
const Lib = "libenet.so.1(|.0.3)"
{.deadCodeElim: ON.}
const
ENET_VERSION_MAJOR* = 1
@@ -267,7 +266,7 @@ const
ENET_PEER_RELIABLE_WINDOW_SIZE = 0x1000
ENET_PEER_FREE_RELIABLE_WINDOWS = 8
when defined(Linux):
when defined(Linux) or true:
import posix
const
ENET_SOCKET_NULL*: cint = -1

View File

@@ -6,7 +6,12 @@ when defined(linux):
LibS = "libcsfml-system.so.2.0"
LibW = "libcsfml-window.so.2.0"
else:
{.error: "Platform unsupported".}
# We only compile for testing here, so it doesn't matter it's not supported
const
LibG = "libcsfml-graphics.so.2.0"
LibS = "libcsfml-system.so.2.0"
LibW = "libcsfml-window.so.2.0"
#{.error: "Platform unsupported".}
{.deadCodeElim: on.}
{.pragma: pf, pure, final.}
type
@@ -153,8 +158,9 @@ type
KeyF15, #/< The F15 key
KeyPause, #/< The Pause key
KeyCount #/< Keep last -- the total number of keyboard keys
when defined(linux): #or defined(bsd) ??
type TWindowHandle* = clong
type TWindowHandle* = clong
#elif defined(mac):
# type TWindowHandle* = pointer ##typedef void* sfWindowHandle; <- whatever the hell that is
#elif defined(windows):

View File

@@ -1,9 +1,6 @@
version 0.9.4
=============
- fix macros\tstringinterp.nim:
- problem: needs another level of indirection for 'seq'
- problem: deref is not correct
- fix GC issues
- test and fix showoff
@@ -26,7 +23,6 @@ version 0.9.x
- implement 'union' and 'bits' pragmas
- fix closures
- test and fix exception handling
- ensure (ref T)(a, b) works as a type conversion and type constructor
- optimize 'genericReset'; 'newException' leads to code bloat
- stack-less GC
@@ -40,7 +36,7 @@ version 0.9.x
- built-in 'getImpl'
- change comment handling in the AST; that's lots of work as c2nim and pas2nim
make use of the fast every node can have a comment!
make use of the fact every node can have a comment!
version 0.9.X