summary refs log tree commit diff stats
diff options
context:
space:
mode:
-rw-r--r--compiler/vm.nim59
-rw-r--r--compiler/vmdef.nim24
-rw-r--r--compiler/vmgen.nim114
3 files changed, 145 insertions, 52 deletions
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 7ae5b7878..642bfd94c 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -10,7 +10,10 @@
 ## This file implements the new evaluation engine for Nimrod code.
 ## An instruction is 1-2 int32s in memory, it is a register based VM.
 
-import ast, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned
+import
+  strutils, ast, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned
+
+from semfold import leValueConv
 
 type
   PStackFrame* = ref TStackFrame
@@ -79,10 +82,6 @@ template decodeBx(k: expr) {.immediate, dirty.} =
   let rbx = instr.regBx - wordExcess
   ensureKind(k)
 
-proc compile(c: PCtx, s: PSym): int = 
-  result = vmgen.genProc(c, s)
-  #c.echoCode
-
 proc myreset(n: PNode) =
   when defined(system.reset): 
     var oldInfo = n.info
@@ -130,18 +129,14 @@ proc pushSafePoint(f: PStackFrame; pc: int) =
 
 proc popSafePoint(f: PStackFrame) = discard f.safePoints.pop()
 
-proc nextSafePoint(f: PStackFrame): int =
-  var f = f
-  while f.safePoints.isNil or f.safePoints.len == 0:
-    f = f.next
-    if f.isNil: return -1
-  result = f.safePoints.pop
-
 proc cleanUpOnException(c: PCtx; tos: PStackFrame; regs: TNodeSeq): int =
   let raisedType = c.currentExceptionA.typ.skipTypes(abstractPtrs)
+  var f = tos
   while true:
-    var pc2 = tos.nextSafePoint
-    if pc2 == -1: return -1
+    while f.safePoints.isNil or f.safePoints.len == 0:
+      f = f.next
+      if f.isNil: return -1
+    var pc2 = f.safePoints[f.safePoints.high]
 
     var nextExceptOrFinally = -1
     if c.code[pc2].opcode == opcExcept:
@@ -163,6 +158,8 @@ proc cleanUpOnException(c: PCtx; tos: PStackFrame; regs: TNodeSeq): int =
     if c.code[pc2].opcode == opcFinally:
       # execute the corresponding handler, but don't quit walking the stack:
       return pc2
+    # not the right one:
+    discard f.safePoints.pop
 
 proc cleanUpOnReturn(c: PCtx; f: PStackFrame): int =
   if f.safePoints.isNil: return -1
@@ -174,6 +171,10 @@ proc cleanUpOnReturn(c: PCtx; f: PStackFrame): int =
       return pc
   return -1
 
+proc compile(c: PCtx, s: PSym): int = 
+  result = vmgen.genProc(c, s)
+  #c.echoCode
+
 proc execute(c: PCtx, start: int) =
   var pc = start
   var regs: TNodeSeq # alias to tos.slots for performance
@@ -188,11 +189,12 @@ proc execute(c: PCtx, start: int) =
     of opcEof: break
     of opcRet:
       # XXX perform any cleanup actions
+      pc = tos.comesFrom
       tos = tos.next
       if tos.isNil: return
+      
       let retVal = regs[0]
       move(regs, tos.slots)
-      pc = tos.comesFrom
       assert c.code[pc].opcode in {opcIndCall, opcIndCallAsgn}
       if c.code[pc].opcode == opcIndCallAsgn:
         regs[c.code[pc].regA] = retVal
@@ -222,6 +224,10 @@ proc execute(c: PCtx, start: int) =
       let idx = regs[rc].intVal
       # XXX what if the array is not 0-based? -> codegen should insert a sub
       regs[ra] = regs[rb].sons[idx.int]
+    of opcLdStrIdx:
+      decodeBC(nkIntLit)
+      let idx = regs[rc].intVal
+      regs[ra].intVal = regs[rb].strVal[idx.int].ord
     of opcWrArr:
       # a[b] = c
       let rb = instr.regB
@@ -432,6 +438,15 @@ proc execute(c: PCtx, start: int) =
       regs[ra].strVal = getstr(regs[rb])
       for i in rb+1..rb+rc-1:
         regs[ra].strVal.add getstr(regs[i])
