summary refs log tree commit diff stats
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/ast.nim20
-rw-r--r--compiler/astalgo.nim29
-rw-r--r--compiler/ccgcalls.nim20
-rw-r--r--compiler/ccgexprs.nim46
-rw-r--r--compiler/ccgtypes.nim4
-rw-r--r--compiler/cgen.nim6
-rw-r--r--compiler/docgen.nim6
-rw-r--r--compiler/evaltempl.nim16
-rw-r--r--compiler/jsgen.nim317
-rw-r--r--compiler/lambdalifting.nim43
-rw-r--r--compiler/lookups.nim2
-rw-r--r--compiler/modules.nim49
-rw-r--r--compiler/pragmas.nim9
-rw-r--r--compiler/rod.nim2
-rw-r--r--compiler/rodimpl.nim58
-rw-r--r--compiler/sem.nim11
-rw-r--r--compiler/semexprs.nim31
-rw-r--r--compiler/seminst.nim6
-rw-r--r--compiler/semstmts.nim52
-rw-r--r--compiler/semtypes.nim8
-rw-r--r--compiler/semtypinst.nim2
-rw-r--r--compiler/sizealignoffsetimpl.nim3
-rw-r--r--compiler/trees.nim3
-rw-r--r--compiler/vm.nim18
-rw-r--r--compiler/vmops.nim3
25 files changed, 515 insertions, 249 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 7cf35450b..0247acb03 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -757,8 +757,6 @@ type
     OnUnknown,                # location is unknown (stack, heap or static)
     OnStatic,                 # in a static section
     OnStack,                  # location is on hardware stack
-    OnStackShadowDup,         # location is on the stack but also replicated
-                              # on the shadow stack
     OnHeap                    # location is on heap or global
                               # (reference counting needed)
   TLocFlags* = set[TLocFlag]
@@ -898,6 +896,8 @@ type
     loc*: TLoc
     typeInst*: PType          # for generic instantiations the tyGenericInst that led to this
                               # type.
+    uniqueId*: int            # due to a design mistake, we need to keep the real ID here as it
+                              # required by the --incremental:on mode.
 
   TPair* = object
     key*, val*: RootRef
@@ -1087,9 +1087,6 @@ proc newSym*(symKind: TSymKind, name: PIdent, owner: PSym,
   result.id = getID()
   when debugIds:
     registerId(result)
-  #if result.id == 77131:
-  #  writeStacktrace()
-  #  echo name.s
 
 proc isMetaType*(t: PType): bool =
   return t.kind in tyMetaTypes or
@@ -1261,6 +1258,9 @@ proc `$`*(x: TLockLevel): string =
   elif x.ord == UnknownLockLevel.ord: result = "<unknown>"
   else: result = $int16(x)
 
+proc `$`*(s: PSym): string =
+  result = s.name.s & "@" & $s.id
+
 proc newType*(kind: TTypeKind, owner: PSym): PType =
   new(result)
   result.kind = kind
@@ -1268,6 +1268,7 @@ proc newType*(kind: TTypeKind, owner: PSym): PType =
   result.size = -1
   result.align = -1            # default alignment
   result.id = getID()
+  result.uniqueId = result.id
   result.lockLevel = UnspecifiedLockLevel
   when debugIds:
     registerId(result)
@@ -1341,15 +1342,12 @@ proc copyType*(t: PType, owner: PSym, keepId: bool): PType =
 
 proc exactReplica*(t: PType): PType = copyType(t, t.owner, true)
 
-proc copySym*(s: PSym, keepId: bool = false): PSym =
+proc copySym*(s: PSym): PSym =
   result = newSym(s.kind, s.name, s.owner, s.info, s.options)
   #result.ast = nil            # BUGFIX; was: s.ast which made problems
   result.typ = s.typ
-  if keepId:
-    result.id = s.id
-  else:
-    result.id = getID()
-    when debugIds: registerId(result)
+  result.id = getID()
+  when debugIds: registerId(result)
   result.flags = s.flags
   result.magic = s.magic
   if s.kind == skModule:
diff --git a/compiler/astalgo.nim b/compiler/astalgo.nim
index b716882dc..b2671d81e 100644
--- a/compiler/astalgo.nim
+++ b/compiler/astalgo.nim
@@ -254,21 +254,26 @@ proc symToYamlAux(conf: ConfigRef; n: PSym, marker: var IntSet, indent: int,
   if n == nil:
     result = rope("null")
   elif containsOrIncl(marker, n.id):
-    result = "\"$1 @$2\"" % [rope(n.name.s), rope(
-        strutils.toHex(cast[ByteAddress](n), sizeof(n) * 2))]
+    result = "\"$1\"" % [rope(n.name.s)]
   else:
     var ast = treeToYamlAux(conf, n.ast, marker, indent + 2, maxRecDepth - 1)
     result = ropeConstr(indent, [rope("kind"),
                                  makeYamlString($n.kind),
                                  rope("name"), makeYamlString(n.name.s),
-                                 rope("typ"), typeToYamlAux(conf, n.typ, marker,
-                                   indent + 2, maxRecDepth - 1),
+                                 #rope("typ"), typeToYamlAux(conf, n.typ, marker,
+                                 #  indent + 2, maxRecDepth - 1),
                                  rope("info"), lineInfoToStr(conf, n.info),
                                  rope("flags"), flagsToStr(n.flags),
                                  rope("magic"), makeYamlString($n.magic),
                                  rope("ast"), ast, rope("options"),
                                  flagsToStr(n.options), rope("position"),
-                                 rope(n.position)])
+                                 rope(n.position),
+                                 rope("k"), makeYamlString($n.loc.k),
+                                 rope("storage"), makeYamlString($n.loc.storage),
+                                 rope("flags"), makeYamlString($n.loc.flags),
+                                 rope("r"), n.loc.r,
+                                 rope("lode"), treeToYamlAux(conf, n.loc.lode, marker, indent + 2, maxRecDepth - 1)
+    ])
 
 proc typeToYamlAux(conf: ConfigRef; n: PType, marker: var IntSet, indent: int,
                    maxRecDepth: int): Rope =
@@ -394,10 +399,16 @@ proc debugTree(conf: ConfigRef; n: PNode, indent: int, maxRecDepth: int;
       of nkStrLit..nkTripleStrLit:
         addf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
       of nkSym:
-        addf(result, ",$N$1\"sym\": $2_$3",
-            [istr, rope(n.sym.name.s), rope(n.sym.id)])
-        #     [istr, symToYaml(n.sym, indent, maxRecDepth),
-        #     rope(n.sym.id)])
+        let s = n.sym
+        addf(result, ",$N$1\"sym\": $2_$3 k: $4 storage: $5 flags: $6 r: $7",
+             [istr, rope(s.name.s), rope(s.id),
+                                 rope($s.loc.k),
+                                 rope($s.loc.storage),
+                                 rope($s.loc.flags),
+                                 s.loc.r
+             ])
+#             [istr, symToYaml(conf, n.sym, indent, maxRecDepth),
+#             rope(n.sym.id)])
         if renderType and n.sym.typ != nil:
           addf(result, ",$N$1\"typ\": $2", [istr, debugType(conf, n.sym.typ, 2)])
       of nkIdent:
diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim
index b23cd598e..d177e1f88 100644
--- a/compiler/ccgcalls.nim
+++ b/compiler/ccgcalls.nim
@@ -63,26 +63,6 @@ proc fixupCall(p: BProc, le, ri: PNode, d: var TLoc,
     add(pl, ~");$n")
     line(p, cpsStmts, pl)
 
-proc isInCurrentFrame(p: BProc, n: PNode): bool =
-  # checks if `n` is an expression that refers to the current frame;
-  # this does not work reliably because of forwarding + inlining can break it
-  case n.kind
-  of nkSym:
-    if n.sym.kind in {skVar, skResult, skTemp, skLet} and p.prc != nil:
-      result = p.prc.id == n.sym.owner.id
-  of nkDotExpr, nkBracketExpr:
-    if skipTypes(n.sons[0].typ, abstractInst).kind notin {tyVar,tyLent,tyPtr,tyRef}:
-      result = isInCurrentFrame(p, n.sons[0])
-  of nkHiddenStdConv, nkHiddenSubConv, nkConv:
-    result = isInCurrentFrame(p, n.sons[1])
-  of nkHiddenDeref, nkDerefExpr:
-    # what about: var x = addr(y); callAsOpenArray(x[])?
-    # *shrug* ``addr`` is unsafe anyway.
-    result = false
-  of nkObjUpConv, nkObjDownConv, nkCheckedFieldExpr:
-    result = isInCurrentFrame(p, n.sons[0])
-  else: discard
-
 proc genBoundsCheck(p: BProc; arr, a, b: TLoc)
 
 proc openArrayLoc(p: BProc, n: PNode): Rope =
diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim
index 34836d843..cab2c78f5 100644
--- a/compiler/ccgexprs.nim
+++ b/compiler/ccgexprs.nim
@@ -31,10 +31,18 @@ proc intLiteral(i: BiggestInt): Rope =
     result = ~"(IL64(-9223372036854775807) - IL64(1))"
 
 proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
-  if ty == nil: internalError(p.config, n.info, "genLiteral: ty is nil")
   case n.kind
   of nkCharLit..nkUInt64Lit:
-    case skipTypes(ty, abstractVarRange).kind
+    var k: TTypeKind
+    if ty != nil:
+      k = skipTypes(ty, abstractVarRange).kind
+    else:
+      case n.kind
+      of nkCharLit: k = tyChar
+      of nkUInt64Lit: k = tyUInt64
+      of nkInt64Lit: k = tyInt64
+      else: k = tyNil # don't go into the case variant that uses 'ty'
+    case k
     of tyChar, tyNil:
       result = intLiteral(n.intVal)
     of tyBool:
@@ -46,8 +54,8 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
       result = "(($1) $2)" % [getTypeDesc(p.module,
           ty), intLiteral(n.intVal)]
   of nkNilLit:
-    let t = skipTypes(ty, abstractVarRange)
-    if t.kind == tyProc and t.callConv == ccClosure:
+    let k = if ty == nil: tyPointer else: skipTypes(ty, abstractVarRange).kind
+    if k == tyProc and skipTypes(ty, abstractVarRange).callConv == ccClosure:
       let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
       result = p.module.tmpBase & rope(id)
       if id == p.module.labels:
@@ -59,7 +67,9 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
     else:
       result = rope("NIM_NIL")
   of nkStrLit..nkTripleStrLit:
-    case skipTypes(ty, abstractVarRange + {tyStatic, tyUserTypeClass, tyUserTypeClassInst}).kind
+    let k = if ty == nil: tyString
+            else: skipTypes(ty, abstractVarRange + {tyStatic, tyUserTypeClass, tyUserTypeClassInst}).kind
+    case k
     of tyNil:
       result = genNilStringLiteral(p.module, n.info)
     of tyString:
@@ -168,7 +178,7 @@ proc canMove(p: BProc, n: PNode): bool =
   #  echo n.info, " optimized ", n
   #  result = false
 
-proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
+proc genRefAssign(p: BProc, dest, src: TLoc) =
   if (dest.storage == OnStack and p.config.selectedGC != gcGo) or not usesWriteBarrier(p.config):
     linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
   elif dest.storage == OnHeap:
@@ -266,12 +276,12 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   let ty = skipTypes(dest.t, abstractRange + tyUserTypeClasses + {tyStatic})
   case ty.kind
   of tyRef:
-    genRefAssign(p, dest, src, flags)
+    genRefAssign(p, dest, src)
   of tySequence:
     if p.config.selectedGC == gcDestructors:
       genGenericAsgn(p, dest, src, flags)
     elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode):
-      genRefAssign(p, dest, src, flags)
+      genRefAssign(p, dest, src)
     else:
       linefmt(p, cpsStmts, "#genericSeqAssign($1, $2, $3);$n",
               addrLoc(p.config, dest), rdLoc(src),
@@ -280,7 +290,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
     if p.config.selectedGC == gcDestructors:
       genGenericAsgn(p, dest, src, flags)
     elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode):
-      genRefAssign(p, dest, src, flags)
+      genRefAssign(p, dest, src)
     else:
       if (dest.storage == OnStack and p.config.selectedGC != gcGo) or not usesWriteBarrier(p.config):
         linefmt(p, cpsStmts, "$1 = #copyString($2);$n", dest.rdLoc, src.rdLoc)
@@ -295,16 +305,16 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
         linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, #copyString($2));$n",
                addrLoc(p.config, dest), rdLoc(src))
   of tyProc:
