summary refs log tree commit diff stats
diff options
context:
space:
mode:
-rw-r--r--compiler/aliases.nim4
-rw-r--r--compiler/ast.nim22
-rw-r--r--compiler/canonicalizer.nim2
-rw-r--r--compiler/ccgcalls.nim12
-rw-r--r--compiler/ccgexprs.nim101
-rw-r--r--compiler/ccgmerge.nim27
-rw-r--r--compiler/ccgstmts.nim2
-rw-r--r--compiler/ccgtrav.nim28
-rw-r--r--compiler/ccgtypes.nim323
-rw-r--r--compiler/ccgutils.nim140
-rw-r--r--compiler/cgen.nim58
-rw-r--r--compiler/cgendata.nim10
-rw-r--r--compiler/cgmeth.nim4
-rw-r--r--compiler/debuginfo.nim23
-rw-r--r--compiler/evalffi.nim56
-rw-r--r--compiler/extccomp.nim6
-rw-r--r--compiler/guards.nim2
-rw-r--r--compiler/jsgen.nim25
-rw-r--r--compiler/jstypes.nim6
-rw-r--r--compiler/lowerings.nim2
-rw-r--r--compiler/renderer.nim3
-rw-r--r--compiler/rodwrite.nim4
-rw-r--r--compiler/sem.nim8
-rw-r--r--compiler/semasgn.nim6
-rw-r--r--compiler/semcall.nim2
-rw-r--r--compiler/semdestruct.nim4
-rw-r--r--compiler/semexprs.nim44
-rw-r--r--compiler/semfold.nim3
-rw-r--r--compiler/semmacrosanity.nim2
-rw-r--r--compiler/semstmts.nim17
-rw-r--r--compiler/semtypes.nim52
-rw-r--r--compiler/semtypinst.nim5
-rw-r--r--compiler/sighashes.nim264
-rw-r--r--compiler/sigmatch.nim24
-rw-r--r--compiler/suggest.nim4
-rw-r--r--compiler/transf.nim4
-rw-r--r--compiler/trees.nim2
-rw-r--r--compiler/types.nim96
-rw-r--r--compiler/vmdeps.nim4
-rw-r--r--compiler/vmgen.nim2
-rw-r--r--compiler/vmmarshal.nim4
-rw-r--r--koch.nim19
-rw-r--r--lib/pure/securehash.nim14
-rw-r--r--lib/pure/strtabs.nim2
44 files changed, 886 insertions, 556 deletions
diff --git a/compiler/aliases.nim b/compiler/aliases.nim
index 4186900ec..0c836bb24 100644
--- a/compiler/aliases.nim
+++ b/compiler/aliases.nim
@@ -49,9 +49,9 @@ proc isPartOfAux(a, b: PType, marker: var IntSet): TAnalysisResult =
     if a.sons[0] != nil:
       result = isPartOfAux(a.sons[0].skipTypes(skipPtrs), b, marker)
     if result == arNo: result = isPartOfAux(a.n, b, marker)
-  of tyGenericInst, tyDistinct:
+  of tyGenericInst, tyDistinct, tyAlias:
     result = isPartOfAux(lastSon(a), b, marker)
-  of tyArray, tyArrayConstr, tySet, tyTuple:
+  of tyArray, tySet, tyTuple:
     for i in countup(0, sonsLen(a) - 1):
       result = isPartOfAux(a.sons[i], b, marker)
       if result == arYes: return
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 8f4acfc3b..38f481282 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -322,7 +322,7 @@ type
                      # (apparently something with bootstrapping)
                      # if you need to add a type, they can apparently be reused
     tyNone, tyBool, tyChar,
-    tyEmpty, tyArrayConstr, tyNil, tyExpr, tyStmt, tyTypeDesc,
+    tyEmpty, tyAlias, tyNil, tyExpr, tyStmt, tyTypeDesc,
     tyGenericInvocation, # ``T[a, b]`` for types to invoke
     tyGenericBody,       # ``T[a, b, body]`` last parameter is the body
     tyGenericInst,       # ``T[a, b, realInstance]`` instantiated generic type
@@ -853,6 +853,8 @@ type
     align*: int16             # the type's alignment requirements
     lockLevel*: TLockLevel    # lock level as required for deadlock checking
     loc*: TLoc
+    typeInst*: PType          # for generic instantiations the tyGenericInst that led to this
+                              # type.
 
   TPair* = object
     key*, val*: RootRef
@@ -907,7 +909,7 @@ const
   GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody,
     tyGenericParam}
 
-  StructuralEquivTypes*: TTypeKinds = {tyArrayConstr, tyNil, tyTuple, tyArray,
+  StructuralEquivTypes*: TTypeKinds = {tyNil, tyTuple, tyArray,
     tySet, tyRange, tyPtr, tyRef, tyVar, tySequence, tyProc, tyOpenArray,
     tyVarargs}
 
@@ -920,7 +922,7 @@ const
     tyUInt..tyUInt64}
   IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64,
     tyFloat..tyFloat128, tyUInt..tyUInt64}
-  ConstantDataTypes*: TTypeKinds = {tyArrayConstr, tyArray, tySet,
+  ConstantDataTypes*: TTypeKinds = {tyArray, tySet,
                                     tyTuple, tySequence}
   NilableTypes*: TTypeKinds = {tyPointer, tyCString, tyRef, tyPtr, tySequence,
     tyProc, tyString, tyError}
@@ -1209,10 +1211,10 @@ proc newType*(kind: TTypeKind, owner: PSym): PType =
   result.lockLevel = UnspecifiedLockLevel
   when debugIds:
     registerId(result)
-  #if result.id == 92231:
-  #  echo "KNID ", kind
-  #  writeStackTrace()
-  #  messageOut(typeKindToStr[kind] & ' has id: ' & toString(result.id))
+  when false:
+    if result.id == 205734:
+      echo "KNID ", kind
+      writeStackTrace()
 
 proc mergeLoc(a: var TLoc, b: TLoc) =
   if a.k == low(a.k): a.k = b.k
@@ -1370,8 +1372,8 @@ proc propagateToOwner*(owner, elem: PType) =
     owner.flags.incl tfHasMeta
 
   if tfHasAsgn in elem.flags:
-    let o2 = elem.skipTypes({tyGenericInst})
-    if o2.kind in {tyTuple, tyObject, tyArray, tyArrayConstr,
+    let o2 = elem.skipTypes({tyGenericInst, tyAlias})
+    if o2.kind in {tyTuple, tyObject, tyArray,
                    tySequence, tySet, tyDistinct}:
       o2.flags.incl tfHasAsgn
       owner.flags.incl tfHasAsgn
@@ -1381,7 +1383,7 @@ proc propagateToOwner*(owner, elem: PType) =
 
   if owner.kind notin {tyProc, tyGenericInst, tyGenericBody,
                        tyGenericInvocation, tyPtr}:
-    let elemB = elem.skipTypes({tyGenericInst})
+    let elemB = elem.skipTypes({tyGenericInst, tyAlias})
     if elemB.isGCedMem or tfHasGCedMem in elemB.flags:
       # for simplicity, we propagate this flag even to generics. We then
       # ensure this doesn't bite us in sempass2.
diff --git a/compiler/canonicalizer.nim b/compiler/canonicalizer.nim
index 2abe0a0e6..d17d928c8 100644
--- a/compiler/canonicalizer.nim
+++ b/compiler/canonicalizer.nim
@@ -132,7 +132,7 @@ proc hashType(c: var MD5Context, t: PType) =
       c.hashType t.sons[i]
   of tyFromExpr, tyFieldAccessor:
     c.hashTree(t.n)
-  of tyArrayConstr:
+  of tyArray:
     c.hashTree(t.sons[0].n)
     c.hashType(t.sons[1])
   of tyTuple:
diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim
index 48157925c..772a208cb 100644
--- a/compiler/ccgcalls.nim
+++ b/compiler/ccgcalls.nim
@@ -95,7 +95,7 @@ proc openArrayLoc(p: BProc, n: PNode): Rope =
     initLocExpr(p, q[3], c)
     let fmt =
       case skipTypes(a.t, abstractVar+{tyPtr}).kind
-      of tyOpenArray, tyVarargs, tyArray, tyArrayConstr:
+      of tyOpenArray, tyVarargs, tyArray:
         "($1)+($2), ($3)-($2)+1"
       of tyString, tySequence:
         if skipTypes(n.typ, abstractInst).kind == tyVar and
@@ -116,13 +116,13 @@ proc openArrayLoc(p: BProc, n: PNode): Rope =
         result = "(*$1)->data, (*$1)->$2" % [a.rdLoc, lenField(p)]
       else:
         result = "$1->data, $1->$2" % [a.rdLoc, lenField(p)]
-    of tyArray, tyArrayConstr:
+    of tyArray:
       result = "$1, $2" % [rdLoc(a), rope(lengthOrd(a.t))]
     of tyPtr, tyRef:
       case lastSon(a.t).kind
       of tyString, tySequence:
         result = "(*$1)->data, (*$1)->$2" % [a.rdLoc, lenField(p)]
-      of tyArray, tyArrayConstr:
+      of tyArray:
         result = "$1, $2" % [rdLoc(a), rope(lengthOrd(lastSon(a.t)))]
       else:
         internalError("openArrayLoc: " & typeToString(a.t))
@@ -331,7 +331,7 @@ proc genThisArg(p: BProc; ri: PNode; i: int; typ: PType): Rope =
   # skip the deref:
   var ri = ri[i]
   while ri.kind == nkObjDownConv: ri = ri[0]
-  let t = typ.sons[i].skipTypes({tyGenericInst})
+  let t = typ.sons[i].skipTypes({tyGenericInst, tyAlias})
   if t.kind == tyVar:
     let x = if ri.kind == nkHiddenAddr: ri[0] else: ri
     if x.typ.kind == tyPtr:
@@ -527,7 +527,7 @@ proc genNamedParamCall(p: BProc, ri: PNode, d: var TLoc) =
     line(p, cpsStmts, pl)
 
 proc genCall(p: BProc, e: PNode, d: var TLoc) =
-  if e.sons[0].typ.skipTypes({tyGenericInst}).callConv == ccClosure:
+  if e.sons[0].typ.skipTypes({tyGenericInst, tyAlias}).callConv == ccClosure:
     genClosureCall(p, nil, e, d)
   elif e.sons[0].kind == nkSym and sfInfixCall in e.sons[0].sym.flags:
     genInfixCall(p, nil, e, d)
@@ -538,7 +538,7 @@ proc genCall(p: BProc, e: PNode, d: var TLoc) =
   postStmtActions(p)
 
 proc genAsgnCall(p: BProc, le, ri: PNode, d: var TLoc) =
-  if ri.sons[0].typ.skipTypes({tyGenericInst}).callConv == ccClosure:
+  if ri.sons[0].typ.skipTypes({tyGenericInst, tyAlias}).callConv == ccClosure:
     genClosureCall(p, le, ri, d)
   elif ri.sons[0].kind == nkSym and sfInfixCall in ri.sons[0].sym.flags:
     genInfixCall(p, le, ri, d)
diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim
index 2761f888b..d68e26ec3 100644
--- a/compiler/ccgexprs.nim
+++ b/compiler/ccgexprs.nim
@@ -50,7 +50,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
     of tyUInt64: result = uint64Literal(uint64(n.intVal))
     else:
       result = "(($1) $2)" % [getTypeDesc(p.module,
-          skipTypes(ty, abstractVarRange)), intLiteral(n.intVal)]
+          ty), intLiteral(n.intVal)]
   of nkNilLit:
     let t = skipTypes(ty, abstractVarRange)
     if t.kind == tyProc and t.callConv == ccClosure:
@@ -61,7 +61,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
         inc(p.module.labels)
         addf(p.module.s[cfsData],
              "static NIM_CONST $1 $2 = {NIM_NIL,NIM_NIL};$n",
-             [getTypeDesc(p.module, t), result])
+             [getTypeDesc(p.module, ty), result])
     else:
       result = rope("NIM_NIL")
   of nkStrLit..nkTripleStrLit:
@@ -266,7 +266,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
     # little HACK to support the new 'var T' as return type:
     linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
     return
-  var ty = skipTypes(dest.t, abstractRange)
+  let ty = skipTypes(dest.t, abstractRange)
   case ty.kind
   of tyRef:
     genRefAssign(p, dest, src, flags)
@@ -315,22 +315,21 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
       genGenericAsgn(p, dest, src, flags)
     elif needsComplexAssignment(ty):
       if ty.sons[0].isNil and asgnComplexity(ty.n) <= 4:
-        discard getTypeDesc(p.module, ty)
-        ty = getUniqueType(ty)
+        discard getTypeDesc(p.module, dest.t)
         internalAssert ty.n != nil
         genOptAsgnObject(p, dest, src, flags, ty.n)
       else:
         genGenericAsgn(p, dest, src, flags)
     else:
       linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
-  of tyArray, tyArrayConstr:
+  of tyArray:
     if needsComplexAssignment(dest.t):
       genGenericAsgn(p, dest, src, flags)
     else:
       useStringh(p.module)
       linefmt(p, cpsStmts,
            "memcpy((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n",
-           rdLoc(dest), rdLoc(src), getTypeDesc(p.module, ty))
+           rdLoc(dest), rdLoc(src), getTypeDesc(p.module, dest.t))
   of tyOpenArray, tyVarargs:
     # open arrays are always on the stack - really? What if a sequence is
     # passed to an open array?
@@ -366,7 +365,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
 proc genDeepCopy(p: BProc; dest, src: TLoc) =
   var ty = skipTypes(dest.t, abstractVarRange)
   case ty.kind
-  of tyPtr, tyRef, tyProc, tyTuple, tyObject, tyArray, tyArrayConstr:
+  of tyPtr, tyRef, tyProc, tyTuple, tyObject, tyArray:
     # XXX optimize this
     linefmt(p, cpsStmts, "#genericDeepCopy((void*)$1, (void*)$2, $3);$n",
             addrLoc(dest), addrLoc(src), genTypeInfo(p.module, dest.t))
@@ -502,12 +501,12 @@ proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
   # later via 'chckRange'
   let t = e.typ.skipTypes(abstractRange)
   if optOverflowCheck notin p.options:
-    let res = opr[m] % [getTypeDesc(p.module, t), rdLoc(a), rdLoc(b)]
+    let res = opr[m] % [getTypeDesc(p.module, e.typ), rdLoc(a), rdLoc(b)]
     putIntoDest(p, d, e.typ, res)
   else:
     let res = binaryArithOverflowRaw(p, t, a, b,
                                    if t.kind == tyInt64: prc64[m] else: prc[m])
-    putIntoDest(p, d, e.typ, "($#)($#)" % [getTypeDesc(p.module, t), res])
+    putIntoDest(p, d, e.typ, "($#)($#)" % [getTypeDesc(p.module, e.typ), res])
 
 proc unaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
   const
@@ -708,12 +707,11 @@ proc genAddr(p: BProc, e: PNode, d: var TLoc) =
 template inheritLocation(d: var TLoc, a: TLoc) =
   if d.k == locNone: d.s = a.s
 
-proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc): PType =
+proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc) =
   initLocExpr(p, e.sons[0], a)
   if e.sons[1].kind != nkSym: internalError(e.info, "genRecordFieldAux")
   d.inheritLocation(a)
   discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
-  result = a.t.getUniqueType
 
 proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
   var
@@ -722,13 +720,12 @@ proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
   initLocExpr(p, e.sons[0], a)
   d.inheritLocation(a)
   discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
-  var ty = a.t.getUniqueType
   var r = rdLoc(a)
   case e.sons[1].kind
   of nkIntLit..nkUInt64Lit: i = int(e.sons[1].intVal)
   else: internalError(e.info, "genTupleElem")
   addf(r, ".Field$1", [rope(i)])
-  putIntoDest(p, d, ty.sons[i], r, a.s)
+  putIntoDest(p, d, a.t.sons[i], r, a.s)
 
 proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope): PSym =
   var ty = ty
@@ -739,14 +736,15 @@ proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope): PSym =
     result = lookupInRecord(ty.n, field.name)
     if result != nil: break
     if not p.module.compileToCpp: add(r, ".Sup")
-    ty = getUniqueType(ty.sons[0])
+    ty = ty.sons[0]
   if result == nil: internalError(field.info, "genCheckedRecordField")
 
 proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
   var a: TLoc
-  var ty = genRecordFieldAux(p, e, d, a)
+  genRecordFieldAux(p, e, d, a)
   var r = rdLoc(a)
   var f = e.sons[1].sym
+  let ty = skipTypes(a.t, abstractInst)
   if ty.kind == tyTuple:
     # we found a unique tuple type which lacks field information
     # so we use Field$i
@@ -754,7 +752,8 @@ proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
     putIntoDest(p, d, f.typ, r, a.s)
   else:
     let field = lookupFieldAgain(p, ty, f, r)
-    if field.loc.r == nil: internalError(e.info, "genRecordField 3")
+    if field.loc.r == nil: fillObjectFields(p.module, ty)
+    if field.loc.r == nil: internalError(e.info, "genRecordField 3 " & typeToString(ty))
     addf(r, ".$1", [field.loc.r])
     putIntoDest(p, d, field.typ, r, a.s)
   #d.s = a.s
@@ -797,10 +796,12 @@ proc genFieldCheck(p: BProc, e: PNode, obj: Rope, field: PSym;
 proc genCheckedRecordField(p: BProc, e: PNode, d: var TLoc) =
   if optFieldCheck in p.options:
     var a: TLoc
-    let ty = genRecordFieldAux(p, e.sons[0], d, a)
+    genRecordFieldAux(p, e.sons[0], d, a)
+    let ty = skipTypes(a.t, abstractInst)
     var r = rdLoc(a)
     let f = e.sons[0].sons[1].sym
     let field = lookupFieldAgain(p, ty, f, r)
+    if field.loc.r == nil: fillObjectFields(p.module, ty)
     if field.loc.r == nil:
       internalError(e.info, "genCheckedRecordField") # generate the checks:
     genFieldCheck(p, e, r, field, ty)
@@ -880,7 +881,7 @@ proc genBracketExpr(p: BProc; n: PNode; d: var TLoc) =
   var ty = skipTypes(n.sons[0].typ, abstractVarRange)
   if ty.kind in {tyRef, tyPtr}: ty = skipTypes(ty.lastSon, abstractVarRange)
   case ty.kind
-  of tyArray, tyArrayConstr: genArrayElem(p, n.sons[0], n.sons[1], d)
+  of tyArray: genArrayElem(p, n.sons[0], n.sons[1], d)
   of tyOpenArray, tyVarargs: genOpenArrayElem(p, n.sons[0], n.sons[1], d)
   of tySequence, tyString: genSeqElem(p, n.sons[0], n.sons[1], d)
   of tyCString: genCStringElem(p, n.sons[0], n.sons[1], d)
@@ -1037,10 +1038,10 @@ proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
   var a, b, dest: TLoc
   initLocExpr(p, e.sons[1], a)
   initLocExpr(p, e.sons[2], b)
-  let bt = skipTypes(e.sons[2].typ, abstractVar)
+  let bt = skipTypes(e.sons[2].typ, {tyVar})
   lineCg(p, cpsStmts, seqAppendPattern, [
       rdLoc(a),
-      getTypeDesc(p.module, skipTypes(e.sons[1].typ, abstractVar)),
+      getTypeDesc(p.module, e.sons[1].typ),
       getTypeDesc(p.module, bt)])
   #if bt != b.t:
   #  echo "YES ", e.info, " new: ", typeToString(bt), " old: ", typeToString(b.t)
@@ -1054,16 +1055,17 @@ proc genReset(p: BProc, n: PNode) =
   var a: TLoc
   initLocExpr(p, n.sons[1], a)
   linefmt(p, cpsStmts, "#genericReset((void*)$1, $2);$n",
-          addrLoc(a), genTypeInfo(p.module, skipTypes(a.t, abstractVarRange)))
+          addrLoc(a), genTypeInfo(p.module, skipTypes(a.t, {tyVar})))
 
 proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) =
   var sizeExpr = sizeExpr
-  let refType = skipTypes(a.t, abstractVarRange)
+  let refType = a.t
   var b: TLoc
   initLoc(b, locExpr, a.t, OnHeap)
+  let bt = refType.lastSon
   if sizeExpr.isNil:
     sizeExpr = "sizeof($1)" %
-        [getTypeDesc(p.module, skipTypes(refType.sons[0], abstractRange))]
+        [getTypeDesc(p.module, bt)]
   let args = [getTypeDesc(p.module, refType),
               genTypeInfo(p.module, refType),
               sizeExpr]
@@ -1078,7 +1080,6 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: Rope) =
   else:
     b.r = ropecg(p.module, "($1) #newObj($2, $3)", args)
     genAssignment(p, a, b, {})  # set the object type:
-  let bt = skipTypes(refType.sons[0], abstractRange)
   genObjectInit(p, cpsStmts, bt, a, false)
 
 proc genNew(p: BProc, e: PNode) =
@@ -1130,7 +1131,7 @@ proc genNewSeqOfCap(p: BProc; e: PNode; d: var TLoc) =
 proc genConstExpr(p: BProc, n: PNode): Rope
 proc handleConstExpr(p: BProc, n: PNode, d: var TLoc): bool =
   if d.k == locNone and n.len > ord(n.kind == nkObjConstr) and n.isDeepConstExpr:
-    var t = getUniqueType(n.typ)
+    let t = n.typ
     discard getTypeDesc(p.module, t) # so that any fields are initialized
     let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
     fillLoc(d, locData, t, p.module.tmpBase & rope(id), OnStatic)
@@ -1165,6 +1166,7 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
     var tmp2: TLoc
     tmp2.r = r
     let field = lookupFieldAgain(p, ty, it.sons[0].sym, tmp2.r)
+    if field.loc.r == nil: fillObjectFields(p.module, ty)
     if field.loc.r == nil: internalError(e.info, "genObjConstr")
     if it.len == 3 and optFieldCheck in p.options:
       genFieldCheck(p, it.sons[2], r, field, ty)
@@ -1310,15 +1312,14 @@ proc genRepr(p: BProc, e: PNode, d: var TLoc) =
     of tyString, tySequence:
       putIntoDest(p, b, e.typ,
                   "$1->data, $1->$2" % [rdLoc(a), lenField(p)], a.s)
-    of tyArray, tyArrayConstr:
+    of tyArray:
       putIntoDest(p, b, e.typ,
                   "$1, $2" % [rdLoc(a), rope(lengthOrd(a.t))], a.s)
     else: internalError(e.sons[0].info, "genRepr()")
     putIntoDest(p, d, e.typ,
         ropecg(p.module, "#reprOpenArray($1, $2)", [rdLoc(b),
         genTypeInfo(p.module, elemType(t))]), a.s)
-  of tyCString, tyArray, tyArrayConstr, tyRef, tyPtr, tyPointer, tyNil,
-     tySequence:
+  of tyCString, tyArray, tyRef, tyPtr, tyPointer, tyNil, tySequence:
     putIntoDest(p, d, e.typ,
                 ropecg(p.module, "#reprAny($1, $2)", [
                 rdLoc(a), genTypeInfo(p.module, t)]), a.s)