+    of opcAddStrCh:
+      decodeB(nkStrLit)
+      regs[ra].strVal.add(regs[rb].intVal.chr)
+    of opcAddStrStr:
+      decodeB(nkStrLit)
+      regs[ra].strVal.add(regs[rb].strVal)
+    of opcAddSeqElem:
+      decodeB(nkBracket)
+      regs[ra].add(copyTree(regs[rb]))
     of opcEcho:
       echo regs[ra].strVal
     of opcContainsSet:
@@ -444,6 +459,14 @@ proc execute(c: PCtx, start: int) =
       let rd = c.code[pc].regA
       regs[ra].strVal = substr(regs[rb].strVal, regs[rc].intVal.int, 
                                regs[rd].intVal.int)
+    of opcRangeChck:
+      let rb = instr.regB
+      let rc = instr.regC
+      if not (leValueConv(regs[rb], regs[ra]) and
+              leValueConv(regs[ra], regs[rc])):
+        stackTrace(c, tos, pc, errGenerated,
+          msgKindToString(errIllegalConvFromXtoY) % [
+          "unknown type" , "unknown type"])
     of opcIndCall, opcIndCallAsgn:
       # dest = call regStart, n; where regStart = fn, arg1, ...
       let rb = instr.regB
@@ -545,6 +568,12 @@ proc execute(c: PCtx, start: int) =
       regs[ra] = getNullValue(typ, c.debug[pc])
     of opcLdConst:
       regs[ra] = c.constants.sons[instr.regBx - wordExcess]
+    of opcAsgnConst:
+      let rb = instr.regBx - wordExcess
+      if regs[ra].isNil:
+        regs[ra] = copyTree(c.constants.sons[rb])
+      else:
+        asgnComplex(regs[ra], c.constants.sons[rb])
     of opcNBindSym:
       # trivial implementation:
       let rb = instr.regB
diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim
index cbad16516..93e243bce 100644
--- a/compiler/vmdef.nim
+++ b/compiler/vmdef.nim
@@ -21,10 +21,6 @@ type
   TDest* = range[-1 .. 255]
   TInstr* = distinct uint32
 
-  TInstrFormat = enum
-    ifABC,  # three registers
-    ifABx,  # A + extended B
-
   TOpcode* = enum
     opcEof,         # end of code
     opcRet,         # return
@@ -46,6 +42,7 @@ type
     opcAddr,
     opcDeref,
     opcWrStrIdx,
+    opcLdStrIdx, # a = b[c]
     
     opcAddInt, 
     opcAddImmInt,
@@ -66,12 +63,18 @@ type
     opcSwap, opcIsNil, opcOf,
     opcSubStr, opcConv, opcCast, opcQuit, opcReset,
     
+    opcAddStrCh,
+    opcAddStrStr,
+    opcAddSeqElem,
+    opcRangeChck,
+    
     opcEcho,
     opcIndCall, # dest = call regStart, n; where regStart = fn, arg1, ...
     opcIndCallAsgn, # dest = call regStart, n; where regStart = fn, arg1, ...
 
     opcRaise,
     opcNBindSym, # opcodes for the AST manipulation following
+    opcNewStr,
   
     opcTJmp,  # jump Bx if A != 0
     opcFJmp,  # jump Bx if A == 0
@@ -83,9 +86,9 @@ type
     opcFinallyEnd,
     opcNew,
     opcNewSeq,
-    opcNewStr,
     opcLdNull,    # dest = nullvalue(types[Bx])
     opcLdConst,   # dest = constants[Bx]
+    opcAsgnConst, # dest = copy(constants[Bx])
     opcLdGlobal,  # dest = globals[Bx]
     opcLdImmInt,  # dest = immediate value
     opcWrGlobal,
@@ -100,7 +103,8 @@ type
                       # temporary slot usage. This is required for the parameter
                       # passing implementation.
     slotEmpty,        # slot is unused
-    slotFixed,        # slot is used for a fixed var/param/result
+    slotFixedVar,     # slot is used for a fixed var/result (requires copy then)
+    slotFixedLet,     # slot is used for a fixed param/let
     slotTempUnknown,  # slot but type unknown (argument of proc call)
     slotTempInt,      # some temporary int
     slotTempFloat,    # some temporary float
@@ -117,11 +121,6 @@ type
     code*: seq[TInstr]
     debug*: seq[TLineInfo]  # line info for every instruction; kept separate
                             # to not slow down interpretation