-    if needsComplexAssignment(dest.t):
+    if containsGarbageCollectedRef(dest.t):
       # optimize closure assignment:
       let a = optAsgnLoc(dest, dest.t, "ClE_0".rope)
       let b = optAsgnLoc(src, dest.t, "ClE_0".rope)
-      genRefAssign(p, a, b, flags)
+      genRefAssign(p, a, b)
       linefmt(p, cpsStmts, "$1.ClP_0 = $2.ClP_0;$n", rdLoc(dest), rdLoc(src))
     else:
       linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
   of tyTuple:
-    if needsComplexAssignment(dest.t):
+    if containsGarbageCollectedRef(dest.t):
       if dest.t.len <= 4: genOptAsgnTuple(p, dest, src, flags)
       else: genGenericAsgn(p, dest, src, flags)
     else:
@@ -315,7 +325,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
       linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
     elif not isObjLackingTypeField(ty):
       genGenericAsgn(p, dest, src, flags)
-    elif needsComplexAssignment(ty):
+    elif containsGarbageCollectedRef(ty):
       if ty.sons[0].isNil and asgnComplexity(ty.n) <= 4:
         discard getTypeDesc(p.module, ty)
         internalAssert p.config, ty.n != nil
@@ -325,7 +335,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
     else:
       linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
   of tyArray:
-    if needsComplexAssignment(dest.t):
+    if containsGarbageCollectedRef(dest.t):
       genGenericAsgn(p, dest, src, flags)
     else:
       linefmt(p, cpsStmts,
@@ -334,7 +344,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   of tyOpenArray, tyVarargs:
     # open arrays are always on the stack - really? What if a sequence is
     # passed to an open array?
-    if needsComplexAssignment(dest.t):
+    if containsGarbageCollectedRef(dest.t):
       linefmt(p, cpsStmts,     # XXX: is this correct for arrays?
            "#genericAssignOpenArray((void*)$1, (void*)$2, $1Len_0, $3);$n",
            addrLoc(p.config, dest), addrLoc(p.config, src),
@@ -840,7 +850,6 @@ proc genUncheckedArrayElem(p: BProc, n, x, y: PNode, d: var TLoc) =
   var a, b: TLoc
   initLocExpr(p, x, a)
   initLocExpr(p, y, b)
-  var ty = skipTypes(a.t, abstractVarRange + abstractPtrs + tyUserTypeClasses)
   d.inheritLocation(a)
   putIntoDest(p, d, n, ropecg(p.module, "$1[$2]", rdLoc(a), rdCharLoc(b)),
               a.storage)
@@ -874,7 +883,6 @@ proc genCStringElem(p: BProc, n, x, y: PNode, d: var TLoc) =
   var a, b: TLoc
   initLocExpr(p, x, a)
   initLocExpr(p, y, b)
-  var ty = skipTypes(a.t, abstractVarRange)
   inheritLocation(d, a)
   putIntoDest(p, d, n,
               ropecg(p.module, "$1[$2]", rdLoc(a), rdCharLoc(b)), a.storage)
@@ -1128,7 +1136,7 @@ proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
     genTypeInfo(p.module, seqType, e.info)])
   # emit the write barrier if required, but we can always move here, so
   # use 'genRefAssign' for the seq.
-  genRefAssign(p, a, call, {})
+  genRefAssign(p, a, call)
   #if bt != b.t:
   #  echo "YES ", e.info, " new: ", typeToString(bt), " old: ", typeToString(b.t)
   initLoc(dest, locExpr, e.sons[2], OnHeap)
@@ -1392,7 +1400,6 @@ proc genArrToSeq(p: BProc, n: PNode, d: var TLoc) =
   else:
     var i: TLoc
     getTemp(p, getSysType(p.module.g.graph, unknownLineInfo(), tyInt), i)
-    let oldCode = p.s(cpsStmts)
     linefmt(p, cpsStmts, "for ($1 = 0; $1 < $2; $1++) {$n",  i.r, L.rope)
     initLoc(elem, locExpr, lodeTyp elemType(skipTypes(n.typ, abstractInst)), OnHeap)
     elem.r = ropecg(p.module, "$1$3[$2]", rdLoc(d), rdLoc(i), dataField(p))
@@ -2566,7 +2573,6 @@ proc genConstObjConstr(p: BProc; n: PNode): Rope =
 proc genConstSimpleList(p: BProc, n: PNode): Rope =
   var length = sonsLen(n)
   result = rope("{")
-  let t = n.typ.skipTypes(abstractInst)
   for i in countup(0, length - 2):
     addf(result, "$1,$n", [genNamedConstExpr(p, n.sons[i])])
   if length > 0:
diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim
index bbfd72354..266f63647 100644
--- a/compiler/ccgtypes.nim
+++ b/compiler/ccgtypes.nim
@@ -193,8 +193,6 @@ proc isImportedCppType(t: PType): bool =
            (x.sym != nil and sfInfixCall in x.sym.flags)
 
 proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope
-proc needsComplexAssignment(typ: PType): bool =
-  result = containsGarbageCollectedRef(typ)
 
 proc isObjLackingTypeField(typ: PType): bool {.inline.} =
   result = (typ.kind == tyObject) and ((tfFinal in typ.flags) and
@@ -214,7 +212,7 @@ proc isInvalidReturnType(conf: ConfigRef; rettype: PType): bool =
     of ctStruct:
       let t = skipTypes(rettype, typedescInst)
       if rettype.isImportedCppType or t.isImportedCppType: return false
-      result = needsComplexAssignment(t) or
+      result = containsGarbageCollectedRef(t) or
           (t.kind == tyObject and not isObjLackingTypeField(t))
     else: result = false
 
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index 199a93be2..3545edc88 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -297,7 +297,7 @@ type
     needToCopy
   TAssignmentFlags = set[TAssignmentFlag]
 
-proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags)
+proc genRefAssign(p: BProc, dest, src: TLoc)
 
 proc isComplexValueType(t: PType): bool {.inline.} =
   let t = t.skipTypes(abstractInst + tyUserTypeClasses)
@@ -313,7 +313,7 @@ proc resetLoc(p: BProc, loc: var TLoc) =
       var nilLoc: TLoc
       initLoc(nilLoc, locTemp, loc.lode, OnStack)
       nilLoc.r = rope("NIM_NIL")
-      genRefAssign(p, loc, nilLoc, {})
+      genRefAssign(p, loc, nilLoc)
     else:
       linefmt(p, cpsStmts, "$1 = 0;$n", rdLoc(loc))
   else:
@@ -1490,7 +1490,7 @@ proc shouldRecompile(m: BModule; code: Rope, cfile: Cfile): bool =
   result = true
   if optForceFullMake notin m.config.globalOptions:
     if not equalsFile(code, cfile.cname):
-      if isDefined(m.config, "nimdiff"):
+      if m.config.symbolFiles == readOnlySf: #isDefined(m.config, "nimdiff"):
         if fileExists(cfile.cname):
           copyFile(cfile.cname.string, cfile.cname.string & ".backup")
           echo "diff ", cfile.cname.string, ".backup ", cfile.cname.string
diff --git a/compiler/docgen.nim b/compiler/docgen.nim
index 6f61d020d..67f4108e1 100644
--- a/compiler/docgen.nim
+++ b/compiler/docgen.nim
@@ -400,7 +400,13 @@ proc extractImports(n: PNode; result: PNode) =
   for i in 0..<n.safeLen: extractImports(n[i], result)
 
 proc prepareExamples(d: PDoc; n: PNode) =
+
+  var docComment = newTree(nkCommentStmt)
+  let loc = d.conf.toFileLineCol(n.info)
+  docComment.comment = "autogenerated by docgen from " & loc
+
   var runnableExamples = newTree(nkStmtList,
+      docComment,
       newTree(nkImportStmt, newStrNode(nkStrLit, d.filename)))
   runnableExamples.info = n.info
   let imports = newTree(nkStmtList)
diff --git a/compiler/evaltempl.nim b/compiler/evaltempl.nim
index 43d5a8698..0f9220102 100644
--- a/compiler/evaltempl.nim
+++ b/compiler/evaltempl.nim
@@ -37,18 +37,21 @@ proc evalTemplateAux(templ, actual: PNode, c: var TemplCtx, result: PNode) =
   case templ.kind
   of nkSym:
     var s = templ.sym
-    if s.owner.id == c.owner.id:
+    if s.owner == nil or s.owner.id == c.owner.id:
       if s.kind == skParam and sfGenSym notin s.flags:
         handleParam actual.sons[s.position]
-      elif s.kind == skGenericParam or
-           s.kind == skType and s.typ != nil and s.typ.kind == tyGenericParam:
+      elif (s.owner != nil) and (s.kind == skGenericParam or
+           s.kind == skType and s.typ != nil and s.typ.kind == tyGenericParam):
         handleParam actual.sons[s.owner.typ.len + s.position - 1]
       else:
         internalAssert c.config, sfGenSym in s.flags or s.kind == skType
         var x = PSym(idTableGet(c.mapping, s))
         if x == nil:
-          x = copySym(s, false)
-          x.owner = c.genSymOwner
+          x = copySym(s)
+          # sem'check needs to set the owner properly later, see bug #9476
+          x.owner = nil # c.genSymOwner
+          #if x.kind == skParam and x.owner.kind == skModule:
+          #  internalAssert c.config, false
           idTablePut(c.mapping, s, x)
         result.add newSymNode(x, if c.instLines: actual.info else: templ.info)
     else:
