summary refs log tree commit diff stats
diff options
context:
space:
mode:
authorAraq <rumpf_a@web.de>2015-02-24 00:13:15 +0100
committerAraq <rumpf_a@web.de>2015-02-24 00:13:28 +0100
commit752052e903c8f238a6e3a6f67ae36ee7e0943801 (patch)
tree6118e60ccd1cc87f21830779dd2cc47207c09626
parent9080d3a9a9483b84745e391e699493c31d85cb34 (diff)
downloadNim-752052e903c8f238a6e3a6f67ae36ee7e0943801.tar.gz
implements a type API for macros
-rw-r--r--compiler/ast.nim14
-rw-r--r--compiler/semtypes.nim19
-rw-r--r--compiler/vm.nim20
-rw-r--r--compiler/vmdeps.nim125
-rw-r--r--compiler/vmgen.nim7
-rw-r--r--lib/core/macros.nim42
-rw-r--r--todo.txt1
7 files changed, 194 insertions, 34 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 28b34095b..6afc1db26 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -945,6 +945,13 @@ template `{}`*(n: PNode, i: int): expr = n[i -| n]
 template `{}=`*(n: PNode, i: int, s: PNode): stmt =
   n.sons[i -| n] = s
 
+when defined(useNodeIds):
+  const nodeIdToDebug* = -1 # 884953 # 612794
+  #612840 # 612905 # 614635 # 614637 # 614641
+  # 423408
+  #429107 # 430443 # 441048 # 441090 # 441153
+  var gNodeId: int
+
 proc newNode*(kind: TNodeKind): PNode = 
   new(result)
   result.kind = kind
@@ -1061,13 +1068,6 @@ proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) =
 proc discardSons*(father: PNode) = 
   father.sons = nil
 
-when defined(useNodeIds):
-  const nodeIdToDebug* = -1 # 884953 # 612794
-  #612840 # 612905 # 614635 # 614637 # 614641
-  # 423408
-  #429107 # 430443 # 441048 # 441090 # 441153
-  var gNodeId: int
-
 proc withInfo*(n: PNode, info: TLineInfo): PNode =
   n.info = info
   return n
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 7cd748829..d9c7b6c92 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -332,10 +332,15 @@ proc semTypeIdent(c: PContext, n: PNode): PSym =
       if result.typ.kind != tyGenericParam:
         # XXX get rid of this hack!
         var oldInfo = n.info
+        when defined(useNodeIds):
+          let oldId = n.id
         reset(n[])
+        when defined(useNodeIds):
+          n.id = oldId
         n.kind = nkSym
         n.sym = result
         n.info = oldInfo
+        n.typ = result.typ
     else:
       localError(n.info, errIdentifierExpected)
       result = errorSym(c, n)
@@ -1179,11 +1184,12 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     var typeExpr = semExpr(c, n)
     if typeExpr.typ.kind != tyTypeDesc:
       localError(n.info, errTypeExpected)
-      return errorType(c)
-    result = typeExpr.typ.base
-    if result.isMetaType:
-      var preprocessed = semGenericStmt(c, n)
-      return makeTypeFromExpr(c, preprocessed)
+      result = errorType(c)
+    else:
+      result = typeExpr.typ.base
+      if result.isMetaType:
+        var preprocessed = semGenericStmt(c, n)
+        result = makeTypeFromExpr(c, preprocessed)
   of nkIdent, nkAccQuoted:
     var s = semTypeIdent(c, n)
     if s.typ == nil: 
@@ -1254,7 +1260,8 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
   else:
     localError(n.info, errTypeExpected)
     result = newOrPrevType(tyError, prev, c)
-  
+  n.typ = result
+
 proc setMagicType(m: PSym, kind: TTypeKind, size: int) = 
   m.typ.kind = kind
   m.typ.align = size.int16
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 891718274..e96b89f49 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -123,8 +123,12 @@ proc createStrKeepNode(x: var TFullReg) =
   if x.node.isNil:
     x.node = newNode(nkStrLit)
   elif x.node.kind == nkNilLit:
+    when defined(useNodeIds):
+      let id = x.node.id
     system.reset(x.node[])
     x.node.kind = nkStrLit
+    when defined(useNodeIds):
+      x.node.id = id
   elif x.node.kind notin {nkStrLit..nkTripleStrLit} or
       nfAllConst in x.node.flags:
     # XXX this is hacky; tests/txmlgen triggers it:
@@ -1133,7 +1137,21 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg =
       else:
         stackTrace(c, tos, pc, errFieldXNotFound, "ident")
     of opcNGetType:
-      internalError(c.debug[pc], "unknown opcode " & $instr.opcode)
+      let rb = instr.regB
+      let rc = instr.regC
+      if rc == 0:
+        ensureKind(rkNode)
+        if regs[rb].kind == rkNode and regs[rb].node.typ != nil:
+          regs[ra].node = opMapTypeToAst(regs[rb].node.typ, c.debug[pc])
+        else:
+          stackTrace(c, tos, pc, errGenerated, "node has no type")
+      else:
+        # typeKind opcode:
+        ensureKind(rkInt)
+        if regs[rb].kind == rkNode and regs[rb].node.typ != nil:
+          regs[ra].intVal = ord(regs[rb].node.typ.kind)
+        #else:
+        #  stackTrace(c, tos, pc, errGenerated, "node has no type")
     of opcNStrVal:
       decodeB(rkNode)
       createStr regs[ra]
diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim
index c44910b81..7fa88de6e 100644
--- a/compiler/vmdeps.nim
+++ b/compiler/vmdeps.nim
@@ -1,13 +1,13 @@
 #
 #
 #           The Nim Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2015 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
 #
 
-import ast, types, msgs, osproc, streams, options
+import ast, types, msgs, osproc, streams, options, idents
 
 proc readOutput(p: Process): string =
   result = ""
@@ -19,11 +19,14 @@ proc readOutput(p: Process): string =
   discard p.waitForExit
 
 proc opGorge*(cmd, input: string): string =
-  var p = startProcess(cmd, options={poEvalCommand})
-  if input.len != 0:
-    p.inputStream.write(input)
-    p.inputStream.close()
-  result = p.readOutput
+  try:
+    var p = startProcess(cmd, options={poEvalCommand})
+    if input.len != 0:
+      p.inputStream.write(input)
+      p.inputStream.close()
+    result = p.readOutput
+  except IOError, OSError:
+    result = ""
 
 proc opSlurp*(file: string, info: TLineInfo, module: PSym): string = 
   try:
@@ -36,3 +39,111 @@ proc opSlurp*(file: string, info: TLineInfo, module: PSym): string =
   except IOError:
     localError(info, errCannotOpenFile, file)
     result = ""
+
+proc atomicTypeX(name: string; t: PType; info: TLineInfo): PNode =
+  let sym = newSym(skType, getIdent(name), t.owner, info)
+  result = newSymNode(sym)
+  result.typ = t
+
+proc mapTypeToAst(t: PType, info: TLineInfo; allowRecursion=false): PNode
+
+proc mapTypeToBracket(name: string; t: PType; info: TLineInfo): PNode =
+  result = newNodeIT(nkBracketExpr, info, t)
+  result.add atomicTypeX(name, t, info)
+  for i in 0 .. < t.len:
+    result.add mapTypeToAst(t.sons[i], info)
+
+proc mapTypeToAst(t: PType, info: TLineInfo; allowRecursion=false): PNode =
+  template atomicType(name): expr = atomicTypeX(name, t, info)
+
+  case t.kind
+  of tyNone: result = atomicType("none")
+  of tyBool: result = atomicType("bool")
+  of tyChar: result = atomicType("char")
+  of tyNil: result = atomicType("nil")
+  of tyExpr: result = atomicType("expr")
+  of tyStmt: result = atomicType("stmt")
+  of tyEmpty: result = atomicType"void"
+  of tyArrayConstr, tyArray:
+    result = newNodeIT(nkBracketExpr, info, t)
+    result.add atomicType("array")
+    result.add mapTypeToAst(t.sons[0], info)
+    result.add mapTypeToAst(t.sons[1], info)
+  of tyTypeDesc:
+    if t.base != nil:
+      result = newNodeIT(nkBracketExpr, info, t)
+      result.add atomicType("typeDesc")
+      result.add mapTypeToAst(t.base, info)
+    else:
+      result = atomicType"typeDesc"
+  of tyGenericInvocation:
+    result = newNodeIT(nkBracketExpr, info, t)
+    for i in 0 .. < t.len:
+      result.add mapTypeToAst(t.sons[i], info)
+  of tyGenericInst, tyGenericBody, tyOrdinal, tyUserTypeClassInst:
+    result = mapTypeToAst(t.lastSon, info)
+  of tyGenericParam, tyDistinct, tyForward: result = atomicType(t.sym.name.s)
+  of tyObject:
+    if allowRecursion:
+      result = newNodeIT(nkObjectTy, info, t)
+      if t.sons[0] == nil:
+        result.add ast.emptyNode
+      else:
+        result.add mapTypeToAst(t.sons[0], info)
+      result.add copyTree(t.n)
+    else:
+      result = atomicType(t.sym.name.s)
+  of tyEnum:
+    result = newNodeIT(nkEnumTy, info, t)
+    result.add copyTree(t.n)
+  of tyTuple: result = mapTypeToBracket("tuple", t, info)
+  of tySet: result = mapTypeToBracket("set", t, info)
+  of tyPtr: result = mapTypeToBracket("ptr", t, info)
+  of tyRef: result = mapTypeToBracket("ref", t, info)
+  of tyVar: result = mapTypeToBracket("var", t, info)
+  of tySequence: result = mapTypeToBracket("sequence", t, info)
+  of tyProc: result = mapTypeToBracket("proc", t, info)
+  of tyOpenArray: result = mapTypeToBracket("openArray", t, info)
+  of tyRange:
+    result = newNodeIT(nkBracketExpr, info, t)
+    result.add atomicType("range")
+    result.add t.n.sons[0].copyTree
+    result.add t.n.sons[1].copyTree
+  of tyPointer: result = atomicType"pointer"
+  of tyString: result = atomicType"string"
+  of tyCString: result = atomicType"cstring"
+  of tyInt: result = atomicType"int"
+  of tyInt8: result = atomicType"int8"
+  of tyInt16: result = atomicType"int16"
+  of tyInt32: result = atomicType"int32"
+  of tyInt64: result = atomicType"int64"
+  of tyFloat: result = atomicType"float"
+  of tyFloat32: result = atomicType"float32"
+  of tyFloat64: result = atomicType"float64"
+  of tyFloat128: result = atomicType"float128"
+  of tyUInt: result = atomicType"uint"
+  of tyUInt8: result = atomicType"uint8"
+  of tyUInt16: result = atomicType"uint16"
+  of tyUInt32: result = atomicType"uint32"
+  of tyUInt64: result = atomicType"uint64"
+  of tyBigNum: result = atomicType"bignum"
+  of tyConst: result = mapTypeToBracket("const", t, info)
+  of tyMutable: result = mapTypeToBracket("mutable", t, info)
+  of tyVarargs: result = mapTypeToBracket("varargs", t, info)
+  of tyIter: result = mapTypeToBracket("iter", t, info)
+  of tyProxy: result = atomicType"error"
+  of tyBuiltInTypeClass: result = mapTypeToBracket("builtinTypeClass", t, info)
+  of tyUserTypeClass: result = mapTypeToBracket("userTypeClass", t, info)
+  of tyCompositeTypeClass: result = mapTypeToBracket("compositeTypeClass", t, info)
+  of tyAnd: result = mapTypeToBracket("and", t, info)
+  of tyOr: result = mapTypeToBracket("or", t, info)
+  of tyNot: result = mapTypeToBracket("not", t, info)
+  of tyAnything: result = atomicType"anything"
+  of tyStatic, tyFromExpr, tyFieldAccessor:
+    result = newNodeIT(nkBracketExpr, info, t)
+    result.add atomicType("static")
+    if t.n != nil:
+      result.add t.n.copyTree
+
+proc opMapTypeToAst*(t: PType; info: TLineInfo): PNode =
+  result = mapTypeToAst(t, info, true)
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index f367d4cf9..5b7b0b0fd 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -950,7 +950,12 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
   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 mNGetType:
+    let tmp = c.genx(n.sons[1])
+    if dest < 0: dest = c.getTemp(n.typ)
+    c.gABC(n, opcNGetType, dest, tmp, if n[0].sym.name.s == "typeKind": 1 else: 0)
+    c.freeTemp(tmp)
+    #genUnaryABC(c, n, dest, opcNGetType)
   of mNStrVal: genUnaryABC(c, n, dest, opcNStrVal)
   of mNSetIntVal:
     unused(n, dest)
diff --git a/lib/core/macros.nim b/lib/core/macros.nim
index 9697724bd..c6453aeaa 100644
--- a/lib/core/macros.nim
+++ b/lib/core/macros.nim
@@ -83,7 +83,13 @@ type
     ntySequence, ntyProc, ntyPointer, ntyOpenArray,
     ntyString, ntyCString, ntyForward, ntyInt,
     ntyInt8, ntyInt16, ntyInt32, ntyInt64,
-    ntyFloat, ntyFloat32, ntyFloat64, ntyFloat128
+    ntyFloat, ntyFloat32, ntyFloat64, ntyFloat128,
+    ntyUInt, ntyUInt8, ntyUInt16, ntyUInt32, ntyUInt64,
+    ntyBigNum, 
+    ntyConst, ntyMutable, ntyVarargs, 
+    ntyIter,
+    ntyError
+    
   TNimTypeKinds* {.deprecated.} = set[NimTypeKind]
   NimSymKind* = enum
     nskUnknown, nskConditional, nskDynLib, nskParam,
@@ -100,7 +106,7 @@ type
   NimIdent* = object of RootObj
     ## represents a Nim identifier in the AST
 
-  NimSymObj {.final.} = object # hidden
+  NimSymObj = object # hidden
   NimSym* = ref NimSymObj
     ## represents a Nim *symbol* in the compiler; a *symbol* is a looked-up
     ## *ident*.
@@ -125,16 +131,16 @@ proc `!`*(s: string): NimIdent {.magic: "StrToIdent", noSideEffect.}
   ## constructs an identifier from the string `s`
 
 proc `$`*(i: NimIdent): string {.magic: "IdentToStr", noSideEffect.}
-  ## converts a Nimrod identifier to a string
+  ## converts a Nim identifier to a string
 
 proc `$`*(s: NimSym): string {.magic: "IdentToStr", noSideEffect.}
-  ## converts a Nimrod symbol to a string
+  ## converts a Nim symbol to a string
 
 proc `==`*(a, b: NimIdent): bool {.magic: "EqIdent", noSideEffect.}
-  ## compares two Nimrod identifiers
+  ## compares two Nim identifiers
 
 proc `==`*(a, b: PNimrodNode): bool {.magic: "EqNimrodNode", noSideEffect.}
-  ## compares two Nimrod nodes
+  ## compares two Nim nodes
 
 proc len*(n: PNimrodNode): int {.magic: "NLen", noSideEffect.}
   ## returns the number of children of `n`.
@@ -159,7 +165,19 @@ proc intVal*(n: PNimrodNode): BiggestInt {.magic: "NIntVal", noSideEffect.}
 proc floatVal*(n: PNimrodNode): BiggestFloat {.magic: "NFloatVal", noSideEffect.}
 proc symbol*(n: PNimrodNode): NimSym {.magic: "NSymbol", noSideEffect.}
 proc ident*(n: PNimrodNode): NimIdent {.magic: "NIdent", noSideEffect.}
-proc typ*(n: PNimrodNode): typedesc {.magic: "NGetType", noSideEffect.}
+
+proc getType*(n: PNimrodNode): PNimrodNode {.magic: "NGetType", noSideEffect.}
+  ## with 'getType' you can access the node's `type`:idx:. A Nim type is
+  ## mapped to a Nim AST too, so it's slightly confusing but it means the same
+  ## API can be used to traverse types. Recursive types are flattened for you
+  ## so there is no danger of infinite recursions during traversal. To
+  ## resolve recursive types, you have to call 'getType' again. To see what
+  ## kind of type it is, call `typeKind` on getType's result.
+
+proc typeKind*(n: PNimrodNode): NimTypeKind {.magic: "NGetType", noSideEffect.}
+  ## Returns the type kind of the node 'n' that should represent a type, that
+  ## means the node should have been obtained via `getType`.
+
 proc strVal*(n: PNimrodNode): string  {.magic: "NStrVal", noSideEffect.}
 
 proc `intVal=`*(n: PNimrodNode, val: BiggestInt) {.magic: "NSetIntVal", noSideEffect.}
@@ -216,7 +234,7 @@ proc newIdentNode*(i: string): PNimrodNode {.compileTime.} =
   result.ident = !i
 
 type
-  TBindSymRule* = enum   ## specifies how ``bindSym`` behaves
+  BindSymRule* = enum    ## specifies how ``bindSym`` behaves
     brClosed,            ## only the symbols in current scope are bound
     brOpen,              ## open wrt overloaded symbols, but may be a single
                          ## symbol if not ambiguous (the rules match that of
@@ -225,7 +243,9 @@ type
                          ## if not ambiguous (this cannot be achieved with
                          ## any other means in the language currently)
 
-proc bindSym*(ident: string, rule: TBindSymRule = brClosed): PNimrodNode {.
+{.deprecated: [TBindSymRule: BindSymRule].}
+
+proc bindSym*(ident: string, rule: BindSymRule = brClosed): PNimrodNode {.
               magic: "NBindSym", noSideEffect.}
   ## creates a node that binds `ident` to a symbol node. The bound symbol
   ## may be an overloaded symbol.
@@ -236,7 +256,7 @@ proc bindSym*(ident: string, rule: TBindSymRule = brClosed): PNimrodNode {.
   ## If ``rule == brForceOpen`` always an ``nkOpenSymChoice`` tree is
   ## returned even if the symbol is not ambiguous.
 
-proc genSym*(kind: TNimrodSymKind = nskLet; ident = ""): PNimrodNode {.
+proc genSym*(kind: NimSymKind = nskLet; ident = ""): PNimrodNode {.
   magic: "NGenSym", noSideEffect.}
   ## generates a fresh symbol that is guaranteed to be unique. The symbol
   ## needs to occur in a declaration context.
@@ -245,7 +265,7 @@ proc callsite*(): PNimrodNode {.magic: "NCallSite", benign.}
   ## returns the AST of the invocation expression that invoked this macro.
 
 proc toStrLit*(n: PNimrodNode): PNimrodNode {.compileTime.} =
-  ## converts the AST `n` to the concrete Nimrod code and wraps that
+  ## converts the AST `n` to the concrete Nim code and wraps that
   ## in a string literal node
   return newStrLitNode(repr(n))
 
diff --git a/todo.txt b/todo.txt
index 408bfefe5..79fe9d05a 100644
--- a/todo.txt
+++ b/todo.txt
@@ -74,7 +74,6 @@ version 0.9.X
 =============
 
 - macros as type pragmas
-- implement type API for macros
 - lazy overloading resolution:
   * special case ``tyStmt``
 - document NimMain and check whether it works for threading