-    jumpTargets*: TIntSet   # we need to mark instructions that are
-                            # jump targets;
-                            # we must not optimize over a jump target and we
-                            # need to generate a label for a jump target when
-                            # producing a VM listing
     globals*: PNode         # 
     constants*: PNode       # constant data
     types*: seq[PType]      # some instructions reference types (e.g. 'except')
@@ -132,7 +131,7 @@ type
   TPosition* = distinct int
   
 proc newCtx*(): PCtx =
-  PCtx(code: @[], debug: @[], jumpTargets: initIntSet(),
+  PCtx(code: @[], debug: @[],
     globals: newNode(nkStmtList), constants: newNode(nkStmtList), types: @[],
     prc: PProc(blocks: @[]))
 
@@ -141,6 +140,7 @@ const
   largeInstrs* = { # instructions which use 2 int32s instead of 1:
     opcSubstr, opcConv, opcCast, opcNewSeq, opcOf}
   slotSomeTemp* = slotTempUnknown
+  relativeJumps* = {opcTJmp, opcFJmp, opcJmp}
 
 template opcode*(x: TInstr): TOpcode {.immediate.} = TOpcode(x.uint32 and 0xff'u32)
 template regA*(x: TInstr): TRegister {.immediate.} = TRegister(x.uint32 shr 8'u32 and 0xff'u32)
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index 00acbd48d..f697ba0e6 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -14,16 +14,30 @@ import
   trees, intsets, rodread
 
 proc codeListing(c: PCtx, result: var string) =
+  # first iteration: compute all necessary labels:
+  var jumpTargets = initIntSet()
+  
+  for i in 0.. < c.code.len:
+    let x = c.code[i]
+    if x.opcode in relativeJumps:
+      jumpTargets.incl(i+x.regBx-wordExcess)
+
   # for debugging purposes
   var i = 0
   while i < c.code.len:
-    if i in c.jumpTargets: result.addf("L$1:\n", i)
+    if i in jumpTargets: result.addf("L$1:\n", i)
     let x = c.code[i]
 
     let opc = opcode(x)
     if opc < firstABxInstr:
       result.addf("\t$#\tr$#, r$#, r$#", ($opc).substr(3), x.regA, 
                   x.regB, x.regC)
+    elif opc in relativeJumps:
+      result.addf("\t$#\tr$#, L$#", ($opc).substr(3), x.regA,
+                  i+x.regBx-wordExcess)
+    elif opc in {opcLdConst, opcAsgnConst}:
+      result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, 
+        c.constants[x.regBx-wordExcess].renderTree)
     else:
       result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, x.regBx-wordExcess)
     result.add("\t#")
@@ -64,7 +78,7 @@ proc xjmp(c: PCtx; n: PNode; opc: TOpcode; a: TRegister = 0): TPosition =
 
 proc genLabel(c: PCtx): TPosition =
   result = TPosition(c.code.len)
-  c.jumpTargets.incl(c.code.len)
+  #c.jumpTargets.incl(c.code.len)
 
 proc jmpBack(c: PCtx, n: PNode, opc: TOpcode, p = TPosition(0)) =
   let dist = p.int - c.code.len
@@ -75,7 +89,7 @@ proc patch(c: PCtx, p: TPosition) =
   # patch with current index
   let p = p.int
   let diff = c.code.len - p
-  c.jumpTargets.incl(c.code.len)
+  #c.jumpTargets.incl(c.code.len)
   InternalAssert(-0x7fff < diff and diff < 0x7fff)
   let oldInstr = c.code[p]
   # opcode and regA stay the same:
@@ -195,10 +209,11 @@ proc genBlock(c: PCtx; n: PNode; dest: var TDest) =
 proc genBreak(c: PCtx; n: PNode) =
   let L1 = c.xjmp(n, opcJmp)
   if n.sons[0].kind == nkSym:
+    echo cast[int](n.sons[0].sym)
     for i in countdown(c.prc.blocks.len-1, 0):
       if c.prc.blocks[i].label == n.sons[0].sym:
         c.prc.blocks[i].fixups.add L1
-        break
+        return
     InternalError(n.info, "cannot find 'break' target")
   else:
     c.prc.blocks[c.prc.blocks.high].fixups.add L1
@@ -365,7 +380,10 @@ proc genCall(c: PCtx; n: PNode; dest: var TDest) =
 
 proc genNew(c: PCtx; n: PNode) =
   let dest = c.genx(n.sons[1])