@@ -1330,7 +1331,7 @@ proc genRepr(p: BProc, e: PNode, d: var TLoc) =
   gcUsage(e)
 
 proc genGetTypeInfo(p: BProc, e: PNode, d: var TLoc) =
-  var t = skipTypes(e.sons[1].typ, abstractVarRange)
+  let t = e.sons[1].typ
   putIntoDest(p, d, e.typ, genTypeInfo(p.module, t))
 
 proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
@@ -1344,7 +1345,7 @@ proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
 proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
   var a = e.sons[1]
   if a.kind == nkHiddenAddr: a = a.sons[0]
-  var typ = skipTypes(a.typ, abstractVar)
+  let typ = skipTypes(a.typ, abstractVar)
   case typ.kind
   of tyOpenArray, tyVarargs:
     if op == mHigh: unaryExpr(p, e, d, "($1Len0-1)")
@@ -1360,7 +1361,7 @@ proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
     else:
       if op == mHigh: unaryExpr(p, e, d, "($1 ? ($1->len-1) : -1)")
       else: unaryExpr(p, e, d, "($1 ? $1->len : 0)")
-  of tyArray, tyArrayConstr:
+  of tyArray:
     # YYY: length(sideeffect) is optimized away incorrectly?
     if op == mHigh: putIntoDest(p, d, e.typ, rope(lastOrd(typ)))
     else: putIntoDest(p, d, e.typ, rope(lengthOrd(typ)))
@@ -1371,7 +1372,7 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
   assert(d.k == locNone)
   initLocExpr(p, e.sons[1], a)
   initLocExpr(p, e.sons[2], b)
-  var t = skipTypes(e.sons[1].typ, abstractVar)
+  let t = skipTypes(e.sons[1].typ, {tyVar})
   let setLenPattern = if not p.module.compileToCpp:
       "$1 = ($3) #setLengthSeq(&($1)->Sup, sizeof($4), $2);$n"
     else:
@@ -1379,7 +1380,7 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
 
   lineCg(p, cpsStmts, setLenPattern, [
       rdLoc(a), rdLoc(b), getTypeDesc(p.module, t),
-      getTypeDesc(p.module, t.sons[0])])
+      getTypeDesc(p.module, t.skipTypes(abstractInst).sons[0])])
   gcUsage(e)
 
 proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) =
@@ -1540,8 +1541,7 @@ proc genOrd(p: BProc, e: PNode, d: var TLoc) =
 
 proc genSomeCast(p: BProc, e: PNode, d: var TLoc) =
   const
-    ValueTypes = {tyTuple, tyObject, tyArray, tyOpenArray, tyVarargs,
-                  tyArrayConstr}
+    ValueTypes = {tyTuple, tyObject, tyArray, tyOpenArray, tyVarargs}
   # we use whatever C gives us. Except if we have a value-type, we need to go
   # through its address:
   var a: TLoc
@@ -1558,8 +1558,7 @@ proc genSomeCast(p: BProc, e: PNode, d: var TLoc) =
         [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.s)
 
 proc genCast(p: BProc, e: PNode, d: var TLoc) =
-  const ValueTypes = {tyFloat..tyFloat128, tyTuple, tyObject,
-                      tyArray, tyArrayConstr}
+  const ValueTypes = {tyFloat..tyFloat128, tyTuple, tyObject, tyArray}
   let
     destt = skipTypes(e.typ, abstractRange)
     srct = skipTypes(e.sons[1].typ, abstractRange)
@@ -1570,7 +1569,7 @@ proc genCast(p: BProc, e: PNode, d: var TLoc) =
     var tmp: TLoc
     tmp.r = "LOC$1.source" % [lbl]
     linefmt(p, cpsLocals, "union { $1 source; $2 dest; } LOC$3;$n",
-      getTypeDesc(p.module, srct), getTypeDesc(p.module, destt), lbl)
+      getTypeDesc(p.module, e.sons[1].typ), getTypeDesc(p.module, e.typ), lbl)
     tmp.k = locExpr
     tmp.t = srct
     tmp.s = OnStack
@@ -1599,7 +1598,7 @@ proc genRangeChck(p: BProc, n: PNode, d: var TLoc, magic: string) =
         rope(magic)]), a.s)
 
 proc genConv(p: BProc, e: PNode, d: var TLoc) =
-  let destType = e.typ.skipTypes({tyVar, tyGenericInst})
+  let destType = e.typ.skipTypes({tyVar, tyGenericInst, tyAlias})
   if compareTypes(destType, e.sons[1].typ, dcEqIgnoreDistinct):
     expr(p, e.sons[1], d)
   else:
@@ -1673,7 +1672,7 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
                                                "$# = #subInt64($#, $#);$n"]
     const fun: array[mInc..mDec, string] = ["$# = #addInt($#, $#);$n",
                                              "$# = #subInt($#, $#);$n"]
-    let underlying = skipTypes(e.sons[1].typ, {tyGenericInst, tyVar, tyRange})
+    let underlying = skipTypes(e.sons[1].typ, {tyGenericInst, tyAlias, tyVar, tyRange})
     if optOverflowCheck notin p.options or underlying.kind in {tyUInt..tyUInt64}:
       binaryStmt(p, e, d, opr[op])
     else:
@@ -1683,7 +1682,7 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
       initLocExpr(p, e.sons[1], a)
       initLocExpr(p, e.sons[2], b)
 
-      let ranged = skipTypes(e.sons[1].typ, {tyGenericInst, tyVar})
+      let ranged = skipTypes(e.sons[1].typ, {tyGenericInst, tyAlias, tyVar})
       let res = binaryArithOverflowRaw(p, ranged, a, b,
         if underlying.kind == tyInt64: fun64[op] else: fun[op])
       putIntoDest(p, a, ranged, "($#)($#)" % [
@@ -1804,7 +1803,7 @@ proc genSetConstr(p: BProc, e: PNode, d: var TLoc) =
 proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
   var rec: TLoc
   if not handleConstExpr(p, n, d):
-    var t = getUniqueType(n.typ)
+    let t = n.typ
     discard getTypeDesc(p.module, t) # so that any fields are initialized
     if d.k == locNone: getTemp(p, t, d)
     for i in countup(0, sonsLen(n) - 1):
@@ -1813,11 +1812,6 @@ proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
       initLoc(rec, locExpr, it.typ, d.s)
       rec.r = "$1.Field$2" % [rdLoc(d), rope(i)]
       expr(p, it, rec)
-      when false:
-        initLoc(rec, locExpr, it.typ, d.s)
-        if (t.n.sons[i].kind != nkSym): InternalError(n.info, "genTupleConstr")
-        rec.r = "$1.$2" % [rdLoc(d), mangleRecFieldName(t.n.sons[i].sym, t)]
-        expr(p, it, rec)
 
 proc isConstClosure(n: PNode): bool {.inline.} =
   result = n.sons[0].kind == nkSym and isRoutine(n.sons[0].sym) and
@@ -1871,7 +1865,7 @@ proc genStmtListExpr(p: BProc, n: PNode, d: var TLoc) =
 proc upConv(p: BProc, n: PNode, d: var TLoc) =
   var a: TLoc
   initLocExpr(p, n.sons[0], a)
-  var dest = skipTypes(n.typ, abstractPtrs)
+  let dest = skipTypes(n.typ, abstractPtrs)
   if optObjCheck in p.options and not isObjLackingTypeField(dest):
     var r = rdLoc(a)
     var nilCheck: Rope = nil
@@ -1933,7 +1927,7 @@ proc downConv(p: BProc, n: PNode, d: var TLoc) =
       putIntoDest(p, d, n.typ, r, a.s)
 
 proc exprComplexConst(p: BProc, n: PNode, d: var TLoc) =
-  var t = getUniqueType(n.typ)
+  let t = n.typ
   discard getTypeDesc(p.module, t) # so that any fields are initialized
   let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
   let tmp = p.module.tmpBase & rope(id)
@@ -1962,7 +1956,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
     of skMethod:
       if {sfDispatcher, sfForward} * sym.flags != {}:
         # we cannot produce code for the dispatcher yet:
-        fillProcLoc(sym)
+        fillProcLoc(p.module, sym)
         genProcPrototype(p.module, sym)
       else:
         genProc(p.module, sym)
@@ -2170,13 +2164,14 @@ proc genConstSeq(p: BProc, n: PNode, t: PType): Rope =
   data.add("}")
 
   result = getTempName(p.module)
+  let base = t.skipTypes(abstractInst).sons[0]
 
   appcg(p.module, cfsData,
         "NIM_CONST struct {$n" &
         "  #TGenericSeq Sup;$n" &
         "  $1 data[$2];$n" &
         "} $3 = $4;$n", [
-        getTypeDesc(p.module, t.sons[0]), n.len.rope, result, data])
+        getTypeDesc(p.module, base), n.len.rope, result, data])
 
   result = "(($1)&$2)" % [getTypeDesc(p.module, t), result]
 
@@ -2191,7 +2186,7 @@ proc genConstExpr(p: BProc, n: PNode): Rope =
   of nkBracket, nkPar, nkClosure, nkObjConstr:
     var t = skipTypes(n.typ, abstractInst)
     if t.kind == tySequence:
-      result = genConstSeq(p, n, t)
+      result = genConstSeq(p, n, n.typ)
     else:
       result = genConstSimpleList(p, n)
   else:
diff --git a/compiler/ccgmerge.nim b/compiler/ccgmerge.nim
index 92b6aa9dc..46982d0a2 100644
--- a/compiler/ccgmerge.nim
+++ b/compiler/ccgmerge.nim
@@ -12,7 +12,7 @@
 
 import
   ast, astalgo, ropes, options, strutils, nimlexbase, msgs, cgendata, rodutils,
-  intsets, platform, llstream
+  intsets, platform, llstream, tables, sighashes
 
 # Careful! Section marks need to contain a tabulator so that they cannot
 # be part of C string literals.
@@ -69,7 +69,7 @@ proc genSectionEnd*(ps: TCProcSection): Rope =
   if compilationCachePresent:
     result = rope(NimMergeEndMark & tnl)
 
-proc writeTypeCache(a: TIdTable, s: var string) =
+proc writeTypeCache(a: TypeCache, s: var string) =
   var i = 0
   for id, value in pairs(a):
     if i == 10:
@@ -77,9 +77,9 @@ proc writeTypeCache(a: TIdTable, s: var string) =
       s.add(tnl)
     else:
       s.add(' ')
-    encodeVInt(id, s)
+    encodeStr($id, s)
     s.add(':')
-    encodeStr($Rope(value), s)
+    encodeStr($value, s)
     inc i
   s.add('}')
 
@@ -103,8 +103,9 @@ proc genMergeInfo*(m: BModule): Rope =
   writeTypeCache(m.typeCache, s)
   s.add("declared:{")
   writeIntSet(m.declaredThings, s)
-  s.add("typeInfo:{")
-  writeIntSet(m.typeInfoMarker, s)
+  when false:
+    s.add("typeInfo:{")
+    writeIntSet(m.typeInfoMarker, s)
   s.add("labels:")
   encodeVInt(m.labels, s)
   s.add(" flags:")
@@ -185,19 +186,18 @@ proc newFakeType(id: int): PType =
   new(result)
   result.id = id
 
-proc readTypeCache(L: var TBaseLexer, result: var TIdTable) =
+proc readTypeCache(L: var TBaseLexer, result: var TypeCache) =
   if ^L.bufpos != '{': internalError("ccgmerge: '{' expected")
   inc L.bufpos
   while ^L.bufpos != '}':
     skipWhite(L)
-    var key = decodeVInt(L.buf, L.bufpos)
+    var key = decodeStr(L.buf, L.bufpos)
     if ^L.bufpos != ':': internalError("ccgmerge: ':' expected")
     inc L.bufpos
     var value = decodeStr(L.buf, L.bufpos)
-    # XXX little hack: we create a "fake" type object with the correct Id
-    # better would be to adapt the data structure to not even store the
-    # object as key, but only the Id
-    idTablePut(result, newFakeType(key), value.rope)
+    # XXX implement me
+    when false:
+      idTablePut(result, newFakeType(key), value.rope)
   inc L.bufpos
 
 proc readIntSet(L: var TBaseLexer, result: var IntSet) =
@@ -220,7 +220,8 @@ proc processMergeInfo(L: var TBaseLexer, m: BModule) =
     case k
     of "typeCache": readTypeCache(L, m.typeCache)
     of "declared":  readIntSet(L, m.declaredThings)
-    of "typeInfo":  readIntSet(L, m.typeInfoMarker)
+    of "typeInfo":
+      when false: readIntSet(L, m.typeInfoMarker)
     of "labels":    m.labels = decodeVInt(L.buf, L.bufpos)
     of "flags":
       m.flags = cast[set[CodegenFlag]](decodeVInt(L.buf, L.bufpos) != 0)
diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim
index 10b5641c5..a1ec73e5c 100644
--- a/compiler/ccgstmts.nim
+++ b/compiler/ccgstmts.nim
@@ -970,7 +970,7 @@ proc genAsmOrEmitStmt(p: BProc, t: PNode, isAsmStmt=false): Rope =
         if r == nil:
           # if no name has already been given,
           # it doesn't matter much:
-          r = mangleName(sym)
+          r = mangleName(p.module, sym)
           sym.loc.r = r       # but be consequent!
         res.add($r)
     else: internalError(t.sons[i].info, "genAsmOrEmitStmt()")
diff --git a/compiler/ccgtrav.nim b/compiler/ccgtrav.nim
index a8c079b35..731dc55a0 100644
--- a/compiler/ccgtrav.nim
+++ b/compiler/ccgtrav.nim
@@ -21,12 +21,13 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, typ: PType)
 proc genCaseRange(p: BProc, branch: PNode)
 proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false)
 
-proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, n: PNode) =
+proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, n: PNode;
+                     typ: PType) =
   if n == nil: return
   case n.kind
   of nkRecList:
     for i in countup(0, sonsLen(n) - 1):
-      genTraverseProc(c, accessor, n.sons[i])
+      genTraverseProc(c, accessor, n.sons[i], typ)
   of nkRecCase:
     if (n.sons[0].kind != nkSym): internalError(n.info, "genTraverseProc")
     var p = c.p
@@ -39,11 +40,13 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, n: PNode) =
         genCaseRange(c.p, branch)
       else:
         lineF(p, cpsStmts, "default:$n", [])
-      genTraverseProc(c, accessor, lastSon(branch))
+      genTraverseProc(c, accessor, lastSon(branch), typ)
       lineF(p, cpsStmts, "break;$n", [])
     lineF(p, cpsStmts, "} $n", [])
   of nkSym:
     let field = n.sym
+    if field.typ.kind == tyVoid: return
+    if field.loc.r == nil: fillObjectFields(c.p.module, typ)
     if field.loc.t == nil:
       internalError(n.info, "genTraverseProc()")
     genTraverseProc(c, "$1.$2" % [accessor, field.loc.r], field.loc.t)
@@ -58,12 +61,11 @@ proc parentObj(accessor: Rope; m: BModule): Rope {.inline.} =
 proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, typ: PType) =
   if typ == nil: return
 
-  let typ = getUniqueType(typ)
   var p = c.p
   case typ.kind
-  of tyGenericInst, tyGenericBody, tyTypeDesc:
+  of tyGenericInst, tyGenericBody, tyTypeDesc, tyAlias:
     genTraverseProc(c, accessor, lastSon(typ))
-  of tyArrayConstr, tyArray:
+  of tyArray:
     let arraySize = lengthOrd(typ.sons[0])
     var i: TLoc
     getTemp(p, getSysType(tyInt), i)
@@ -76,7 +78,7 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: Rope, typ: PType) =
       var x = typ.sons[i]
       if x != nil: x = x.skipTypes(skipPtrs)
       genTraverseProc(c, accessor.parentObj(c.p.module), x)
-    if typ.n != nil: genTraverseProc(c, accessor, typ.n)
+    if typ.n != nil: genTraverseProc(c, accessor, typ.n, typ)
   of tyTuple:
     let typ = getUniqueType(typ)
     for i in countup(0, sonsLen(typ) - 1):
@@ -99,16 +101,18 @@ proc genTraverseProcSeq(c: var TTraversalClosure, accessor: Rope, typ: PType) =
   genTraverseProc(c, "$1->data[$2]" % [accessor, i.r], typ.sons[0])
   lineF(p, cpsStmts, "}$n", [])
 
-proc genTraverseProc(m: BModule, typ: PType, reason: TTypeInfoReason): Rope =
+proc genTraverseProc(m: BModule, origTyp: PType; sig: SigHash;
+                     reason: TTypeInfoReason): Rope =
   var c: TTraversalClosure
   var p = newProc(nil, m)
-  result = getTempName(m)
+  result = "Marker_" & getTypeName(m, origTyp, sig)
+  let typ = origTyp.skipTypes(abstractInst)
 
   case reason
   of tiNew: c.visitorFrmt = "#nimGCvisit((void*)$1, op);$n"
   else: assert false
 
-  let header = "N_NIMCALL(void, $1)(void* p, NI op)" % [result]
+  let header = "static N_NIMCALL(void, $1)(void* p, NI op)" % [result]
 
   let t = getTypeDesc(m, typ)
   lineF(p, cpsLocals, "$1 a;$n", [t])
@@ -119,7 +123,7 @@ proc genTraverseProc(m: BModule, typ: PType, reason: TTypeInfoReason): Rope =
   if typ.kind == tySequence:
     genTraverseProcSeq(c, "a".rope, typ)
   else:
-    if skipTypes(typ.sons[0], typedescInst).kind in {tyArrayConstr, tyArray}:
+    if skipTypes(typ.sons[0], typedescInst).kind == tyArray:
       # C's arrays are broken beyond repair:
       genTraverseProc(c, "a".rope, typ.sons[0])
     else:
@@ -145,7 +149,7 @@ proc genTraverseProcForGlobal(m: BModule, s: PSym): Rope =
 
   c.visitorFrmt = "#nimGCvisit((void*)$1, 0);$n"
   c.p = p
-  let header = "N_NIMCALL(void, $1)(void)" % [result]
+  let header = "static N_NIMCALL(void, $1)(void)" % [result]
   genTraverseProc(c, sLoc, s.loc.t)
 
   let generatedProc = "$1 {$n$2$3$4}$n" %
diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim
index 68e98e92e..5c13d8186 100644
--- a/compiler/ccgtypes.nim
+++ b/compiler/ccgtypes.nim
@@ -11,7 +11,7 @@
 
 # ------------------------- Name Mangling --------------------------------
 
-import debuginfo
+import sighashes
 
 proc isKeyword(w: PIdent): bool =
   # Nim and C++ share some keywords
@@ -29,14 +29,25 @@ proc mangleField(name: PIdent): string =
     # Mangling makes everything lowercase,
     # but some identifiers are C keywords
 
-proc hashOwner(s: PSym): FilenameHash =
-  var m = s
-  while m.kind != skModule: m = m.owner
-  let p = m.owner
-  assert p.kind == skPackage
-  result = gDebugInfo.register(p.name.s, m.name.s)
+when false:
+  proc hashOwner(s: PSym): SigHash =
+    var m = s
+    while m.kind != skModule: m = m.owner
+    let p = m.owner
+    assert p.kind == skPackage
+    result = gDebugInfo.register(p.name.s, m.name.s)
+
+proc idOrSig(m: BModule; s: PSym): Rope =
+  if s.kind in routineKinds and s.typ != nil and sfExported in s.flags and
+     s.typ.callConv != ccInline:
+    # signatures for exported routines are reliable enough to
+    # produce a unique name and this means produced C++ is more stable wrt
+    # Nim changes:
+    result = rope($hashProc(s))
+  else:
+    result = "_" & rope s.id
 
-proc mangleName(s: PSym): Rope =
+proc mangleName(m: BModule; s: PSym): Rope =
   result = s.loc.r
   if result == nil:
     let keepOrigName = s.kind in skLocalVars - {skForVar} and
@@ -85,22 +96,26 @@ proc mangleName(s: PSym): Rope =
     if keepOrigName:
       result.add "0"
     else:
-      add(result, ~"_")
-      add(result, rope(s.id))
-      add(result, ~"_")
-      add(result, rope(hashOwner(s).BiggestInt))
+      add(result, m.idOrSig(s))
+      #add(result, ~"_")
+      #add(result, rope(hashOwner(s).BiggestInt))
     s.loc.r = result
 
 proc typeName(typ: PType): Rope =
   result = if typ.sym != nil: typ.sym.name.s.mangle.rope
            else: ~"TY"
 
-proc getTypeName(typ: PType): Rope =
+proc getTypeName(m: BModule; typ: PType; sig: SigHash): Rope =
+  let typ = if typ.kind == tyAlias: typ.lastSon else: typ
   if typ.sym != nil and {sfImportc, sfExportc} * typ.sym.flags != {}:
     result = typ.sym.loc.r
   else:
     if typ.loc.r == nil:
-      typ.loc.r = typ.typeName & typ.id.rope
+      typ.loc.r = typ.typeName & $sig
+    else:
+      when defined(debugSigHashes):
+        # check consistency:
+        assert($typ.loc.r == $(typ.typeName & $sig))
     result = typ.loc.r
   if result == nil: internalError("getTypeName: " & $typ.kind)
 
@@ -119,10 +134,10 @@ proc mapType(typ: PType): TCTypeKind =
   of tyBool: result = ctBool
   of tyChar: result = ctChar
   of tySet: result = mapSetType(typ)
-  of tyOpenArray, tyArrayConstr, tyArray, tyVarargs: result = ctArray
+  of tyOpenArray, tyArray, tyVarargs: result = ctArray
   of tyObject, tyTuple: result = ctStruct
   of tyGenericBody, tyGenericInst, tyGenericParam, tyDistinct, tyOrdinal,
-     tyTypeDesc:
+     tyTypeDesc, tyAlias:
     result = mapType(lastSon(typ))
   of tyEnum:
     if firstOrd(typ) < 0:
@@ -138,7 +153,7 @@ proc mapType(typ: PType): TCTypeKind =
   of tyPtr, tyVar, tyRef:
     var base = skipTypes(typ.lastSon, typedescInst)
     case base.kind
-    of tyOpenArray, tyArrayConstr, tyArray, tyVarargs: result = ctPtrToArray
+    of tyOpenArray, tyArray, tyVarargs: result = ctPtrToArray
     #of tySet:
     #  if mapSetType(base) == ctArray: result = ctPtrToArray
     #  else: result = ctPtr
@@ -167,7 +182,7 @@ proc isImportedType(t: PType): bool =
 proc isImportedCppType(t: PType): bool =
   result = t.sym != nil and sfInfixCall in t.sym.flags
 
-proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope
+proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope
 proc needsComplexAssignment(typ: PType): bool =
   result = containsGarbageCollectedRef(typ)
 
@@ -200,11 +215,11 @@ const
                  # but one can #define it to what one wants
     "N_INLINE", "N_NOINLINE", "N_FASTCALL", "N_CLOSURE", "N_NOCONV"]
 