@@ -173,6 +176,7 @@ proc evalTemplate*(n: PNode, tmpl, genSymOwner: PSym;
   initIdTable(ctx.mapping)
 
   let body = tmpl.getBody
+  #echo "instantion of ", renderTree(body, {renderIds})
   if isAtom(body):
     result = newNodeI(nkPar, body.info)
     evalTemplateAux(body, args, ctx, result)
@@ -189,5 +193,7 @@ proc evalTemplate*(n: PNode, tmpl, genSymOwner: PSym;
       evalTemplateAux(body.sons[i], args, ctx, result)
   result.flags.incl nfFromTemplate
   result = wrapInComesFrom(n.info, tmpl, result)
+  #if ctx.debugActive:
+  #  echo "instantion of ", renderTree(result, {renderIds})
   dec(conf.evalTemplateCounter)
 
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index 3af34c03b..a9813f5c5 100644
--- a/compiler/jsgen.nim
+++ b/compiler/jsgen.nim
@@ -66,6 +66,12 @@ type
     res: Rope               # result part; index if this is an
                              # (address, index)-tuple
     address: Rope           # address of an (address, index)-tuple
+    tmpLoc: Rope            # tmp var which stores the (address, index)
+                            # pair to prevent multiple evals.
+                            # the tmp is initialized upon evaling the
+                            # address.
+                            # might be nil.
+                            # (see `maybeMakeTemp`)
 
   TBlock = object
     id: int                  # the ID of the label; positive means that it
@@ -131,16 +137,15 @@ proc newGlobals(): PGlobals =
 proc initCompRes(r: var TCompRes) =
   r.address = nil
   r.res = nil
+  r.tmpLoc = nil
   r.typ = etyNone
   r.kind = resNone
 
 proc rdLoc(a: TCompRes): Rope {.inline.} =
-  result = a.res
-  when false:
-    if a.typ != etyBaseIndex:
-      result = a.res
-    else:
-      result = "$1[$2]" % [a.address, a.res]
+  if a.typ != etyBaseIndex:
+    result = a.res
+  else:
+    result = "$1[$2]" % [a.address, a.res]
 
 proc newProc(globals: PGlobals, module: BModule, procDef: PNode,
              options: TOptions): PProc =
@@ -447,12 +452,48 @@ const # magic checked op; magic unchecked op; checked op; unchecked op
     ["cstrToNimstr", "cstrToNimstr", "cstrToNimstr($1)", "cstrToNimstr($1)"],
     ["", "", "$1", "$1"]]
 
+proc needsTemp(p: PProc; n: PNode): bool =
+  # check if n contains a call to determine
+  # if a temp should be made to prevent multiple evals
+  if n.kind in nkCallKinds + {nkTupleConstr, nkObjConstr, nkBracket, nkCurly}:
+    return true
+  for c in n:
+    if needsTemp(p, c):
+      return true
+
+proc maybeMakeTemp(p: PProc, n: PNode; x: TCompRes): tuple[a, tmp: Rope] =
+  var
+    a = x.rdLoc
+    b = a
+  if needsTemp(p, n):
+    # if we have tmp just use it
+    if x.tmpLoc != nil and (mapType(n.typ) == etyBaseIndex or n.kind in {nkHiddenDeref, nkDerefExpr}):
+      b = "$1[0][$1[1]]" % [x.tmpLoc]
+      (a: a, tmp: b)
+    else:
+      let tmp = p.getTemp
+      b = tmp
+      a = "($1 = $2, $1)" % [tmp, a]
+      (a: a, tmp: b)
+  else:
+    (a: a, tmp: b)
+
 proc binaryExpr(p: PProc, n: PNode, r: var TCompRes, magic, frmt: string) =
+  # $1 and $2 in the `frmt` string bind to lhs and rhs of the expr,
+  # if $3 or $4 are present they will be substituted with temps for
+  # lhs and rhs respectively
   var x, y: TCompRes
   useMagic(p, magic)
   gen(p, n.sons[1], x)
   gen(p, n.sons[2], y)
-  r.res = frmt % [x.rdLoc, y.rdLoc]
+
+  var
+    a, tmp = x.rdLoc
+    b, tmp2 = y.rdLoc
+  if "$3" in frmt: (a, tmp) = maybeMakeTemp(p, n[1], x)
+  if "$4" in frmt: (a, tmp) = maybeMakeTemp(p, n[1], x)
+
+  r.res = frmt % [a, b, tmp, tmp2]
   r.kind = resExpr
 
 proc unsignedTrimmerJS(size: BiggestInt): Rope =
@@ -473,7 +514,8 @@ proc binaryUintExpr(p: PProc, n: PNode, r: var TCompRes, op: string,
   gen(p, n.sons[2], y)
   let trimmer = unsignedTrimmer(n[1].typ.skipTypes(abstractRange).size)
   if reassign:
-    r.res = "$1 = (($1 $2 $3) $4)" % [x.rdLoc, rope op, y.rdLoc, trimmer]
+    let (a, tmp) = maybeMakeTemp(p, n[1], x)
+    r.res = "$1 = (($5 $2 $3) $4)" % [a, rope op, y.rdLoc, trimmer, tmp]
   else:
     r.res = "(($1 $2 $3) $4)" % [x.rdLoc, rope op, y.rdLoc, trimmer]
 
@@ -487,9 +529,12 @@ proc ternaryExpr(p: PProc, n: PNode, r: var TCompRes, magic, frmt: string) =
   r.kind = resExpr
 
 proc unaryExpr(p: PProc, n: PNode, r: var TCompRes, magic, frmt: string) =
+  # $1 binds to n[1], if $2 is present it will be substituted to a tmp of $1
   useMagic(p, magic)
   gen(p, n.sons[1], r)
-  r.res = frmt % [r.rdLoc]
+  var a, tmp = r.rdLoc
+  if "$2" in frmt: (a, tmp) = maybeMakeTemp(p, n[1], r)
+  r.res = frmt % [a, tmp]
   r.kind = resExpr
 
 proc arithAux(p: PProc, n: PNode, r: var TCompRes, op: TMagic) =
@@ -524,6 +569,14 @@ proc arith(p: PProc, n: PNode, r: var TCompRes, op: TMagic) =
   of mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr,
       mCStrToStr, mStrToStr, mEnumToStr:
     arithAux(p, n, r, op)
+  of mEqRef, mEqUntracedRef:
+    if mapType(n[1].typ) != etyBaseIndex:
+      arithAux(p, n, r, op)
+    else:
+      var x, y: TCompRes
+      gen(p, n[1], x)
+      gen(p, n[2], y)
+      r.res = "($# == $# && $# == $#)" % [x.address, y.address, x.res, y.res]
   else:
     arithAux(p, n, r, op)
   r.kind = resExpr
@@ -801,6 +854,7 @@ proc genAsmOrEmitStmt(p: PProc, n: PNode) =
           # A fat pointer is disguised as an array
           r.res = r.address
           r.address = nil
+          r.typ = etyNone
         elif r.typ == etyBaseIndex:
           # Deference first
           r.res = "$1[$2]" % [r.address, r.res]
@@ -863,26 +917,42 @@ proc countJsParams(typ: PType): int =
 
 const
   nodeKindsNeedNoCopy = {nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit,
-    nkFloatLit..nkFloat64Lit, nkCurly, nkPar, nkTupleConstr, nkObjConstr, nkStringToCString,
+    nkFloatLit..nkFloat64Lit, nkCurly, nkPar, nkStringToCString,
     nkCStringToString, nkCall, nkPrefix, nkPostfix, nkInfix,
     nkCommand, nkHiddenCallConv, nkCallStrLit}
 
 proc needsNoCopy(p: PProc; y: PNode): bool =
-  result = (y.kind in nodeKindsNeedNoCopy) or
-      (skipTypes(y.typ, abstractInst).kind in {tyRef, tyPtr, tyLent, tyVar})
+  # if the node is a literal object constructor we have to recursively
+  # check the expressions passed into it
+  case y.kind
+  of nkObjConstr:
+    for arg in y.sons[1..^1]:
+      if not needsNoCopy(p, arg[1]):
+        return false
+  of nkTupleConstr:
+    for arg in y.sons:
+      var arg = arg
+      if arg.kind == nkExprColonExpr:
+        arg = arg[1]
+      if not needsNoCopy(p, arg):
+        return false
+  of nkBracket:
+    for arg in y.sons:
+      if not needsNoCopy(p, arg):
+        return false
+  of nodeKindsNeedNoCopy:
+    return true
+  else:
+    return (mapType(y.typ) != etyBaseIndex and
+            (skipTypes(y.typ, abstractInst).kind in
+             {tyRef, tyPtr, tyLent, tyVar, tyCString} + IntegralTypes))
+  return true
 
 proc genAsgnAux(p: PProc, x, y: PNode, noCopyNeeded: bool) =
   var a, b: TCompRes
   var xtyp = mapType(p, x.typ)
 
-  if x.kind == nkHiddenDeref and x.sons[0].kind == nkCall and xtyp != etyObject:
-    gen(p, x.sons[0], a)
-    let tmp = p.getTemp(false)
-    lineF(p, "var $1 = $2;$n", [tmp, a.rdLoc])
-    a.res = "$1[0][$1[1]]" % [tmp]
-  else:
-    gen(p, x, a)
-
+  gen(p, x, a)
   genLineDir(p, y)
   gen(p, y, b)
 
@@ -911,13 +981,13 @@ proc genAsgnAux(p: PProc, x, y: PNode, noCopyNeeded: bool) =
         let tmp = p.getTemp(false)
         lineF(p, "var $1 = $4; $2 = $1[0]; $3 = $1[1];$n", [tmp, a.address, a.res, b.rdLoc])
       elif b.typ == etyBaseIndex:
-        lineF(p, "$# = $#;$n", [a.res, b.rdLoc])
+        lineF(p, "$# = [$#, $#];$n", [a.res, b.address, b.res])
       else:
         internalError(p.config, x.info, "genAsgn")
     else:
       lineF(p, "$1 = $2; $3 = $4;$n", [a.address, b.address, a.res, b.res])
   else:
-    lineF(p, "$1 = $2;$n", [a.res, b.res])
+    lineF(p, "$1 = $2;$n", [a.rdLoc, b.rdLoc])
 
 proc genAsgn(p: PProc, n: PNode) =
   genAsgnAux(p, n.sons[0], n.sons[1], noCopyNeeded=false)
@@ -971,17 +1041,30 @@ proc genFieldAddr(p: PProc, n: PNode, r: var TCompRes) =
   r.kind = resExpr
 
 proc genFieldAccess(p: PProc, n: PNode, r: var TCompRes) =
-  r.typ = etyNone
   gen(p, n.sons[0], r)
+  r.typ = mapType(n.typ)
   let otyp = skipTypes(n.sons[0].typ, abstractVarRange)
+
+  template mkTemp(i: int) =
+    if r.typ == etyBaseIndex:
+      if needsTemp(p, n[i]):
+        let tmp = p.getTemp
+        r.address = "($1 = $2, $1)[0]" % [tmp, r.res]
+        r.res = "$1[1]" % [tmp]
+        r.tmpLoc = tmp
+      else:
+        r.address = "$1[0]" % [r.res]
+        r.res = "$1[1]" % [r.res]
   if otyp.kind == tyTuple:
     r.res = ("$1.Field$2") %
         [r.res, getFieldPosition(p, n.sons[1]).rope]
+    mkTemp(0)
   else:
     if n.sons[1].kind != nkSym: internalError(p.config, n.sons[1].info, "genFieldAccess")
     var f = n.sons[1].sym
     if f.loc.r == nil: f.loc.r = mangleName(p.module, f)
     r.res = "$1.$2" % [r.res, f.loc.r]
+    mkTemp(1)
   r.kind = resExpr
 
 proc genAddr(p: PProc, n: PNode, r: var TCompRes)
@@ -1039,14 +1122,15 @@ proc genArrayAddr(p: PProc, n: PNode, r: var TCompRes) =
   let m = if n.kind == nkHiddenAddr: n.sons[0] else: n
   gen(p, m.sons[0], a)
   gen(p, m.sons[1], b)
-  internalAssert p.config, a.typ != etyBaseIndex and b.typ != etyBaseIndex
-  r.address = a.res
+  #internalAssert p.config, a.typ != etyBaseIndex and b.typ != etyBaseIndex
+  let (x, tmp) = maybeMakeTemp(p, m[0], a)
+  r.address = x
   var typ = skipTypes(m.sons[0].typ, abstractPtrs)
   if typ.kind == tyArray: first = firstOrd(p.config, typ.sons[0])
   else: first = 0
   if optBoundsCheck in p.options:
     useMagic(p, "chckIndx")
-    r.res = "chckIndx($1, $2, $3.length+$2-1)-$2" % [b.res, rope(first), a.res]
+    r.res = "chckIndx($1, $2, $3.length+$2-1)-$2" % [b.res, rope(first), tmp]
   elif first != 0:
     r.res = "($1)-$2" % [b.res, rope(first)]
   else:
@@ -1062,13 +1146,22 @@ proc genArrayAccess(p: PProc, n: PNode, r: var TCompRes) =
   of tyTuple:
     genFieldAddr(p, n, r)
   else: internalError(p.config, n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
-  r.typ = etyNone
+  r.typ = mapType(n.typ)
   if r.res == nil: internalError(p.config, n.info, "genArrayAccess")
   if ty.kind == tyCString:
     r.res = "$1.charCodeAt($2)" % [r.address, r.res]
+  elif r.typ == etyBaseIndex:
+    if needsTemp(p, n[0]):
+      let tmp = p.getTemp
+      r.address = "($1 = $2, $1)[0]" % [tmp, r.rdLoc]
+      r.res = "$1[1]" % [tmp]
+      r.tmpLoc = tmp
+    else:
+      let x = r.rdLoc
+      r.address = "$1[0]" % [x]
+      r.res = "$1[1]" % [x]
   else:
     r.res = "$1[$2]" % [r.address, r.res]
-  r.address = nil
   r.kind = resExpr
 
 template isIndirect(x: PSym): bool =
@@ -1169,8 +1262,12 @@ proc genSym(p: PProc, n: PNode, r: var TCompRes) =
     if k == etyBaseIndex:
       r.typ = etyBaseIndex
       if {sfAddrTaken, sfGlobal} * s.flags != {}:
-        r.address = "$1[0]" % [s.loc.r]
-        r.res = "$1[1]" % [s.loc.r]
+        if isIndirect(s):
+          r.address = "$1[0][0]" % [s.loc.r]
+          r.res = "$1[0][1]" % [s.loc.r]
+        else:
+          r.address = "$1[0]" % [s.loc.r]
+          r.res = "$1[1]" % [s.loc.r]
       else:
         r.address = s.loc.r
         r.res = s.loc.r & "_Idx"
@@ -1210,14 +1307,17 @@ proc genDeref(p: PProc, n: PNode, r: var TCompRes) =
   else:
     var a: TCompRes
     gen(p, it, a)
-    r.kind = resExpr
-    if a.typ == etyBaseIndex:
-      r.res = "$1[$2]" % [a.address, a.res]
-    elif it.kind == nkCall:
+    r.kind = a.kind
+    r.typ = mapType(p, n.typ)
+    if r.typ == etyBaseIndex:
       let tmp = p.getTemp
-      r.res = "($1 = $2, $1[0])[$1[1]]" % [tmp, a.res]
-    elif t == etyBaseIndex:
-      r.res = "$1[0]" % [a.res]
+      r.address = "($1 = $2, $1)[0]" % [tmp, a.rdLoc]
+      r.res = "$1[1]" % [tmp]
+      r.tmpLoc = tmp
+    elif a.typ == etyBaseIndex:
+      if a.tmpLoc != nil:
+        r.tmpLoc = a.tmpLoc
+      r.res = a.rdLoc
     else:
       internalError(p.config, n.info, "genDeref")
 
@@ -1242,7 +1342,7 @@ proc genArg(p: PProc, n: PNode, param: PSym, r: var TCompRes; emitted: ptr int =
     add(r.res, ", ")
     add(r.res, a.res)
     if emitted != nil: inc emitted[]
-  elif n.typ.kind in {tyVar, tyLent} and n.kind in nkCallKinds and mapType(param.typ) == etyBaseIndex:
+  elif n.typ.kind in {tyVar, tyPtr, tyRef, tyLent} and n.kind in nkCallKinds and mapType(param.typ) == etyBaseIndex:
     # this fixes bug #5608:
     let tmp = getTemp(p)
     add(r.res, "($1 = $2, $1[0]), $1[1]" % [tmp, a.rdLoc])
@@ -1366,6 +1466,14 @@ proc genCall(p: PProc, n: PNode, r: var TCompRes) =
     return
   gen(p, n.sons[0], r)
   genArgs(p, n, r)
+  if n.typ != nil:
+    let t = mapType(n.typ)
+    if t == etyBaseIndex:
+      let tmp = p.getTemp
+      r.address = "($1 = $2, $1)[0]" % [tmp, r.rdLoc]
+      r.res = "$1[1]" % [tmp]
+      r.tmpLoc = tmp
+      r.typ = t
 
 proc genEcho(p: PProc, n: PNode, r: var TCompRes) =
   let n = n[1].skipConv
@@ -1472,12 +1580,12 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope =
     createObjInitList(p, t, initIntSet(), initList)
     result = ("{$1}") % [initList]
     if indirect: result = "[$1]" % [result]
-  of tyVar, tyPtr, tyLent, tyRef:
+  of tyVar, tyPtr, tyLent, tyRef, tyPointer:
     if mapType(p, t) == etyBaseIndex:
       result = putToSeq("[null, 0]", indirect)
     else:
       result = putToSeq("null", indirect)
-  of tySequence, tyOpt, tyString, tyCString, tyPointer, tyProc:
+  of tySequence, tyOpt, tyString, tyCString, tyProc:
     result = putToSeq("null", indirect)
   of tyStatic:
     if t.n != nil:
@@ -1511,10 +1619,13 @@ proc genVarInit(p: PProc, v: PSym, n: PNode) =
     varCode = v.constraint.strVal
 
   if n.kind == nkEmpty:
-    lineF(p, varCode & " = $3;$n",
-               [returnType, varName, createVar(p, v.typ, isIndirect(v))])
-    if v.typ.kind in {tyVar, tyPtr, tyLent, tyRef} and mapType(p, v.typ) == etyBaseIndex:
+    if not isIndirect(v) and
+      v.typ.kind in {tyVar, tyPtr, tyLent, tyRef} and mapType(p, v.typ) == etyBaseIndex:
+      lineF(p, "var $1 = null;$n", [varName])
       lineF(p, "var $1_Idx = 0;$n", [varName])
+    else:
+      lineF(p, varCode & " = $3;$n",
+                [returnType, varName, createVar(p, v.typ, isIndirect(v))])
   else:
     gen(p, n, a)
     case mapType(p, v.typ)
@@ -1531,8 +1642,12 @@ proc genVarInit(p: PProc, v: PSym, n: PNode) =
           lineF(p, varCode & " = $3, $2_Idx = $4;$n",
                    [returnType, v.loc.r, a.address, a.res])
         else:
-          lineF(p, varCode & " = [$3, $4];$n",
-                   [returnType, v.loc.r, a.address, a.res])
+          if isIndirect(v):
+            lineF(p, varCode & " = [[$3, $4]];$n",
+                     [returnType, v.loc.r, a.address, a.res])
+          else:
+            lineF(p, varCode & " = [$3, $4];$n",
+                     [returnType, v.loc.r, a.address, a.res])
       else:
         if targetBaseIndex:
           let tmp = p.getTemp
@@ -1579,7 +1694,12 @@ proc genNew(p: PProc, n: PNode) =
   var a: TCompRes
   gen(p, n.sons[1], a)
   var t = skipTypes(n.sons[1].typ, abstractVar).sons[0]
-  lineF(p, "$1 = $2;$n", [a.res, createVar(p, t, false)])
+  if mapType(t) == etyObject:
+    lineF(p, "$1 = $2;$n", [a.rdLoc, createVar(p, t, false)])
+  elif a.typ == etyBaseIndex:
+    lineF(p, "$1 = [$3]; $2 = 0;$n", [a.address, a.res, createVar(p, t, false)])
+  else:
+    lineF(p, "$1 = [[$2], 0];$n", [a.rdLoc, createVar(p, t, false)])
 
 proc genNewSeq(p: PProc, n: PNode) =
   var x, y: TCompRes
@@ -1603,20 +1723,20 @@ proc genConStrStr(p: PProc, n: PNode, r: var TCompRes) =
   if skipTypes(n.sons[1].typ, abstractVarRange).kind == tyChar:
     r.res.add("[$1].concat(" % [a.res])
   else:
-    r.res.add("($1).concat(" % [a.res])
+    r.res.add("($1 || []).concat(" % [a.res])
 
   for i in countup(2, sonsLen(n) - 2):
     gen(p, n.sons[i], a)
     if skipTypes(n.sons[i].typ, abstractVarRange).kind == tyChar:
       r.res.add("[$1]," % [a.res])
     else:
-      r.res.add("$1," % [a.res])
+      r.res.add("$1 || []," % [a.res])
 
   gen(p, n.sons[sonsLen(n) - 1], a)
   if skipTypes(n.sons[sonsLen(n) - 1].typ, abstractVarRange).kind == tyChar:
     r.res.add("[$1])" % [a.res])
   else:
-    r.res.add("$1)" % [a.res])
+    r.res.add("$1 || [])" % [a.res])
 
 proc genToArray(p: PProc; n: PNode; r: var TCompRes) =
   # we map mArray to PHP's array constructor, a mild hack:
@@ -1701,8 +1821,12 @@ proc genReset(p: PProc, n: PNode) =
   var x: TCompRes
   useMagic(p, "genericReset")
   gen(p, n.sons[1], x)
-  addf(p.body, "$1 = genericReset($1, $2);$n", [x.res,
-                genTypeInfo(p, n.sons[1].typ)])
+  if x.typ == etyBaseIndex:
+    lineF(p, "$1 = null, $2 = 0;$n", [x.address, x.res])
+  else:
+    let (a, tmp) = maybeMakeTemp(p, n[1], x)
+    lineF(p, "$1 = genericReset($3, $2);$n", [a,
+                  genTypeInfo(p, n.sons[1].typ), tmp])
 
 proc genMagic(p: PProc, n: PNode, r: var TCompRes) =
   var
@@ -1721,32 +1845,37 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) =
     else: unaryExpr(p, n, r, "subInt", "subInt($1, 1)")
   of mAppendStrCh:
     binaryExpr(p, n, r, "addChar",
-        "if ($1 != null) { addChar($1, $2); } else { $1 = [$2]; }")
+        "if ($1 != null) { addChar($3, $2); } else { $3 = [$2]; }")
   of mAppendStrStr:
     var lhs, rhs: TCompRes
     gen(p, n[1], lhs)
     gen(p, n[2], rhs)
 
     let rhsIsLit = n[2].kind in nkStrKinds
+    let (a, tmp) = maybeMakeTemp(p, n[1], lhs)
     if skipTypes(n.sons[1].typ, abstractVarRange).kind == tyCString:
-      r.res = "if ($1 != null) { $1 += $2; } else { $1 = $2$3; }" % [
-        lhs.rdLoc, rhs.rdLoc, if rhsIsLit: nil else: ~".slice()"]
+      r.res = "if ($1 != null) { $4 += $2; } else { $4 = $2$3; }" % [
+        a, rhs.rdLoc, if rhsIsLit: nil else: ~".slice()", tmp]
     else:
-      r.res = "if ($1 != null) { $1 = ($1).concat($2); } else { $1 = $2$3; }" % [
-          lhs.rdLoc, rhs.rdLoc, if rhsIsLit: nil else: ~".slice()"]
+      r.res = "if ($1 != null) { $4 = ($4).concat($2); } else { $4 = $2$3; }" % [
+          lhs.rdLoc, rhs.rdLoc, if rhsIsLit: nil else: ~".slice()", tmp]
     r.kind = resExpr
   of mAppendSeqElem:
     var x, y: TCompRes
     gen(p, n.sons[1], x)
     gen(p, n.sons[2], y)
-    if needsNoCopy(p, n[2]):
-      r.res = "if ($1 != null) { $1.push($2); } else { $1 = [$2]; }" % [x.rdLoc, y.rdLoc]
+    let (a, tmp) = maybeMakeTemp(p, n[1], x)
+    if mapType(n[2].typ) == etyBaseIndex:
+      let c = "[$1, $2]" % [y.address, y.res]
+      r.res = "if ($1 != null) { $3.push($2); } else { $3 = [$2]; }" % [a, c, tmp]
+    elif needsNoCopy(p, n[2]):
+      r.res = "if ($1 != null) { $3.push($2); } else { $3 = [$2]; }" % [a, y.rdLoc, tmp]
     else:
       useMagic(p, "nimCopy")
       let c = getTemp(p, defineInLocals=false)
       lineF(p, "var $1 = nimCopy(null, $2, $3);$n",
             [c, y.rdLoc, genTypeInfo(p, n[2].typ)])
-      r.res = "if ($1 != null) { $1.push($2); } else { $1 = [$2]; }" % [x.rdLoc, c]
+      r.res = "if ($1 != null) { $3.push($2); } else { $3 = [$2]; }" % [a, c, tmp]
     r.kind = resExpr
   of mConStrStr:
     genConStrStr(p, n, r)
@@ -1756,39 +1885,56 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) =
     binaryExpr(p, n, r, "cmpStrings", "(cmpStrings($1, $2) <= 0)")
   of mLtStr:
     binaryExpr(p, n, r, "cmpStrings", "(cmpStrings($1, $2) < 0)")
-  of mIsNil: unaryExpr(p, n, r, "", "($1 === null)")
+  of mIsNil:
+    if mapType(n[1].typ) != etyBaseIndex:
+      unaryExpr(p, n, r, "", "($1 === null)")
+    else:
+      var x: TCompRes
+      gen(p, n[1], x)
+      r.res = "($# === null && $# === 0)" % [x.address, x.res]
   of mEnumToStr: genRepr(p, n, r)
   of mNew, mNewFinalize: genNew(p, n)
-  of mChr, mArrToSeq: gen(p, n.sons[1], r)      # nothing to do
+  of mChr: gen(p, n.sons[1], r)
+  of mArrToSeq:
+    if needsNoCopy(p, n.sons[1]):
+      gen(p, n.sons[1], r)
+    else:
+      var x: TCompRes
+      gen(p, n.sons[1], x)
+      useMagic(p, "nimCopy")
+      r.res = "nimCopy(null, $1, $2)" % [x.rdLoc, genTypeInfo(p, n.typ)]
   of mDestroy: discard "ignore calls to the default destructor"
   of mOrd: genOrd(p, n, r)
   of mLengthStr, mLengthSeq, mLengthOpenArray, mLengthArray:
-    unaryExpr(p, n, r, "", "($1 != null ? $1.length : 0)")
+    unaryExpr(p, n, r, "", "($1 != null ? $2.length : 0)")
   of mXLenStr, mXLenSeq:
     unaryExpr(p, n, r, "", "$1.length")
   of mHigh:
-    unaryExpr(p, n, r, "", "($1 != null ? ($1.length-1) : -1)")
+    unaryExpr(p, n, r, "", "($1 != null ? ($2.length-1) : -1)")
   of mInc:
     if n[1].typ.skipTypes(abstractRange).kind in tyUInt .. tyUInt64:
       binaryUintExpr(p, n, r, "+", true)
     else:
       if optOverflowCheck notin p.options: binaryExpr(p, n, r, "", "$1 += $2")
-      else: binaryExpr(p, n, r, "addInt", "$1 = addInt($1, $2)")
+      else: binaryExpr(p, n, r, "addInt", "$1 = addInt($3, $2)")
   of ast.mDec:
     if n[1].typ.skipTypes(abstractRange).kind in tyUInt .. tyUInt64:
       binaryUintExpr(p, n, r, "-", true)
     else:
       if optOverflowCheck notin p.options: binaryExpr(p, n, r, "", "$1 -= $2")
-      else: binaryExpr(p, n, r, "subInt", "$1 = subInt($1, $2)")
+      else: binaryExpr(p, n, r, "subInt", "$1 = subInt($3, $2)")
   of mSetLengthStr:
-    binaryExpr(p, n, r, "", "$1.length = $2")
+    binaryExpr(p, n, r, "mnewString", "($1 === null ? $3 = mnewString($2) : $3.length = $2)")
   of mSetLengthSeq:
     var x, y: TCompRes
     gen(p, n.sons[1], x)
     gen(p, n.sons[2], y)
     let t = skipTypes(n.sons[1].typ, abstractVar).sons[0]
-    r.res = """if ($1.length < $2) { for (var i=$1.length;i<$2;++i) $1.push($3); }
-               else { $1.length = $2; }""" % [x.rdLoc, y.rdLoc, createVar(p, t, false)]
+    let (a, tmp) = maybeMakeTemp(p, n[1], x)
+    let (b, tmp2) = maybeMakeTemp(p, n[2], y)
+    r.res = """if ($1 === null) $4 = [];
+               if ($4.length < $2) { for (var i=$4.length;i<$5;++i) $4.push($3); }
+               else { $4.length = $5; }""" % [a, b, createVar(p, t, false), tmp, tmp2]
     r.kind = resExpr
   of mCard: unaryExpr(p, n, r, "SetCard", "SetCard($1)")
   of mLtSet: binaryExpr(p, n, r, "SetLt", "SetLt($1, $2)")
@@ -1856,7 +2002,10 @@ proc genArrayConstr(p: PProc, n: PNode, r: var TCompRes) =
   for i in countup(0, sonsLen(n) - 1):
     if i > 0: add(r.res, ", ")
     gen(p, n.sons[i], a)
-    add(r.res, a.res)
+    if a.typ == etyBaseIndex:
+      addf(r.res, "[$1, $2]", [a.address, a.res])
+    else:
+      add(r.res, a.res)
   add(r.res, "]")
 
 proc genTupleConstr(p: PProc, n: PNode, r: var TCompRes) =
@@ -1868,7 +2017,10 @@ proc genTupleConstr(p: PProc, n: PNode, r: var TCompRes) =
     var it = n.sons[i]
     if it.kind == nkExprColonExpr: it = it.sons[1]
     gen(p, it, a)
-    addf(r.res, "Field$#: $#", [i.rope, a.res])
+    if a.typ == etyBaseIndex:
+      addf(r.res, "Field$#: [$#, $#]", [i.rope, a.address, a.res])
+    else:
+      addf(r.res, "Field$#: $#", [i.rope, a.res])
   r.res.add("}")
 
 proc genObjConstr(p: PProc, n: PNode, r: var TCompRes) =
@@ -1888,12 +2040,17 @@ proc genObjConstr(p: PProc, n: PNode, r: var TCompRes) =
 
     let typ = val.typ.skipTypes(abstractInst)
     if (typ.kind in IntegralTypes+{tyCstring, tyRef, tyPtr} and
-          mapType(p, typ) != etyBaseIndex) or needsNoCopy(p, it.sons[1]):
+          mapType(p, typ) != etyBaseIndex) or
+          a.typ == etyBaseIndex or
+          needsNoCopy(p, it.sons[1]):
       discard
     else:
       useMagic(p, "nimCopy")
       a.res = "nimCopy(null, $1, $2)" % [a.rdLoc, genTypeInfo(p, typ)]
-    addf(initList, "$#: $#", [f.loc.r, a.res])
+    if a.typ == etyBaseIndex:
+      addf(initList, "$#: [$#, $#]", [f.loc.r, a.address, a.res])
+    else:
+      addf(initList, "$#: $#", [f.loc.r, a.res])
   let t = skipTypes(n.typ, abstractInst + skipPtrs)
   createObjInitList(p, t, fieldIDs, initList)
   r.res = ("{$1}") % [initList]
@@ -2011,11 +2168,14 @@ proc genProc(oldProc: PProc, prc: PSym): Rope =
   if prc.typ.sons[0] != nil and sfPure notin prc.flags:
     resultSym = prc.ast.sons[resultPos].sym
     let mname = mangleName(p.module, resultSym)
-    let resVar = createVar(p, resultSym.typ, isIndirect(resultSym))
-    resultAsgn = p.indentLine(("var $# = $#;$n") % [mname, resVar])
-    if resultSym.typ.kind in {tyVar, tyPtr, tyLent, tyRef} and
+    if not isindirect(resultSym) and
+      resultSym.typ.kind in {tyVar, tyPtr, tyLent, tyRef} and
         mapType(p, resultSym.typ) == etyBaseIndex:
+      resultAsgn = p.indentLine(("var $# = null;$n") % [mname])
       resultAsgn.add p.indentLine("var $#_Idx = 0;$n" % [mname])
+    else:
+      let resVar = createVar(p, resultSym.typ, isIndirect(resultSym))
+      resultAsgn = p.indentLine(("var $# = $#;$n") % [mname, resVar])
     gen(p, prc.ast.sons[resultPos], a)
     if mapType(p, resultSym.typ) == etyBaseIndex:
       returnStmt = "return [$#, $#];$n" % [a.address, a.res]
@@ -2107,6 +2267,13 @@ proc genCast(p: PProc, n: PNode, r: var TCompRes) =
           of 4: "0xfffffffe"
           else: ""
         r.res = "($1 - ($2 $3))" % [rope minuend, r.res, trimmer]
+  elif (src.kind == tyPtr and mapType(p, src) == etyObject) and dest.kind == tyPointer:
+    r.address = r.res
+    r.res = ~"null"
+    r.typ = etyBaseIndex
+  elif (dest.kind == tyPtr and mapType(p, dest) == etyObject) and src.kind == tyPointer:
+    r.res = r.address
+    r.typ = etyObject
 
 proc gen(p: PProc, n: PNode, r: var TCompRes) =
   r.typ = etyNone
diff --git a/compiler/lambdalifting.nim b/compiler/lambdalifting.nim
index c318421fa..ddde1be31 100644
--- a/compiler/lambdalifting.nim
+++ b/compiler/lambdalifting.nim
@@ -258,7 +258,7 @@ proc liftIterSym*(g: ModuleGraph; n: PNode; owner: PSym): PNode =
   # add 'new' statement:
   result.add newCall(getSysSym(g, n.info, "internalNew"), env)
   result.add makeClosure(g, iter, env, n.info)
-  
+
 proc freshVarForClosureIter*(g: ModuleGraph; s, owner: PSym): PNode =
   let envParam = getHiddenParam(g, owner)
   let obj = envParam.typ.lastSon
@@ -407,11 +407,8 @@ proc detectCapturedVars(n: PNode; owner: PSym; c: var DetectionPass) =
               obj.n[0].sym.id = -s.id
             else:
               addField(obj, s, c.graph.cache)
-      # but always return because the rest of the proc is only relevant when
-      # ow != owner:
-      return
     # direct or indirect dependency:
-    if (innerProc and s.typ.callConv == ccClosure) or interestingVar(s):
+    elif (innerProc and s.typ.callConv == ccClosure) or interestingVar(s):
       discard """
         proc outer() =
           var x: int
@@ -454,11 +451,10 @@ proc detectCapturedVars(n: PNode; owner: PSym; c: var DetectionPass) =
           createUpField(c, w, up, n.info)
           w = up
   of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit,
-     nkTemplateDef, nkTypeSection:
-    discard
-  of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef:
+     nkTemplateDef, nkTypeSection, nkProcDef, nkMethodDef,
+     nkConverterDef, nkMacroDef, nkFuncDef:
     discard
-  of nkLambdaKinds, nkIteratorDef, nkFuncDef:
+  of nkLambdaKinds, nkIteratorDef:
     if n.typ != nil:
       detectCapturedVars(n[namePos], owner, c)
   of nkReturnStmt:
@@ -672,9 +668,8 @@ proc liftCapturedVars(n: PNode; owner: PSym; d: DetectionPass;
       else:
         result = accessViaEnvVar(n, owner, d, c)
   of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit, nkComesFrom,
-     nkTemplateDef, nkTypeSection:
-    discard
-  of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef:
+     nkTemplateDef, nkTypeSection, nkProcDef, nkMethodDef, nkConverterDef,
+     nkMacroDef, nkFuncDef:
     discard
   of nkClosure:
     if n[1].kind == nkNilLit:
@@ -685,7 +680,7 @@ proc liftCapturedVars(n: PNode; owner: PSym; d: DetectionPass;
         # now we know better, so patch it:
         n.sons[0] = x.sons[0]
         n.sons[1] = x.sons[1]
-  of nkLambdaKinds, nkIteratorDef, nkFuncDef:
+  of nkLambdaKinds, nkIteratorDef:
     if n.typ != nil and n[namePos].kind == nkSym:
       let oldInContainer = c.inContainer
       c.inContainer = 0
@@ -720,19 +715,37 @@ proc liftCapturedVars(n: PNode; owner: PSym; d: DetectionPass;
 # ------------------ old stuff -------------------------------------------
 
 proc semCaptureSym*(s, owner: PSym) =
+  discard """
+    proc outer() =
+      var x: int
+      proc inner() =
+        proc innerInner() =
+          echo x
+        innerInner()
+      inner()
+    # inner() takes a closure too!
+  """
+  proc propagateClosure(start, last: PSym) =
+    var o = start
+    while o != nil and o.kind != skModule:
+      if o == last: break
+      o.typ.callConv = ccClosure
+      o = o.skipGenericOwner
+
   if interestingVar(s) and s.kind != skResult:
     if owner.typ != nil and not isGenericRoutine(owner):
       # XXX: is this really safe?
       # if we capture a var from another generic routine,
       # it won't be consider captured.
       var o = owner.skipGenericOwner
-      while o.kind != skModule and o != nil:
+      while o != nil and o.kind != skModule:
         if s.owner == o:
           if owner.typ.callConv in {ccClosure, ccDefault} or owner.kind == skIterator:
             owner.typ.callConv = ccClosure
+            propagateClosure(owner.skipGenericOwner, s.owner)
           else:
             discard "do not produce an error here, but later"
-          #echo "computing .closure for ", owner.name.s, " ", owner.info, " because of ", s.name.s
+          #echo "computing .closure for ", owner.name.s, " because of ", s.name.s
         o = o.skipGenericOwner
     # since the analysis is not entirely correct, we don't set 'tfCapturesEnv'
     # here
diff --git a/compiler/lookups.nim b/compiler/lookups.nim
index 2fb4e5241..db03ac2e0 100644
--- a/compiler/lookups.nim
+++ b/compiler/lookups.nim
@@ -169,7 +169,7 @@ proc ensureNoMissingOrUnusedSymbols(c: PContext; scope: PScope) =
             getSymRepr(c.config, s))
       inc missingImpls
     elif {sfUsed, sfExported} * s.flags == {}:
-      if s.kind notin {skForVar, skParam, skMethod, skUnknown, skGenericParam}:
+      if s.kind notin {skForVar, skParam, skMethod, skUnknown, skGenericParam, skEnumField}:
         # XXX: implicit type params are currently skTypes
         # maybe they can be made skGenericParam as well.
         if s.typ != nil and tfImplicitTypeParam notin s.typ.flags and
diff --git a/compiler/modules.nim b/compiler/modules.nim
index e2f322561..442305a06 100644
--- a/compiler/modules.nim
+++ b/compiler/modules.nim
@@ -17,18 +17,7 @@ import
 proc resetSystemArtifacts*(g: ModuleGraph) =
   magicsys.resetSysTypes(g)
 
-proc newModule(graph: ModuleGraph; fileIdx: FileIndex): PSym =
-  # We cannot call ``newSym`` here, because we have to circumvent the ID
-  # mechanism, which we do in order to assign each module a persistent ID.
-  new(result)
-  result.id = -1             # for better error checking
-  result.kind = skModule
-  let filename = toFullPath(graph.config, fileIdx)
-  result.name = getIdent(graph.cache, splitFile(filename).name)
-  if not isNimIdentifier(result.name.s):
-    rawMessage(graph.config, errGenerated, "invalid module name: " & result.name.s)
-
-  result.info = newLineInfo(fileIdx, 1, 1)
+proc partialInitModule(result: PSym; graph: ModuleGraph; fileIdx: FileIndex; filename: string) =
   let
     pck = getPackageName(graph.config, filename)
     pck2 = if pck.len > 0: pck else: "unknown"
@@ -38,13 +27,11 @@ proc newModule(graph: ModuleGraph; fileIdx: FileIndex): PSym =
     packSym = newSym(skPackage, getIdent(graph.cache, pck2), nil, result.info)
     initStrTable(packSym.tab)
     graph.packageSyms.strTableAdd(packSym)
-
   result.owner = packSym
   result.position = int fileIdx
 
   if int(fileIdx) >= graph.modules.len:
     setLen(graph.modules, int(fileIdx) + 1)
-  #growCache graph.modules, int fileIdx
   graph.modules[result.position] = result
 
   incl(result.flags, sfUsed)
@@ -58,16 +45,36 @@ proc newModule(graph: ModuleGraph; fileIdx: FileIndex): PSym =
   # strTableIncl() for error corrections:
   discard strTableIncl(packSym.tab, result)
 
+proc newModule(graph: ModuleGraph; fileIdx: FileIndex): PSym =
+  # We cannot call ``newSym`` here, because we have to circumvent the ID
+  # mechanism, which we do in order to assign each module a persistent ID.
+  new(result)
+  result.id = -1             # for better error checking
+  result.kind = skModule
+  let filename = toFullPath(graph.config, fileIdx)
+  result.name = getIdent(graph.cache, splitFile(filename).name)
+  if not isNimIdentifier(result.name.s):
+    rawMessage(graph.config, errGenerated, "invalid module name: " & result.name.s)
+  result.info = newLineInfo(fileIdx, 1, 1)
+  partialInitModule(result, graph, fileIdx, filename)
+
 proc compileModule*(graph: ModuleGraph; fileIdx: FileIndex; flags: TSymFlags): PSym =
   result = graph.getModule(fileIdx)
   if result == nil:
-    result = newModule(graph, fileIdx)
-    result.flags = result.flags + flags
-    if sfMainModule in result.flags:
-      graph.config.mainPackageId = result.owner.id
-
-    result.id = getModuleId(graph, fileIdx, AbsoluteFile toFullPath(graph.config, fileIdx))
-    registerModule(graph, result)
+    let filename = toFullPath(graph.config, fileIdx)
+    let (r, id) = loadModuleSym(graph, fileIdx, AbsoluteFile filename)
+    result = r
+    if result == nil:
+      result = newModule(graph, fileIdx)
+      result.flags = result.flags + flags
+      if sfMainModule in result.flags:
+        graph.config.mainPackageId = result.owner.id
+      result.id = id
+      registerModule(graph, result)
+    else:
+      partialInitModule(result, graph, fileIdx, filename)
+      result.id = id
+      assert result.id < 0
     discard processModule(graph, result,
       if sfMainModule in flags and graph.config.projectIsStdin: stdin.llStreamOpen else: nil)
   elif graph.isDirty(result):
diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim
index 2ce6b2231..247f6ad54 100644
--- a/compiler/pragmas.nim
+++ b/compiler/pragmas.nim
@@ -1119,6 +1119,12 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: var int,
     else:
       invalidPragma(c, it)
 
+proc mergePragmas(n, pragmas: PNode) =
+  if n[pragmasPos].kind == nkEmpty:
+    n[pragmasPos] = pragmas
+  else:
+    for p in pragmas: n.sons[pragmasPos].add p
+
 proc implicitPragmas*(c: PContext, sym: PSym, n: PNode,
                       validPragmas: TSpecialWords) =
   if sym != nil and sym.kind != skModule:
@@ -1127,11 +1133,12 @@ proc implicitPragmas*(c: PContext, sym: PSym, n: PNode,
       if not o.isNil:
         pushInfoContext(c.config, n.info)
         var i = 0
-        while i < o.len():
+        while i < o.len:
           if singlePragma(c, sym, o, i, validPragmas):
             internalError(c.config, n.info, "implicitPragmas")
           inc i
         popInfoContext(c.config)
+        if sym.kind in routineKinds and sym.ast != nil: mergePragmas(sym.ast, o)
 
     if lfExportLib in sym.loc.flags and sfExportc notin sym.flags:
       localError(c.config, n.info, ".dynlib requires .exportc")
diff --git a/compiler/rod.nim b/compiler/rod.nim
index 92489ffdd..bbd2f0c6c 100644
--- a/compiler/rod.nim
+++ b/compiler/rod.nim
@@ -16,7 +16,7 @@ when not nimIncremental:
   template storeNode*(g: ModuleGraph; module: PSym; n: PNode) = discard
   template loadNode*(g: ModuleGraph; module: PSym): PNode = newNode(nkStmtList)
 
-  template getModuleId*(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): int = getID()
+  proc loadModuleSym*(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): (PSym, int) {.inline.} = (nil, getID())
 
   template addModuleDep*(g: ModuleGraph; module, fileIdx: FileIndex; isIncludeFile: bool) = discard
 
diff --git a/compiler/rodimpl.nim b/compiler/rodimpl.nim
index 730328642..147e8c3d6 100644
--- a/compiler/rodimpl.nim
+++ b/compiler/rodimpl.nim
@@ -52,7 +52,7 @@ proc needsRecompile(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile;
       return true
   return false
 
-proc getModuleId*(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): int =
+proc getModuleId(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): int =
   ## Analyse the known dependency graph.
   if g.config.symbolFiles == disabledSf: return getID()
   when false:
@@ -82,8 +82,12 @@ proc getModuleId*(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): i
     db.exec(sql"delete from toplevelstmts where module = ?", module[0])
     db.exec(sql"delete from statics where module = ?", module[0])
 
+proc loadModuleSym*(g: ModuleGraph; fileIdx: FileIndex; fullpath: AbsoluteFile): (PSym, int) =
+  let id = getModuleId(g, fileIdx, fullpath)
+  result = (g.incr.r.syms.getOrDefault(abs id), id)
+
 proc pushType(w: var Writer, t: PType) =
-  if not containsOrIncl(w.tmarks, t.id):
+  if not containsOrIncl(w.tmarks, t.uniqueId):
     w.tstack.add(t)
 
 proc pushSym(w: var Writer, s: PSym) =
@@ -109,7 +113,8 @@ proc encodeNode(g: ModuleGraph; fInfo: TLineInfo, n: PNode,
     result.add(',')
     encodeVInt(int n.info.line, result)
     result.add(',')
-    encodeVInt(toDbFileId(g.incr, g.config, n.info.fileIndex), result)
+    #encodeVInt(toDbFileId(g.incr, g.config, n.info.fileIndex), result)
+    encodeVInt(n.info.fileIndex.int, result)
   elif fInfo.line != n.info.line:
     result.add('?')
     encodeVInt(n.info.col, result)
@@ -126,7 +131,7 @@ proc encodeNode(g: ModuleGraph; fInfo: TLineInfo, n: PNode,
     encodeVInt(cast[int32](f), result)
   if n.typ != nil:
     result.add('^')
-    encodeVInt(n.typ.id, result)
+    encodeVInt(n.typ.uniqueId, result)
     pushType(w, n.typ)
   case n.kind
   of nkCharLit..nkUInt64Lit:
@@ -187,7 +192,10 @@ proc encodeType(g: ModuleGraph, t: PType, result: var string) =
   add(result, '[')
   encodeVInt(ord(t.kind), result)
   add(result, '+')
-  encodeVInt(t.id, result)
+  encodeVInt(t.uniqueId, result)
+  if t.id != t.uniqueId:
+    add(result, '+')
+    encodeVInt(t.id, result)
   if t.n != nil:
     encodeNode(g, unknownLineInfo(), t.n, result)
   if t.flags != {}:
@@ -236,12 +244,16 @@ proc encodeType(g: ModuleGraph, t: PType, result: var string) =
     encodeVInt(s.id, result)
     pushSym(w, s)
   encodeLoc(g, t.loc, result)
+  if t.typeInst != nil:
+    add(result, '\21')
+    encodeVInt(t.typeInst.uniqueId, result)
+    pushType(w, t.typeInst)
   for i in countup(0, sonsLen(t) - 1):
     if t.sons[i] == nil:
       add(result, "^()")
     else:
       add(result, '^')
-      encodeVInt(t.sons[i].id, result)
+      encodeVInt(t.sons[i].uniqueId, result)
       pushType(w, t.sons[i])
 
 proc encodeLib(g: ModuleGraph, lib: PLib, info: TLineInfo, result: var string) =
@@ -260,7 +272,7 @@ proc encodeInstantiations(g: ModuleGraph; s: seq[PInstantiation];
     pushSym(w, t.sym)
     for tt in t.concreteTypes:
       result.add('\17')
-      encodeVInt(tt.id, result)
+      encodeVInt(tt.uniqueId, result)
       pushType(w, tt)
     result.add('\20')
     encodeVInt(t.compilesId, result)
@@ -278,14 +290,15 @@ proc encodeSym(g: ModuleGraph, s: PSym, result: var string) =
   encodeStr(s.name.s, result)
   if s.typ != nil:
     result.add('^')
-    encodeVInt(s.typ.id, result)
+    encodeVInt(s.typ.uniqueId, result)
     pushType(w, s.typ)
   result.add('?')
   if s.info.col != -1'i16: encodeVInt(s.info.col, result)
   result.add(',')
   encodeVInt(int s.info.line, result)
   result.add(',')
-  encodeVInt(toDbFileId(g.incr, g.config, s.info.fileIndex), result)
+  #encodeVInt(toDbFileId(g.incr, g.config, s.info.fileIndex), result)
+  encodeVInt(s.info.fileIndex.int, result)
   if s.owner != nil:
     result.add('*')
     encodeVInt(s.owner.id, result)
@@ -313,7 +326,7 @@ proc encodeSym(g: ModuleGraph, s: PSym, result: var string) =
   of skType, skGenericParam:
     for t in s.typeInstCache:
       result.add('\14')
-      encodeVInt(t.id, result)
+      encodeVInt(t.uniqueId, result)
       pushType(w, t)
   of routineKinds:
     encodeInstantiations(g, s.procInstCache, result)
@@ -364,12 +377,12 @@ proc storeType(g: ModuleGraph; t: PType) =
   let m = if t.owner != nil: getModule(t.owner) else: nil
   let mid = if m == nil: 0 else: abs(m.id)
   db.exec(sql"insert into types(nimid, module, data) values (?, ?, ?)",
-    t.id, mid, buf)
+    t.uniqueId, mid, buf)
 
 proc transitiveClosure(g: ModuleGraph) =
   var i = 0
   while true:
-    if i > 10_000:
+    if i > 100_000:
       doAssert false, "loop never ends!"
     if w.sstack.len > 0:
       let s = w.sstack.pop()
@@ -380,7 +393,7 @@ proc transitiveClosure(g: ModuleGraph) =
       let t = w.tstack.pop()
       storeType(g, t)
       when false:
-        echo "popped type ", typeToString(t), " ", t.id
+        echo "popped type ", typeToString(t), " ", t.uniqueId
     else:
       break
     inc i
@@ -446,9 +459,11 @@ proc decodeLineInfo(g; b; info: var TLineInfo) =
       else: info.line = uint16(decodeVInt(b.s, b.pos))
       if b.s[b.pos] == ',':
         inc(b.pos)
-        info.fileIndex = fromDbFileId(g.incr, g.config, decodeVInt(b.s, b.pos))
+        #info.fileIndex = fromDbFileId(g.incr, g.config, decodeVInt(b.s, b.pos))
+        info.fileIndex = FileIndex decodeVInt(b.s, b.pos)
 
 proc skipNode(b) =
+  # ')' itself cannot be part of a string literal so that this is correct.
   assert b.s[b.pos] == '('
   var par = 0
   var pos = b.pos+1
@@ -583,13 +598,18 @@ proc loadType(g; id: int; info: TLineInfo): PType =
   result.kind = TTypeKind(decodeVInt(b.s, b.pos))
   if b.s[b.pos] == '+':
     inc(b.pos)
-    result.id = decodeVInt(b.s, b.pos)
-    setId(result.id)
+    result.uniqueId = decodeVInt(b.s, b.pos)
+    setId(result.uniqueId)
     #if debugIds: registerID(result)
   else:
     internalError(g.config, info, "decodeType: no id")
+  if b.s[b.pos] == '+':
+    inc(b.pos)
+    result.id = decodeVInt(b.s, b.pos)
+  else:
+    result.id = result.uniqueId
   # here this also avoids endless recursion for recursive type
-  g.incr.r.types.add(result.id, result)
+  g.incr.r.types.add(result.uniqueId, result)
   if b.s[b.pos] == '(': result.n = decodeNode(g, b, unknownLineInfo())
   if b.s[b.pos] == '$':
     inc(b.pos)
@@ -640,6 +660,10 @@ proc loadType(g; id: int; info: TLineInfo): PType =
     let y = loadSym(g, decodeVInt(b.s, b.pos), info)
     result.methods.add((x, y))
   decodeLoc(g, b, result.loc, info)
+  if b.s[b.pos] == '\21':
+    inc(b.pos)
+    let d = decodeVInt(b.s, b.pos)
+    result.typeInst = loadType(g, d, info)
   while b.s[b.pos] == '^':
     inc(b.pos)
     if b.s[b.pos] == '(':
diff --git a/compiler/sem.nim b/compiler/sem.nim
index 924e53b66..8332af346 100644
--- a/compiler/sem.nim
+++ b/compiler/sem.nim
@@ -207,11 +207,12 @@ proc newSymG*(kind: TSymKind, n: PNode, c: PContext): PSym =
     if result.kind notin {kind, skTemp}:
       localError(c.config, n.info, "cannot use symbol of kind '" &
                  $result.kind & "' as a '" & $kind & "'")
-    if sfGenSym in result.flags and result.kind notin {skTemplate, skMacro, skParam}:
-      # declarative context, so produce a fresh gensym:
-      result = copySym(result)
-      result.ast = n.sym.ast
-      put(c.p, n.sym, result)
+    when false:
+      if sfGenSym in result.flags and result.kind notin {skTemplate, skMacro, skParam}:
+        # declarative context, so produce a fresh gensym:
+        result = copySym(result)
+        result.ast = n.sym.ast
+        put(c.p, n.sym, result)
     # when there is a nested proc inside a template, semtmpl
     # will assign a wrong owner during the first pass over the
     # template; we must fix it here: see #909
diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim
index 669862c56..ddec457a1 100644
--- a/compiler/semexprs.nim
+++ b/compiler/semexprs.nim
@@ -1083,6 +1083,8 @@ proc semSym(c: PContext, n: PNode, sym: PSym, flags: TExprFlags): PNode =
       # XXX see the hack in sigmatch.nim ...
       return s.typ.n
     elif sfGenSym in s.flags:
+      # the owner should have been set by now by addParamOrResult
+      internalAssert c.config, s.owner != nil
       if c.p.wasForwarded:
         # gensym'ed parameters that nevertheless have been forward declared
         # need a special fixup:
@@ -1490,6 +1492,13 @@ proc asgnToResultVar(c: PContext, n, le, ri: PNode) {.inline.} =
 template resultTypeIsInferrable(typ: PType): untyped =
   typ.isMetaType and typ.kind != tyTypeDesc
 
+
+proc goodLineInfo(arg: PNode): TLineinfo =
+  if arg.kind == nkStmtListExpr and arg.len > 0:
+    goodLineInfo(arg[^1])
+  else:
+    arg.info
+
 proc semAsgn(c: PContext, n: PNode; mode=asgnNormal): PNode =
   checkSonsLen(n, 2, c.config)
   var a = n.sons[0]
@@ -1571,7 +1580,7 @@ proc semAsgn(c: PContext, n: PNode; mode=asgnNormal): PNode =
         else:
           typeMismatch(c.config, n.info, lhs.typ, rhsTyp)
 
-    n.sons[1] = fitNode(c, le, rhs, n.info)
+    n.sons[1] = fitNode(c, le, rhs, goodLineInfo(n[1]))
     liftTypeBoundOps(c, lhs.typ, lhs.info)
     #liftTypeBoundOps(c, n.sons[0].typ, n.sons[0].info)
 
@@ -1968,6 +1977,22 @@ proc setMs(n: PNode, s: PSym): PNode =
   n.sons[0] = newSymNode(s)
   n.sons[0].info = n.info
 
+proc semSizeof(c: PContext, n: PNode): PNode =
+  if sonsLen(n) != 2:
+    localError(c.config, n.info, errXExpectsTypeOrValue % "sizeof")
+  else:
+    n.sons[1] = semExprWithType(c, n.sons[1], {efDetermineType})
+    #restoreOldStyleType(n.sons[1])
+  n.typ = getSysType(c.graph, n.info, tyInt)
+
+  let size = getSize(c.config, n[1].typ)
+  if size >= 0:
+    result = newIntNode(nkIntLit, size)
+    result.info = n.info
+    result.typ = n.typ
+  else:
+    result = n
+
 proc semMagic(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
   # this is a hotspot in the compiler!
   result = n
@@ -2039,6 +2064,7 @@ proc semMagic(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
   of mRunnableExamples:
     if c.config.cmd == cmdDoc and n.len >= 2 and n.lastSon.kind == nkStmtList:
       when false:
+        # some of this dead code was moved to `prepareExamples`
         if sfMainModule in c.module.flags:
           let inp = toFullPath(c.config, c.module.info)
           if c.runnableExamples == nil:
@@ -2052,6 +2078,7 @@ proc semMagic(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
       result = setMs(n, s)
     else:
       result = c.graph.emptyNode
+  of mSizeOf: result = semSizeof(c, setMs(n, s))
   of mOmpParFor:
     checkMinSonsLen(n, 3, c.config)
     result = semDirectOp(c, n, flags)
@@ -2264,6 +2291,8 @@ proc semBlock(c: PContext, n: PNode; flags: TExprFlags): PNode =
     var labl = newSymG(skLabel, n.sons[0], c)
     if sfGenSym notin labl.flags:
       addDecl(c, labl)
+    elif labl.owner == nil:
+      labl.owner = c.p.owner
     n.sons[0] = newSymNode(labl, n.sons[0].info)
     suggestSym(c.config, n.sons[0].info, labl, c.graph.usageSym)
     styleCheckDef(c.config, labl)
diff --git a/compiler/seminst.nim b/compiler/seminst.nim
index de2e10a9b..09991048e 100644
--- a/compiler/seminst.nim
+++ b/compiler/seminst.nim
@@ -116,9 +116,9 @@ proc freshGenSyms(n: PNode, owner, orig: PSym, symMap: var TIdTable) =
     var x = PSym(idTableGet(symMap, s))
     if x != nil:
       n.sym = x
-    elif s.owner.kind == skPackage:
+    elif s.owner == nil or s.owner.kind == skPackage:
       #echo "copied this ", s.name.s
-      x = copySym(s, false)
+      x = copySym(s)
       x.owner = owner
       idTablePut(symMap, s, x)
       n.sym = x
@@ -337,7 +337,7 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
   c.matchedConcept = nil
   let oldScope = c.currentScope
   while not isTopLevel(c): c.currentScope = c.currentScope.parent
-  result = copySym(fn, false)
+  result = copySym(fn)
   incl(result.flags, sfFromGeneric)
   result.owner = fn
   result.ast = n
diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim
index 2af34646c..04fe91cfb 100644
--- a/compiler/semstmts.nim
+++ b/compiler/semstmts.nim
@@ -497,8 +497,10 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
       var v = semIdentDef(c, a.sons[j], symkind)
       styleCheckDef(c.config, v)
       onDef(a[j].info, v)
-      if sfGenSym notin v.flags and not isDiscardUnderscore(v):
-        addInterfaceDecl(c, v)
+      if sfGenSym notin v.flags:
+        if not isDiscardUnderscore(v): addInterfaceDecl(c, v)
+      else:
+        if v.owner == nil: v.owner = c.p.owner
       when oKeepVariableNames:
         if c.inUnrolledContext > 0: v.flags.incl(sfShadowed)
         else:
@@ -573,6 +575,7 @@ proc semConst(c: PContext, n: PNode): PNode =
     setVarType(c, v, typ)
     v.ast = def               # no need to copy
     if sfGenSym notin v.flags: addInterfaceDecl(c, v)
+    elif v.owner == nil: v.owner = getCurrOwner(c)
     var b = newNodeI(nkConstDef, a.info)
     if importantComments(c.config): b.comment = a.comment
     addSon(b, newSymNode(v))
@@ -616,6 +619,7 @@ proc semForVars(c: PContext, n: PNode; flags: TExprFlags): PNode =
       v.typ = iterBase
       n.sons[0] = newSymNode(v)
       if sfGenSym notin v.flags: addForVarDecl(c, v)
+      elif v.owner == nil: v.owner = getCurrOwner(c)
     else:
       localError(c.config, n.info, errWrongNumberOfVariables)
   elif length-2 != sonsLen(iter):
@@ -626,8 +630,9 @@ proc semForVars(c: PContext, n: PNode; flags: TExprFlags): PNode =
       if getCurrOwner(c).kind == skModule: incl(v.flags, sfGlobal)
       v.typ = iter.sons[i]
       n.sons[i] = newSymNode(v)
-      if sfGenSym notin v.flags and not isDiscardUnderscore(v):
-        addForVarDecl(c, v)
+      if sfGenSym notin v.flags:
+        if not isDiscardUnderscore(v): addForVarDecl(c, v)
+      elif v.owner == nil: v.owner = getCurrOwner(c)
   inc(c.p.nestedLoopCounter)
   openScope(c)
   n.sons[length-1] = semExprBranch(c, n.sons[length-1], flags)
@@ -922,6 +927,7 @@ proc typeSectionLeftSidePass(c: PContext, n: PNode) =
             s = typsym
       # add it here, so that recursive types are possible:
       if sfGenSym notin s.flags: addInterfaceDecl(c, s)
+      elif s.owner == nil: s.owner = getCurrOwner(c)
 
     if name.kind == nkPragmaExpr:
       a.sons[0].sons[0] = newSymNode(s)
@@ -1268,7 +1274,7 @@ proc semProcAnnotation(c: PContext, prc: PNode;
     x.add(prc)
 
     # recursion assures that this works for multiple macro annotations too:
-    var r = semOverloadedCall(c, x, x, {skMacro}, {efNoUndeclared})
+    var r = semOverloadedCall(c, x, x, {skMacro, skTemplate}, {efNoUndeclared})
     if r == nil:
       # Restore the old list of pragmas since we couldn't process this
       prc.sons[pragmasPos] = n
@@ -1620,7 +1626,8 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
     else:
       s.typ.callConv = lastOptionEntry(c).defaultCC
     # add it here, so that recursive procs are possible:
-    if sfGenSym in s.flags: discard
+    if sfGenSym in s.flags:
+      if s.owner == nil: s.owner = getCurrOwner(c)
     elif kind in OverloadableSyms:
       if not typeIsDetermined:
         addInterfaceOverloadableSymAt(c, oldScope, s)
@@ -1836,17 +1843,33 @@ proc semMacroDef(c: PContext, n: PNode): PNode =
   if n.sons[bodyPos].kind == nkEmpty:
     localError(c.config, n.info, errImplOfXexpected % s.name.s)
 
+proc incMod(c: PContext, n: PNode, it: PNode, includeStmtResult: PNode) =
+  var f = checkModuleName(c.config, it)
+  if f != InvalidFileIDX:
+    if containsOrIncl(c.includedFiles, f.int):
+      localError(c.config, n.info, errRecursiveDependencyX % toFilename(c.config, f))
+    else:
+      addSon(includeStmtResult, semStmt(c, c.graph.includeFileCallback(c.graph, c.module, f), {}))
+      excl(c.includedFiles, f.int)
+
 proc evalInclude(c: PContext, n: PNode): PNode =
   result = newNodeI(nkStmtList, n.info)
   addSon(result, n)
   for i in countup(0, sonsLen(n) - 1):
-    var f = checkModuleName(c.config, n.sons[i])
-    if f != InvalidFileIDX:
-      if containsOrIncl(c.includedFiles, f.int):
-        localError(c.config, n.info, errRecursiveDependencyX % toFilename(c.config, f))
-      else:
-        addSon(result, semStmt(c, c.graph.includeFileCallback(c.graph, c.module, f), {}))
-        excl(c.includedFiles, f.int)
+    var imp: PNode
+    let it = n.sons[i]
+    if it.kind == nkInfix and it.len == 3 and it[2].kind == nkBracket:
+      let sep = it[0]
+      let dir = it[1]
+      imp = newNodeI(nkInfix, it.info)
+      imp.add sep
+      imp.add dir
+      imp.add sep # dummy entry, replaced in the loop
+      for x in it[2]:
+        imp.sons[2] = x
+        incMod(c, n, imp, result)
+    else:
+      incMod(c, n, it, result)
 
 proc setLine(n: PNode, info: TLineInfo) =
   for i in 0 ..< safeLen(n): setLine(n.sons[i], info)
@@ -1963,7 +1986,8 @@ proc semStmtList(c: PContext, n: PNode, flags: TExprFlags): PNode =
         case n.sons[j].kind
         of nkPragma, nkCommentStmt, nkNilLit, nkEmpty, nkBlockExpr,
             nkBlockStmt, nkState: discard
-        else: localError(c.config, n.sons[j].info, "unreachable statement after 'return'")
+        else: localError(c.config, n.sons[j].info,
+          "unreachable statement after 'return' statement or '{.noReturn.}' proc")
     else: discard
 
   if result.len == 1 and
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 78d8c17f7..1e75b563e 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -392,7 +392,7 @@ proc semTypeIdent(c: PContext, n: PNode): PSym =
           localError(c.config, n.info, errTypeExpected)
           return errorSym(c, n)
         result = result.typ.sym.copySym
-        result.typ = copyType(result.typ, result.typ.owner, true)
+        result.typ = exactReplica(result.typ)
         result.typ.flags.incl tfUnresolved
 
       if result.kind == skGenericParam:
@@ -821,7 +821,11 @@ proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind) =
       a.typ = nn.typ
       addDecl(c, a)
   else:
-    if sfGenSym notin param.flags: addDecl(c, param)
+    if sfGenSym in param.flags:
+      # bug #XXX, fix the gensym'ed parameters owner:
+      if param.owner == nil:
+        param.owner = getCurrOwner(c)
+    else: addDecl(c, param)
 
 template shouldHaveMeta(t) =
   internalAssert c.config, tfHasMeta in t.flags
diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim
index b05fb37ae..ffa913f1d 100644
--- a/compiler/semtypinst.nim
+++ b/compiler/semtypinst.nim
@@ -233,7 +233,7 @@ proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym =
 
   #result = PSym(idTableGet(cl.symMap, s))
   #if result == nil:
-  result = copySym(s, false)
+  result = copySym(s)
   incl(result.flags, sfFromGeneric)
   #idTablePut(cl.symMap, s, result)
   result.owner = s.owner
diff --git a/compiler/sizealignoffsetimpl.nim b/compiler/sizealignoffsetimpl.nim
index 2f50a99f6..a34383d9f 100644
--- a/compiler/sizealignoffsetimpl.nim
+++ b/compiler/sizealignoffsetimpl.nim
@@ -52,6 +52,7 @@ proc computeSubObjectAlign(conf: ConfigRef; n: PNode): BiggestInt =
 proc computeObjectOffsetsFoldFunction(conf: ConfigRef; n: PNode, initialOffset: BiggestInt): tuple[offset, align: BiggestInt] =
   ## ``offset`` is the offset within the object, after the node has been written, no padding bytes added
   ## ``align`` maximum alignment from all sub nodes
+  assert n != nil
   if n.typ != nil and n.typ.size == szIllegalRecursion:
     result.offset = szIllegalRecursion
     result.align  = szIllegalRecursion
@@ -177,7 +178,7 @@ proc computePackedObjectOffsetsFoldFunction(conf: ConfigRef; n: PNode, initialOf
 
 proc computeSizeAlign(conf: ConfigRef; typ: PType) =
   ## computes and sets ``size`` and ``align`` members of ``typ``
-
+  assert typ != nil
   let hasSize = typ.size != szUncomputedSize
   let hasAlign = typ.align != szUncomputedSize
 
diff --git a/compiler/trees.nim b/compiler/trees.nim
index fb523de9d..ca2360e12 100644
--- a/compiler/trees.nim
+++ b/compiler/trees.nim
@@ -92,8 +92,7 @@ proc isCaseObj*(n: PNode): bool =
 
 proc isDeepConstExpr*(n: PNode): bool =
   case n.kind
-  of nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit,
-      nkFloatLit..nkFloat64Lit, nkNilLit:
+  of nkCharLit..nkNilLit:
     result = true
   of nkExprEqExpr, nkExprColonExpr, nkHiddenStdConv, nkHiddenSubConv:
     result = isDeepConstExpr(n.sons[1])
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 7e7ec8903..c8784c3e7 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -413,26 +413,12 @@ proc recSetFlagIsRef(arg: PNode) =
     arg.sons[i].recSetFlagIsRef
 
 proc setLenSeq(c: PCtx; node: PNode; newLen: int; info: TLineInfo) =
-  # FIXME: this doesn't attempt to solve incomplete
-  # support of tyPtr, tyRef in VM.
   let typ = node.typ.skipTypes(abstractInst+{tyRange}-{tyTypeDesc})
-  let typeEntry = typ.sons[0].skipTypes(abstractInst+{tyRange}-{tyTypeDesc})
-  let typeKind = case typeEntry.kind
-                 of tyUInt..tyUInt64: nkUIntLit
-                 of tyRange, tyEnum, tyBool, tyChar, tyInt..tyInt64: nkIntLit
-                 of tyFloat..tyFloat128: nkFloatLit
-                 of tyString: nkStrLit
-                 of tyObject: nkObjConstr
-                 of tySequence: nkNilLit
-                 of tyProc, tyTuple: nkTupleConstr
-                 else: nkEmpty
-
   let oldLen = node.len
   setLen(node.sons, newLen)
   if oldLen < newLen:
-    # TODO: This is still not correct for tyPtr, tyRef default value
     for i in oldLen ..< newLen:
-      node.sons[i] = newNodeI(typeKind, info)
+      node.sons[i] = getNullValue(typ.sons[0], info, c.config)
 
 const
   errIndexOutOfBounds = "index out of bounds"
@@ -458,7 +444,7 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg =
     #if c.traceActive:
     when traceCode:
       echo "PC ", pc, " ", c.code[pc].opcode, " ra ", ra, " rb ", instr.regB, " rc ", instr.regC
-    #  message(c.config, c.debug[pc], warnUser, "Trace")
+      # message(c.config, c.debug[pc], warnUser, "Trace")
 
     case instr.opcode
     of opcEof: return regs[ra]
diff --git a/compiler/vmops.nim b/compiler/vmops.nim
index f87ab4508..75873bfe8 100644
--- a/compiler/vmops.nim
+++ b/compiler/vmops.nim
@@ -11,7 +11,7 @@
 #import vmdeps, vm
 from math import sqrt, ln, log10, log2, exp, round, arccos, arcsin,
   arctan, arctan2, cos, cosh, hypot, sinh, sin, tan, tanh, pow, trunc,
-  floor, ceil, `mod`, fmod
+  floor, ceil, `mod`
 
 from os import getEnv, existsEnv, dirExists, fileExists, putEnv, walkDir
 
@@ -102,7 +102,6 @@ proc registerAdditionalOps*(c: PCtx) =
   wrap1f_math(trunc)
   wrap1f_math(floor)
   wrap1f_math(ceil)
-  wrap2f_math(fmod)
 
   proc `mod Wrapper`(a: VmArgs) {.nimcall.} =
     setResult(a, `mod`(getFloat(a, 0), getFloat(a, 1)))