-  c.gABx(n, opcNew, dest, c.genType(n.sons[1].typ.skipTypes(abstractVar)))
+  # we use the ref's base type here as the VM conflates 'ref object' 
+  # and 'object' since internally we already have a pointer.
+  c.gABx(n, opcNew, dest, 
+         c.genType(n.sons[1].typ.skipTypes(abstractVar).sons[0]))
   c.freeTemp(dest)
 
 proc genNewSeq(c: PCtx; n: PNode) =
@@ -382,6 +400,12 @@ proc genUnaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   c.gABC(n, opc, dest, tmp)
   c.freeTemp(tmp)
 
+proc genUnaryABI(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
+  let tmp = c.genx(n.sons[1])
+  if dest < 0: dest = c.getTemp(n.typ)
+  c.gABI(n, opc, dest, tmp, 0)
+  c.freeTemp(tmp)
+
 proc genBinaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   let
     tmp = c.genx(n.sons[1])
@@ -391,6 +415,13 @@ proc genBinaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   c.freeTemp(tmp)
   c.freeTemp(tmp2)
 
+proc genBinaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
+  let
+    dest = c.genx(n.sons[1])
+    tmp = c.genx(n.sons[2])
+  c.gABC(n, opc, dest, tmp, 0)
+  c.freeTemp(tmp)
+
 proc genVarargsABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   if dest < 0: dest = getTemp(c, n.typ)
   var x = c.getTempRange(n.len-1, slotTempStr)
@@ -465,9 +496,9 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
     c.gABC(n, opcNewStr, dest, tmp)
     c.freeTemp(tmp)
   of mLengthOpenArray, mLengthArray, mLengthSeq:
-    genUnaryABC(c, n, dest, opcLenSeq)
+    genUnaryABI(c, n, dest, opcLenSeq)
   of mLengthStr:
-    genUnaryABC(c, n, dest, opcLenStr)
+    genUnaryABI(c, n, dest, opcLenStr)
   of mIncl, mExcl:
     unused(n, dest)
     var d = c.genx(n.sons[1])
@@ -596,9 +627,15 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
       var d = c.genx(n.sons[i])
       c.gABC(n, opcEcho, d)
       c.freeTemp(d)
-  of mAppendStrCh: InternalError(n.info, "cannot generate code for: " & $m)
-  of mAppendStrStr: InternalError(n.info, "cannot generate code for: " & $m)
-  of mAppendSeqElem: InternalError(n.info, "cannot generate code for: " & $m)
+  of mAppendStrCh: 
+    unused(n, dest)
+    genBinaryStmt(c, n, opcAddStrCh)
+  of mAppendStrStr: 
+    unused(n, dest)
+    genBinaryStmt(c, n, opcAddStrStr)
+  of mAppendSeqElem:
+    unused(n, dest)
+    genBinaryStmt(c, n, opcAddSeqElem)
   of mParseExprToAst: InternalError(n.info, "cannot generate code for: " & $m)
   of mParseStmtToAst: InternalError(n.info, "cannot generate code for: " & $m)
   of mExpandToAst: InternalError(n.info, "cannot generate code for: " & $m)
@@ -664,18 +701,18 @@ proc requiresCopy(n: PNode): bool =
   else:
     result = true
 
-proc unnecessaryIndirection(n: PNode): bool =
+proc unneededIndirection(n: PNode): bool =
   n.typ.skipTypes(abstractInst).kind == tyRef
 
 proc skipDeref(n: PNode): PNode =
-  if n.kind in {nkDerefExpr, nkHiddenDeref} and unnecessaryIndirection(n):
+  if n.kind in {nkDerefExpr, nkHiddenDeref} and unneededIndirection(n.sons[0]):
     result = n.sons[0]
   else:
     result = n
 
 proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) = 
   # a nop for certain types
-  if unnecessaryIndirection(n):
+  if unneededIndirection(n.sons[0]):
     gen(c, n.sons[0], dest)
   else:
     let tmp = c.genx(n.sons[0])
@@ -740,9 +777,11 @@ proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
     genAsgn(c, dest, ri, requiresCopy)
 
 proc genLit(c: PCtx; n: PNode; dest: var TDest) =
+  var opc = opcLdConst
   if dest < 0: dest = c.getTemp(n.typ)
+  elif c.prc.slots[dest].kind == slotFixedVar: opc = opcAsgnConst
   let lit = genLiteral(c, n)
-  c.gABx(n, opcLdConst, dest, lit)
+  c.gABx(n, opc, dest, lit)
 
 proc genRdVar(c: PCtx; n: PNode; dest: var TDest) =
   let s = n.sym