-proc cacheGetType(tab: TIdTable, key: PType): Rope =
+proc cacheGetType(tab: TypeCache; sig: SigHash): Rope =
   # returns nil if we need to declare this type
   # since types are now unique via the ``getUniqueType`` mechanism, this slow
   # linear search is not necessary anymore:
-  result = Rope(idTableGet(tab, key))
+  result = tab.getOrDefault(sig)
 
 proc addAbiCheck(m: BModule, t: PType, name: Rope) =
   if isDefined("checkabi"):
@@ -239,9 +254,9 @@ proc fillResult(param: PSym) =
     incl(param.loc.flags, lfIndirect)
     param.loc.s = OnUnknown
 
-proc typeNameOrLiteral(t: PType, literal: string): Rope =
+proc typeNameOrLiteral(m: BModule; t: PType, literal: string): Rope =
   if t.sym != nil and sfImportc in t.sym.flags and t.sym.magic == mNone:
-    result = getTypeName(t)
+    result = t.sym.loc.r
   else:
     result = rope(literal)
 
@@ -253,21 +268,21 @@ proc getSimpleTypeDesc(m: BModule, typ: PType): Rope =
       "NU", "NU8", "NU16", "NU32", "NU64"]
   case typ.kind
   of tyPointer:
-    result = typeNameOrLiteral(typ, "void*")
+    result = typeNameOrLiteral(m, typ, "void*")
   of tyString:
     discard cgsym(m, "NimStringDesc")
-    result = typeNameOrLiteral(typ, "NimStringDesc*")
-  of tyCString: result = typeNameOrLiteral(typ, "NCSTRING")
-  of tyBool: result = typeNameOrLiteral(typ, "NIM_BOOL")
-  of tyChar: result = typeNameOrLiteral(typ, "NIM_CHAR")
-  of tyNil: result = typeNameOrLiteral(typ, "0")
+    result = typeNameOrLiteral(m, typ, "NimStringDesc*")
+  of tyCString: result = typeNameOrLiteral(m, typ, "NCSTRING")
+  of tyBool: result = typeNameOrLiteral(m, typ, "NIM_BOOL")
+  of tyChar: result = typeNameOrLiteral(m, typ, "NIM_CHAR")
+  of tyNil: result = typeNameOrLiteral(m, typ, "0")
   of tyInt..tyUInt64:
-    result = typeNameOrLiteral(typ, NumericalTypeToStr[typ.kind])
+    result = typeNameOrLiteral(m, typ, NumericalTypeToStr[typ.kind])
   of tyDistinct, tyRange, tyOrdinal: result = getSimpleTypeDesc(m, typ.sons[0])
   of tyStatic:
     if typ.n != nil: result = getSimpleTypeDesc(m, lastSon typ)
     else: internalError("tyStatic for getSimpleTypeDesc")
-  of tyGenericInst:
+  of tyGenericInst, tyAlias:
     result = getSimpleTypeDesc(m, lastSon typ)
   else: result = nil
 
@@ -279,11 +294,11 @@ proc getSimpleTypeDesc(m: BModule, typ: PType): Rope =
 proc pushType(m: BModule, typ: PType) =
   add(m.typeStack, typ)
 
-proc getTypePre(m: BModule, typ: PType): Rope =
+proc getTypePre(m: BModule, typ: PType; sig: SigHash): Rope =
   if typ == nil: result = rope("void")
   else:
     result = getSimpleTypeDesc(m, typ)
-    if result == nil: result = cacheGetType(m.typeCache, typ)
+    if result == nil: result = cacheGetType(m.typeCache, sig)
 
 proc structOrUnion(t: PType): Rope =
   (if tfUnion in t.flags: rope("union") else: rope("struct"))
@@ -292,42 +307,44 @@ proc getForwardStructFormat(m: BModule): string =
   if m.compileToCpp: result = "$1 $2;$n"
   else: result = "typedef $1 $2 $2;$n"
 
-proc getTypeForward(m: BModule, typ: PType): Rope =
-  result = cacheGetType(m.forwTypeCache, typ)
+proc getTypeForward(m: BModule, typ: PType; sig: SigHash): Rope =
+  result = cacheGetType(m.forwTypeCache, sig)
   if result != nil: return
-  result = getTypePre(m, typ)
+  result = getTypePre(m, typ, sig)
   if result != nil: return
-  case typ.kind
+  case typ.skipTypes(abstractInst).kind
   of tySequence, tyTuple, tyObject:
-    result = getTypeName(typ)
+    result = getTypeName(m, typ, sig)
+    m.forwTypeCache[sig] = result
     if not isImportedType(typ):
+      addf(m.s[cfsForwardTypes], "/* getTypeForward: $1 $2 $3 */", [rope typeToString typ,
+          rope typ.id, rope m.module.id])
       addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
           [structOrUnion(typ), result])
-    idTablePut(m.forwTypeCache, typ, result)
+    doAssert m.forwTypeCache[sig] == result
   else: internalError("getTypeForward(" & $typ.kind & ')')
 
 proc getTypeDescWeak(m: BModule; t: PType; check: var IntSet): Rope =
   ## like getTypeDescAux but creates only a *weak* dependency. In other words
   ## we know we only need a pointer to it so we only generate a struct forward
   ## declaration:
-  var etB = t.skipTypes(abstractInst)
+  let etB = t.skipTypes(abstractInst)
   case etB.kind
   of tyObject, tyTuple:
     if isImportedCppType(etB) and t.kind == tyGenericInst:
       result = getTypeDescAux(m, t, check)
     else:
-      let x = getUniqueType(etB)
-      result = getTypeForward(m, x)
-      pushType(m, x)
+      result = getTypeForward(m, t, hashType(t))
+      pushType(m, t)
   of tySequence:
-    let x = getUniqueType(etB)
-    result = getTypeForward(m, x) & "*"
-    pushType(m, x)
+    result = getTypeForward(m, t, hashType(t)) & "*"
+    pushType(m, t)
   else:
     result = getTypeDescAux(m, t, check)
 
 proc paramStorageLoc(param: PSym): TStorageLoc =
-  if param.typ.skipTypes({tyVar, tyTypeDesc}).kind notin {tyArray, tyOpenArray, tyVarargs, tyArrayConstr}:
+  if param.typ.skipTypes({tyVar, tyTypeDesc}).kind notin {
+          tyArray, tyOpenArray, tyVarargs}:
     result = OnStack
   else:
     result = OnUnknown
@@ -345,7 +362,7 @@ proc genProcParams(m: BModule, t: PType, rettype, params: var Rope,
     var param = t.n.sons[i].sym
     if isCompileTimeOnly(param.typ): continue
     if params != nil: add(params, ~", ")
-    fillLoc(param.loc, locParam, param.typ, mangleName(param),
+    fillLoc(param.loc, locParam, param.typ, mangleName(m, param),
             param.paramStorageLoc)
     if ccgIntroducedPtr(param):
       add(params, getTypeDescWeak(m, param.typ, check))
@@ -399,10 +416,6 @@ proc mangleRecFieldName(field: PSym, rectype: PType): Rope =
 proc genRecordFieldsAux(m: BModule, n: PNode,
                         accessExpr: Rope, rectype: PType,
                         check: var IntSet): Rope =
-  var
-    ae, uname, sname, a: Rope
-    k: PNode
-    field: PSym
   result = nil
   case n.kind
   of nkRecList:
@@ -411,18 +424,18 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
   of nkRecCase:
     if n.sons[0].kind != nkSym: internalError(n.info, "genRecordFieldsAux")
     add(result, genRecordFieldsAux(m, n.sons[0], accessExpr, rectype, check))
-    uname = rope(mangle(n.sons[0].sym.name.s) & 'U')
-    if accessExpr != nil: ae = "$1.$2" % [accessExpr, uname]
-    else: ae = uname
+    let uname = rope(mangle(n.sons[0].sym.name.s) & 'U')
+    let ae = if accessExpr != nil: "$1.$2" % [accessExpr, uname]
+             else: uname
     var unionBody: Rope = nil
     for i in countup(1, sonsLen(n) - 1):
       case n.sons[i].kind
       of nkOfBranch, nkElse:
-        k = lastSon(n.sons[i])
+        let k = lastSon(n.sons[i])
         if k.kind != nkSym:
-          sname = "S" & rope(i)
-          a = genRecordFieldsAux(m, k, "$1.$2" % [ae, sname], rectype,
-                                 check)
+          let sname = "S" & rope(i)
+          let a = genRecordFieldsAux(m, k, "$1.$2" % [ae, sname], rectype,
+                                     check)
           if a != nil:
             add(unionBody, "struct {")
             add(unionBody, a)
@@ -433,12 +446,12 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
     if unionBody != nil:
       addf(result, "union{$n$1} $2;$n", [unionBody, uname])
   of nkSym:
-    field = n.sym
+    let field = n.sym
     if field.typ.kind == tyVoid: return
     #assert(field.ast == nil)
-    sname = mangleRecFieldName(field, rectype)
-    if accessExpr != nil: ae = "$1.$2" % [accessExpr, sname]
-    else: ae = sname
+    let sname = mangleRecFieldName(field, rectype)
+    let ae = if accessExpr != nil: "$1.$2" % [accessExpr, sname]
+             else: sname
     fillLoc(field.loc, locField, field.typ, ae, OnUnknown)
     # for importcpp'ed objects, we only need to set field.loc, but don't
     # have to recurse via 'getTypeDescAux'. And not doing so prevents problems
@@ -462,6 +475,12 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
 proc getRecordFields(m: BModule, typ: PType, check: var IntSet): Rope =
   result = genRecordFieldsAux(m, typ.n, nil, typ, check)
 
+proc fillObjectFields*(m: BModule; typ: PType) =
+  # sometimes generic objects are not consistently merged. We patch over
+  # this fact here.
+  var check = initIntSet()
+  discard getRecordFields(m, typ, check)
+
 proc getRecordDesc(m: BModule, typ: PType, name: Rope,
                    check: var IntSet): Rope =
   # declare the record:
@@ -538,26 +557,31 @@ proc resolveStarsInCppType(typ: PType, idx, stars: int): PType =
       result = if result.kind == tyGenericInst: result.sons[1]
                else: result.elemType
 
-proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
+const
+  irrelevantForBackend = {tyGenericBody, tyGenericInst, tyGenericInvocation,
+                          tyDistinct, tyRange, tyStatic, tyAlias}
+
+proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope =
   # returns only the type's name
-  var t = getUniqueType(typ)
-  if t == nil: internalError("getTypeDescAux: t == nil")
+  var t = origTyp.skipTypes(irrelevantForBackend)
   if t.sym != nil: useHeader(m, t.sym)
-  result = getTypePre(m, t)
+  if t != origTyp and origTyp.sym != nil: useHeader(m, origTyp.sym)
+  let sig = hashType(origTyp)
+  result = getTypePre(m, t, sig)
   if result != nil: return
   if containsOrIncl(check, t.id):
-    if not (isImportedCppType(typ) or isImportedCppType(t)):
-      internalError("cannot generate C type for: " & typeToString(typ))
+    if not (isImportedCppType(origTyp) or isImportedCppType(t)):
+      internalError("cannot generate C type for: " & typeToString(origTyp))
     # XXX: this BUG is hard to fix -> we need to introduce helper structs,
     # but determining when this needs to be done is hard. We should split
     # C type generation into an analysis and a code generation phase somehow.
   case t.kind
   of tyRef, tyPtr, tyVar:
-    var star = if t.kind == tyVar and tfVarIsPtr notin typ.flags and
+    var star = if t.kind == tyVar and tfVarIsPtr notin origTyp.flags and
                     compileToCpp(m): "&" else: "*"
-    var et = typ.skipTypes(abstractInst).lastSon
+    var et = origTyp.skipTypes(abstractInst).lastSon
     var etB = et.skipTypes(abstractInst)
-    if etB.kind in {tyArrayConstr, tyArray, tyOpenArray, tyVarargs}:
+    if etB.kind in {tyArray, tyOpenArray, tyVarargs}:
       # this is correct! sets have no proper base type, so we treat
       # ``var set[char]`` in `getParamTypeDesc`
       et = elemType(etB)
@@ -569,33 +593,30 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
         result = getTypeDescAux(m, et, check) & star
       else:
         # no restriction! We have a forward declaration for structs
-        let x = getUniqueType(etB)
-        let name = getTypeForward(m, x)
+        let name = getTypeForward(m, et, hashType et)
         result = name & star
-        idTablePut(m.typeCache, t, result)
-        pushType(m, x)
+        m.typeCache[sig] = result
+        pushType(m, et)
     of tySequence:
       # no restriction! We have a forward declaration for structs
-      let x = getUniqueType(etB)
-      let name = getTypeForward(m, x)
+      let name = getTypeForward(m, et, hashType et)
       result = name & "*" & star
-      idTablePut(m.typeCache, t, result)
-      pushType(m, x)
+      m.typeCache[sig] = result
+      pushType(m, et)
     else:
       # else we have a strong dependency  :-(
       result = getTypeDescAux(m, et, check) & star
-      idTablePut(m.typeCache, t, result)
+      m.typeCache[sig] = result
   of tyOpenArray, tyVarargs:
     result = getTypeDescWeak(m, t.sons[0], check) & "*"
-    idTablePut(m.typeCache, t, result)
-  of tyRange, tyEnum:
-    let t = if t.kind == tyRange: t.lastSon else: t
-    result = cacheGetType(m.typeCache, t)
+    m.typeCache[sig] = result
+  of tyEnum:
+    result = cacheGetType(m.typeCache, sig)
     if result == nil:
-      result = getTypeName(t)
+      result = getTypeName(m, origTyp, sig)
       if not (isImportedCppType(t) or
           (sfImportc in t.sym.flags and t.sym.magic == mNone)):
-        idTablePut(m.typeCache, t, result)
+        m.typeCache[sig] = result
         var size: int
         if firstOrd(t) < 0:
           addf(m.s[cfsTypes], "typedef NI32 $1;$n", [result])
@@ -608,18 +629,19 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
           of 4: addf(m.s[cfsTypes], "typedef NI32 $1;$n", [result])
           of 8: addf(m.s[cfsTypes], "typedef NI64 $1;$n", [result])
           else: internalError(t.sym.info, "getTypeDescAux: enum")
-        let owner = hashOwner(t.sym)
-        if not gDebugInfo.hasEnum(t.sym.name.s, t.sym.info.line, owner):
-          var vals: seq[(string, int)] = @[]
-          for i in countup(0, t.n.len - 1):
-            assert(t.n.sons[i].kind == nkSym)
-            let field = t.n.sons[i].sym
-            vals.add((field.name.s, field.position.int))
-          gDebugInfo.registerEnum(EnumDesc(size: size, owner: owner, id: t.sym.id,
-            name: t.sym.name.s, values: vals))
+        when false:
+          let owner = hashOwner(t.sym)
+          if not gDebugInfo.hasEnum(t.sym.name.s, t.sym.info.line, owner):
+            var vals: seq[(string, int)] = @[]
+            for i in countup(0, t.n.len - 1):
+              assert(t.n.sons[i].kind == nkSym)
+              let field = t.n.sons[i].sym
+              vals.add((field.name.s, field.position.int))
+            gDebugInfo.registerEnum(EnumDesc(size: size, owner: owner, id: t.sym.id,
+              name: t.sym.name.s, values: vals))
   of tyProc:
-    result = getTypeName(t)
-    idTablePut(m.typeCache, t, result)
+    result = getTypeName(m, origTyp, sig)
+    m.typeCache[sig] = result
     var rettype, desc: Rope
     genProcParams(m, t, rettype, desc, check, true, true)
     if not isImportedType(t):
@@ -634,15 +656,15 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
   of tySequence:
     # we cannot use getTypeForward here because then t would be associated
     # with the name of the struct, not with the pointer to the struct:
-    result = cacheGetType(m.forwTypeCache, t)
+    result = cacheGetType(m.forwTypeCache, sig)
     if result == nil:
-      result = getTypeName(t)
+      result = getTypeName(m, origTyp, sig)
       if not isImportedType(t):
         addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
             [structOrUnion(t), result])
-      idTablePut(m.forwTypeCache, t, result)
-    assert(cacheGetType(m.typeCache, t) == nil)
-    idTablePut(m.typeCache, t, result & "*")
+      m.forwTypeCache[sig] = result
+    assert(cacheGetType(m.typeCache, sig) == nil)
+    m.typeCache[sig] = result & "*"
     if not isImportedType(t):
       if skipTypes(t.sons[0], typedescInst).kind != tyEmpty:
         const
@@ -656,21 +678,21 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
       else:
         result = rope("TGenericSeq")
     add(result, "*")
-  of tyArrayConstr, tyArray:
+  of tyArray:
     var n: BiggestInt = lengthOrd(t)
     if n <= 0: n = 1   # make an array of at least one element
-    result = getTypeName(t)
-    idTablePut(m.typeCache, t, result)
+    result = getTypeName(m, origTyp, sig)
+    m.typeCache[sig] = result
     if not isImportedType(t):
       let foo = getTypeDescAux(m, t.sons[1], check)
       addf(m.s[cfsTypes], "typedef $1 $2[$3];$n",
            [foo, result, rope(n)])
     else: addAbiCheck(m, t, result)
   of tyObject, tyTuple:
-    if isImportedCppType(t) and typ.kind == tyGenericInst:
+    if isImportedCppType(t) and origTyp.kind == tyGenericInst:
       # for instantiated templates we do not go through the type cache as the
       # the type cache is not aware of 'tyGenericInst'.
-      let cppName = getTypeName(t)
+      let cppName = getTypeName(m, t, sig)
       var i = 0
       var chunkStart = 0
       while i < cppName.data.len:
@@ -681,7 +703,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
             result.add cppName.data.substr(chunkStart, chunkEnd)
             chunkStart = i
 
-            let typeInSlot = resolveStarsInCppType(typ, idx + 1, stars)
+            let typeInSlot = resolveStarsInCppType(origTyp, idx + 1, stars)
             if typeInSlot == nil or typeInSlot.kind == tyVoid:
               result.add(~"void")
             else:
@@ -693,37 +715,53 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope =
         result.add cppName.data.substr(chunkStart)
       else:
         result = cppName & "<"
-        for i in 1 .. typ.len-2:
+        for i in 1 .. origTyp.len-2:
           if i > 1: result.add(" COMMA ")
-          result.add(getTypeDescAux(m, typ.sons[i], check))
+          result.add(getTypeDescAux(m, origTyp.sons[i], check))
         result.add("> ")
       # always call for sideeffects:
       assert t.kind != tyTuple
       discard getRecordDesc(m, t, result, check)
     else:
-      result = cacheGetType(m.forwTypeCache, t)
+      when false:
+        if t.sym != nil and t.sym.name.s == "KeyValuePair":
+          if t == origTyp:
+            echo "wtf: came here"
+            writeStackTrace()
+            quit 1
+      result = cacheGetType(m.forwTypeCache, sig)
       if result == nil:
-        result = getTypeName(t)
+        when false:
+          if t.sym != nil and t.sym.name.s == "KeyValuePair":
+            # or {sfImportc, sfExportc} * t.sym.flags == {}:
+            if t.loc.r != nil:
+              echo t.kind, " ", hashType t
+              echo origTyp.kind, " ", sig
+            assert t.loc.r == nil
+        result = getTypeName(m, origTyp, sig)
+        m.forwTypeCache[sig] = result
         if not isImportedType(t):
+          addf(m.s[cfsForwardTypes], "/* tyObject: $1 $2 $3 */", [rope typeToString origTyp,
+            rope t.id, rope m.module.id])
           addf(m.s[cfsForwardTypes], getForwardStructFormat(m),
              [structOrUnion(t), result])
-        idTablePut(m.forwTypeCache, t, result)
-      idTablePut(m.typeCache, t, result) # always call for sideeffects:
+        assert m.forwTypeCache[sig] == result
+      m.typeCache[sig] = result # always call for sideeffects:
       let recdesc = if t.kind != tyTuple: getRecordDesc(m, t, result, check)
                     else: getTupleDesc(m, t, result, check)
       if not isImportedType(t):
         add(m.s[cfsTypes], recdesc)
       elif tfIncompleteStruct notin t.flags: addAbiCheck(m, t, result)
   of tySet:
-    result = getTypeName(t.lastSon) & "Set"
-    idTablePut(m.typeCache, t, result)
+    result = getTypeName(m, t.lastSon, hashType t.lastSon) & "_Set"
+    m.typeCache[sig] = result
     if not isImportedType(t):
       let s = int(getSize(t))
       case s
       of 1, 2, 4, 8: addf(m.s[cfsTypes], "typedef NU$2 $1;$n", [result, rope(s*8)])
       else: addf(m.s[cfsTypes], "typedef NU8 $1[$2];$n",
              [result, rope(getSize(t))])
-  of tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc:
+  of tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias:
     result = getTypeDescAux(m, lastSon(t), check)
   else:
     internalError("getTypeDescAux(" & $t.kind & ')')
@@ -776,7 +814,7 @@ proc genProcHeader(m: BModule, prc: PSym): Rope =
   elif prc.typ.callConv == ccInline:
     result.add "static "
   var check = initIntSet()
-  fillLoc(prc.loc, locProc, prc.typ, mangleName(prc), OnUnknown)
+  fillLoc(prc.loc, locProc, prc.typ, mangleName(m, prc), OnUnknown)
   genProcParams(m, prc.typ, rettype, params, check)
   # careful here! don't access ``prc.ast`` as that could reload large parts of
   # the object graph!
@@ -804,8 +842,7 @@ proc genTypeInfoAuxBase(m: BModule; typ, origType: PType; name, base: Rope) =
 
   var size: Rope
   if tfIncompleteStruct in typ.flags: size = rope"void*"
-  elif m.compileToCpp: size = getTypeDesc(m, origType)
-  else: size = getTypeDesc(m, typ)
+  else: size = getTypeDesc(m, origType)
   addf(m.s[cfsTypeInit3],
        "$1.size = sizeof($2);$n" & "$1.kind = $3;$n" & "$1.base = $4;$n",
        [name, size, rope(nimtypeKind), base])
@@ -824,7 +861,7 @@ proc genTypeInfoAuxBase(m: BModule; typ, origType: PType; name, base: Rope) =
 
 proc genTypeInfoAux(m: BModule, typ, origType: PType, name: Rope) =
   var base: Rope
-  if (sonsLen(typ) > 0) and (typ.sons[0] != nil):
+  if sonsLen(typ) > 0 and typ.sons[0] != nil:
     var x = typ.sons[0]
     if typ.kind == tyObject: x = x.skipTypes(skipPtrs)
     base = genTypeInfo(m, x)
@@ -839,26 +876,26 @@ proc discriminatorTableName(m: BModule, objtype: PType, d: PSym): Rope =
     objtype = objtype.sons[0]
   if objtype.sym == nil:
     internalError(d.info, "anonymous obj with discriminator")
-  result = "NimDT_$1_$2" % [rope(objtype.id), rope(d.name.s.mangle)]
+  result = "NimDT_$1_$2" % [rope($hashType(objtype)), rope(d.name.s.mangle)]
 
 proc discriminatorTableDecl(m: BModule, objtype: PType, d: PSym): Rope =
   discard cgsym(m, "TNimNode")
   var tmp = discriminatorTableName(m, objtype, d)
   result = "TNimNode* $1[$2];$n" % [tmp, rope(lengthOrd(d.typ)+1)]
 
-proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
+proc genObjectFields(m: BModule, typ, origType: PType, n: PNode, expr: Rope) =
   case n.kind
   of nkRecList:
     var L = sonsLen(n)
     if L == 1:
-      genObjectFields(m, typ, n.sons[0], expr)
+      genObjectFields(m, typ, origType, n.sons[0], expr)
     elif L > 0:
       var tmp = getTempName(m)
       addf(m.s[cfsTypeInit1], "static TNimNode* $1[$2];$n", [tmp, rope(L)])
       for i in countup(0, L-1):
         var tmp2 = getNimNode(m)
         addf(m.s[cfsTypeInit3], "$1[$2] = &$3;$n", [tmp, rope(i), tmp2])
-        genObjectFields(m, typ, n.sons[i], tmp2)
+        genObjectFields(m, typ, origType, n.sons[i], tmp2)
       addf(m.s[cfsTypeInit3], "$1.len = $2; $1.kind = 2; $1.sons = &$3[0];$n",
            [expr, rope(L), tmp])
     else:
@@ -872,7 +909,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
     addf(m.s[cfsTypeInit3], "$1.kind = 3;$n" &
         "$1.offset = offsetof($2, $3);$n" & "$1.typ = $4;$n" &
         "$1.name = $5;$n" & "$1.sons = &$6[0];$n" &
-        "$1.len = $7;$n", [expr, getTypeDesc(m, typ), field.loc.r,
+        "$1.len = $7;$n", [expr, getTypeDesc(m, origType), field.loc.r,
                            genTypeInfo(m, field.typ),
                            makeCString(field.name.s),
                            tmp, rope(L)])
@@ -880,7 +917,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
     for i in countup(1, sonsLen(n)-1):
       var b = n.sons[i]           # branch
       var tmp2 = getNimNode(m)
-      genObjectFields(m, typ, lastSon(b), tmp2)
+      genObjectFields(m, typ, origType, lastSon(b), tmp2)
       case b.kind
       of nkOfBranch:
         if sonsLen(b) < 2:
@@ -904,7 +941,7 @@ proc genObjectFields(m: BModule, typ: PType, n: PNode, expr: Rope) =
     if field.bitsize == 0:
       addf(m.s[cfsTypeInit3], "$1.kind = 1;$n" &
           "$1.offset = offsetof($2, $3);$n" & "$1.typ = $4;$n" &
-          "$1.name = $5;$n", [expr, getTypeDesc(m, typ),
+          "$1.name = $5;$n", [expr, getTypeDesc(m, origType),
           field.loc.r, genTypeInfo(m, field.typ), makeCString(field.name.s)])
   else: internalError(n.info, "genObjectFields")
 
@@ -913,7 +950,7 @@ proc genObjectInfo(m: BModule, typ, origType: PType, name: Rope) =
   else: genTypeInfoAuxBase(m, typ, origType, name, rope("0"))
   var tmp = getNimNode(m)
   if not isImportedCppType(typ):
-    genObjectFields(m, typ, typ.n, tmp)
+    genObjectFields(m, typ, origType, typ.n, tmp)
   addf(m.s[cfsTypeInit3], "$1.node = &$2;$n", [name, tmp])
   var t = typ.sons[0]
   while t != nil:
@@ -921,7 +958,7 @@ proc genObjectInfo(m: BModule, typ, origType: PType, name: Rope) =
     t.flags.incl tfObjHasKids
     t = t.sons[0]
 
-proc genTupleInfo(m: BModule, typ: PType, name: Rope) =
+proc genTupleInfo(m: BModule, typ, origType: PType, name: Rope) =
   genTypeInfoAuxBase(m, typ, typ, name, rope("0"))
   var expr = getNimNode(m)
   var length = sonsLen(typ)
@@ -936,7 +973,7 @@ proc genTupleInfo(m: BModule, typ: PType, name: Rope) =
           "$1.offset = offsetof($2, Field$3);$n" &
           "$1.typ = $4;$n" &
           "$1.name = \"Field$3\";$n",
-           [tmp2, getTypeDesc(m, typ), rope(i), genTypeInfo(m, a)])
+           [tmp2, getTypeDesc(m, origType), rope(i), genTypeInfo(m, a)])
     addf(m.s[cfsTypeInit3], "$1.len = $2; $1.kind = 2; $1.sons = &$3[0];$n",
          [expr, rope(length), tmp])
   else:
@@ -1018,17 +1055,20 @@ proc genDeepCopyProc(m: BModule; s: PSym; result: Rope) =
 
 proc genTypeInfo(m: BModule, t: PType): Rope =
   let origType = t
-  var t = getUniqueType(t)
-  result = "NTI$1" % [rope(t.id)]
-  if containsOrIncl(m.typeInfoMarker, t.id):
+  var t = skipTypes(origType, irrelevantForBackend)
+
+  let sig = hashType(origType)
+  result = m.typeInfoMarker.getOrDefault(sig)
+  if result != nil:
     return "(&".rope & result & ")".rope
 
-  # getUniqueType doesn't skip tyDistinct when that has an overriden operation:
-  while t.kind == tyDistinct: t = t.lastSon
+  result = "NTI$1" % [rope($sig)]
+  m.typeInfoMarker[sig] = result
+
   let owner = t.skipTypes(typedescPtrs).owner.getModule
   if owner != m.module:
     # make sure the type info is created in the owner module
-    discard genTypeInfo(owner.bmod, t)
+    discard genTypeInfo(owner.bmod, origType)
     # reference the type info as extern here
     discard cgsym(m, "TNimType")
     discard cgsym(m, "TNimNode")
@@ -1046,14 +1086,15 @@ proc genTypeInfo(m: BModule, t: PType): Rope =
     if t.callConv != ccClosure:
       genTypeInfoAuxBase(m, t, t, result, rope"0")
     else:
-      genTupleInfo(m, fakeClosureType(t.owner), result)
+      let x = fakeClosureType(t.owner)
+      genTupleInfo(m, x, x, result)
   of tySequence, tyRef:
     genTypeInfoAux(m, t, t, result)
     if gSelectedGC >= gcMarkAndSweep:
-      let markerProc = genTraverseProc(m, t, tiNew)
+      let markerProc = genTraverseProc(m, origType, sig, tiNew)
       addf(m.s[cfsTypeInit3], "$1.marker = $2;$n", [result, markerProc])
   of tyPtr, tyRange: genTypeInfoAux(m, t, t, result)
-  of tyArrayConstr, tyArray: genArrayInfo(m, t, result)
+  of tyArray: genArrayInfo(m, t, result)
   of tySet: genSetInfo(m, t, result)
   of tyEnum: genEnumInfo(m, t, result)
   of tyObject: genObjectInfo(m, t, origType, result)
@@ -1062,7 +1103,7 @@ proc genTypeInfo(m: BModule, t: PType): Rope =
     # else:
     # BUGFIX: use consistently RTTI without proper field names; otherwise
     # results are not deterministic!
-    genTupleInfo(m, t, result)
+    genTupleInfo(m, t, origType, result)
   else: internalError("genTypeInfo(" & $t.kind & ')')
   if t.deepCopy != nil:
     genDeepCopyProc(m, t.deepCopy, result)
diff --git a/compiler/ccgutils.nim b/compiler/ccgutils.nim
index 2216cb4fd..4d6ba858c 100644
--- a/compiler/ccgutils.nim
+++ b/compiler/ccgutils.nim
@@ -85,87 +85,77 @@ proc slowSearch(key: PType; k: TTypeKind): PType =
 
 proc getUniqueType*(key: PType): PType =
   # this is a hotspot in the compiler!
-  if key == nil: return
-  var k = key.kind
-  case k
-  of tyBool, tyChar, tyInt..tyUInt64:
-    # no canonicalization for integral types, so that e.g. ``pid_t`` is
-    # produced instead of ``NI``.
-    result = key
-  of  tyEmpty, tyNil, tyExpr, tyStmt, tyPointer, tyString,
-      tyCString, tyNone, tyVoid:
-    result = gCanonicalTypes[k]
-    if result == nil:
-      gCanonicalTypes[k] = key
-      result = key
-  of tyTypeDesc, tyTypeClasses, tyGenericParam, tyFromExpr, tyFieldAccessor:
-    if key.sym != nil:
-      internalError(key.sym.info, "metatype not eliminated")
-    else:
-      internalError("metatype not eliminated")
-  of tyDistinct:
-    if key.deepCopy != nil: result = key
-    else: result = getUniqueType(lastSon(key))
-  of tyGenericInst, tyOrdinal, tyStatic:
-    result = getUniqueType(lastSon(key))
-    #let obj = lastSon(key)
-    #if obj.sym != nil and obj.sym.name.s == "TOption":
-    #  echo "for ", typeToString(key), " I returned "
-    #  debug result
-  of tyPtr, tyRef, tyVar:
-    let elemType = lastSon(key)
-    if elemType.kind in {tyBool, tyChar, tyInt..tyUInt64}:
-      # no canonicalization for integral types, so that e.g. ``ptr pid_t`` is
-      # produced instead of ``ptr NI``.
+  result = key
+  when false:
+    if key == nil: return
+    var k = key.kind
+    case k
+    of tyBool, tyChar, tyInt..tyUInt64:
+      # no canonicalization for integral types, so that e.g. ``pid_t`` is
+      # produced instead of ``NI``.
       result = key
-    else:
+    of  tyEmpty, tyNil, tyExpr, tyStmt, tyPointer, tyString,
+        tyCString, tyNone, tyVoid:
+      result = gCanonicalTypes[k]
+      if result == nil:
+        gCanonicalTypes[k] = key
+        result = key
+    of tyTypeDesc, tyTypeClasses, tyGenericParam, tyFromExpr, tyFieldAccessor:
+      if key.sym != nil:
+        internalError(key.sym.info, "metatype not eliminated")
+      else:
+        internalError("metatype not eliminated")
+    of tyDistinct:
+      if key.deepCopy != nil: result = key
+      else: result = getUniqueType(lastSon(key))
+    of tyGenericInst, tyOrdinal, tyStatic, tyAlias:
+      result = getUniqueType(lastSon(key))
+      #let obj = lastSon(key)
+      #if obj.sym != nil and obj.sym.name.s == "TOption":
+      #  echo "for ", typeToString(key), " I returned "
+      #  debug result
+    of tyPtr, tyRef, tyVar:
+      let elemType = lastSon(key)
+      if elemType.kind in {tyBool, tyChar, tyInt..tyUInt64}:
+        # no canonicalization for integral types, so that e.g. ``ptr pid_t`` is
+        # produced instead of ``ptr NI``.
+        result = key
+      else:
+        result = slowSearch(key, k)
+    of tyGenericInvocation, tyGenericBody,
+       tyOpenArray, tyArray, tySet, tyRange, tyTuple,
+       tySequence, tyForward, tyVarargs, tyProxy:
+      # we have to do a slow linear search because types may need
+      # to be compared by their structure:
       result = slowSearch(key, k)
-  of tyArrayConstr, tyGenericInvocation, tyGenericBody,
-     tyOpenArray, tyArray, tySet, tyRange, tyTuple,
-     tySequence, tyForward, tyVarargs, tyProxy:
-    # we have to do a slow linear search because types may need
-    # to be compared by their structure:
-    result = slowSearch(key, k)
-  of tyObject:
-    if tfFromGeneric notin key.flags:
-      # fast case; lookup per id suffices:
+    of tyObject:
+      if tfFromGeneric notin key.flags:
+        # fast case; lookup per id suffices:
+        result = PType(idTableGet(gTypeTable[k], key))
+        if result == nil:
+          idTablePut(gTypeTable[k], key, key)
+          result = key
+      else:
+        # ugly slow case: need to compare by structure
+        if idTableHasObjectAsKey(gTypeTable[k], key): return key
+        for h in countup(0, high(gTypeTable[k].data)):
+          var t = PType(gTypeTable[k].data[h].key)
+          if t != nil and sameBackendType(t, key):
+            return t
+        idTablePut(gTypeTable[k], key, key)
+        result = key
+    of tyEnum:
       result = PType(idTableGet(gTypeTable[k], key))
       if result == nil:
         idTablePut(gTypeTable[k], key, key)
         result = key
-    else:
-      # ugly slow case: need to compare by structure
-      if idTableHasObjectAsKey(gTypeTable[k], key): return key
-      for h in countup(0, high(gTypeTable[k].data)):
-        var t = PType(gTypeTable[k].data[h].key)
-        if t != nil and sameBackendType(t, key):
-          return t
-      idTablePut(gTypeTable[k], key, key)
-      result = key
-  of tyEnum:
-    result = PType(idTableGet(gTypeTable[k], key))
-    if result == nil:
-      idTablePut(gTypeTable[k], key, key)
-      result = key
-  of tyProc:
-    if key.callConv != ccClosure:
-      result = key
-    else:
-      # ugh, we need the canon here:
-      result = slowSearch(key, k)
-  of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("getUniqueType")
-
-proc tableGetType*(tab: TIdTable, key: PType): RootRef =
-  # returns nil if we need to declare this type
-  result = idTableGet(tab, key)
-  if (result == nil) and (tab.counter > 0):
-    # we have to do a slow linear search because types may need
-    # to be compared by their structure:
-    for h in countup(0, high(tab.data)):
-      var t = PType(tab.data[h].key)
-      if t != nil:
-        if sameType(t, key):
-          return tab.data[h].val
+    of tyProc:
+      if key.callConv != ccClosure:
+        result = key
+      else:
+        # ugh, we need the canon here:
+        result = slowSearch(key, k)
+    of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("getUniqueType")
 
 proc makeSingleLineCString*(s: string): string =
   result = "\""
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index 6e18c8389..db7070941 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -14,7 +14,7 @@ import
   nversion, nimsets, msgs, securehash, bitsets, idents, lists, types,
   ccgutils, os, ropes, math, passes, rodread, wordrecg, treetab, cgmeth,
   condsyms, rodutils, renderer, idgen, cgendata, ccgmerge, semfold, aliases,
-  lowerings, semparallel
+  lowerings, semparallel, tables
 
 from modulegraphs import ModuleGraph
 
@@ -62,7 +62,7 @@ proc fillLoc(a: var TLoc, k: TLocKind, typ: PType, r: Rope, s: TStorageLoc) =
 proc isSimpleConst(typ: PType): bool =
   let t = skipTypes(typ, abstractVar)
   result = t.kind notin
-      {tyTuple, tyObject, tyArray, tyArrayConstr, tySet, tySequence} and not
+      {tyTuple, tyObject, tyArray, tySet, tySequence} and not
       (t.kind == tyProc and t.callConv == ccClosure)
 
 proc useStringh(m: BModule) =
@@ -190,21 +190,24 @@ proc freshLineInfo(p: BProc; info: TLineInfo): bool =
     result = true
 
 proc genLineDir(p: BProc, t: PNode) =
-  var line = t.info.safeLineNm
+  let info = t.info
+  #if t.kind in nkCallKinds+{nkStmtListExpr} and t.len > 1: t[1].info
+  #else: t.info
+  var line = info.safeLineNm
   if optEmbedOrigSrc in gGlobalOptions:
-    add(p.s(cpsStmts), ~"//" & t.info.sourceLine & rnl)
-  genCLineDir(p.s(cpsStmts), t.info.toFullPath, line)
+    add(p.s(cpsStmts), ~"//" & info.sourceLine & rnl)
+  genCLineDir(p.s(cpsStmts), info.toFullPath, line)
   if ({optStackTrace, optEndb} * p.options == {optStackTrace, optEndb}) and
       (p.prc == nil or sfPure notin p.prc.flags):
-    if freshLineInfo(p, t.info):
+    if freshLineInfo(p, info):
       linefmt(p, cpsStmts, "#endb($1, $2);$n",
-              line.rope, makeCString(toFilename(t.info)))
+              line.rope, makeCString(toFilename(info)))
   elif ({optLineTrace, optStackTrace} * p.options ==
       {optLineTrace, optStackTrace}) and
-      (p.prc == nil or sfPure notin p.prc.flags) and t.info.fileIndex >= 0:
-    if freshLineInfo(p, t.info):
+      (p.prc == nil or sfPure notin p.prc.flags) and info.fileIndex >= 0:
+    if freshLineInfo(p, info):
       linefmt(p, cpsStmts, "nimln($1, $2);$n",
-              line.rope, t.info.quotedFilename)
+              line.rope, info.quotedFilename)
 
 proc postStmtActions(p: BProc) {.inline.} =
   add(p.s(cpsStmts), p.module.injectStmt)
@@ -263,7 +266,8 @@ type
 proc genRefAssign(p: BProc, dest, src: TLoc, flags: TAssignmentFlags)
 
 proc isComplexValueType(t: PType): bool {.inline.} =
-  result = t.kind in {tyArray, tyArrayConstr, tySet, tyTuple, tyObject} or
+  let t = t.skipTypes(abstractInst)
+  result = t.kind in {tyArray, tySet, tyTuple, tyObject} or
     (t.kind == tyProc and t.callConv == ccClosure)
 
 proc resetLoc(p: BProc, loc: var TLoc) =
@@ -296,7 +300,7 @@ proc resetLoc(p: BProc, loc: var TLoc) =
       genObjectInit(p, cpsStmts, loc.t, loc, true)
 
 proc constructLoc(p: BProc, loc: TLoc, isTemp = false) =
-  let typ = skipTypes(loc.t, abstractRange)
+  let typ = loc.t
   if not isComplexValueType(typ):
     linefmt(p, cpsStmts, "$1 = ($2)0;$n", rdLoc(loc),
       getTypeDesc(p.module, typ))
@@ -325,13 +329,9 @@ proc initLocalVar(p: BProc, v: PSym, immediateAsgn: bool) =
 proc getTemp(p: BProc, t: PType, result: var TLoc; needsInit=false) =
   inc(p.labels)
   result.r = "LOC" & rope(p.labels)
-  #addf(p.blocks[0].sections[cpsLocals],
-  #   "$1 $2;$n", [getTypeDesc(p.module, t), result.r])
   linefmt(p, cpsLocals, "$1 $2;$n", getTypeDesc(p.module, t), result.r)
   result.k = locTemp
-  #result.a = - 1
   result.t = t
-  #result.t = getUniqueType(t)
   result.s = OnStack
   result.flags = {}
   constructLoc(p, result, not needsInit)
@@ -359,9 +359,9 @@ proc localDebugInfo(p: BProc, s: PSym) =
 
 proc localVarDecl(p: BProc; s: PSym): Rope =
   if s.loc.k == locNone:
-    fillLoc(s.loc, locLocalVar, s.typ, mangleName(s), OnStack)
+    fillLoc(s.loc, locLocalVar, s.typ, mangleName(p.module, s), OnStack)
     if s.kind == skLet: incl(s.loc.flags, lfNoDeepCopy)
-  result = getTypeDesc(p.module, s.loc.t)
+  result = getTypeDesc(p.module, s.typ)
   if s.constraint.isNil:
     if sfRegister in s.flags: add(result, " register")
     #elif skipTypes(s.typ, abstractInst).kind in GcTypeKinds:
@@ -387,7 +387,7 @@ proc mangleDynLibProc(sym: PSym): Rope
 
 proc assignGlobalVar(p: BProc, s: PSym) =
   if s.loc.k == locNone:
-    fillLoc(s.loc, locGlobalVar, s.typ, mangleName(s), OnHeap)
+    fillLoc(s.loc, locGlobalVar, s.typ, mangleName(p.module, s), OnHeap)
 
   if lfDynamicLib in s.loc.flags:
     var q = findPendingModule(p.module, s)
@@ -426,9 +426,9 @@ proc assignParam(p: BProc, s: PSym) =
   assert(s.loc.r != nil)
   localDebugInfo(p, s)
 
-proc fillProcLoc(sym: PSym) =
+proc fillProcLoc(m: BModule; sym: PSym) =
   if sym.loc.k == locNone:
-    fillLoc(sym.loc, locProc, sym.typ, mangleName(sym), OnStack)
+    fillLoc(sym.loc, locProc, sym.typ, mangleName(m, sym), OnStack)
 
 proc getLabel(p: BProc): TLabel =
   inc(p.labels)
@@ -729,7 +729,7 @@ proc genProcPrototype(m: BModule, sym: PSym) =
     add(m.s[cfsProcHeaders], rfmt(nil, "$1;$n", header))
 
 proc genProcNoForward(m: BModule, prc: PSym) =
-  fillProcLoc(prc)
+  fillProcLoc(m, prc)
   useHeader(m, prc)
   if lfImportCompilerProc in prc.loc.flags:
     # dependency to a compilerproc:
@@ -757,7 +757,7 @@ proc requestConstImpl(p: BProc, sym: PSym) =
   var m = p.module
   useHeader(m, sym)
   if sym.loc.k == locNone:
-    fillLoc(sym.loc, locData, sym.typ, mangleName(sym), OnStatic)
+    fillLoc(sym.loc, locData, sym.typ, mangleName(p.module, sym), OnStatic)
   if lfNoDecl in sym.loc.flags: return
   # declare implementation:
   var q = findPendingModule(m, sym)
@@ -778,7 +778,7 @@ proc isActivated(prc: PSym): bool = prc.typ != nil
 
 proc genProc(m: BModule, prc: PSym) =
   if sfBorrow in prc.flags or not isActivated(prc): return
-  fillProcLoc(prc)
+  fillProcLoc(m, prc)
   if sfForward in prc.flags: addForwardedProc(m, prc)
   else:
     genProcNoForward(m, prc)
@@ -792,7 +792,7 @@ proc genProc(m: BModule, prc: PSym) =
 proc genVarPrototypeAux(m: BModule, sym: PSym) =
   #assert(sfGlobal in sym.flags)
   useHeader(m, sym)
-  fillLoc(sym.loc, locGlobalVar, sym.typ, mangleName(sym), OnHeap)
+  fillLoc(sym.loc, locGlobalVar, sym.typ, mangleName(m, sym), OnHeap)
   if (lfNoDecl in sym.loc.flags) or containsOrIncl(m.declaredThings, sym.id):
     return
   if sym.owner.id != m.module.id:
@@ -1094,10 +1094,10 @@ proc rawNewModule(module: PSym, filename: string): BModule =
   result.declaredProtos = initIntSet()
   result.cfilename = filename
   result.filename = filename
-  initIdTable(result.typeCache)
-  initIdTable(result.forwTypeCache)
+  result.typeCache = initTable[SigHash, Rope]()
+  result.forwTypeCache = initTable[SigHash, Rope]()
   result.module = module
-  result.typeInfoMarker = initIntSet()
+  result.typeInfoMarker = initTable[SigHash, Rope]()
   result.initProc = newProc(nil, result)
   result.initProc.options = initProcOptions(result)
   result.preInitProc = newPreInitProc(result)
@@ -1123,7 +1123,7 @@ proc resetModule*(m: BModule) =
   # away all the data that was written to disk
   initLinkedList(m.headerFiles)
   m.declaredProtos = initIntSet()
-  initIdTable(m.forwTypeCache)
+  m.forwTypeCache = initTable[SigHash, Rope]()
   m.initProc = newProc(nil, m)
   m.initProc.options = initProcOptions(m)
   m.preInitProc = newPreInitProc(m)
diff --git a/compiler/cgendata.nim b/compiler/cgendata.nim
index faeea7afb..c8146fc5f 100644
--- a/compiler/cgendata.nim
+++ b/compiler/cgendata.nim
@@ -10,7 +10,8 @@
 ## This module contains the data structures for the C code generation phase.
 
 import
-  ast, astalgo, ropes, passes, options, intsets, lists, platform
+  ast, astalgo, ropes, passes, options, intsets, lists, platform, sighashes,
+  tables
 
 from msgs import TLineInfo
 
@@ -93,6 +94,7 @@ type
     gcFrameType*: Rope        # the struct {} we put the GC markers into
 
   TTypeSeq* = seq[PType]
+  TypeCache* = Table[SigHash, Rope]
 
   Codegenflag* = enum
     preventStackTrace,  # true if stack traces need to be prevented
@@ -110,12 +112,12 @@ type
     cfilename*: string        # filename of the module (including path,
                               # without extension)
     tmpBase*: Rope            # base for temp identifier generation
-    typeCache*: TIdTable      # cache the generated types
-    forwTypeCache*: TIdTable  # cache for forward declarations of types
+    typeCache*: TypeCache     # cache the generated types
+    forwTypeCache*: TypeCache # cache for forward declarations of types
     declaredThings*: IntSet   # things we have declared in this .c file
     declaredProtos*: IntSet   # prototypes we have declared in this .c file
     headerFiles*: TLinkedList # needed headers to include
-    typeInfoMarker*: IntSet   # needed for generating type information
+    typeInfoMarker*: TypeCache # needed for generating type information
     initProc*: BProc          # code for init procedure
     postInitProc*: BProc      # code to be executed after the init proc
     preInitProc*: BProc       # code executed before the init proc
diff --git a/compiler/cgmeth.nim b/compiler/cgmeth.nim
index 5f0d71cc6..eda80be30 100644
--- a/compiler/cgmeth.nim
+++ b/compiler/cgmeth.nim
@@ -61,8 +61,8 @@ proc sameMethodBucket(a, b: PSym): MethodResult =
     var aa = a.typ.sons[i]
     var bb = b.typ.sons[i]
     while true:
-      aa = skipTypes(aa, {tyGenericInst})
-      bb = skipTypes(bb, {tyGenericInst})
+      aa = skipTypes(aa, {tyGenericInst, tyAlias})
+      bb = skipTypes(bb, {tyGenericInst, tyAlias})
       if aa.kind == bb.kind and aa.kind in {tyVar, tyPtr, tyRef}:
         aa = aa.lastSon
         bb = bb.lastSon
diff --git a/compiler/debuginfo.nim b/compiler/debuginfo.nim
index 8589730b9..7729a6a51 100644
--- a/compiler/debuginfo.nim
+++ b/compiler/debuginfo.nim
@@ -7,18 +7,19 @@
 #    distribution, for details about the copyright.
 #
 
-## The compiler can generate debuginfo to help debuggers in translating back from C/C++/JS code
-## to Nim. The data structure has been designed to produce something useful with Nim's marshal
-## module.
+## The compiler can generate debuginfo to help debuggers in translating back
+## from C/C++/JS code to Nim. The data structure has been designed to produce
+## something useful with Nim's marshal module.
+
+import sighashes
 
 type
-  FilenameHash* = uint32
   FilenameMapping* = object
     package*, file*: string
-    mangled*: FilenameHash
+    mangled*: SigHash
   EnumDesc* = object
     size*: int
-    owner*: FilenameHash
+    owner*: SigHash
     id*: int
     name*: string
     values*: seq[(string, int)]
@@ -28,11 +29,7 @@ type
     enums*: seq[EnumDesc]
     conflicts*: bool
 
-proc sdbmHash(hash: FilenameHash, c: char): FilenameHash {.inline.} =
-  return FilenameHash(c) + (hash shl 6) + (hash shl 16) - hash
-
-proc sdbmHash(package, file: string): FilenameHash =
-  template `&=`(x, c) = x = sdbmHash(x, c)
+proc sdbmHash(package, file: string): SigHash =
   result = 0
   for i in 0..<package.len:
     result &= package[i]
@@ -40,7 +37,7 @@ proc sdbmHash(package, file: string): FilenameHash =
   for i in 0..<file.len:
     result &= file[i]
 
-proc register*(self: var DebugInfo; package, file: string): FilenameHash =
+proc register*(self: var DebugInfo; package, file: string): SigHash =
   result = sdbmHash(package, file)
   for f in self.files:
     if f.mangled == result:
@@ -49,7 +46,7 @@ proc register*(self: var DebugInfo; package, file: string): FilenameHash =
       break
   self.files.add(FilenameMapping(package: package, file: file, mangled: result))
 
-proc hasEnum*(self: DebugInfo; ename: string; id: int; owner: FilenameHash): bool =
+proc hasEnum*(self: DebugInfo; ename: string; id: int; owner: SigHash): bool =
   for en in self.enums:
     if en.owner == owner and en.name == ename and en.id == id: return true
 
diff --git a/compiler/evalffi.nim b/compiler/evalffi.nim
index 75394c2f3..987cfaf42 100644
--- a/compiler/evalffi.nim
+++ b/compiler/evalffi.nim
@@ -45,7 +45,7 @@ var myerrno {.importc: "errno", header: "<errno.h>".}: cint ## error variable
 
 proc importcSymbol*(sym: PSym): PNode =
   let name = ropeToStr(sym.loc.r)
-  
+
   # the AST does not support untyped pointers directly, so we use an nkIntLit
   # that contains the address instead:
   result = newNodeIT(nkPtrLit, sym.info, sym.typ)
@@ -67,7 +67,7 @@ proc importcSymbol*(sym: PSym): PNode =
         let dllhandle = gDllCache.getDll(libcDll, sym.info)
         theAddr = dllhandle.symAddr(name)
     elif not lib.isNil:
-      let dllhandle = gDllCache.getDll(if lib.kind == libHeader: libcDll 
+      let dllhandle = gDllCache.getDll(if lib.kind == libHeader: libcDll
                                        else: lib.path.strVal, sym.info)
       theAddr = dllhandle.symAddr(name)
     if theAddr.isNil: globalError(sym.info, "cannot import: " & sym.name.s)
@@ -75,7 +75,7 @@ proc importcSymbol*(sym: PSym): PNode =
 
 proc mapType(t: ast.PType): ptr libffi.TType =
   if t == nil: return addr libffi.type_void
-  
+
   case t.kind
   of tyBool, tyEnum, tyChar, tyInt..tyInt64, tyUInt..tyUInt64, tySet:
     case t.getSize
@@ -87,9 +87,9 @@ proc mapType(t: ast.PType): ptr libffi.TType =
   of tyFloat, tyFloat64: result = addr libffi.type_double
   of tyFloat32: result = addr libffi.type_float
   of tyVar, tyPointer, tyPtr, tyRef, tyCString, tySequence, tyString, tyExpr,
-     tyStmt, tyTypeDesc, tyProc, tyArray, tyArrayConstr, tyStatic, tyNil:
+     tyStmt, tyTypeDesc, tyProc, tyArray, tyStatic, tyNil:
     result = addr libffi.type_pointer
-  of tyDistinct:
+  of tyDistinct, tyAlias:
     result = mapType(t.sons[0])
   else:
     result = nil
@@ -117,9 +117,9 @@ proc packSize(v: PNode, typ: PType): int =
       result = sizeof(pointer)
     else:
       result = sizeof(pointer) + packSize(v.sons[0], typ.lastSon)
-  of tyDistinct, tyGenericInst:
+  of tyDistinct, tyGenericInst, tyAlias:
     result = packSize(v, typ.sons[0])
-  of tyArray, tyArrayConstr:
+  of tyArray:
     # consider: ptr array[0..1000_000, int] which is common for interfacing;
     # we use the real length here instead
     if v.kind in {nkNilLit, nkPtrLit}:
@@ -136,7 +136,7 @@ proc getField(n: PNode; position: int): PSym =
   of nkRecList:
     for i in countup(0, sonsLen(n) - 1):
       result = getField(n.sons[i], position)
-      if result != nil: return 
+      if result != nil: return
   of nkRecCase:
     result = getField(n.sons[0], position)
     if result != nil: return
@@ -198,7 +198,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
   of tyFloat: awr(float, v.floatVal)
   of tyFloat32: awr(float32, v.floatVal)
   of tyFloat64: awr(float64, v.floatVal)
-  
+
   of tyPointer, tyProc,  tyCString, tyString:
     if v.kind == nkNilLit:
       # nothing to do since the memory is 0 initialized anyway
@@ -223,7 +223,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
       pack(v.sons[0], typ.lastSon, res +! sizeof(pointer))
       dec packRecCheck
       awr(pointer, res +! sizeof(pointer))
-  of tyArray, tyArrayConstr:
+  of tyArray:
     let baseSize = typ.sons[1].getSize
     for i in 0 .. <v.len:
       pack(v.sons[i], typ.sons[1], res +! i * baseSize)
@@ -231,7 +231,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
     packObject(v, typ, res)
   of tyNil:
     discard
-  of tyDistinct, tyGenericInst:
+  of tyDistinct, tyGenericInst, tyAlias:
     pack(v, typ.sons[0], res)
   else:
     globalError(v.info, "cannot map value to FFI " & typeToString(v.typ))
@@ -256,7 +256,7 @@ proc unpackObjectAdd(x: pointer, n, result: PNode) =
 proc unpackObject(x: pointer, typ: PType, n: PNode): PNode =
   # compute the field's offsets:
   discard typ.getSize
-  
+
   # iterate over any actual field of 'n' ... if n is nil we need to create
   # the nkPar node:
   if n.isNil:
@@ -329,7 +329,7 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode =
   template awi(kind, v: expr) {.immediate, dirty.} = aw(kind, v, intVal)
   template awf(kind, v: expr) {.immediate, dirty.} = aw(kind, v, floatVal)
   template aws(kind, v: expr) {.immediate, dirty.} = aw(kind, v, strVal)
-  
+
   case typ.kind
   of tyBool: awi(nkIntLit, rd(bool, x).ord)
   of tyChar: awi(nkCharLit, rd(char, x).ord)
@@ -378,7 +378,7 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode =
       globalError(n.info, "cannot map value from FFI " & typeToString(typ))
   of tyObject, tyTuple:
     result = unpackObject(x, typ, n)
-  of tyArray, tyArrayConstr:
+  of tyArray:
     result = unpackArray(x, typ, n)
   of tyCString, tyString:
     let p = rd(cstring, x)
@@ -388,15 +388,15 @@ proc unpack(x: pointer, typ: PType, n: PNode): PNode =
       aws(nkStrLit, $p)
   of tyNil:
     setNil()
-  of tyDistinct, tyGenericInst:
-    result = unpack(x, typ.sons[0], n)
+  of tyDistinct, tyGenericInst, tyAlias:
+    result = unpack(x, typ.lastSon, n)
   else:
     # XXX what to do with 'array' here?
     globalError(n.info, "cannot map value from FFI " & typeToString(typ))
 
 proc fficast*(x: PNode, destTyp: PType): PNode =
-  if x.kind == nkPtrLit and x.typ.kind in {tyPtr, tyRef, tyVar, tyPointer, 
-                                           tyProc, tyCString, tyString, 
+  if x.kind == nkPtrLit and x.typ.kind in {tyPtr, tyRef, tyVar, tyPointer,
+                                           tyProc, tyCString, tyString,
                                            tySequence}:
     result = newNodeIT(x.kind, x.info, destTyp)
     result.intVal = x.intVal
@@ -416,7 +416,7 @@ proc fficast*(x: PNode, destTyp: PType): PNode =
 
 proc callForeignFunction*(call: PNode): PNode =
   internalAssert call.sons[0].kind == nkPtrLit
-  
+
   var cif: TCif
   var sig: TParamList
   # use the arguments' types for varargs support:
@@ -424,12 +424,12 @@ proc callForeignFunction*(call: PNode): PNode =
     sig[i-1] = mapType(call.sons[i].typ)
     if sig[i-1].isNil:
       globalError(call.info, "cannot map FFI type")
-  
+
   let typ = call.sons[0].typ
   if prep_cif(cif, mapCallConv(typ.callConv, call.info), cuint(call.len-1),
               mapType(typ.sons[0]), sig) != OK:
     globalError(call.info, "error in FFI call")
-  
+
   var args: TArgList
   let fn = cast[pointer](call.sons[0].intVal)
   for i in 1 .. call.len-1:
@@ -440,8 +440,8 @@ proc callForeignFunction*(call: PNode): PNode =
                else: alloc(typ.sons[0].getSize.int)
 
   libffi.call(cif, fn, retVal, args)
-  
-  if retVal.isNil: 
+
+  if retVal.isNil:
     result = emptyNode
   else:
     result = unpack(retVal, typ.sons[0], nil)
@@ -456,7 +456,7 @@ proc callForeignFunction*(fn: PNode, fntyp: PType,
                           args: var TNodeSeq, start, len: int,
                           info: TLineInfo): PNode =
   internalAssert fn.kind == nkPtrLit
-  
+
   var cif: TCif
   var sig: TParamList
   for i in 0..len-1:
@@ -467,11 +467,11 @@ proc callForeignFunction*(fn: PNode, fntyp: PType,
       args[i+start].typ = aTyp
     sig[i] = mapType(aTyp)
     if sig[i].isNil: globalError(info, "cannot map FFI type")
-  
+
   if prep_cif(cif, mapCallConv(fntyp.callConv, info), cuint(len),
               mapType(fntyp.sons[0]), sig) != OK:
     globalError(info, "error in FFI call")
-  
+
   var cargs: TArgList
   let fn = cast[pointer](fn.intVal)
   for i in 0 .. len-1:
@@ -482,8 +482,8 @@ proc callForeignFunction*(fn: PNode, fntyp: PType,
                else: alloc(fntyp.sons[0].getSize.int)
 
   libffi.call(cif, fn, retVal, cargs)
-  
-  if retVal.isNil: 
+
+  if retVal.isNil:
     result = emptyNode
   else:
     result = unpack(retVal, fntyp.sons[0], nil)
diff --git a/compiler/extccomp.nim b/compiler/extccomp.nim
index 6f8b0b197..4eb68a771 100644
--- a/compiler/extccomp.nim
+++ b/compiler/extccomp.nim
@@ -16,7 +16,7 @@ import
   lists, ropes, os, strutils, osproc, platform, condsyms, options, msgs,
   securehash, streams
 
-from debuginfo import writeDebugInfo
+#from debuginfo import writeDebugInfo
 
 type
   TSystemCC* = enum
@@ -734,8 +734,8 @@ proc callCCompiler*(projectfile: string) =
       if not noAbsolutePaths():
         if not exefile.isAbsolute():
           exefile = joinPath(splitFile(projectfile).dir, exefile)
-      if optCDebug in gGlobalOptions:
-        writeDebugInfo(exefile.changeFileExt("ndb"))
+      #if optCDebug in gGlobalOptions:
+      #  writeDebugInfo(exefile.changeFileExt("ndb"))
       exefile = quoteShell(exefile)
       let linkOptions = getLinkOptions() & " " &
                         getConfigVar(cCompiler, ".options.linker")
diff --git a/compiler/guards.nim b/compiler/guards.nim
index 4e887d3e3..b53365617 100644
--- a/compiler/guards.nim
+++ b/compiler/guards.nim
@@ -207,7 +207,7 @@ proc lowBound*(x: PNode): PNode =
 
 proc highBound*(x: PNode): PNode =
   let typ = x.typ.skipTypes(abstractInst)
-  result = if typ.kind in {tyArrayConstr, tyArray}:
+  result = if typ.kind == tyArray:
              nkIntLit.newIntNode(lastOrd(typ))
            elif typ.kind == tySequence and x.kind == nkSym and
                x.sym.kind == skConst:
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index 028dd00f0..cf681d580 100644
--- a/compiler/jsgen.nim
+++ b/compiler/jsgen.nim
@@ -139,7 +139,7 @@ proc declareGlobal(p: PProc; id: int; r: Rope) =
     p.locals.addf("global $1;$n", [r])
 
 const
-  MappedToObject = {tyObject, tyArray, tyArrayConstr, tyTuple, tyOpenArray,
+  MappedToObject = {tyObject, tyArray, tyTuple, tyOpenArray,
     tySet, tyVarargs}
 
 proc mapType(typ: PType): TJSTypeKind =
@@ -153,18 +153,19 @@ proc mapType(typ: PType): TJSTypeKind =
   of tyPointer:
     # treat a tyPointer like a typed pointer to an array of bytes
     result = etyBaseIndex
-  of tyRange, tyDistinct, tyOrdinal, tyProxy: result = mapType(t.sons[0])
+  of tyRange, tyDistinct, tyOrdinal, tyProxy:
+    result = mapType(t.sons[0])
   of tyInt..tyInt64, tyUInt..tyUInt64, tyEnum, tyChar: result = etyInt
   of tyBool: result = etyBool
   of tyFloat..tyFloat128: result = etyFloat
   of tySet: result = etyObject # map a set to a table
   of tyString, tySequence: result = etySeq
-  of tyObject, tyArray, tyArrayConstr, tyTuple, tyOpenArray, tyVarargs:
+  of tyObject, tyArray, tyTuple, tyOpenArray, tyVarargs:
     result = etyObject
   of tyNil: result = etyNull
   of tyGenericInst, tyGenericParam, tyGenericBody, tyGenericInvocation,
      tyNone, tyFromExpr, tyForward, tyEmpty, tyFieldAccessor,
-     tyExpr, tyStmt, tyTypeDesc, tyTypeClasses, tyVoid:
+     tyExpr, tyStmt, tyTypeDesc, tyTypeClasses, tyVoid, tyAlias:
     result = etyNone
   of tyStatic:
     if t.n != nil: result = mapType(lastSon t)
@@ -796,8 +797,8 @@ proc generateHeader(p: PProc, typ: PType): Rope =
         add(result, name)
         add(result, "_Idx")
     elif not (i == 1 and param.name.s == "this"):
-      let k = param.typ.skipTypes({tyGenericInst}).kind
-      if k in { tyVar, tyRef, tyPtr, tyPointer }:
+      let k = param.typ.skipTypes({tyGenericInst, tyAlias}).kind
+      if k in {tyVar, tyRef, tyPtr, tyPointer}:
         add(result, "&")
       add(result, "$")
       add(result, name)
@@ -964,7 +965,7 @@ proc genArrayAddr(p: PProc, n: PNode, r: var TCompRes) =
   internalAssert a.typ != etyBaseIndex and b.typ != etyBaseIndex
   r.address = a.res
   var typ = skipTypes(m.sons[0].typ, abstractPtrs)
-  if typ.kind in {tyArray, tyArrayConstr}: first = firstOrd(typ.sons[0])
+  if typ.kind == tyArray: first = firstOrd(typ.sons[0])
   else: first = 0
   if optBoundsCheck in p.options and not isConstExpr(m.sons[1]):
     useMagic(p, "chckIndx")
@@ -985,8 +986,7 @@ proc genArrayAccess(p: PProc, n: PNode, r: var TCompRes) =
   var ty = skipTypes(n.sons[0].typ, abstractVarRange)
   if ty.kind in {tyRef, tyPtr}: ty = skipTypes(ty.lastSon, abstractVarRange)
   case ty.kind
-  of tyArray, tyArrayConstr, tyOpenArray, tySequence, tyString, tyCString,
-     tyVarargs:
+  of tyArray, tyOpenArray, tySequence, tyString, tyCString, tyVarargs:
     genArrayAddr(p, n, r)
   of tyTuple:
     if p.target == targetPHP:
@@ -1066,8 +1066,7 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) =
     else:
       let kindOfIndexedExpr = skipTypes(n.sons[0].sons[0].typ, abstractVarRange).kind
       case kindOfIndexedExpr
-      of tyArray, tyArrayConstr, tyOpenArray, tySequence, tyString, tyCString,
-          tyVarargs:
+      of tyArray, tyOpenArray, tySequence, tyString, tyCString, tyVarargs:
         genArrayAddr(p, n.sons[0], r)
       of tyTuple:
         genFieldAddr(p, n.sons[0], r)
@@ -1387,13 +1386,13 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope =
     result = putToSeq("0", indirect)
   of tyFloat..tyFloat128:
     result = putToSeq("0.0", indirect)
-  of tyRange, tyGenericInst:
+  of tyRange, tyGenericInst, tyAlias:
     result = createVar(p, lastSon(typ), indirect)
   of tySet:
     result = putToSeq("{}" | "array()", indirect)
   of tyBool:
     result = putToSeq("false", indirect)
-  of tyArray, tyArrayConstr:
+  of tyArray:
     let length = int(lengthOrd(t))
     let e = elemType(t)
     let jsTyp = arrayTypeForElemType(e)
diff --git a/compiler/jstypes.nim b/compiler/jstypes.nim
index 0aaf93579..b96a260b3 100644
--- a/compiler/jstypes.nim
+++ b/compiler/jstypes.nim
@@ -118,7 +118,7 @@ proc genEnumInfo(p: PProc, typ: PType, name: Rope) =
          [name, genTypeInfo(p, typ.sons[0])])
 
 proc genEnumInfoPHP(p: PProc; t: PType): Rope =
-  let t = t.skipTypes({tyGenericInst, tyDistinct})
+  let t = t.skipTypes({tyGenericInst, tyDistinct, tyAlias})
   result = "$$NTI$1" % [rope(t.id)]
   p.declareGlobal(t.id, result)
   if containsOrIncl(p.g.typeInfoGenerated, t.id): return
@@ -137,7 +137,7 @@ proc genEnumInfoPHP(p: PProc; t: PType): Rope =
 proc genTypeInfo(p: PProc, typ: PType): Rope =
   if p.target == targetPHP:
     return makeJSString(typeToString(typ, preferModuleInfo))
-  let t = typ.skipTypes({tyGenericInst, tyDistinct})
+  let t = typ.skipTypes({tyGenericInst, tyDistinct, tyAlias})
   result = "NTI$1" % [rope(t.id)]
   if containsOrIncl(p.g.typeInfoGenerated, t.id): return
   case t.kind
@@ -155,7 +155,7 @@ proc genTypeInfo(p: PProc, typ: PType): Rope =
     prepend(p.g.typeInfo, s)
     addf(p.g.typeInfo, "$1.base = $2;$n",
          [result, genTypeInfo(p, t.lastSon)])
-  of tyArrayConstr, tyArray:
+  of tyArray:
     var s =
       "var $1 = {size: 0,kind: $2,base: null,node: null,finalizer: null};$n" %
               [result, rope(ord(t.kind))]
diff --git a/compiler/lowerings.nim b/compiler/lowerings.nim
index 6a8eccb83..7da332335 100644
--- a/compiler/lowerings.nim
+++ b/compiler/lowerings.nim
@@ -441,7 +441,7 @@ proc newIntLit*(value: BiggestInt): PNode =
   result.typ = getSysType(tyInt)
 
 proc genHigh*(n: PNode): PNode =
-  if skipTypes(n.typ, abstractVar).kind in {tyArrayConstr, tyArray}:
+  if skipTypes(n.typ, abstractVar).kind == tyArray:
     result = newIntLit(lastOrd(skipTypes(n.typ, abstractVar)))
   else:
     result = newNodeI(nkCall, n.info, 2)
diff --git a/compiler/renderer.nim b/compiler/renderer.nim
index 926e67743..1602988dd 100644
--- a/compiler/renderer.nim
+++ b/compiler/renderer.nim
@@ -287,7 +287,8 @@ proc lsub(n: PNode): int
 proc litAux(n: PNode, x: BiggestInt, size: int): string =
   proc skip(t: PType): PType =
     result = t
-    while result.kind in {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal}:
+    while result.kind in {tyGenericInst, tyRange, tyVar, tyDistinct,
+                          tyOrdinal, tyAlias}:
       result = lastSon(result)
   if n.typ != nil and n.typ.skip.kind in {tyBool, tyEnum}:
     let enumfields = n.typ.skip.n
diff --git a/compiler/rodwrite.nim b/compiler/rodwrite.nim
index f2422f947..4ce9e616a 100644
--- a/compiler/rodwrite.nim
+++ b/compiler/rodwrite.nim
@@ -385,9 +385,9 @@ proc symStack(w: PRodWriter): int =
       inc result
     elif iiTableGet(w.index.tab, s.id) == InvalidKey:
       var m = getModule(s)
-      if m == nil and s.kind != skPackage:
+      if m == nil and s.kind != skPackage and sfGenSym notin s.flags:
         internalError("symStack: module nil: " & s.name.s)
-      if s.kind == skPackage or m.id == w.module.id or sfFromGeneric in s.flags:
+      if s.kind == skPackage or {sfFromGeneric, sfGenSym} * s.flags != {} or m.id == w.module.id:
         # put definition in here
         var L = w.data.len
         addToIndex(w.index, s.id, L)
diff --git a/compiler/sem.nim b/compiler/sem.nim
index 02c779ef0..7524d7388 100644
--- a/compiler/sem.nim
+++ b/compiler/sem.nim
@@ -102,8 +102,8 @@ proc commonType*(x, y: PType): PType =
   # if expressions, etc.:
   if x == nil: return x
   if y == nil: return y
-  var a = skipTypes(x, {tyGenericInst})
-  var b = skipTypes(y, {tyGenericInst})
+  var a = skipTypes(x, {tyGenericInst, tyAlias})
+  var b = skipTypes(y, {tyGenericInst, tyAlias})
   result = x
   if a.kind in {tyExpr, tyNil}: result = y
   elif b.kind in {tyExpr, tyNil}: result = x
@@ -115,10 +115,10 @@ proc commonType*(x, y: PType): PType =
     else:
       result = newType(tyTypeDesc, a.owner)
       rawAddSon(result, newType(tyNone, a.owner))
-  elif b.kind in {tyArray, tyArrayConstr, tySet, tySequence} and
+  elif b.kind in {tyArray, tySet, tySequence} and
       a.kind == b.kind:
     # check for seq[empty] vs. seq[int]
-    let idx = ord(b.kind in {tyArray, tyArrayConstr})
+    let idx = ord(b.kind == tyArray)
     if a.sons[idx].kind == tyEmpty: return y
   elif a.kind == tyTuple and b.kind == tyTuple and a.len == b.len:
     var nt: PType
diff --git a/compiler/semasgn.nim b/compiler/semasgn.nim
index c4116a814..c4dc13624 100644
--- a/compiler/semasgn.nim
+++ b/compiler/semasgn.nim
@@ -187,7 +187,7 @@ proc liftBodyAux(c: var TLiftCtx; t: PType; body, x, y: PNode) =
   of tyPointer, tySet, tyBool, tyChar, tyEnum, tyInt..tyUInt64, tyCString,
       tyPtr, tyString, tyRef:
     defaultOp(c, t, body, x, y)
-  of tyArrayConstr, tyArray, tySequence:
+  of tyArray, tySequence:
     if tfHasAsgn in t.flags:
       if t.kind == tySequence:
         # XXX add 'nil' handling here
@@ -227,7 +227,7 @@ proc liftBodyAux(c: var TLiftCtx; t: PType; body, x, y: PNode) =
      tyTypeDesc, tyGenericInvocation, tyForward:
     internalError(c.info, "assignment requested for type: " & typeToString(t))
   of tyOrdinal, tyRange,
-     tyGenericInst, tyFieldAccessor, tyStatic, tyVar:
+     tyGenericInst, tyFieldAccessor, tyStatic, tyVar, tyAlias:
     liftBodyAux(c, lastSon(t), body, x, y)
   of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("liftBodyAux")
 
@@ -276,7 +276,7 @@ proc liftBody(c: PContext; typ: PType; info: TLineInfo): PSym =
   #echo "Produced this ", n
 
 proc getAsgnOrLiftBody(c: PContext; typ: PType; info: TLineInfo): PSym =
-  let t = typ.skipTypes({tyGenericInst, tyVar})
+  let t = typ.skipTypes({tyGenericInst, tyVar, tyAlias})
   result = t.assignment
   if result.isNil:
     result = liftBody(c, t, info)
diff --git a/compiler/semcall.nim b/compiler/semcall.nim
index ca9b5effb..ae7bab89d 100644
--- a/compiler/semcall.nim
+++ b/compiler/semcall.nim
@@ -370,7 +370,7 @@ proc semResolvedCall(c: PContext, n: PNode, x: TCandidate): PNode =
 
 proc canDeref(n: PNode): bool {.inline.} =
   result = n.len >= 2 and (let t = n[1].typ;
-    t != nil and t.skipTypes({tyGenericInst}).kind in {tyPtr, tyRef})
+    t != nil and t.skipTypes({tyGenericInst, tyAlias}).kind in {tyPtr, tyRef})
 
 proc tryDeref(n: PNode): PNode =
   result = newNodeI(nkHiddenDeref, n.info)
diff --git a/compiler/semdestruct.nim b/compiler/semdestruct.nim
index 85d106056..a8873bbe2 100644
--- a/compiler/semdestruct.nim
+++ b/compiler/semdestruct.nim
@@ -136,9 +136,9 @@ proc instantiateDestructor(c: PContext, typ: PType): PType =
     else:
       return nil
 
-  t = t.skipTypes({tyGenericInst})
+  t = t.skipTypes({tyGenericInst, tyAlias})
   case t.kind
-  of tySequence, tyArray, tyArrayConstr, tyOpenArray, tyVarargs:
+  of tySequence, tyArray, tyOpenArray, tyVarargs:
     t.destructor = analyzingDestructor
     if instantiateDestructor(c, t.sons[0]) != nil:
       t.destructor = getCompilerProc"nimDestroyRange"
diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim
index 8aaf4f9d8..60435202b 100644
--- a/compiler/semexprs.nim
+++ b/compiler/semexprs.nim
@@ -238,7 +238,7 @@ proc semLowHigh(c: PContext, n: PNode, m: TMagic): PNode =
     case typ.kind
     of tySequence, tyString, tyCString, tyOpenArray, tyVarargs:
       n.typ = getSysType(tyInt)
-    of tyArrayConstr, tyArray:
+    of tyArray:
       n.typ = typ.sons[0] # indextype
     of tyInt..tyInt64, tyChar, tyBool, tyEnum, tyUInt8, tyUInt16, tyUInt32:
       # do not skip the range!
@@ -373,7 +373,7 @@ proc changeType(n: PNode, newType: PType, check: bool) =
     for i in countup(0, sonsLen(n) - 1):
       changeType(n.sons[i], elemType(newType), check)
   of nkPar:
-    let tup = newType.skipTypes({tyGenericInst})
+    let tup = newType.skipTypes({tyGenericInst, tyAlias})
     if tup.kind != tyTuple:
       if tup.kind == tyObject: return
       globalError(n.info, "no tuple type for constructor")
@@ -416,7 +416,7 @@ proc arrayConstrType(c: PContext, n: PNode): PType =
   if sonsLen(n) == 0:
     rawAddSon(typ, newTypeS(tyEmpty, c)) # needs an empty basetype!
   else:
-    var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyOrdinal})
+    var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyOrdinal, tyAlias})
     addSonSkipIntLit(typ, t)
   typ.sons[0] = makeRangeType(c, 0, sonsLen(n) - 1, n.info)
   result = typ
@@ -522,7 +522,7 @@ proc analyseIfAddressTakenInCall(c: PContext, n: PNode) =
 
   # get the real type of the callee
   # it may be a proc var with a generic alias type, so we skip over them
-  var t = n.sons[0].typ.skipTypes({tyGenericInst})
+  var t = n.sons[0].typ.skipTypes({tyGenericInst, tyAlias})
 
   if n.sons[0].kind == nkSym and n.sons[0].sym.magic in FakeVarParams:
     # BUGFIX: check for L-Value still needs to be done for the arguments!
@@ -888,18 +888,18 @@ proc lookupInRecordAndBuildCheck(c: PContext, n, r: PNode, field: PIdent,
   else: illFormedAst(n)
 
 proc makeDeref(n: PNode): PNode =
-  var t = skipTypes(n.typ, {tyGenericInst})
+  var t = skipTypes(n.typ, {tyGenericInst, tyAlias})
   result = n
   if t.kind == tyVar:
     result = newNodeIT(nkHiddenDeref, n.info, t.sons[0])
     addSon(result, n)
-    t = skipTypes(t.sons[0], {tyGenericInst})
+    t = skipTypes(t.sons[0], {tyGenericInst, tyAlias})
   while t.kind in {tyPtr, tyRef}:
     var a = result
     let baseTyp = t.lastSon
     result = newNodeIT(nkHiddenDeref, n.info, baseTyp)
     addSon(result, a)
-    t = skipTypes(baseTyp, {tyGenericInst})
+    t = skipTypes(baseTyp, {tyGenericInst, tyAlias})
 
 const
   tyTypeParamsHolders = {tyGenericInst, tyCompositeTypeClass}
@@ -1013,7 +1013,8 @@ proc semSym(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
     while p != nil and p.selfSym == nil:
       p = p.next
     if p != nil and p.selfSym != nil:
-      var ty = skipTypes(p.selfSym.typ, {tyGenericInst, tyVar, tyPtr, tyRef})
+      var ty = skipTypes(p.selfSym.typ, {tyGenericInst, tyVar, tyPtr, tyRef,
+                                         tyAlias})
       while tfBorrowDot in ty.flags: ty = ty.skipTypes({tyDistinct})
       var check: PNode = nil
       if ty.kind == tyObject:
@@ -1103,7 +1104,7 @@ proc builtinFieldAccess(c: PContext, n: PNode, flags: TExprFlags): PNode =
     # reset to prevent 'nil' bug: see "tests/reject/tenumitems.nim":
     ty = n.sons[0].typ
     return nil
-  ty = skipTypes(ty, {tyGenericInst, tyVar, tyPtr, tyRef})
+  ty = skipTypes(ty, {tyGenericInst, tyVar, tyPtr, tyRef, tyAlias})
   while tfBorrowDot in ty.flags: ty = ty.skipTypes({tyDistinct})
   var check: PNode = nil
   if ty.kind == tyObject:
@@ -1171,7 +1172,7 @@ proc semDeref(c: PContext, n: PNode): PNode =
   checkSonsLen(n, 1)
   n.sons[0] = semExprWithType(c, n.sons[0])
   result = n
-  var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar})
+  var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyAlias})
   case t.kind
   of tyRef, tyPtr: n.typ = t.lastSon
   else: result = nil
@@ -1190,9 +1191,10 @@ proc semSubscript(c: PContext, n: PNode, flags: TExprFlags): PNode =
   # make sure we don't evaluate generic macros/templates
   n.sons[0] = semExprWithType(c, n.sons[0],
                               {efNoProcvarCheck, efNoEvaluateGeneric})
-  let arr = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyPtr, tyRef})
+  let arr = skipTypes(n.sons[0].typ, {tyGenericInst,
+                                      tyVar, tyPtr, tyRef, tyAlias})
   case arr.kind
-  of tyArray, tyOpenArray, tyVarargs, tyArrayConstr, tySequence, tyString,
+  of tyArray, tyOpenArray, tyVarargs, tySequence, tyString,
      tyCString:
     if n.len != 2: return nil
     n.sons[0] = makeDeref(n.sons[0])
@@ -1220,7 +1222,7 @@ proc semSubscript(c: PContext, n: PNode, flags: TExprFlags): PNode =
     c.p.bracketExpr = n.sons[0]
     # [] operator for tuples requires constant expression:
     n.sons[1] = semConstExpr(c, n.sons[1])
-    if skipTypes(n.sons[1].typ, {tyGenericInst, tyRange, tyOrdinal}).kind in
+    if skipTypes(n.sons[1].typ, {tyGenericInst, tyRange, tyOrdinal, tyAlias}).kind in
         {tyInt..tyInt64}:
       var idx = getOrdValue(n.sons[1])
       if idx >= 0 and idx < sonsLen(arr): n.typ = arr.sons[int(idx)]
@@ -1364,7 +1366,7 @@ proc semAsgn(c: PContext, n: PNode; mode=asgnNormal): PNode =
   # a = b # both are vars, means: a[] = b[]
   # a = b # b no 'var T' means: a = addr(b)
   var le = a.typ
-  if (skipTypes(le, {tyGenericInst}).kind != tyVar and
+  if (skipTypes(le, {tyGenericInst, tyAlias}).kind != tyVar and
         isAssignable(c, a) == arNone) or
       skipTypes(le, abstractVar).kind in {tyOpenArray, tyVarargs}:
     # Direct assignment to a discriminant is allowed!
@@ -1456,13 +1458,13 @@ proc semProcBody(c: PContext, n: PNode): PNode =
   closeScope(c)
 
 proc semYieldVarResult(c: PContext, n: PNode, restype: PType) =
-  var t = skipTypes(restype, {tyGenericInst})
+  var t = skipTypes(restype, {tyGenericInst, tyAlias})
   case t.kind
   of tyVar:
     n.sons[0] = takeImplicitAddr(c, n.sons[0])
   of tyTuple:
     for i in 0.. <t.sonsLen:
-      var e = skipTypes(t.sons[i], {tyGenericInst})
+      var e = skipTypes(t.sons[i], {tyGenericInst, tyAlias})
       if e.kind == tyVar:
         if n.sons[0].kind == nkPar:
           n.sons[0].sons[i] = takeImplicitAddr(c, n.sons[0].sons[i])
@@ -1904,17 +1906,17 @@ proc semSetConstr(c: PContext, n: PNode): PNode =
         n.sons[i].sons[2] = semExprWithType(c, n.sons[i].sons[2])
         if typ == nil:
           typ = skipTypes(n.sons[i].sons[1].typ,
-                          {tyGenericInst, tyVar, tyOrdinal})
+                          {tyGenericInst, tyVar, tyOrdinal, tyAlias})
         n.sons[i].typ = n.sons[i].sons[2].typ # range node needs type too
       elif n.sons[i].kind == nkRange:
         # already semchecked
         if typ == nil:
           typ = skipTypes(n.sons[i].sons[0].typ,
-                          {tyGenericInst, tyVar, tyOrdinal})
+                          {tyGenericInst, tyVar, tyOrdinal, tyAlias})
       else:
         n.sons[i] = semExprWithType(c, n.sons[i])
         if typ == nil:
-          typ = skipTypes(n.sons[i].typ, {tyGenericInst, tyVar, tyOrdinal})
+          typ = skipTypes(n.sons[i].typ, {tyGenericInst, tyVar, tyOrdinal, tyAlias})
     if not isOrdinalType(typ):
       localError(n.info, errOrdinalTypeExpected)
       typ = makeRangeType(c, 0, MaxSetElements-1, n.info)
@@ -2046,8 +2048,8 @@ proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
   result = n
   result.typ = t
   result.kind = nkObjConstr
-  t = skipTypes(t, {tyGenericInst})
-  if t.kind == tyRef: t = skipTypes(t.sons[0], {tyGenericInst})
+  t = skipTypes(t, {tyGenericInst, tyAlias})
+  if t.kind == tyRef: t = skipTypes(t.sons[0], {tyGenericInst, tyAlias})
   if t.kind != tyObject:
     localError(n.info, errGenerated, "object constructor needs an object type")
     return
diff --git a/compiler/semfold.nim b/compiler/semfold.nim
index 42fa60781..0f1138e04 100644
--- a/compiler/semfold.nim
+++ b/compiler/semfold.nim
@@ -538,7 +538,8 @@ proc getArrayConstr(m: PSym, n: PNode): PNode =
 
 proc foldArrayAccess(m: PSym, n: PNode): PNode =
   var x = getConstExpr(m, n.sons[0])
-  if x == nil or x.typ.skipTypes({tyGenericInst}).kind == tyTypeDesc: return
+  if x == nil or x.typ.skipTypes({tyGenericInst, tyAlias}).kind == tyTypeDesc:
+    return
 
   var y = getConstExpr(m, n.sons[1])
   if y == nil: return
diff --git a/compiler/semmacrosanity.nim b/compiler/semmacrosanity.nim
index 6cd5c4a3c..a6024a42f 100644
--- a/compiler/semmacrosanity.nim
+++ b/compiler/semmacrosanity.nim
@@ -61,7 +61,7 @@ proc annotateType*(n: PNode, t: PType) =
     else:
       globalError(n.info, "() must have a tuple type")
   of nkBracket:
-    if x.kind in {tyArrayConstr, tyArray, tySequence, tyOpenArray}:
+    if x.kind in {tyArray, tySequence, tyOpenArray}:
       n.typ = t
       for m in n: annotateType(m, x.elemType)
     else:
diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim
index 0c6f6848e..b59036ea5 100644
--- a/compiler/semstmts.nim
+++ b/compiler/semstmts.nim
@@ -471,7 +471,7 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
     # this can only happen for errornous var statements:
     if typ == nil: continue
     typeAllowedCheck(a.info, typ, symkind)
-    var tup = skipTypes(typ, {tyGenericInst})
+    var tup = skipTypes(typ, {tyGenericInst, tyAlias})
     if a.kind == nkVarTuple:
       if tup.kind != tyTuple:
         localError(a.info, errXExpected, "tuple")
@@ -583,7 +583,7 @@ proc semForVars(c: PContext, n: PNode): PNode =
   result = n
   var length = sonsLen(n)
   let iterBase = n.sons[length-2].typ
-  var iter = skipTypes(iterBase, {tyGenericInst})
+  var iter = skipTypes(iterBase, {tyGenericInst, tyAlias})
   # length == 3 means that there is one for loop variable
   # and thus no tuple unpacking:
   if iter.kind != tyTuple or length == 3:
@@ -745,7 +745,7 @@ proc typeSectionRightSidePass(c: PContext, n: PNode) =
       var t = semTypeNode(c, a.sons[2], s.typ)
       if s.typ == nil:
         s.typ = t
-      elif t != s.typ:
+      elif t != s.typ and (s.typ == nil or s.typ.kind != tyAlias):
         # this can happen for e.g. tcan_alias_specialised_generic:
         assignType(s.typ, t)
         #debug s.typ
@@ -777,7 +777,7 @@ proc checkForMetaFields(n: PNode) =
     let t = n.sym.typ
     case t.kind
     of tySequence, tySet, tyArray, tyOpenArray, tyVar, tyPtr, tyRef,
-       tyProc, tyGenericInvocation, tyGenericInst:
+       tyProc, tyGenericInvocation, tyGenericInst, tyAlias:
       let start = ord(t.kind in {tyGenericInvocation, tyGenericInst})
       for i in start .. <t.sons.len:
         checkMeta(t.sons[i])
@@ -804,8 +804,9 @@ proc typeSectionFinalPass(c: PContext, n: PNode) =
         assert t != nil
         if t.kind in {tyObject, tyEnum, tyDistinct}:
           assert s.typ != nil
-          assignType(s.typ, t)
-          s.typ.id = t.id     # same id
+          if s.typ.kind != tyAlias:
+            assignType(s.typ, t)
+            s.typ.id = t.id     # same id
       checkConstructedType(s.info, s.typ)
       if s.typ.kind in {tyObject, tyTuple} and not s.typ.n.isNil:
         checkForMetaFields(s.typ.n)
@@ -1366,7 +1367,9 @@ proc semMethod(c: PContext, n: PNode): PNode =
     for col in countup(1, sonsLen(tt)-1):
       let t = tt.sons[col]
       if t != nil and t.kind == tyGenericInvocation:
-        var x = skipTypes(t.sons[0], {tyVar, tyPtr, tyRef, tyGenericInst, tyGenericInvocation, tyGenericBody})
+        var x = skipTypes(t.sons[0], {tyVar, tyPtr, tyRef, tyGenericInst,
+                                      tyGenericInvocation, tyGenericBody,
+                                      tyAlias})
         if x.kind == tyObject and t.len-1 == result.sons[genericParamsPos].len:
           foundObj = true
           x.methods.safeAdd((col,s))
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 5f47bca5c..028baa555 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -95,7 +95,7 @@ proc semSet(c: PContext, n: PNode, prev: PType): PType =
   if sonsLen(n) == 2:
     var base = semTypeNode(c, n.sons[1], nil)
     addSonSkipIntLit(result, base)
-    if base.kind == tyGenericInst: base = lastSon(base)
+    if base.kind in {tyGenericInst, tyAlias}: base = lastSon(base)
     if base.kind != tyGenericParam:
       if not isOrdinalType(base):
         localError(n.info, errOrdinalTypeExpected)
@@ -145,7 +145,8 @@ proc semAnyRef(c: PContext; n: PNode; kind: TTypeKind; prev: PType): PType =
         isNilable = true
       else:
         let region = semTypeNode(c, ni, nil)
-        if region.skipTypes({tyGenericInst}).kind notin {tyError, tyObject}:
+        if region.skipTypes({tyGenericInst, tyAlias}).kind notin {
+              tyError, tyObject}:
           message n[i].info, errGenerated, "region needs to be an object type"
         addSonSkipIntLit(result, region)
     addSonSkipIntLit(result, base)
@@ -266,7 +267,7 @@ proc semArray(c: PContext, n: PNode, prev: PType): PType =
     # 3 = length(array indx base)
     let indx = semArrayIndex(c, n[1])
     var indxB = indx
-    if indxB.kind == tyGenericInst: indxB = lastSon(indxB)
+    if indxB.kind in {tyGenericInst, tyAlias}: indxB = lastSon(indxB)
     if indxB.kind notin {tyGenericParam, tyStatic, tyFromExpr}:
       if not isOrdinalType(indxB):
         localError(n.sons[1].info, errOrdinalTypeExpected)
@@ -647,7 +648,7 @@ proc skipGenericInvocation(t: PType): PType {.inline.} =
   result = t
   if result.kind == tyGenericInvocation:
     result = result.sons[0]
-  while result.kind in {tyGenericInst, tyGenericBody, tyRef, tyPtr}:
+  while result.kind in {tyGenericInst, tyGenericBody, tyRef, tyPtr, tyAlias}:
     result = lastSon(result)
 
 proc addInheritedFields(c: PContext, check: var IntSet, pos: var int,
@@ -950,7 +951,7 @@ proc semProcTypeNode(c: PContext, n, genericParams: PNode,
       if isType: localError(a.info, "':' expected")
       if kind in {skTemplate, skMacro}:
         typ = newTypeS(tyExpr, c)
-    elif skipTypes(typ, {tyGenericInst}).kind == tyVoid:
+    elif skipTypes(typ, {tyGenericInst, tyAlias}).kind == tyVoid:
       continue
     for j in countup(0, length-3):
       var arg = newSymG(skParam, a.sons[j], c)
@@ -982,7 +983,7 @@ proc semProcTypeNode(c: PContext, n, genericParams: PNode,
   if r != nil:
     # turn explicit 'void' return type into 'nil' because the rest of the
     # compiler only checks for 'nil':
-    if skipTypes(r, {tyGenericInst}).kind != tyVoid:
+    if skipTypes(r, {tyGenericInst, tyAlias}).kind != tyVoid:
       # 'auto' as a return type does not imply a generic:
       if r.kind == tyAnything:
         # 'p(): auto' and 'p(): expr' are equivalent, but the rest of the
@@ -1151,6 +1152,13 @@ proc semProcTypeWithScope(c: PContext, n: PNode,
     when useEffectSystem: setEffectsForProcType(result, n.sons[1])
   closeScope(c)
 
+proc maybeAliasType(c: PContext; typeExpr, prev: PType): PType =
+  if typeExpr.kind in {tyObject, tyEnum, tyDistinct} and prev != nil:
+    result = newTypeS(tyAlias, c)
+    result.rawAddSon typeExpr
+    result.sym = prev.sym
+    assignType(prev, result)
+
 proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
   result = nil
   if gCmd == cmdIdeTools: suggestExpr(c, n)
@@ -1180,7 +1188,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
       result = semRangeAux(c, n, prev)
     elif n[0].kind == nkNilLit and n.len == 2:
       result = semTypeNode(c, n.sons[1], prev)
-      if result.skipTypes({tyGenericInst}).kind in NilableTypes+GenericTypes:
+      if result.skipTypes({tyGenericInst, tyAlias}).kind in NilableTypes+GenericTypes:
         if tfNotNil in result.flags:
           result = freshType(result, prev)
           result.flags.excl(tfNotNil)
@@ -1208,7 +1216,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
         case n.len
         of 3:
           result = semTypeNode(c, n.sons[1], prev)
-          if result.skipTypes({tyGenericInst}).kind in NilableTypes+GenericTypes and
+          if result.skipTypes({tyGenericInst, tyAlias}).kind in NilableTypes+GenericTypes and
               n.sons[2].kind == nkNilLit:
             result = freshType(result, prev)
             result.flags.incl(tfNotNil)
@@ -1266,15 +1274,18 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     of mTuple: result = semTuple(c, n, prev)
     else: result = semGeneric(c, n, s, prev)
   of nkDotExpr:
-    var typeExpr = semExpr(c, n)
+    let typeExpr = semExpr(c, n)
     if typeExpr.typ.kind != tyTypeDesc:
       localError(n.info, errTypeExpected)
       result = errorType(c)
     else:
       result = typeExpr.typ.base
       if result.isMetaType:
-        var preprocessed = semGenericStmt(c, n)
+        let preprocessed = semGenericStmt(c, n)
         result = makeTypeFromExpr(c, preprocessed.copyTree)
+      else:
+        let alias = maybeAliasType(c, result, prev)
+        if alias != nil: result = alias
   of nkIdent, nkAccQuoted:
     var s = semTypeIdent(c, n)
     if s.typ == nil:
@@ -1286,16 +1297,23 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     elif prev == nil:
       result = s.typ
     else:
-      assignType(prev, s.typ)
-      # bugfix: keep the fresh id for aliases to integral types:
-      if s.typ.kind notin {tyBool, tyChar, tyInt..tyInt64, tyFloat..tyFloat128,
-                           tyUInt..tyUInt64}:
-        prev.id = s.typ.id
-      result = prev
+      let alias = maybeAliasType(c, s.typ, prev)
+      if alias != nil:
+        result = alias
+      else:
+        assignType(prev, s.typ)
+        # bugfix: keep the fresh id for aliases to integral types:
+        if s.typ.kind notin {tyBool, tyChar, tyInt..tyInt64, tyFloat..tyFloat128,
+                             tyUInt..tyUInt64}:
+          prev.id = s.typ.id
+        result = prev
   of nkSym:
     if n.sym.kind == skType and n.sym.typ != nil:
       var t = n.sym.typ
-      if prev == nil:
+      let alias = maybeAliasType(c, t, prev)
+      if alias != nil:
+        result = alias
+      elif prev == nil:
         result = t
       else:
         assignType(prev, t)
diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim
index b42d58474..29e75e188 100644
--- a/compiler/semtypinst.nim
+++ b/compiler/semtypinst.nim
@@ -310,6 +310,9 @@ proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType =
     # generics *when the type is constructed*:
     newbody.deepCopy = cl.c.instTypeBoundOp(cl.c, dc, result, cl.info,
                                             attachedDeepCopy, 1)
+  newbody.typeInst = result
+  if newbody.kind == tyRef:
+    newbody.lastSon.typeInst = result
   let asgn = newbody.assignment
   if asgn != nil and sfFromGeneric notin asgn.flags:
     # '=' needs to be instantiated for generics when the type is constructed:
@@ -459,7 +462,7 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType =
           var r = replaceTypeVarsT(cl, result.sons[i])
           if result.kind == tyObject:
             # carefully coded to not skip the precious tyGenericInst:
-            let r2 = r.skipTypes({tyGenericInst})
+            let r2 = r.skipTypes({tyGenericInst, tyAlias})
             if r2.kind in {tyPtr, tyRef}:
               r = skipTypes(r2, {tyPtr, tyRef})
           result.sons[i] = r
diff --git a/compiler/sighashes.nim b/compiler/sighashes.nim
new file mode 100644
index 000000000..6918b28a2
--- /dev/null
+++ b/compiler/sighashes.nim
@@ -0,0 +1,264 @@
+#
+#
+#           The Nim Compiler
+#        (c) Copyright 2016 Andreas Rumpf
+#
+#    See the file "copying.txt", included in this
+#    distribution, for details about the copyright.
+#
+
+## Computes hash values for routine (proc, method etc) signatures.
+
+import ast, md5
+from hashes import Hash
+from astalgo import debug
+from types import typeToString
+from strutils import startsWith, contains
+
+when false:
+  type
+    SigHash* = uint32  ## a hash good enough for a filename or a proc signature
+
+  proc sdbmHash(hash: SigHash, c: char): SigHash {.inline.} =
+    return SigHash(c) + (hash shl 6) + (hash shl 16) - hash
+
+  template `&=`*(x: var SigHash, c: char) = x = sdbmHash(x, c)
+  template `&=`*(x: var SigHash, s: string) =
+    for c in s: x = sdbmHash(x, c)
+
+else:
+  type
+    SigHash* = distinct Md5Digest
+
+  const
+    cb64 = [
+      "A", "B", "C", "D", "E", "F", "G", "H", "I", "J", "K", "L", "M", "N",
+      "O", "P", "Q", "R", "S", "T", "U", "V", "W", "X", "Y", "Z",
+      "a", "b", "c", "d", "e", "f", "g", "h", "i", "j", "k", "l", "m", "n",
+      "o", "p", "q", "r", "s", "t", "u", "v", "w", "x", "y", "z",
+      "0", "1", "2", "3", "4", "5", "6", "7", "8", "9a",
+      "9b", "9c"]
+
+  proc toBase64a(s: cstring, len: int): string =
+    ## encodes `s` into base64 representation.
+    result = newStringOfCap(((len + 2) div 3) * 4)
+    result.add '_'
+    var i = 0
+    while i < len - 2:
+      let a = ord(s[i])
+      let b = ord(s[i+1])
+      let c = ord(s[i+2])
+      result.add cb64[a shr 2]
+      result.add cb64[((a and 3) shl 4) or ((b and 0xF0) shr 4)]
+      result.add cb64[((b and 0x0F) shl 2) or ((c and 0xC0) shr 6)]
+      result.add cb64[c and 0x3F]
+      inc(i, 3)
+    if i < len-1:
+      let a = ord(s[i])
+      let b = ord(s[i+1])
+      result.add cb64[a shr 2]
+      result.add cb64[((a and 3) shl 4) or ((b and 0xF0) shr 4)]
+      result.add cb64[((b and 0x0F) shl 2)]
+    elif i < len:
+      let a = ord(s[i])
+      result.add cb64[a shr 2]
+      result.add cb64[(a and 3) shl 4]
+
+  proc `$`*(u: SigHash): string =
+    toBase64a(cast[cstring](unsafeAddr u), sizeof(u))
+  proc `&=`(c: var MD5Context, s: string) = md5Update(c, s, s.len)
+  proc `&=`(c: var MD5Context, ch: char) = md5Update(c, unsafeAddr ch, 1)
+
+  template lowlevel(v) =
+    md5Update(c, cast[cstring](unsafeAddr(v)), sizeof(v))
+
+  proc `==`*(a, b: SigHash): bool =
+    # {.borrow.}
+    result = equalMem(unsafeAddr a, unsafeAddr b, sizeof(a))
+
+  proc hash*(u: SigHash): Hash =
+    result = 0
+    for x in 0..3:
+      result = (result shl 8) or u.MD5Digest[x].int
+
+proc hashSym(c: var MD5Context, s: PSym) =
+  if sfAnon in s.flags or s.kind == skGenericParam:
+    c &= ":anon"
+  else:
+    var it = s
+    while it != nil:
+      c &= it.name.s
+      c &= "."
+      it = it.owner
+
+proc hashTree(c: var MD5Context, n: PNode) =
+  if n == nil:
+    c &= "\255"
+    return
+  let k = n.kind
+  c &= char(k)
+  # we really must not hash line information. 'n.typ' is debatable but
+  # shouldn't be necessary for now and avoids potential infinite recursions.
+  case n.kind
+  of nkEmpty, nkNilLit, nkType: discard
+  of nkIdent:
+    c &= n.ident.s
+  of nkSym:
+    hashSym(c, n.sym)
+  of nkCharLit..nkUInt64Lit:
+    let v = n.intVal
+    lowlevel v
+  of nkFloatLit..nkFloat64Lit:
+    let v = n.floatVal
+    lowlevel v
+  of nkStrLit..nkTripleStrLit:
+    c &= n.strVal
+  else:
+    for i in 0.. <n.len: hashTree(c, n.sons[i])
+
+type
+  ConsiderFlag* = enum
+    CoProc
+    CoType
+
+proc hashType(c: var MD5Context, t: PType; flags: set[ConsiderFlag]) =
+  if t == nil:
+    c &= "\254"
+    return
+
+  case t.kind
+  of tyGenericInst:
+    var x = t.lastSon
+    if x.kind == tyGenericBody: x = x.lastSon
+    if x.kind == tyTuple:
+      c.hashType x, flags
+      return
+    for i in countup(0, sonsLen(t) - 2):
+      c.hashType t.sons[i], flags
+    return
+  of tyGenericInvocation:
+    for i in countup(0, sonsLen(t) - 1):
+      c.hashType t.sons[i], flags
+    return
+  of tyDistinct:
+    if CoType in flags:
+      c.hashType t.lastSon, flags
+    else:
+      c.hashSym(t.sym)
+    return
+  of tyAlias:
+    c.hashType t.lastSon, flags
+    return
+  else:
+    discard
+
+  c &= char(t.kind)
+
+  case t.kind
+  of tyObject, tyEnum:
+    # Every cyclic type in Nim need to be constructed via some 't.sym', so this
+    # is actually safe without an infinite recursion check:
+    if t.sym != nil:
+      #if "Future:" in t.sym.name.s and t.typeInst == nil:
+      #  writeStackTrace()
+      #  echo "yes ", t.sym.name.s
+      #  #quit 1
+      if t.typeInst != nil:
+        assert t.typeInst.kind == tyGenericInst
+        for i in countup(1, sonsLen(t.typeInst) - 2):
+          c.hashType t.typeInst.sons[i], flags
+      c.hashSym(t.sym)
+    else:
+      lowlevel(t.id)
+  of tyRef, tyPtr, tyGenericBody:
+    c.hashType t.lastSon, flags
+  of tyUserTypeClass:
+    if t.sym != nil and t.sym.owner != nil:
+      c &= t.sym.owner.name.s
+    else:
+      c &= "unknown typeclass"
+  of tyUserTypeClassInst:
+    let body = t.sons[0]
+    c.hashSym body.sym
+    for i in countup(1, sonsLen(t) - 2):
+      c.hashType t.sons[i], flags
+  of tyFromExpr, tyFieldAccessor:
+    c.hashTree(t.n)
+  of tyTuple:
+    if t.n != nil and CoType notin flags:
+      assert(sonsLen(t.n) == sonsLen(t))
+      for i in countup(0, sonsLen(t.n) - 1):
+        assert(t.n.sons[i].kind == nkSym)
+        c &= t.n.sons[i].sym.name.s
+        c &= ':'
+        c.hashType(t.sons[i], flags)
+        c &= ','
+    else:
+      for i in countup(0, sonsLen(t) - 1): c.hashType t.sons[i], flags
+  of tyRange:
+    #if CoType notin flags:
+    c.hashTree(t.n)
+    c.hashType(t.sons[0], flags)
+  of tyProc:
+    c &= (if tfIterator in t.flags: "iterator " else: "proc ")
+    if CoProc in flags and t.n != nil:
+      let params = t.n
+      for i in 1..<params.len:
+        let param = params[i].sym
+        c &= param.name.s
+        c &= ':'
+        c.hashType(param.typ, flags)
+        c &= ','
+      c.hashType(t.sons[0], flags)
+    else:
+      for i in 0.. <t.len: c.hashType(t.sons[i], flags)
+    c &= char(t.callConv)
+    if CoType notin flags:
+      if tfNoSideEffect in t.flags: c &= ".noSideEffect"
+      if tfThread in t.flags: c &= ".thread"
+  else:
+    for i in 0.. <t.len: c.hashType(t.sons[i], flags)
+  if tfNotNil in t.flags and CoType notin flags: c &= "not nil"
+
+when defined(debugSigHashes):
+  import db_sqlite
+
+  let db = open(connection="sighashes.db", user="araq", password="",
+                database="sighashes")
+
+proc hashType*(t: PType; flags: set[ConsiderFlag] = {CoType}): SigHash =
+  var c: MD5Context
+  md5Init c
+  hashType c, t, flags
+  md5Final c, result.Md5Digest
+  when defined(debugSigHashes):
+    db.exec(sql"INSERT OR IGNORE INTO sighashes(type, hash) VALUES (?, ?)",
+            typeToString(t), $result)
+
+proc hashProc*(s: PSym): SigHash =
+  var c: MD5Context
+  md5Init c
+  hashType c, s.typ, {CoProc}
+
+  var m = s
+  while m.kind != skModule: m = m.owner
+  let p = m.owner
+  assert p.kind == skPackage
+  c &= p.name.s
+  c &= "."
+  c &= m.name.s
+
+  md5Final c, result.Md5Digest
+
+proc hashOwner*(s: PSym): SigHash =
+  var c: MD5Context
+  md5Init c
+  var m = s
+  while m.kind != skModule: m = m.owner
+  let p = m.owner
+  assert p.kind == skPackage
+  c &= p.name.s
+  c &= "."
+  c &= m.name.s
+
+  md5Final c, result.Md5Digest
diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim
index 15171874f..16358b1a8 100644
--- a/compiler/sigmatch.nim
+++ b/compiler/sigmatch.nim
@@ -158,7 +158,7 @@ proc sumGeneric(t: PType): int =
   var isvar = 1
   while true:
     case t.kind
-    of tyGenericInst, tyArray, tyRef, tyPtr, tyDistinct, tyArrayConstr,
+    of tyGenericInst, tyArray, tyRef, tyPtr, tyDistinct,
         tyOpenArray, tyVarargs, tySet, tyRange, tySequence, tyGenericBody:
       t = t.lastSon
       inc result
@@ -175,6 +175,7 @@ proc sumGeneric(t: PType): int =
       for i in 0 .. <t.len: result += t.sons[i].sumGeneric
       break
     of tyGenericParam, tyExpr, tyStatic, tyStmt: break
+    of tyAlias: t = t.lastSon
     of tyBool, tyChar, tyEnum, tyObject, tyPointer,
         tyString, tyCString, tyInt..tyInt64, tyFloat..tyFloat128,
         tyUInt..tyUInt64:
@@ -273,11 +274,6 @@ proc describeArgs*(c: PContext, n: PNode, startIdx = 1;
 proc typeRel*(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation
 proc concreteType(c: TCandidate, t: PType): PType =
   case t.kind
-  of tyArrayConstr:
-    # make it an array
-    result = newType(tyArray, t.owner)
-    addSonSkipIntLit(result, t.sons[0]) # XXX: t.owner is wrong for ID!
-    addSonSkipIntLit(result, t.sons[1]) # XXX: semantic checking for the type?
   of tyNil:
     result = nil              # what should it be?
   of tyTypeDesc:
@@ -394,7 +390,7 @@ proc skipToObject(t: PType; skipped: var SkippedPtr): PType =
       inc ptrs
       skipped = skippedPtr
       r = r.lastSon
-    of tyGenericBody, tyGenericInst:
+    of tyGenericBody, tyGenericInst, tyAlias:
       r = r.lastSon
     else:
       break
@@ -692,7 +688,7 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
   # for example, but unfortunately `prepareOperand` is not called in certain
   # situation when nkDotExpr are rotated to nkDotCalls
 
-  if a.kind == tyGenericInst and
+  if a.kind in {tyGenericInst, tyAlias} and
       skipTypes(f, {tyVar}).kind notin {
         tyGenericBody, tyGenericInvocation,
         tyGenericInst, tyGenericParam} + tyTypeClasses:
@@ -799,11 +795,9 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
     if aOrig.kind == tyVar: result = typeRel(c, f.base, aOrig.base)
     else: result = typeRel(c, f.base, aOrig)
     subtypeCheck()
-  of tyArray, tyArrayConstr:
-    # tyArrayConstr cannot happen really, but
-    # we wanna be safe here
+  of tyArray:
     case a.kind
-    of tyArray, tyArrayConstr:
+    of tyArray:
       var fRange = f.sons[0]
       if fRange.kind == tyGenericParam:
         var prev = PType(idTableGet(c.bindings, fRange))
@@ -848,7 +842,7 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
     of tyOpenArray, tyVarargs:
       result = typeRel(c, base(f), base(a))
       if result < isGeneric: result = isNone
-    of tyArray, tyArrayConstr:
+    of tyArray:
       if (f.sons[0].kind != tyGenericParam) and (a.sons[1].kind == tyEmpty):
         result = isSubtype
       elif typeRel(c, base(f), a.sons[1]) >= isGeneric:
@@ -984,7 +978,7 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
   of tyEmpty, tyVoid:
     if a.kind == f.kind: result = isEqual
 
-  of tyGenericInst:
+  of tyGenericInst, tyAlias:
     result = typeRel(c, lastSon(f), a)
 
   of tyGenericBody:
@@ -1090,7 +1084,7 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
   of tyBuiltInTypeClass:
     considerPreviousT:
       let targetKind = f.sons[0].kind
-      if targetKind == a.skipTypes({tyRange, tyGenericInst, tyBuiltInTypeClass}).kind or
+      if targetKind == a.skipTypes({tyRange, tyGenericInst, tyBuiltInTypeClass, tyAlias}).kind or
          (targetKind in {tyProc, tyPointer} and a.kind == tyNil):
         put(c, f, a)
         return isGeneric
diff --git a/compiler/suggest.nim b/compiler/suggest.nim
index 39689099a..888e80085 100644
--- a/compiler/suggest.nim
+++ b/compiler/suggest.nim
@@ -201,7 +201,7 @@ proc typeFits(c: PContext, s: PSym, firstArg: PType): bool {.inline.} =
     let m = s.getModule()
     if m != nil and sfSystemModule in m.flags:
       if s.kind == skType: return
-      var exp = s.typ.sons[1].skipTypes({tyGenericInst, tyVar})
+      var exp = s.typ.sons[1].skipTypes({tyGenericInst, tyVar, tyAlias})
       if exp.kind == tyVarargs: exp = elemType(exp)
       if exp.kind in {tyExpr, tyStmt, tyGenericParam, tyAnything}: return
     result = sigmatch.argtypeMatches(c, s.typ.sons[1], firstArg)
@@ -267,7 +267,7 @@ proc suggestFieldAccess(c: PContext, n: PNode, outputs: var int) =
       t = t.sons[0]
     suggestOperations(c, n, typ, outputs)
   else:
-    typ = skipTypes(typ, {tyGenericInst, tyVar, tyPtr, tyRef})
+    typ = skipTypes(typ, {tyGenericInst, tyVar, tyPtr, tyRef, tyAlias})
     if typ.kind == tyObject:
       var t = typ
       while true:
diff --git a/compiler/transf.nim b/compiler/transf.nim
index 5cd5e298b..4b6bff197 100644
--- a/compiler/transf.nim
+++ b/compiler/transf.nim
@@ -95,7 +95,7 @@ proc getCurrOwner(c: PTransf): PSym =
 
 proc newTemp(c: PTransf, typ: PType, info: TLineInfo): PNode =
   let r = newSym(skTemp, getIdent(genPrefix), getCurrOwner(c), info)
-  r.typ = typ #skipTypes(typ, {tyGenericInst})
+  r.typ = typ #skipTypes(typ, {tyGenericInst, tyAlias})
   incl(r.flags, sfFromGeneric)
   let owner = getCurrOwner(c)
   if owner.isIterator and not c.tooEarly:
@@ -326,7 +326,7 @@ proc transformYield(c: PTransf, n: PNode): PTransNode =
   # c.transCon.forStmt.len == 3 means that there is one for loop variable
   # and thus no tuple unpacking:
   if e.typ.isNil: return result # can happen in nimsuggest for unknown reasons
-  if skipTypes(e.typ, {tyGenericInst}).kind == tyTuple and
+  if skipTypes(e.typ, {tyGenericInst, tyAlias}).kind == tyTuple and
       c.transCon.forStmt.len != 3:
     e = skipConv(e)
     if e.kind == nkPar:
diff --git a/compiler/trees.nim b/compiler/trees.nim
index 08a1a8c1f..7208f7d7b 100644
--- a/compiler/trees.nim
+++ b/compiler/trees.nim
@@ -101,7 +101,7 @@ proc isDeepConstExpr*(n: PNode): bool =
       if not isDeepConstExpr(n.sons[i]): return false
     if n.typ.isNil: result = true
     else:
-      let t = n.typ.skipTypes({tyGenericInst, tyDistinct})
+      let t = n.typ.skipTypes({tyGenericInst, tyDistinct, tyAlias})
       if t.kind in {tyRef, tyPtr}: return false
       if t.kind != tyObject or not isCaseObj(t.n):
         result = true
diff --git a/compiler/types.nim b/compiler/types.nim
index fc50449ec..d5ec2972a 100644
--- a/compiler/types.nim
+++ b/compiler/types.nim
@@ -20,8 +20,11 @@ type
     preferName, preferDesc, preferExported, preferModuleInfo, preferGenericArg
 
 proc typeToString*(typ: PType; prefer: TPreferedDesc = preferName): string
-proc base*(t: PType): PType
-  # ------------------- type iterator: ----------------------------------------
+
+proc base*(t: PType): PType =
+  result = t.sons[0]
+
+# ------------------- type iterator: ----------------------------------------
 type
   TTypeIter* = proc (t: PType, closure: RootRef): bool {.nimcall.} # true if iteration should stop
   TTypeMutator* = proc (t: PType, closure: RootRef): PType {.nimcall.} # copy t and mutate it
@@ -51,14 +54,16 @@ const
   # TODO: Remove tyTypeDesc from each abstractX and (where necessary)
   # replace with typedescX
   abstractPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyDistinct, tyOrdinal,
-                   tyTypeDesc}
-  abstractVar* = {tyVar, tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc}
-  abstractRange* = {tyGenericInst, tyRange, tyDistinct, tyOrdinal, tyTypeDesc}
+                   tyTypeDesc, tyAlias}
+  abstractVar* = {tyVar, tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc,
+                  tyAlias}
+  abstractRange* = {tyGenericInst, tyRange, tyDistinct, tyOrdinal, tyTypeDesc,
+                    tyAlias}
   abstractVarRange* = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
-                       tyTypeDesc}
-  abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc}
+                       tyTypeDesc, tyAlias}
+  abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias}
 
-  skipPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyTypeDesc}
+  skipPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyTypeDesc, tyAlias}
   # typedescX is used if we're sure tyTypeDesc should be included (or skipped)
   typedescPtrs* = abstractPtrs + {tyTypeDesc}
   typedescInst* = abstractInst + {tyTypeDesc}
@@ -112,7 +117,7 @@ proc isFloatLit*(t: PType): bool {.inline.} =
 proc isCompatibleToCString(a: PType): bool =
   if a.kind == tyArray:
     if (firstOrd(a.sons[0]) == 0) and
-        (skipTypes(a.sons[0], {tyRange, tyGenericInst}).kind in
+        (skipTypes(a.sons[0], {tyRange, tyGenericInst, tyAlias}).kind in
             {tyInt..tyInt64, tyUInt..tyUInt64}) and
         (a.sons[1].kind == tyChar):
       result = true
@@ -136,8 +141,8 @@ proc getProcHeader*(sym: PSym; prefer: TPreferedDesc = preferName): string =
 proc elemType*(t: PType): PType =
   assert(t != nil)
   case t.kind
-  of tyGenericInst, tyDistinct: result = elemType(lastSon(t))
-  of tyArray, tyArrayConstr: result = t.sons[1]
+  of tyGenericInst, tyDistinct, tyAlias: result = elemType(lastSon(t))
+  of tyArray: result = t.sons[1]
   else: result = t.lastSon
   assert(result != nil)
 
@@ -146,12 +151,12 @@ proc isOrdinalType(t: PType): bool =
   const
     # caution: uint, uint64 are no ordinal types!
     baseKinds = {tyChar,tyInt..tyInt64,tyUInt8..tyUInt32,tyBool,tyEnum}
-    parentKinds = {tyRange, tyOrdinal, tyGenericInst, tyDistinct}
+    parentKinds = {tyRange, tyOrdinal, tyGenericInst, tyAlias, tyDistinct}
   t.kind in baseKinds or (t.kind in parentKinds and isOrdinalType(t.sons[0]))
 
 proc enumHasHoles(t: PType): bool =
   var b = t
-  while b.kind in {tyRange, tyGenericInst}: b = b.sons[0]
+  while b.kind in {tyRange, tyGenericInst, tyAlias}: b = b.sons[0]
   result = b.kind == tyEnum and tfEnumHasHoles in b.flags
 
 proc iterOverTypeAux(marker: var IntSet, t: PType, iter: TTypeIter,
@@ -176,7 +181,7 @@ proc iterOverTypeAux(marker: var IntSet, t: PType, iter: TTypeIter,
   if result: return
   if not containsOrIncl(marker, t.id):
     case t.kind
-    of tyGenericInst, tyGenericBody:
+    of tyGenericInst, tyGenericBody, tyAlias:
       result = iterOverTypeAux(marker, lastSon(t), iter, closure)
     else:
       for i in countup(0, sonsLen(t) - 1):
@@ -226,9 +231,9 @@ proc searchTypeForAux(t: PType, predicate: TTypePredicate,
     if t.sons[0] != nil:
       result = searchTypeForAux(t.sons[0].skipTypes(skipPtrs), predicate, marker)
     if not result: result = searchTypeNodeForAux(t.n, predicate, marker)
-  of tyGenericInst, tyDistinct:
+  of tyGenericInst, tyDistinct, tyAlias:
     result = searchTypeForAux(lastSon(t), predicate, marker)
-  of tyArray, tyArrayConstr, tySet, tyTuple:
+  of tyArray, tySet, tyTuple:
     for i in countup(0, sonsLen(t) - 1):
       result = searchTypeForAux(t.sons[i], predicate, marker)
       if result: return
@@ -269,9 +274,9 @@ proc analyseObjectWithTypeFieldAux(t: PType,
       if res == frHeader: result = frHeader
     if result == frNone:
       if isObjectWithTypeFieldPredicate(t): result = frHeader
-  of tyGenericInst, tyDistinct:
+  of tyGenericInst, tyDistinct, tyAlias:
     result = analyseObjectWithTypeFieldAux(lastSon(t), marker)
-  of tyArray, tyArrayConstr, tyTuple:
+  of tyArray, tyTuple:
     for i in countup(0, sonsLen(t) - 1):
       res = analyseObjectWithTypeFieldAux(t.sons[i], marker)
       if res != frNone:
@@ -328,8 +333,7 @@ proc canFormAcycleAux(marker: var IntSet, typ: PType, startId: int): bool =
   var t = skipTypes(typ, abstractInst-{tyTypeDesc})
   if tfAcyclic in t.flags: return
   case t.kind
-  of tyTuple, tyObject, tyRef, tySequence, tyArray, tyArrayConstr, tyOpenArray,
-     tyVarargs:
+  of tyTuple, tyObject, tyRef, tySequence, tyArray, tyOpenArray, tyVarargs:
     if not containsOrIncl(marker, t.id):
       for i in countup(0, sonsLen(t) - 1):
         result = canFormAcycleAux(marker, t.sons[i], startId)
@@ -394,7 +398,7 @@ proc rangeToStr(n: PNode): string =
 
 const
   typeToStr: array[TTypeKind, string] = ["None", "bool", "Char", "empty",
-    "Array Constructor [$1]", "nil", "untyped", "typed", "typeDesc",
+    "Alias", "nil", "untyped", "typed", "typeDesc",
     "GenericInvocation", "GenericBody", "GenericInst", "GenericParam",
     "distinct $1", "enum", "ordinal[$1]", "array[$1, $2]", "object", "tuple",
     "set[$1]", "range[$1]", "ptr ", "ref ", "var ", "seq[$1]", "proc",
@@ -444,8 +448,8 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
       add(result, typeToString(t.sons[i], preferGenericArg))
     add(result, ']')
   of tyTypeDesc:
-    if t.base.kind == tyNone: result = "typedesc"
-    else: result = "typedesc[" & typeToString(t.base) & "]"
+    if t.sons[0].kind == tyNone: result = "typedesc"
+    else: result = "typedesc[" & typeToString(t.sons[0]) & "]"
   of tyStatic:
     internalAssert t.len > 0
     if prefer == preferGenericArg and t.n != nil:
@@ -496,9 +500,6 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
     else:
       result = "array[" & typeToString(t.sons[0]) & ", " &
           typeToString(t.sons[1]) & ']'
-  of tyArrayConstr:
-    result = "Array constructor[" & rangeToStr(t.sons[0].n) & ", " &
-        typeToString(t.sons[1]) & ']'
   of tySequence:
     result = "seq[" & typeToString(t.sons[0]) & ']'
   of tyOrdinal:
@@ -572,15 +573,12 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
     result = typeToStr[t.kind]
   result.addTypeFlags(t)
 
-proc base(t: PType): PType =
-  result = t.sons[0]
-
 proc firstOrd(t: PType): BiggestInt =
   case t.kind
   of tyBool, tyChar, tySequence, tyOpenArray, tyString, tyVarargs, tyProxy:
     result = 0
   of tySet, tyVar: result = firstOrd(t.sons[0])
-  of tyArray, tyArrayConstr: result = firstOrd(t.sons[0])
+  of tyArray: result = firstOrd(t.sons[0])
   of tyRange:
     assert(t.n != nil)        # range directly given:
     assert(t.n.kind == nkRange)
@@ -600,7 +598,7 @@ proc firstOrd(t: PType): BiggestInt =
     else:
       assert(t.n.sons[0].kind == nkSym)
       result = t.n.sons[0].sym.position
-  of tyGenericInst, tyDistinct, tyTypeDesc, tyFieldAccessor:
+  of tyGenericInst, tyDistinct, tyTypeDesc, tyFieldAccessor, tyAlias:
     result = firstOrd(lastSon(t))
   of tyOrdinal:
     if t.len > 0: result = firstOrd(lastSon(t))
@@ -614,7 +612,7 @@ proc lastOrd(t: PType): BiggestInt =
   of tyBool: result = 1
   of tyChar: result = 255
   of tySet, tyVar: result = lastOrd(t.sons[0])
-  of tyArray, tyArrayConstr: result = lastOrd(t.sons[0])
+  of tyArray: result = lastOrd(t.sons[0])
   of tyRange:
     assert(t.n != nil)        # range directly given:
     assert(t.n.kind == nkRange)
@@ -636,7 +634,7 @@ proc lastOrd(t: PType): BiggestInt =
   of tyEnum:
     assert(t.n.sons[sonsLen(t.n) - 1].kind == nkSym)
     result = t.n.sons[sonsLen(t.n) - 1].sym.position
-  of tyGenericInst, tyDistinct, tyTypeDesc, tyFieldAccessor:
+  of tyGenericInst, tyDistinct, tyTypeDesc, tyFieldAccessor, tyAlias:
     result = lastOrd(lastSon(t))
   of tyProxy: result = 0
   of tyOrdinal:
@@ -778,8 +776,8 @@ proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool =
       var x = a.sons[i]
       var y = b.sons[i]
       if IgnoreTupleFields in c.flags:
-        x = skipTypes(x, {tyRange, tyGenericInst})
-        y = skipTypes(y, {tyRange, tyGenericInst})
+        x = skipTypes(x, {tyRange, tyGenericInst, tyAlias})
+        y = skipTypes(y, {tyRange, tyGenericInst, tyAlias})
 
       result = sameTypeAux(x, y, c)
       if not result: return
@@ -833,8 +831,8 @@ proc sameObjectTree(a, b: PNode, c: var TSameTypeClosure): bool =
     var x = a.typ
     var y = b.typ
     if IgnoreTupleFields in c.flags:
-      if x != nil: x = skipTypes(x, {tyRange, tyGenericInst})
-      if y != nil: y = skipTypes(y, {tyRange, tyGenericInst})
+      if x != nil: x = skipTypes(x, {tyRange, tyGenericInst, tyAlias})
+      if y != nil: y = skipTypes(y, {tyRange, tyGenericInst, tyAlias})
     if sameTypeOrNilAux(x, y, c):
       case a.kind
       of nkSym:
@@ -888,8 +886,8 @@ proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     result = eqTypeFlags*a.flags == eqTypeFlags*b.flags
 
   if x == y: return true
-  var a = skipTypes(x, {tyGenericInst})
-  var b = skipTypes(y, {tyGenericInst})
+  var a = skipTypes(x, {tyGenericInst, tyAlias})
+  var b = skipTypes(y, {tyGenericInst, tyAlias})
   assert(a != nil)
   assert(b != nil)
   if a.kind != b.kind:
@@ -957,7 +955,7 @@ proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     if result and ExactGenericParams in c.flags:
       result = a.sym.position == b.sym.position
   of tyGenericInvocation, tyGenericBody, tySequence,
-     tyOpenArray, tySet, tyRef, tyPtr, tyVar, tyArrayConstr,
+     tyOpenArray, tySet, tyRef, tyPtr, tyVar,
      tyArray, tyProc, tyVarargs, tyOrdinal, tyTypeClasses, tyFieldAccessor:
     cycleCheck()
     if a.kind == tyUserTypeClass and a.n != nil: return a.n == b.n
@@ -970,7 +968,7 @@ proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     result = sameTypeOrNilAux(a.sons[0], b.sons[0], c) and
         sameValue(a.n.sons[0], b.n.sons[0]) and
         sameValue(a.n.sons[1], b.n.sons[1])
-  of tyGenericInst: discard
+  of tyGenericInst, tyAlias: discard
   of tyNone: result = false
   of tyUnused, tyUnused0, tyUnused1, tyUnused2: internalError("sameFlags")
 
@@ -1117,7 +1115,7 @@ proc typeAllowedAux(marker: var IntSet, typ: PType, kind: TSymKind,
     result = nil
   of tyOrdinal:
     if kind != skParam: result = t
-  of tyGenericInst, tyDistinct:
+  of tyGenericInst, tyDistinct, tyAlias:
     result = typeAllowedAux(marker, lastSon(t), kind, flags)
   of tyRange:
     if skipTypes(t.sons[0], abstractInst-{tyTypeDesc}).kind notin
@@ -1136,7 +1134,7 @@ proc typeAllowedAux(marker: var IntSet, typ: PType, kind: TSymKind,
     else: result = typeAllowedAux(marker, t.lastSon, skVar, flags+{taHeap})
   of tyPtr:
     result = typeAllowedAux(marker, t.lastSon, skVar, flags+{taHeap})
-  of tyArrayConstr, tySet:
+  of tySet:
     for i in countup(0, sonsLen(t) - 1):
       result = typeAllowedAux(marker, t.sons[i], kind, flags)
       if result != nil: break
@@ -1250,7 +1248,7 @@ proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
       result = szIllegalRecursion
     else: result = ptrSize
     a = result
-  of tyArray, tyArrayConstr:
+  of tyArray:
     let elemSize = computeSizeAux(typ.sons[1], a)
     if elemSize < 0: return elemSize
     result = lengthOrd(typ.sons[0]) * elemSize
@@ -1304,7 +1302,7 @@ proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
     if result < 0: return
     if a < maxAlign: a = maxAlign
     result = align(result, a)
-  of tyGenericInst, tyDistinct, tyGenericBody:
+  of tyGenericInst, tyDistinct, tyGenericBody, tyAlias:
     result = computeSizeAux(lastSon(typ), a)
   of tyTypeDesc:
     result = computeSizeAux(typ.base, a)
@@ -1466,10 +1464,10 @@ proc skipConvTakeType*(n: PNode): PNode =
 proc isEmptyContainer*(t: PType): bool =
   case t.kind
   of tyExpr, tyNil: result = true
-  of tyArray, tyArrayConstr: result = t.sons[1].kind == tyEmpty
+  of tyArray: result = t.sons[1].kind == tyEmpty
   of tySet, tySequence, tyOpenArray, tyVarargs:
     result = t.sons[0].kind == tyEmpty
-  of tyGenericInst: result = isEmptyContainer(t.lastSon)
+  of tyGenericInst, tyAlias: result = isEmptyContainer(t.lastSon)
   else: result = false
 
 proc takeType*(formal, arg: PType): PType =
@@ -1480,8 +1478,8 @@ proc takeType*(formal, arg: PType): PType =
     result = formal
   elif formal.kind in {tyOpenArray, tyVarargs, tySequence} and
       arg.isEmptyContainer:
-    let a = copyType(arg.skipTypes({tyGenericInst}), arg.owner, keepId=false)
-    a.sons[ord(arg.kind in {tyArray, tyArrayConstr})] = formal.sons[0]
+    let a = copyType(arg.skipTypes({tyGenericInst, tyAlias}), arg.owner, keepId=false)
+    a.sons[ord(arg.kind == tyArray)] = formal.sons[0]
     result = a
   elif formal.kind in {tyTuple, tySet} and arg.kind == formal.kind:
     result = formal
diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim
index bd6908722..30b5c17a2 100644
--- a/compiler/vmdeps.nim
+++ b/compiler/vmdeps.nim
@@ -136,7 +136,7 @@ proc mapTypeToAstX(t: PType; info: TLineInfo;
   of tyStmt: result = atomicType("stmt", mStmt)
   of tyVoid: result = atomicType("void", mVoid)
   of tyEmpty: result = atomicType("empty", mNone)
-  of tyArrayConstr, tyArray:
+  of tyArray:
     result = newNodeIT(nkBracketExpr, if t.n.isNil: info else: t.n.info, t)
     result.add atomicType("array", mArray)
     if inst and t.sons[0].kind == tyRange:
@@ -159,7 +159,7 @@ proc mapTypeToAstX(t: PType; info: TLineInfo;
     result = newNodeIT(nkBracketExpr, if t.n.isNil: info else: t.n.info, t)
     for i in 0 .. < t.len:
       result.add mapTypeToAst(t.sons[i], info)
-  of tyGenericInst:
+  of tyGenericInst, tyAlias:
     if inst:
       if allowRecursion:
         result = mapTypeToAstR(t.lastSon, info)
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index ed8f3f338..69249abfe 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -1482,7 +1482,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
       getNullValueAux(skipTypes(base, skipPtrs).n, result)
       base = base.sons[0]
     getNullValueAux(t.n, result)
-  of tyArray, tyArrayConstr:
+  of tyArray:
     result = newNodeIT(nkBracket, info, t)
     for i in countup(0, int(lengthOrd(t)) - 1):
       addSon(result, getNullValue(elemType(t), info))
diff --git a/compiler/vmmarshal.nim b/compiler/vmmarshal.nim
index c08c5d249..51301b931 100644
--- a/compiler/vmmarshal.nim
+++ b/compiler/vmmarshal.nim
@@ -102,7 +102,7 @@ proc storeAny(s: var string; t: PType; a: PNode; stored: var IntSet) =
       else:
         storeAny(s, t.lastSon, a[i], stored)
     s.add("]")
-  of tyRange, tyGenericInst: storeAny(s, t.lastSon, a, stored)
+  of tyRange, tyGenericInst, tyAlias: storeAny(s, t.lastSon, a, stored)
   of tyEnum:
     # we need a slow linear search because of enums with holes:
     for e in items(t.n):
@@ -275,7 +275,7 @@ proc loadAny(p: var JsonParser, t: PType,
       next(p)
       return
     raiseParseErr(p, "float expected")
-  of tyRange, tyGenericInst: result = loadAny(p, t.lastSon, tab)
+  of tyRange, tyGenericInst, tyAlias: result = loadAny(p, t.lastSon, tab)
   else:
     internalError "cannot marshal at compile-time " & t.typeToString
 
diff --git a/koch.nim b/koch.nim
index d8004b3e6..586565fc7 100644
--- a/koch.nim
+++ b/koch.nim
@@ -391,13 +391,28 @@ proc tests(args: string) =
     quit("tests failed", QuitFailure)
 
 proc temp(args: string) =
+  proc splitArgs(a: string): (string, string) =
+    # every --options before the command (indicated by starting
+    # with not a dash) is part of the bootArgs, the rest is part
+    # of the programArgs:
+    let args = os.parseCmdLine a
+    result = ("", "")
+    var i = 0
+    while i < args.len and args[i][0] == '-':
+      result[0].add " " & quoteShell(args[i])
+      inc i
+    while i < args.len:
+      result[1].add " " & quoteShell(args[i])
+      inc i
+
   var output = "compiler" / "nim".exe
   var finalDest = "bin" / "nim_temp".exe
   # 125 is the magic number to tell git bisect to skip the current
   # commit.
-  exec("nim c compiler" / "nim", 125)
+  let (bootArgs, programArgs) = splitArgs(args)
+  exec("nim c " & bootArgs & " compiler" / "nim", 125)
   copyExe(output, finalDest)
-  if args.len > 0: exec(finalDest & " " & args)
+  if programArgs.len > 0: exec(finalDest & " " & programArgs)
 
 proc copyDir(src, dest: string) =
   for kind, path in walkDir(src, relative=true):
diff --git a/lib/pure/securehash.nim b/lib/pure/securehash.nim
index 1f00ce8d3..f141732a7 100644
--- a/lib/pure/securehash.nim
+++ b/lib/pure/securehash.nim
@@ -43,13 +43,13 @@ type
 # Ported to Nim by Erik O'Leary
 
 type
-  Sha1State = array[0 .. 5-1, uint32]
+  Sha1State* = array[0 .. 5-1, uint32]
   Sha1Buffer = array[0 .. 80-1, uint32]
 
 template clearBuffer(w: Sha1Buffer, len = 16) =
   zeroMem(addr(w), len * sizeof(uint32))
 
-proc init(result: var Sha1State) =
+proc init*(result: var Sha1State) =
   result[0] = 0x67452301'u32
   result[1] = 0xefcdab89'u32
   result[2] = 0x98badcfe'u32
@@ -112,7 +112,7 @@ proc innerHash(state: var Sha1State, w: var Sha1Buffer) =
   wrap state[3], d
   wrap state[4], e
 
-template computeInternal(src: untyped) =
+proc sha1(src: cstring; len: int): Sha1Digest =
   #Initialize state
   var state: Sha1State
   init(state)
@@ -121,10 +121,10 @@ template computeInternal(src: untyped) =
   var w: Sha1Buffer
 
   #Loop through all complete 64byte blocks.
-  let byteLen         = src.len
+  let byteLen = len
   let endOfFullBlocks = byteLen - 64
   var endCurrentBlock = 0
-  var currentBlock    = 0
+  var currentBlock = 0
 
   while currentBlock <= endOfFullBlocks:
     endCurrentBlock = currentBlock + 64
@@ -169,9 +169,9 @@ template computeInternal(src: untyped) =
   for i in 0 .. Sha1DigestSize-1:
     result[i] = uint8((int(state[i shr 2]) shr ((3-(i and 3)) * 8)) and 255)
 
-proc sha1(src: string) : Sha1Digest =
+proc sha1(src: string): Sha1Digest =
   ## Calculate SHA1 from input string
-  computeInternal(src)
+  sha1(src, src.len)
 
 proc secureHash*(str: string): SecureHash = SecureHash(sha1(str))
 proc secureHashFile*(filename: string): SecureHash = secureHash(readFile(filename))
diff --git a/lib/pure/strtabs.nim b/lib/pure/strtabs.nim
index c5d471dfa..02bf439b2 100644
--- a/lib/pure/strtabs.nim
+++ b/lib/pure/strtabs.nim
@@ -108,7 +108,7 @@ proc rawGet(t: StringTableRef, key: string): int =
     h = nextTry(h, high(t.data))
   result = - 1
 
-template get(t: StringTableRef, key: string): stmt {.immediate.} =
+template get(t: StringTableRef, key: string) =
   var index = rawGet(t, key)
   if index >= 0: result = t.data[index].val
   else: