summary refs log tree commit diff stats
diff options
context:
space:
mode:
-rw-r--r--compiler/pretty.nim82
-rw-r--r--compiler/vm.nim91
-rw-r--r--compiler/vmdef.nim27
-rw-r--r--compiler/vmdeps.nim108
-rw-r--r--compiler/vmgen.nim69
5 files changed, 350 insertions, 27 deletions
diff --git a/compiler/pretty.nim b/compiler/pretty.nim
new file mode 100644
index 000000000..c205aaa7e
--- /dev/null
+++ b/compiler/pretty.nim
@@ -0,0 +1,82 @@
+#
+#
+#           The Nimrod Compiler
+#        (c) Copyright 2013 Andreas Rumpf
+#
+#    See the file "copying.txt", included in this
+#    distribution, for details about the copyright.
+#
+
+## This module implements the code "prettifier". This is part of the toolchain
+## to convert Nimrod code into a consistent style.
+
+import 
+  os, options, ast, astalgo, msgs, ropes, idents, passes, importer
+
+type 
+  TGen = object of TPassContext
+    module*: PSym
+  PGen = ref TGen
+  
+  TSourceFile = object
+    lines: seq[string]
+    dirty: bool
+    fullpath: string
+
+proc addSourceLine(fileIdx: int32, line: string) =
+  fileInfos[fileIdx].lines.add line
+
+proc sourceLine(i: TLineInfo): PRope =
+  if i.fileIndex < 0: return nil
+  
+  if not optPreserveOrigSource and fileInfos[i.fileIndex].lines.len == 0:
+    try:
+      for line in lines(i.toFullPath):
+        addSourceLine i.fileIndex, line.string
+    except EIO:
+      discard
+  InternalAssert i.fileIndex < fileInfos.len
+  # can happen if the error points to EOF:
+  if i.line > fileInfos[i.fileIndex].lines.len: return nil
+
+  result = fileInfos[i.fileIndex].lines[i.line-1]
+
+proc addDependencyAux(importing, imported: string) = 
+  appf(gDotGraph, "$1 -> $2;$n", [toRope(importing), toRope(imported)]) 
+  # s1 -> s2_4[label="[0-9]"];
+  
+proc addDotDependency(c: PPassContext, n: PNode): PNode = 
+  result = n
+  var g = PGen(c)
+  case n.kind
+  of nkSym:
+    
+  of nkTypeSection:
+    # we need to figure out whether the PType or the TType should become
+    # Type. The other then is either TypePtr/TypeRef or TypeDesc.
+    
+  of nkImportStmt: 
+    for i in countup(0, sonsLen(n) - 1): 
+      var imported = getModuleName(n.sons[i])
+      addDependencyAux(g.module.name.s, imported)
+  of nkFromStmt, nkImportExceptStmt: 
+    var imported = getModuleName(n.sons[0])
+    addDependencyAux(g.module.name.s, imported)
+  of nkStmtList, nkBlockStmt, nkStmtListExpr, nkBlockExpr: 
+    for i in countup(0, sonsLen(n) - 1): discard addDotDependency(c, n.sons[i])
+  else: 
+    nil
+
+proc generateRefactorScript*(project: string) = 
+  writeRope(ropef("digraph $1 {$n$2}$n", [
+      toRope(changeFileExt(extractFileName(project), "")), gDotGraph]), 
+            changeFileExt(project, "dot"))
+
+proc myOpen(module: PSym): PPassContext =
+  var g: PGen
+  new(g)
+  g.module = module
+  result = g
+
+const prettyPass* = makePass(open = myOpen, process = addDotDependency)
+
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 642bfd94c..7b24c3d6c 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -11,7 +11,8 @@
 ## An instruction is 1-2 int32s in memory, it is a register based VM.
 
 import
-  strutils, ast, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned
+  strutils, ast, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned,
+  parser, vmdeps
 
 from semfold import leValueConv
 
@@ -73,6 +74,10 @@ template decodeBC(k: expr) {.immediate, dirty.} =
   let rc = instr.regC
   ensureKind(k)
 
+template declBC() {.immediate, dirty.} =
+  let rb = instr.regB
+  let rc = instr.regC
+
 template decodeBImm(k: expr) {.immediate, dirty.} =
   let rb = instr.regB
   let imm = instr.regC - byteExcess
@@ -283,7 +288,8 @@ proc execute(c: PCtx, start: int) =
       regs[ra].intVal = regs[rb].intVal - imm
     of opcLenSeq:
       decodeBImm(nkIntLit)
-      assert regs[rb].kind == nkBracket
+      #assert regs[rb].kind == nkBracket
+      # also used by mNLen
       regs[ra].intVal = regs[rb].len - imm
     of opcLenStr:
       decodeBImm(nkIntLit)
@@ -578,6 +584,85 @@ proc execute(c: PCtx, start: int) =
       # trivial implementation:
       let rb = instr.regB
       regs[ra] = regs[rb].sons[1]
+    of opcNChild:
+      let rb = instr.regB
+      let rc = instr.regC
+      regs[ra] = regs[rb].sons[regs[rc].intVal.int]
+    of opcNSetChild:
+      let rb = instr.regB
+      let rc = instr.regC
+      regs[ra].sons[regs[rb].intVal.int] = regs[rc]
+    of opcNAdd:
+      declBC()
+      regs[rb].add(regs[rb])
+      regs[ra] = regs[rb]
+    of opcNAddMultiple:
+      declBC()
+      let x = regs[rc]
+      # XXX can be optimized:
+      for i in 0.. <x.len: regs[rb].add(x.sons[i])
+      regs[ra] = regs[rb]
+    of opcNKind:
+      decodeB(nkIntLit)
+      regs[ra].intVal = ord(regs[rb].kind)
+    of opcNIntVal:
+      decodeB(nkIntLit)
+      let a = regs[rb]
+      case a.kind
+      of nkCharLit..nkInt64Lit: regs[ra].intVal = a.intVal
+      else: stackTrace(c, tos, pc, errFieldXNotFound, "intVal")
+    of opcNFloatVal:
+      decodeB(nkFloatLit)
+      let a = regs[rb]
+      case a.kind
+      of nkFloatLit..nkFloat64Lit: regs[ra].floatVal = a.floatVal
+      else: stackTrace(c, tos, pc, errFieldXNotFound, "floatVal")
+    of opcNSymbol:
+      let rb = instr.regB
+      if regs[rb].kind != nkSym: 
+        stackTrace(c, tos, pc, errFieldXNotFound, "symbol")
+      regs[ra] = regs[rb]
+    of opcNIdent:
+      let rb = instr.regB
+      if regs[rb].kind != nkIdent: 
+        stackTrace(c, tos, pc, errFieldXNotFound, "ident")
+      regs[ra] = regs[rb]
+    of opcNGetType:
+      InternalError(c.debug[pc], "unknown opcode " & $instr.opcode)      
+    of opcNStrVal:
+      decodeB(nkStrLit)
+      let a = regs[rb]
+      case a.kind
+      of nkStrLit..nkTripleStrLit: regs[ra].strVal = a.strVal
+      else: stackTrace(c, tos, pc, errFieldXNotFound, "strVal")
+    of opcSlurp:
+      decodeB(nkStrLit)
+      regs[ra].strVal = opSlurp(regs[rb].strVal, c.debug[pc], c.module)
+    of opcGorge:
+      decodeBC(nkStrLit)
+      regs[ra].strVal = opGorge(regs[rb].strVal, regs[rc].strVal)
+    of opcNError:
+      stackTrace(c, tos, pc, errUser, regs[ra].strVal)
+    of opcNWarning:
+      Message(c.debug[pc], warnUser, regs[ra].strVal)
+    of opcNHint:
+      Message(c.debug[pc], hintUser, regs[ra].strVal)
+    of opcParseExprToAst:
+      let rb = instr.regB
+      # c.debug[pc].line.int - countLines(regs[rb].strVal) ?
+      let ast = parseString(regs[rb].strVal, c.debug[pc].toFilename,
+                            c.debug[pc].line.int)
+      if sonsLen(ast) != 1:
+        GlobalError(c.debug[pc], errExprExpected, "multiple statements")
+      regs[ra] = ast.sons[0]
+    of opcParseStmtToAst:
+      let rb = instr.regB
+      let ast = parseString(regs[rb].strVal, c.debug[pc].toFilename,
+                            c.debug[pc].line.int)
+      regs[ra] = ast
+    of opcCallSite:
+      if c.callsite != nil: regs[ra] = c.callsite
+      else: stackTrace(c, tos, pc, errFieldXNotFound, "callsite")
     else:
       InternalError(c.debug[pc], "unknown opcode " & $instr.opcode)
     inc pc
@@ -596,7 +681,7 @@ proc myOpen(module: PSym): PPassContext =
   #var c = newEvalContext(module, emRepl)
   #c.features = {allowCast, allowFFI, allowInfiniteLoops}
   #pushStackFrame(c, newStackFrame())
-  result = newCtx()
+  result = newCtx(module)
 
 var oldErrorCount: int
 
diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim
index 93e243bce..449d632b1 100644
--- a/compiler/vmdef.nim
+++ b/compiler/vmdef.nim
@@ -68,12 +68,33 @@ type
     opcAddSeqElem,
     opcRangeChck,
     
+    opcNAdd,
+    opcNAddMultiple,
+    opcNKind, 
+    opcNIntVal, 
+    opcNFloatVal, 
+    opcNSymbol, 
+    opcNIdent,
+    opcNGetType,
+    opcNStrVal,
+    
+    opcSlurp,
+    opcGorge,
+    opcParseExprToAst,
+    opcParseStmtToAst,
+    opcNError,
+    opcNWarning,
+    opcNHint,
+    
     opcEcho,
     opcIndCall, # dest = call regStart, n; where regStart = fn, arg1, ...
     opcIndCallAsgn, # dest = call regStart, n; where regStart = fn, arg1, ...
 
     opcRaise,
+    opcNChild,
+    opcNSetChild,
     opcNBindSym, # opcodes for the AST manipulation following
+    opcCallSite,
     opcNewStr,
   
     opcTJmp,  # jump Bx if A != 0
@@ -127,13 +148,15 @@ type
     currentExceptionA*, currentExceptionB*: PNode
     exceptionInstr*: int # index of instruction that raised the exception
     prc*: PProc
+    module*: PSym
+    callsite*: PNode
 
   TPosition* = distinct int
   
-proc newCtx*(): PCtx =
+proc newCtx*(module: PSym): PCtx =
   PCtx(code: @[], debug: @[],
     globals: newNode(nkStmtList), constants: newNode(nkStmtList), types: @[],
-    prc: PProc(blocks: @[]))
+    prc: PProc(blocks: @[]), module: module)
 
 const
   firstABxInstr* = opcTJmp
diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim
new file mode 100644
index 000000000..2a9929de0
--- /dev/null
+++ b/compiler/vmdeps.nim
@@ -0,0 +1,108 @@
+#
+#
+#           The Nimrod Compiler
+#        (c) Copyright 2013 Andreas Rumpf
+#
+#    See the file "copying.txt", included in this
+#    distribution, for details about the copyright.
+#
+
+import ast, msgs, osproc, streams, options
+
+proc readOutput(p: PProcess): string =
+  result = ""
+  var output = p.outputStream
+  discard p.waitForExit
+  while not output.atEnd:
+    result.add(output.readLine)
+
+proc opGorge*(cmd, input: string): string =
+  var p = startCmd(cmd)
+  if input.len != 0:
+    p.inputStream.write(input)
+    p.inputStream.close()
+  result = p.readOutput
+
+proc opSlurp*(file: string, info: TLineInfo, module: PSym): string = 
+  try:
+    let filename = file.FindFile
+    result = readFile(filename)
+    # we produce a fake include statement for every slurped filename, so that
+    # the module dependencies are accurate:
+    appendToModule(module, newNode(nkIncludeStmt, info, @[
+      newStrNode(nkStrLit, filename)]))
+  except EIO:
+    result = ""
+    LocalError(info, errCannotOpenFile, file)
+
+when false:
+  proc opExpandToAst*(c: PEvalContext, original: PNode): PNode =
+    var
+      n = original.copyTree
+      macroCall = n.sons[1]
+      expandedSym = macroCall.sons[0].sym
+
+    for i in countup(1, macroCall.sonsLen - 1):
+      macroCall.sons[i] = evalAux(c, macroCall.sons[i], {})
+
+    case expandedSym.kind
+    of skTemplate:
+      let genSymOwner = if c.tos != nil and c.tos.prc != nil:
+                          c.tos.prc 
+                        else:
+                          c.module
+      result = evalTemplate(macroCall, expandedSym, genSymOwner)
+    of skMacro:
+      # At this point macroCall.sons[0] is nkSym node.
+      # To be completely compatible with normal macro invocation,
+      # we want to replace it with nkIdent node featuring
+      # the original unmangled macro name.
+      macroCall.sons[0] = newIdentNode(expandedSym.name, expandedSym.info)
+      result = evalMacroCall(c, macroCall, original, expandedSym)
+    else:
+      InternalError(macroCall.info,
+        "ExpandToAst: expanded symbol is no macro or template")
+      result = emptyNode
+
+  proc opTypeTrait*(n: PNode, context: PSym): PNode =
+    ## XXX: This should be pretty much guaranteed to be true
+    # by the type traits procs' signatures, but until the
+    # code is more mature it doesn't hurt to be extra safe
+    internalAssert n.len >= 2 and n.sons[1].kind == nkSym
+
+    let typ = n.sons[1].sym.typ.skipTypes({tyTypeDesc})
+    case n.sons[0].sym.name.s.normalize
+    of "name":
+      result = newStrNode(nkStrLit, typ.typeToString(preferExported))
+      result.typ = newType(tyString, context)
+      result.info = n.info
+    else:
+      internalAssert false
+
+  proc opIs*(n: PNode): PNode =
+    InternalAssert n.sonsLen == 3 and
+      n[1].kind == nkSym and n[1].sym.kind == skType and
+      n[2].kind in {nkStrLit..nkTripleStrLit, nkType}
+    
+    let t1 = n[1].sym.typ
+
+    if n[2].kind in {nkStrLit..nkTripleStrLit}:
+      case n[2].strVal.normalize
+      of "closure":
+        let t = skipTypes(t1, abstractRange)
+        result = newIntNode(nkIntLit, ord(t.kind == tyProc and
+                                          t.callConv == ccClosure and 
+                                          tfIterator notin t.flags))
+      of "iterator":
+        let t = skipTypes(t1, abstractRange)
+        result = newIntNode(nkIntLit, ord(t.kind == tyProc and
+                                          t.callConv == ccClosure and 
+                                          tfIterator in t.flags))
+    else:
+      let t2 = n[2].typ
+      var match = if t2.kind == tyTypeClass: matchTypeClass(t2, t1)
+                  else: sameType(t1, t2)
+      result = newIntNode(nkIntLit, ord(match))
+
+    result.typ = n.typ
+
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index f697ba0e6..427f8fafe 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -422,6 +422,11 @@ proc genBinaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
   c.gABC(n, opc, dest, tmp, 0)
   c.freeTemp(tmp)
 
+proc genUnaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
+  let tmp = c.genx(n.sons[2])
+  c.gABC(n, opc, tmp, 0, 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)
@@ -636,26 +641,38 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
   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 mParseExprToAst:
+    genUnaryABC(c, n, dest, opcParseExprToAst)
+  of mParseStmtToAst:
+    genUnaryABC(c, n, dest, opcParseStmtToAst)
   of mExpandToAst: InternalError(n.info, "cannot generate code for: " & $m)
   of mTypeTrait: InternalError(n.info, "cannot generate code for: " & $m)
   of mIs: InternalError(n.info, "cannot generate code for: " & $m)
-  of mSlurp: InternalError(n.info, "cannot generate code for: " & $m)
-  of mStaticExec: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNLen: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNChild: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNSetChild: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNAdd: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNAddMultiple: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNDel: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNKind: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNIntVal: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNFloatVal: InternalError(n.info, "cannot generate code for: " & $m) 
-  of mNSymbol: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNIdent: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNGetType: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNStrVal: InternalError(n.info, "cannot generate code for: " & $m)
+  of mSlurp: genUnaryABC(c, n, dest, opcSlurp)
+  of mStaticExec: genBinaryABC(c, n, dest, opcGorge)
+  of mNLen: genUnaryABI(c, n, dest, opcLenSeq)
+  of mNChild: genBinaryABC(c, n, dest, opcNChild)
+  of mNSetChild:
+    unused(n, dest)
+    var
+      tmp1 = c.genx(n.sons[1])
+      tmp2 = c.genx(n.sons[2])
+      tmp3 = c.genx(n.sons[3])
+    c.gABC(n, opcNSetChild, tmp1, tmp2, tmp3)
+    c.freeTemp(tmp1)
+    c.freeTemp(tmp2)
+    c.freeTemp(tmp3)
+  of mNAdd: genBinaryABC(c, n, dest, opcNAdd)
+  of mNAddMultiple: genBinaryABC(c, n, dest, opcNAddMultiple)
+  of mNDel:
+    InternalError(n.info, "cannot generate code for: " & $m)
+  of mNKind: genUnaryABC(c, n, dest, opcNKind)
+  of mNIntVal: genUnaryABC(c, n, dest, opcNIntVal)
+  of mNFloatVal: genUnaryABC(c, n, dest, opcNFloatVal)
+  of mNSymbol: genUnaryABC(c, n, dest, opcNSymbol)
+  of mNIdent: genUnaryABC(c, n, dest, opcNIdent)
+  of mNGetType: genUnaryABC(c, n, dest, opcNGetType)
+  of mNStrVal: genUnaryABC(c, n, dest, opcNStrVal)
   of mNSetIntVal: InternalError(n.info, "cannot generate code for: " & $m)
   of mNSetFloatVal: InternalError(n.info, "cannot generate code for: " & $m)
   of mNSetSymbol: InternalError(n.info, "cannot generate code for: " & $m)
@@ -665,16 +682,24 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
   of mNNewNimNode: InternalError(n.info, "cannot generate code for: " & $m)
   of mNCopyNimNode: InternalError(n.info, "cannot generate code for: " & $m)
   of mNCopyNimTree: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNBindSym: InternalError(n.info, "cannot generate code for: " & $m)
+  of mNBindSym: genUnaryABC(c, n, dest, opcNBindSym)
   of mStrToIdent: InternalError(n.info, "cannot generate code for: " & $m)
   of mIdentToStr: InternalError(n.info, "cannot generate code for: " & $m)
   of mEqIdent: InternalError(n.info, "cannot generate code for: " & $m)
   of mEqNimrodNode: InternalError(n.info, "cannot generate code for: " & $m)
   of mNLineInfo: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNHint: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNWarning: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNError: InternalError(n.info, "cannot generate code for: " & $m)
-  of mNCallSite: InternalError(n.info, "cannot generate code for: " & $m)  
+  of mNHint: 
+    unused(n, dest)
+    genUnaryStmt(c, n, opcNHint)
+  of mNWarning: 
+    unused(n, dest)
+    genUnaryStmt(c, n, opcNWarning)
+  of mNError:
+    unused(n, dest)
+    genUnaryStmt(c, n, opcNError)
+  of mNCallSite:
+    if dest < 0: dest = c.getTemp(n.typ)
+    c.gABC(n, opcCallSite, dest)
   else:
     # XXX get rid of these: mMinI, mMaxI, mMinI64, mMaxI64, mMinF64, mMaxF64
     # mGCref, mGCunref, mEqCString, mAbsI, mAbsI64, mAbsF64