@@ -775,7 +814,10 @@ proc genObjAccess(c: PCtx; n: PNode; dest: var TDest) =
   genAccess(c, n, dest, opcLdObj)
 
 proc genArrAccess(c: PCtx; n: PNode; dest: var TDest) =
-  genAccess(c, n, dest, opcLdArr)
+  if n.sons[0].typ.skipTypes(abstractVarRange).kind in {tyString, tyCString}:
+    genAccess(c, n, dest, opcLdStrIdx)
+  else:
+    genAccess(c, n, dest, opcLdArr)
 
 proc getNullValue*(typ: PType, info: TLineInfo): PNode
 proc getNullValueAux(obj: PNode, result: PNode) = 
@@ -827,7 +869,8 @@ proc setSlot(c: PCtx; v: PSym) =
   # XXX generate type initialization here?
   if v.position == 0:
     v.position = c.prc.maxSlots
-    c.prc.slots[v.position] = (inUse: true, kind: slotFixed)
+    c.prc.slots[v.position] = (inUse: true,
+        kind: if v.kind == skLet: slotFixedLet else: slotFixedVar)
     inc c.prc.maxSlots
 
 proc genVarSection(c: PCtx; n: PNode) =
@@ -959,36 +1002,56 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) =
     let s = n.sons[namePos].sym
     discard genProc(c, s)
     genLit(c, n.sons[namePos], dest)
+  of nkChckRangeF, nkChckRange64, nkChckRange: 
+    let
+      tmp0 = c.genx(n.sons[0])
+      tmp1 = c.genx(n.sons[1])
+      tmp2 = c.genx(n.sons[2])
+    c.gABC(n, opcRangeChck, tmp0, tmp1, tmp2)
+    c.freeTemp(tmp1)
+    c.freeTemp(tmp2)
+    if dest >= 0:
+      gABC(c, n, whichAsgnOpc(n), dest, tmp0)
+      c.freeTemp(tmp0)
+    else:
+      dest = tmp0
   of nkEmpty, nkCommentStmt, nkTypeSection, nkConstSection, nkPragma,
      nkTemplateDef, nkIncludeStmt, nkImportStmt:
     unused(n, dest)
+  of nkStringToCString, nkCStringToString:
+    gen(c, n.sons[0], dest)
   else:
     #of nkCurly, nkBracket, nkPar:
     InternalError n.info, "too implement " & $n.kind
 
+proc removeLastEof(c: PCtx) =
+  let last = c.code.len-1
+  if last >= 0 and c.code[last].opcode == opcEof:
+    # overwrite last EOF:
+    assert c.code.len == c.debug.len
+    c.code.setLen(last)
+    c.debug.setLen(last)
+
 proc genStmt*(c: PCtx; n: PNode): int =
+  c.removeLastEof
   result = c.code.len
   var d: TDest = -1
-  gen(c, n, d)
-  let last = c.code.len-1
-  if last >= 0 and c.code[last].opcode == opcEof:
-    # since we can re-use the EOF nothing happened:
-    result = last
-  else:
-    gABC(c, n, opcEof)
+  c.gen(n, d)
+  c.gABC(n, opcEof)
   InternalAssert d < 0
 
 proc genParams(c: PCtx; params: PNode) =
   # res.sym.position is already 0
-  c.prc.slots[0] = (inUse: true, kind: slotFixed)
+  c.prc.slots[0] = (inUse: true, kind: slotFixedVar)
   for i in 1.. <params.len:
     let param = params.sons[i].sym
-    c.prc.slots[i] = (inUse: true, kind: slotFixed)
+    c.prc.slots[i] = (inUse: true, kind: slotFixedLet)
   c.prc.maxSlots = max(params.len, 1)
 
 proc genProc(c: PCtx; s: PSym): int =
   let x = s.ast.sons[optimizedCodePos]
   if x.kind == nkEmpty:
+    c.removeLastEof
     result = c.code.len+1 # skip the jump instruction
     s.ast.sons[optimizedCodePos] = newIntNode(nkIntLit, result)
     # thanks to the jmp we can add top level statements easily and also nest
@@ -1004,6 +1067,7 @@ proc genProc(c: PCtx; s: PSym): int =
     # generate final 'return' statement:
     c.gABC(body, opcRet)
     c.patch(procStart)
+    c.gABC(body, opcEof)
     s.position = c.prc.maxSlots
     c.prc = oldPrc
   else: