summary refs log tree commit diff stats
diff options
context:
space:
mode:
-rw-r--r--compiler/ast.nim36
-rw-r--r--compiler/ccgutils.nim2
-rw-r--r--compiler/cgen.nim4
-rw-r--r--compiler/evalffi.nim2
-rw-r--r--compiler/evals.nim17
-rw-r--r--compiler/jsgen.nim2
-rw-r--r--compiler/msgs.nim13
-rw-r--r--compiler/parser.nim26
-rw-r--r--compiler/procfind.nim2
-rw-r--r--compiler/ropes.nim17
-rw-r--r--compiler/sem.nim55
-rw-r--r--compiler/semcall.nim20
-rw-r--r--compiler/semdata.nim20
-rw-r--r--compiler/semexprs.nim33
-rw-r--r--compiler/semfold.nim10
-rw-r--r--compiler/seminst.nim41
-rw-r--r--compiler/semmagic.nim15
-rw-r--r--compiler/semstmts.nim16
-rw-r--r--compiler/semtypes.nim160
-rw-r--r--compiler/semtypinst.nim83
-rw-r--r--compiler/sigmatch.nim251
-rw-r--r--compiler/suggest.nim2
-rw-r--r--compiler/types.nim135
-rw-r--r--compiler/vm.nim3
-rw-r--r--compiler/vmgen.nim6
-rw-r--r--doc/manual.txt54
-rw-r--r--lib/core/macros.nim22
-rw-r--r--lib/system.nim30
-rw-r--r--tests/compile/tbindtypedesc.nim60
-rw-r--r--tests/compile/tcompositetypeclasses.nim35
-rw-r--r--tests/compile/tloops.nim128
-rw-r--r--tests/reject/tillrec.nim19
-rw-r--r--tests/reject/typredef.nim6
-rw-r--r--tests/run/tfailedassert.nim51
-rw-r--r--tests/run/tmemoization.nim10
-rw-r--r--tests/run/tsemistatic.nim24
-rw-r--r--tests/run/tstaticparams.nim16
-rw-r--r--tests/run/ttypetraits.nim2
-rw-r--r--tests/run/tusingstatement.nim24
-rw-r--r--todo.txt1
-rw-r--r--web/news.txt18
41 files changed, 902 insertions, 569 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 5a3af27e8..6f30522a2 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -192,6 +192,7 @@ type
     nkObjectTy,           # object body
     nkTupleTy,            # tuple body
     nkTypeClassTy,        # user-defined type class
+    nkStaticTy,           # ``static[T]``
     nkRecList,            # list of object parts
     nkRecCase,            # case section of object
     nkRecWhen,            # when section of object
@@ -336,19 +337,26 @@ type
     tyIter, # unused
     tyProxy # used as errornous type (for idetools)
     tyTypeClass
+    tyParametricTypeClass # structured similarly to tyGenericInst
+                          # lastSon is the body of the type class
+    tyBuiltInTypeClass
+    tyCompositeTypeClass
     tyAnd
     tyOr
     tyNot
     tyAnything
-    tyParametricTypeClass # structured similarly to tyGenericInst
-                          # lastSon is the body of the type class
+    tyStatic
 
 const
   tyPureObject* = tyTuple
   GcTypeKinds* = {tyRef, tySequence, tyString}
   tyError* = tyProxy # as an errornous node should match everything
-  tyTypeClasses* = {tyTypeClass, tyParametricTypeClass, tyAnd, tyOr, tyNot, tyAnything}
+  
+  tyTypeClasses* = {tyTypeClass, tyBuiltInTypeClass, tyCompositeTypeClass,
+                    tyParametricTypeClass, tyAnd, tyOr, tyNot, tyAnything}
 
+  tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyStatic, tyExpr} + tyTypeClasses
+ 
 type
   TTypeKinds* = set[TTypeKind]
 
@@ -383,9 +391,6 @@ type
                       # proc foo(T: typedesc, list: seq[T]): var T
     tfRetType,        # marks return types in proc (used to detect type classes 
                       # used as return types for return type inference)
-    tfAll,            # type class requires all constraints to be met (default)
-    tfAny,            # type class requires any constraint to be met
-    tfNot,            # type class with a negative check
     tfCapturesEnv,    # whether proc really captures some environment
     tfByCopy,         # pass object/tuple by copy (C backend)
     tfByRef,          # pass object/tuple by reference (C backend)
@@ -396,8 +401,11 @@ type
     tfNeedsInit,      # type constains a "not nil" constraint somewhere or some
                       # other type so that it requires inititalization
     tfHasShared,      # type constains a "shared" constraint modifier somewhere
-    tfHasMeta,        # type has "typedesc" or "expr" somewhere; or uses '|'
+    tfHasMeta,        # type contains "wildcard" sub-types such as generic params
+                      # or other type classes
     tfHasGCedMem,     # type contains GC'ed memory
+    tfGenericTypeParam
+    tfHasStatic
 
   TTypeFlags* = set[TTypeFlag]
 
@@ -774,9 +782,11 @@ const
 
   GenericTypes*: TTypeKinds = {tyGenericInvokation, tyGenericBody, 
     tyGenericParam}
+  
   StructuralEquivTypes*: TTypeKinds = {tyArrayConstr, tyNil, tyTuple, tyArray, 
     tySet, tyRange, tyPtr, tyRef, tyVar, tySequence, tyProc, tyOpenArray,
     tyVarargs}
+  
   ConcreteTypes*: TTypeKinds = { # types of the expr that may occur in::
                                  # var x = expr
     tyBool, tyChar, tyEnum, tyArray, tyObject, 
@@ -1219,7 +1229,7 @@ proc newSons(father: PNode, length: int) =
 proc propagateToOwner*(owner, elem: PType) =
   const HaveTheirOwnEmpty = {tySequence, tySet}
   owner.flags = owner.flags + (elem.flags * {tfHasShared, tfHasMeta,
-                                             tfHasGCedMem})
+                                             tfHasStatic, tfHasGCedMem})
   if tfNotNil in elem.flags:
     if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvokation}:
       owner.flags.incl tfNotNil
@@ -1232,10 +1242,14 @@ proc propagateToOwner*(owner, elem: PType) =
     
   if tfShared in elem.flags:
     owner.flags.incl tfHasShared
-  
-  if elem.kind in {tyExpr, tyTypeDesc}:
+ 
+  if elem.kind in tyMetaTypes:
     owner.flags.incl tfHasMeta
-  elif elem.kind in {tyString, tyRef, tySequence} or
+
+  if elem.kind == tyStatic:
+    owner.flags.incl tfHasStatic
+
+  if elem.kind in {tyString, tyRef, tySequence} or
       elem.kind == tyProc and elem.callConv == ccClosure:
     owner.flags.incl tfHasGCedMem
 
diff --git a/compiler/ccgutils.nim b/compiler/ccgutils.nim
index 1c2d7e038..b07047ec4 100644
--- a/compiler/ccgutils.nim
+++ b/compiler/ccgutils.nim
@@ -88,7 +88,7 @@ proc getUniqueType*(key: PType): PType =
       result = key
   of tyTypeDesc, tyTypeClasses:
     internalError("value expected, but got a type")
-  of tyGenericParam:
+  of tyGenericParam, tyStatic:
     internalError("GetUniqueType")
   of tyGenericInst, tyDistinct, tyOrdinal, tyMutable, tyConst, tyIter:
     result = getUniqueType(lastSon(key))
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index c74f0807d..3aef60fa6 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -194,7 +194,7 @@ when compileTimeRopeFmt:
       if i - 1 >= start:
         yield (kind: ffLit, value: substr(s, start, i-1), intValue: 0)
 
-  macro rfmt(m: BModule, fmt: expr[string], args: varargs[PRope]): expr =
+  macro rfmt(m: BModule, fmt: static[string], args: varargs[PRope]): expr =
     ## Experimental optimized rope-formatting operator
     ## The run-time code it produces will be very fast, but will it speed up
     ## the compilation of nimrod itself or will the macro execution time
@@ -209,7 +209,7 @@ when compileTimeRopeFmt:
       of ffParam:
         result.add(args[frag.intValue])
 else:
-  template rfmt(m: BModule, fmt: expr[string], args: varargs[PRope]): expr =
+  template rfmt(m: BModule, fmt: string, args: varargs[PRope]): expr =
     ropecg(m, fmt, args)
 
 proc appcg(m: BModule, c: var PRope, frmt: TFormatStr, 
diff --git a/compiler/evalffi.nim b/compiler/evalffi.nim
index 3b8ce0505..74f0663f3 100644
--- a/compiler/evalffi.nim
+++ b/compiler/evalffi.nim
@@ -87,7 +87,7 @@ 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, tyNil:
+     tyStmt, tyTypeDesc, tyProc, tyArray, tyArrayConstr, tyStatic, tyNil:
     result = addr libffi.type_pointer
   of tyDistinct:
     result = mapType(t.sons[0])
diff --git a/compiler/evals.nim b/compiler/evals.nim
index b4ea973e8..151adf690 100644
--- a/compiler/evals.nim
+++ b/compiler/evals.nim
@@ -91,6 +91,7 @@ proc evalMacroCall*(c: PEvalContext, n, nOrig: PNode, sym: PSym): PNode
 proc evalAux(c: PEvalContext, n: PNode, flags: TEvalFlags): PNode
 
 proc raiseCannotEval(c: PEvalContext, info: TLineInfo): PNode =
+  if defined(debug) and gVerbosity >= 3: writeStackTrace()
   result = newNodeI(nkExceptBranch, info)
   # creating a nkExceptBranch without sons 
   # means that it could not be evaluated
@@ -263,8 +264,8 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
     result = newNodeIT(nkUIntLit, info, t)
   of tyFloat..tyFloat128: 
     result = newNodeIt(nkFloatLit, info, t)
-  of tyVar, tyPointer, tyPtr, tyRef, tyCString, tySequence, tyString, tyExpr, 
-     tyStmt, tyTypeDesc, tyProc:
+  of tyVar, tyPointer, tyPtr, tyRef, tyCString, tySequence, tyString, tyExpr,
+     tyStmt, tyTypeDesc, tyStatic, tyProc:
     result = newNodeIT(nkNilLit, info, t)
   of tyObject: 
     result = newNodeIT(nkPar, info, t)
@@ -358,7 +359,7 @@ proc evalVar(c: PEvalContext, n: PNode): PNode =
 
 proc aliasNeeded(n: PNode, flags: TEvalFlags): bool = 
   result = efLValue in flags or n.typ == nil or 
-    n.typ.kind in {tyExpr, tyStmt, tyTypeDesc}
+    n.typ.kind in {tyExpr, tyStatic, tyStmt, tyTypeDesc}
 
 proc evalVariable(c: PStackFrame, sym: PSym, flags: TEvalFlags): PNode =
   # We need to return a node to the actual value,
@@ -905,17 +906,15 @@ proc evalParseStmt(c: PEvalContext, n: PNode): PNode =
   result = parseString(code.getStrValue, code.info.toFilename,
                        code.info.line.int)
   #result.typ = newType(tyStmt, c.module)
- 
-proc evalTypeTrait*(trait, operand: PNode, context: PSym): PNode =
-  InternalAssert operand.kind == nkSym
 
-  let typ = operand.sym.typ.skipTypes({tyTypeDesc})
+proc evalTypeTrait*(trait, operand: PNode, context: PSym): PNode =
+  let typ = operand.typ.skipTypes({tyTypeDesc})
   case trait.sym.name.s.normalize
   of "name":
     result = newStrNode(nkStrLit, typ.typeToString(preferName))
     result.typ = newType(tyString, context)
     result.info = trait.info
-  of "arity":    
+  of "arity":
     result = newIntNode(nkIntLit, typ.n.len-1)
     result.typ = newType(tyInt, context)
     result.info = trait.info
@@ -1329,7 +1328,7 @@ proc evalAux(c: PEvalContext, n: PNode, flags: TEvalFlags): PNode =
   if gNestedEvals <= 0: stackTrace(c, n.info, errTooManyIterations)
   case n.kind
   of nkSym: result = evalSym(c, n, flags)
-  of nkType..nkNilLit:
+  of nkType..nkNilLit, nkTypeOfExpr:
     # nkStrLit is VERY common in the traces, so we should avoid
     # the 'copyNode' here.
     result = n #.copyNode
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index c6b0b194f..ddfc189dd 100644
--- a/compiler/jsgen.nim
+++ b/compiler/jsgen.nim
@@ -130,7 +130,7 @@ proc mapType(typ: PType): TJSTypeKind =
     result = etyObject
   of tyNil: result = etyNull
   of tyGenericInst, tyGenericParam, tyGenericBody, tyGenericInvokation, tyNone, 
-     tyForward, tyEmpty, tyExpr, tyStmt, tyTypeDesc, tyTypeClasses: 
+     tyForward, tyEmpty, tyExpr, tyStmt, tyStatic, tyTypeDesc, tyTypeClasses: 
     result = etyNone
   of tyProc: result = etyProc
   of tyCString: result = etyString
diff --git a/compiler/msgs.nim b/compiler/msgs.nim
index cc76f857d..1b4d8e47a 100644
--- a/compiler/msgs.nim
+++ b/compiler/msgs.nim
@@ -643,6 +643,8 @@ proc toFileLine*(info: TLineInfo): string {.inline.} =
 proc toFileLineCol*(info: TLineInfo): string {.inline.} =
   result = info.toFilename & "(" & $info.line & "," & $info.col & ")"
 
+template `$`*(info: TLineInfo): expr = toFileLineCol(info)
+
 proc `??`* (info: TLineInfo, filename: string): bool =
   # only for debugging purposes
   result = filename in info.toFilename
@@ -699,21 +701,20 @@ type
   TErrorHandling = enum doNothing, doAbort, doRaise
 
 proc handleError(msg: TMsgKind, eh: TErrorHandling, s: string) =
-  template maybeTrace =
+  template quit =
     if defined(debug) or gVerbosity >= 3 or msg == errInternal:
       writeStackTrace()
+    quit 1
 
   if msg >= fatalMin and msg <= fatalMax: 
-    maybeTrace()
-    quit(1)
+    quit()
   if msg >= errMin and msg <= errMax: 
-    maybeTrace()
     inc(gErrorCounter)
     options.gExitcode = 1'i8
     if gErrorCounter >= gErrorMax: 
-      quit(1)
+      quit()
     elif eh == doAbort and gCmd != cmdIdeTools:
-      quit(1)
+      quit()
     elif eh == doRaise:
       raiseRecoverableError(s)
 
diff --git a/compiler/parser.nim b/compiler/parser.nim
index b3a4e6963..e7a15c8ab 100644
--- a/compiler/parser.nim
+++ b/compiler/parser.nim
@@ -965,14 +965,18 @@ proc primary(p: var TParser, mode: TPrimaryMode): PNode =
   of tkTuple: result = parseTuple(p, mode == pmTypeDef)
   of tkProc: result = parseProcExpr(p, mode notin {pmTypeDesc, pmTypeDef})
   of tkIterator:
-    if mode in {pmTypeDesc, pmTypeDef}:
-      result = parseProcExpr(p, false)
-      result.kind = nkIteratorTy
+    when true:
+      if mode in {pmTypeDesc, pmTypeDef}:
+        result = parseProcExpr(p, false)
+        result.kind = nkIteratorTy
+      else:
+        # no anon iterators for now:
+        parMessage(p, errExprExpected, p.tok)
+        getTok(p)  # we must consume a token here to prevend endless loops!
+        result = ast.emptyNode
     else:
-      # no anon iterators for now:
-      parMessage(p, errExprExpected, p.tok)
-      getTok(p)  # we must consume a token here to prevend endless loops!
-      result = ast.emptyNode
+      result = parseProcExpr(p, mode notin {pmTypeDesc, pmTypeDef})
+      result.kind = nkIteratorTy
   of tkEnum:
     if mode == pmTypeDef:
       result = parseEnum(p)
@@ -995,9 +999,13 @@ proc primary(p: var TParser, mode: TPrimaryMode): PNode =
     getTokNoInd(p)
     addSon(result, primary(p, pmNormal))
   of tkStatic:
-    result = newNodeP(nkStaticExpr, p)
+    let info = parLineInfo(p)
     getTokNoInd(p)
-    addSon(result, primary(p, pmNormal))
+    let next = primary(p, pmNormal)
+    if next.kind == nkBracket and next.sonsLen == 1:
+      result = newNode(nkStaticTy, info, @[next.sons[0]])
+    else:
+      result = newNode(nkStaticExpr, info, @[next])
   of tkBind:
     result = newNodeP(nkBind, p)
     getTok(p)
diff --git a/compiler/procfind.nim b/compiler/procfind.nim
index 51bd7b937..f02e7aed4 100644
--- a/compiler/procfind.nim
+++ b/compiler/procfind.nim
@@ -25,7 +25,7 @@ proc equalGenericParams(procA, procB: PNode): bool =
     let a = procA.sons[i].sym
     let b = procB.sons[i].sym
     if a.name.id != b.name.id or
-        not sameTypeOrNil(a.typ, b.typ, {TypeDescExactMatch}): return
+        not sameTypeOrNil(a.typ, b.typ, {ExactTypeDescValues}): return
     if a.ast != nil and b.ast != nil:
       if not exprStructuralEquivalent(a.ast, b.ast): return
   result = true
diff --git a/compiler/ropes.nim b/compiler/ropes.nim
index 2be40524a..fcf5dd202 100644
--- a/compiler/ropes.nim
+++ b/compiler/ropes.nim
@@ -282,13 +282,16 @@ proc ropef(frmt: TFormatStr, args: varargs[PRope]): PRope =
       app(result, substr(frmt, start, i - 1))
   assert(ropeInvariant(result))
 
-{.push stack_trace: off, line_trace: off.}
-proc `~`*(r: expr[string]): PRope =
-  # this is the new optimized "to rope" operator
-  # the mnemonic is that `~` looks a bit like a rope :)
-  var r {.global.} = r.ropef
-  return r
-{.pop.}
+when true:
+  template `~`*(r: string): PRope = r.ropef
+else:
+  {.push stack_trace: off, line_trace: off.}
+  proc `~`*(r: static[string]): PRope =
+    # this is the new optimized "to rope" operator
+    # the mnemonic is that `~` looks a bit like a rope :)
+    var r {.global.} = r.ropef
+    return r
+  {.pop.}
 
 proc appf(c: var PRope, frmt: TFormatStr, args: varargs[PRope]) = 
   app(c, ropef(frmt, args))
diff --git a/compiler/sem.nim b/compiler/sem.nim
index a5b72e2b8..df37a6384 100644
--- a/compiler/sem.nim
+++ b/compiler/sem.nim
@@ -158,6 +158,16 @@ proc isOpImpl(c: PContext, n: PNode): PNode
 proc semMacroExpr(c: PContext, n, nOrig: PNode, sym: PSym,
                   semCheck: bool = true): PNode
 
+proc symFromType(t: PType, info: TLineInfo): PSym =
+  if t.sym != nil: return t.sym
+  result = newSym(skType, getIdent"AnonType", t.owner, info)
+  result.flags.incl sfAnon
+  result.typ = t
+
+proc symNodeFromType(c: PContext, t: PType, info: TLineInfo): PNode =
+  result = newSymNode(symFromType(t, info), info)
+  result.typ = makeTypeDesc(c, t)
+
 when false:
   proc createEvalContext(c: PContext, mode: TEvalMode): PEvalContext =
     result = newEvalContext(c.module, mode)
@@ -169,10 +179,37 @@ when false:
         result = newSymNode(getSysSym"void")
       else:
         result.typ = makeTypeDesc(c, result.typ)
-
+    
     result.handleIsOperator = proc (n: PNode): PNode =
-      result = IsOpImpl(c, n)
+      result = isOpImpl(c, n)
+
+proc fixupTypeAfterEval(c: PContext, evaluated, eOrig: PNode): PNode =
+  # recompute the types as 'eval' isn't guaranteed to construct types nor
+  # that the types are sound:
+  result = semExprWithType(c, evaluated)
+  #result = fitNode(c, e.typ, result) inlined with special case:
+  let arg = result
+  result = indexTypesMatch(c, eOrig.typ, arg.typ, arg)
+  if result == nil:
+    result = arg
+    # for 'tcnstseq' we support [] to become 'seq'
+    if eOrig.typ.skipTypes(abstractInst).kind == tySequence and 
+       arg.typ.skipTypes(abstractInst).kind == tyArrayConstr:
+      arg.typ = eOrig.typ
+
+proc tryConstExpr(c: PContext, n: PNode): PNode =
+  var e = semExprWithType(c, n)
+  if e == nil: return
+
+  result = getConstExpr(c.module, e)
+  if result != nil: return
 
+  result = evalConstExpr(c.module, e)
+  if result == nil or result.kind == nkEmpty:
+    return nil
+
+  result = fixupTypeAfterEval(c, result, e)
+  
 proc semConstExpr(c: PContext, n: PNode): PNode =
   var e = semExprWithType(c, n)
   if e == nil:
@@ -191,18 +228,7 @@ proc semConstExpr(c: PContext, n: PNode): PNode =
       # error correction:
       result = e
     else:
-      # recompute the types as 'eval' isn't guaranteed to construct types nor
-      # that the types are sound:
-      result = semExprWithType(c, result)
-      #result = fitNode(c, e.typ, result) inlined with special case:
-      let arg = result
-      result = indexTypesMatch(c, e.typ, arg.typ, arg)
-      if result == nil:
-        result = arg
-        # for 'tcnstseq' we support [] to become 'seq'
-        if e.typ.skipTypes(abstractInst).kind == tySequence and 
-           arg.typ.skipTypes(abstractInst).kind == tyArrayConstr:
-          arg.typ = e.typ
+      result = fixupTypeAfterEval(c, result, e)
 
 include hlo, seminst, semcall
 
@@ -282,6 +308,7 @@ proc myOpen(module: PSym): PPassContext =
   c.semConstExpr = semConstExpr
   c.semExpr = semExpr
   c.semTryExpr = tryExpr
+  c.semTryConstExpr = tryConstExpr
   c.semOperand = semOperand
   c.semConstBoolExpr = semConstBoolExpr
   c.semOverloadedCall = semOverloadedCall
diff --git a/compiler/semcall.nim b/compiler/semcall.nim
index 6140d8311..5990f2e96 100644
--- a/compiler/semcall.nim
+++ b/compiler/semcall.nim
@@ -47,14 +47,14 @@ proc pickBestCandidate(c: PContext, headSymbol: PNode,
   var z: TCandidate
   
   if sym == nil: return
-  initCandidate(best, sym, initialBinding, symScope)
-  initCandidate(alt, sym, initialBinding, symScope)
+  initCandidate(c, best, sym, initialBinding, symScope)
+  initCandidate(c, alt, sym, initialBinding, symScope)
   best.state = csNoMatch
   
   while sym != nil:
     if sym.kind in filter:
       determineType(c, sym)
-      initCandidate(z, sym, initialBinding, o.lastOverloadScope)
+      initCandidate(c, z, sym, initialBinding, o.lastOverloadScope)
       z.calleeSym = sym
       matches(c, n, orig, z)
       if errors != nil:
@@ -199,15 +199,15 @@ proc instGenericConvertersSons*(c: PContext, n: PNode, x: TCandidate) =
 
 proc indexTypesMatch(c: PContext, f, a: PType, arg: PNode): PNode = 
   var m: TCandidate
-  initCandidate(m, f)
-  result = paramTypesMatch(c, m, f, a, arg, nil)
+  initCandidate(c, m, f)
+  result = paramTypesMatch(m, f, a, arg, nil)
   if m.genericConverter and result != nil:
     instGenericConvertersArg(c, result, m)
 
 proc convertTo*(c: PContext, f: PType, n: PNode): PNode = 
   var m: TCandidate
-  initCandidate(m, f)
-  result = paramTypesMatch(c, m, f, n.typ, n, nil)
+  initCandidate(c, m, f)
+  result = paramTypesMatch(m, f, n.typ, n, nil)
   if m.genericConverter and result != nil:
     instGenericConvertersArg(c, result, m)
 
@@ -243,9 +243,9 @@ proc explicitGenericInstError(n: PNode): PNode =
   result = n
 
 proc explicitGenericSym(c: PContext, n: PNode, s: PSym): PNode =
-  var x: TCandidate
-  initCandidate(x, s, n)
-  var newInst = generateInstance(c, s, x.bindings, n.info)
+  var m: TCandidate
+  initCandidate(c, m, s, n)
+  var newInst = generateInstance(c, s, m.bindings, n.info)
   markUsed(n, s)
   result = newSymNode(newInst, n.info)
 
diff --git a/compiler/semdata.nim b/compiler/semdata.nim
index 924224fee..3020a6af1 100644
--- a/compiler/semdata.nim
+++ b/compiler/semdata.nim
@@ -75,6 +75,7 @@ type
     semExpr*: proc (c: PContext, n: PNode, flags: TExprFlags = {}): PNode {.nimcall.}
     semTryExpr*: proc (c: PContext, n: PNode,flags: TExprFlags = {},
                        bufferErrors = false): PNode {.nimcall.}
+    semTryConstExpr*: proc (c: PContext, n: PNode): PNode {.nimcall.}
     semOperand*: proc (c: PContext, n: PNode, flags: TExprFlags = {}): PNode {.nimcall.}
     semConstBoolExpr*: proc (c: PContext, n: PNode): PNode {.nimcall.} # XXX bite the bullet
     semOverloadedCall*: proc (c: PContext, n, nOrig: PNode,
@@ -213,7 +214,24 @@ proc makeTypeSymNode*(c: PContext, typ: PType, info: TLineInfo): PNode =
   let sym = newSym(skType, idAnon, getCurrOwner(), info).linkTo(typedesc)
   return newSymNode(sym, info)
 
-proc newTypeS(kind: TTypeKind, c: PContext): PType = 
+proc makeAndType*(c: PContext, t1, t2: PType): PType =
+  result = newTypeS(tyAnd, c)
+  result.sons = @[t1, t2]
+  propagateToOwner(result, t1)
+  propagateToOwner(result, t2)
+
+proc makeOrType*(c: PContext, t1, t2: PType): PType =
+  result = newTypeS(tyOr, c)
+  result.sons = @[t1, t2]
+  propagateToOwner(result, t1)
+  propagateToOwner(result, t2)
+
+proc makeNotType*(c: PContext, t1: PType): PType =
+  result = newTypeS(tyNot, c)
+  result.sons = @[t1]
+  propagateToOwner(result, t1)
+
+proc newTypeS(kind: TTypeKind, c: PContext): PType =
   result = newType(kind, getCurrOwner())
 
 proc newTypeWithSons*(c: PContext, kind: TTypeKind,
diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim
index 082ee7583..4e53a5389 100644
--- a/compiler/semexprs.nim
+++ b/compiler/semexprs.nim
@@ -102,7 +102,7 @@ proc semSym(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
     # if a proc accesses a global variable, it is not side effect free:
     if sfGlobal in s.flags:
       incl(c.p.owner.flags, sfSideEffect)
-    elif s.kind == skParam and s.typ.kind == tyExpr and s.typ.n != nil:
+    elif s.kind == skParam and s.typ.kind == tyStatic and s.typ.n != nil:
       # XXX see the hack in sigmatch.nim ...
       return s.typ.n
     result = newSymNode(s, n.info)
@@ -111,7 +111,7 @@ proc semSym(c: PContext, n: PNode, s: PSym, flags: TExprFlags): PNode =
     # var len = 0 # but won't be called
     # genericThatUsesLen(x) # marked as taking a closure?
   of skGenericParam:
-    if s.typ.kind == tyExpr:
+    if s.typ.kind == tyStatic:
       result = newSymNode(s, n.info)
       result.typ = s.typ
     elif s.ast != nil:
@@ -142,7 +142,7 @@ proc checkConversionBetweenObjects(castDest, src: PType): TConvStatus =
 const 
   IntegralTypes = {tyBool, tyEnum, tyChar, tyInt..tyUInt64}
 
-proc checkConvertible(castDest, src: PType): TConvStatus =
+proc checkConvertible(c: PContext, castDest, src: PType): TConvStatus =
   result = convOK
   if sameType(castDest, src) and castDest.sym == src.sym:
     # don't annoy conversions that may be needed on another processor:
@@ -163,7 +163,7 @@ proc checkConvertible(castDest, src: PType): TConvStatus =
     # accept conversion between integral types
   else:
     # we use d, s here to speed up that operation a bit:
-    case cmpTypes(d, s)
+    case cmpTypes(c, d, s)
     of isNone, isGeneric:
       if not compareTypes(castDest, src, dcEqIgnoreDistinct):
         result = convNotLegal
@@ -202,7 +202,7 @@ proc semConv(c: PContext, n: PNode): PNode =
   var op = result.sons[1]
   
   if not isSymChoice(op):
-    let status = checkConvertible(result.typ, op.typ)
+    let status = checkConvertible(c, result.typ, op.typ)
     case status
     of convOK: nil
     of convNotNeedeed:
@@ -213,7 +213,7 @@ proc semConv(c: PContext, n: PNode): PNode =
   else:
     for i in countup(0, sonsLen(op) - 1):
       let it = op.sons[i]
-      let status = checkConvertible(result.typ, it.typ)
+      let status = checkConvertible(c, result.typ, it.typ)
       if status == convOK:
         markUsed(n, it.sym)
         markIndirect(c, it.sym)
@@ -301,7 +301,7 @@ proc semOf(c: PContext, n: PNode): PNode =
 
 proc isOpImpl(c: PContext, n: PNode): PNode =
   internalAssert n.sonsLen == 3 and
-    n[1].typ != nil and
+    n[1].typ != nil and n[1].typ.kind == tyTypeDesc and
     n[2].kind in {nkStrLit..nkTripleStrLit, nkType}
   
   let t1 = n[1].typ.skipTypes({tyTypeDesc})
@@ -324,15 +324,15 @@ proc isOpImpl(c: PContext, n: PNode): PNode =
     case t2.kind
     of tyTypeClasses:
       var m: TCandidate
-      initCandidate(m, t2)
+      initCandidate(c, m, t2)
       match = matchUserTypeClass(c, m, emptyNode, t2, t1) != nil
     of tyOrdinal:
       var m: TCandidate
-      initCandidate(m, t2)
+      initCandidate(c, m, t2)
       match = isOrdinalType(t1)
     of tySequence, tyArray, tySet:
       var m: TCandidate
-      initCandidate(m, t2)
+      initCandidate(c, m, t2)
       match = typeRel(m, t2, t1) != isNone
     else:
       match = sameType(t1, t2)
@@ -668,6 +668,7 @@ proc semOverloadedCallAnalyseEffects(c: PContext, n: PNode, nOrig: PNode,
   else:
     result = semOverloadedCall(c, n, nOrig, 
       {skProc, skMethod, skConverter, skMacro, skTemplate})
+ 
   if result != nil:
     if result.sons[0].kind != nkSym: 
       internalError("semOverloadedCallAnalyseEffects")
@@ -706,7 +707,7 @@ proc semIndirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode =
   if t != nil and t.kind == tyProc:
     # This is a proc variable, apply normal overload resolution
     var m: TCandidate
-    initCandidate(m, t)
+    initCandidate(c, m, t)
     matches(c, n, nOrig, m)
     if m.state != csMatch:
       if c.inCompilesContext > 0:
@@ -939,7 +940,7 @@ proc builtinFieldAccess(c: PContext, n: PNode, flags: TExprFlags): PNode =
         let tParam = tbody.sons[s]
         if tParam.sym.name == i:
           let rawTyp = ty.sons[s + 1]
-          if rawTyp.kind == tyExpr:
+          if rawTyp.kind == tyStatic:
             return rawTyp.n
           else:
             let foundTyp = makeTypeDesc(c, rawTyp)
@@ -1164,7 +1165,7 @@ proc semAsgn(c: PContext, n: PNode): PNode =
     if lhsIsResult:
       n.typ = enforceVoidContext
       if lhs.sym.typ.kind == tyGenericParam:
-        if matchTypeClass(lhs.typ, rhs.typ):
+        if cmpTypes(c, lhs.typ, rhs.typ) == isGeneric:
           internalAssert c.p.resultSym != nil
           lhs.typ = rhs.typ
           c.p.resultSym.typ = rhs.typ
@@ -1884,7 +1885,7 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
   of nkBind:
     message(n.info, warnDeprecated, "bind")
     result = semExpr(c, n.sons[0], flags)
-  of nkTypeOfExpr, nkTupleTy, nkRefTy..nkEnumTy:
+  of nkTypeOfExpr, nkTupleTy, nkRefTy..nkEnumTy, nkStaticTy:
     var typ = semTypeNode(c, n, nil).skipTypes({tyTypeDesc})
     result.typ = makeTypeDesc(c, typ)
     #result = symNodeFromType(c, typ, n.info)
@@ -1945,7 +1946,9 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
       # type parameters: partial generic specialization
       n.sons[0] = semSymGenericInstantiation(c, n.sons[0], s)
       result = explicitGenericInstantiation(c, n, s)
-    else: 
+    elif s != nil and s.kind in {skType}:
+      result = symNodeFromType(c, semTypeNode(c, n, nil), n.info)
+    else:
       result = semArrayAccess(c, n, flags)
   of nkCurlyExpr:
     result = semExpr(c, buildOverloadedSubscripts(n, getIdent"{}"), flags)
diff --git a/compiler/semfold.nim b/compiler/semfold.nim
index 731085c3a..1d03e6888 100644
--- a/compiler/semfold.nim
+++ b/compiler/semfold.nim
@@ -230,6 +230,7 @@ discard """
 """
 
 proc evalIs(n, a: PNode): PNode =
+  # XXX: This should use the standard isOpImpl
   internalAssert a.kind == nkSym and a.sym.kind == skType
   internalAssert n.sonsLen == 3 and
     n[2].kind in {nkStrLit..nkTripleStrLit, nkType}
@@ -251,7 +252,7 @@ proc evalIs(n, a: PNode): PNode =
   else:
     # XXX semexprs.isOpImpl is slightly different and requires a context. yay.
     let t2 = n[2].typ
-    var match = if t2.kind == tyTypeClass: matchTypeClass(t2, t1)
+    var match = if t2.kind == tyTypeClass: true
                 else: sameType(t1, t2)
     result = newIntNode(nkIntLit, ord(match))
   result.typ = n.typ
@@ -612,9 +613,10 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
     of skType:
       result = newSymNodeTypeDesc(s, n.info)
     of skGenericParam:
-      if s.typ.kind == tyExpr:
-        result = s.typ.n
-        result.typ = s.typ.sons[0]
+      if s.typ.kind == tyStatic:
+        if s.typ.n != nil:
+          result = s.typ.n
+          result.typ = s.typ.sons[0]
       else:
         result = newSymNodeTypeDesc(s, n.info)
     else: discard
diff --git a/compiler/seminst.nim b/compiler/seminst.nim
index 1025457fd..f7f836644 100644
--- a/compiler/seminst.nim
+++ b/compiler/seminst.nim
@@ -20,7 +20,7 @@ proc instantiateGenericParamList(c: PContext, n: PNode, pt: TIdTable,
     if a.kind != nkSym: 
       internalError(a.info, "instantiateGenericParamList; no symbol")
     var q = a.sym
-    if q.typ.kind notin {tyTypeDesc, tyGenericParam, tyExpr}+tyTypeClasses:
+    if q.typ.kind notin {tyTypeDesc, tyGenericParam, tyStatic}+tyTypeClasses:
       continue
     var s = newSym(skType, q.name, getCurrOwner(), q.info)
     s.flags = s.flags + {sfUsed, sfFromGeneric}
@@ -47,7 +47,7 @@ proc sameInstantiation(a, b: TInstantiation): bool =
   if a.concreteTypes.len == b.concreteTypes.len:
     for i in 0..a.concreteTypes.high:
       if not compareTypes(a.concreteTypes[i], b.concreteTypes[i],
-                          flags = {TypeDescExactMatch}): return
+                          flags = {ExactTypeDescValues}): return
     result = true
 
 proc genericCacheGet(genericSym: PSym, entry: TInstantiation): PSym =
@@ -145,11 +145,11 @@ proc lateInstantiateGeneric(c: PContext, invocation: PType, info: TLineInfo): PT
     pushInfoContext(info)
     for i in 0 .. <s.typ.n.sons.len:
       let genericParam = s.typ.n[i].sym
-      let symKind = if genericParam.typ.kind == tyExpr: skConst
+      let symKind = if genericParam.typ.kind == tyStatic: skConst
                     else: skType
 
       var boundSym = newSym(symKind, s.typ.n[i].sym.name, s, info)
-      boundSym.typ = invocation.sons[i+1].skipTypes({tyExpr})
+      boundSym.typ = invocation.sons[i+1].skipTypes({tyStatic})
       boundSym.ast = invocation.sons[i+1].n
       addDecl(c, boundSym)
     # XXX: copyTree would have been unnecessary here if semTypeNode
@@ -165,7 +165,8 @@ proc lateInstantiateGeneric(c: PContext, invocation: PType, info: TLineInfo): PT
       result.sons.add instantiated
       cacheTypeInst result
 
-proc instGenericContainer(c: PContext, info: TLineInfo, header: PType): PType =
+proc instGenericContainer(c: PContext, info: TLineInfo, header: PType,
+                          allowMetaTypes = false): PType =
   when oUseLateInstantiation:
     lateInstantiateGeneric(c, header, info)
   else:
@@ -174,6 +175,7 @@ proc instGenericContainer(c: PContext, info: TLineInfo, header: PType): PType =
     initIdTable(cl.typeMap)
     cl.info = info
     cl.c = c
+    cl.allowMetaTypes = allowMetaTypes
     result = replaceTypeVarsT(cl, header)
 
 proc instGenericContainer(c: PContext, n: PNode, header: PType): PType =
@@ -196,12 +198,31 @@ proc fixupProcType(c: PContext, genericType: PType,
   case genericType.kind
   of tyGenericParam, tyTypeClasses:
     result = inst.concreteTypes[genericType.sym.position]
+  
   of tyTypeDesc:
     result = inst.concreteTypes[genericType.sym.position]
     if tfUnresolved in genericType.flags:
       result = result.sons[0]
-  of tyExpr:
+  
+  of tyStatic:
     result = inst.concreteTypes[genericType.sym.position]
+  
+  of tyGenericInst:
+    result = fixupProcType(c, result.lastSon, inst)
+  
+  of tyObject:
+    var recList = genericType.n
+    for i in 0 .. <recList.sonsLen:
+      let field = recList[i].sym
+      let changed = fixupProcType(c, field.typ, inst)
+      if field.typ != changed:
+        if result == genericType:
+          result = copyType(genericType, genericType.owner, false)
+          result.n = copyTree(recList)
+        result.n.sons[i].sym = copySym(recList[i].sym, true)
+        result.n.sons[i].typ = changed
+        result.n.sons[i].sym.typ = changed
+ 
   of tyOpenArray, tyArray, tySet, tySequence, tyTuple, tyProc,
      tyPtr, tyVar, tyRef, tyOrdinal, tyRange, tyVarargs:
     if genericType.sons == nil: return
@@ -232,7 +253,8 @@ proc fixupProcType(c: PContext, genericType: PType,
             continue
         
         result.sons[head] = changed
-        
+        result.size = 0
+
         if result.n != nil:
           if result.n.kind == nkRecList:
             for son in result.n.sons:
@@ -263,7 +285,7 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
                       info: TLineInfo): PSym =
   # no need to instantiate generic templates/macros:
   if fn.kind in {skTemplate, skMacro}: return fn
-  
+ 
   # generates an instantiated proc
   if c.instCounter > 1000: internalError(fn.ast.info, "nesting too deep")
   inc(c.instCounter)
@@ -288,7 +310,8 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
   var entry = TInstantiation.new
   entry.sym = result
   instantiateGenericParamList(c, n.sons[genericParamsPos], pt, entry[])
-  result.typ = fixupProcType(c, fn.typ, entry[])
+  # let t1 = fixupProcType(c, fn.typ, entry[])
+  result.typ = generateTypeInstance(c, pt, info, fn.typ)
   n.sons[genericParamsPos] = ast.emptyNode
   var oldPrc = genericCacheGet(fn, entry[])
   if oldPrc == nil:
diff --git a/compiler/semmagic.nim b/compiler/semmagic.nim
index 9a2645f7e..a1af94971 100644
--- a/compiler/semmagic.nim
+++ b/compiler/semmagic.nim
@@ -31,7 +31,6 @@ proc semInstantiationInfo(c: PContext, n: PNode): PNode =
   line.intVal = toLinenumber(info)
   result.add(filename)
   result.add(line)
-
  
 proc evalTypeTrait(trait: PNode, operand: PType, context: PSym): PNode =
   let typ = operand.skipTypes({tyTypeDesc})
@@ -40,7 +39,7 @@ proc evalTypeTrait(trait: PNode, operand: PType, context: PSym): PNode =
     result = newStrNode(nkStrLit, typ.typeToString(preferName))
     result.typ = newType(tyString, context)
     result.info = trait.info
-  of "arity":    
+  of "arity":
     result = newIntNode(nkIntLit, typ.n.len-1)
     result.typ = newType(tyInt, context)
     result.info = trait.info
@@ -50,11 +49,11 @@ proc evalTypeTrait(trait: PNode, operand: PType, context: PSym): PNode =
 proc semTypeTraits(c: PContext, n: PNode): PNode =
   checkMinSonsLen(n, 2)
   let t = n.sons[1].typ
-  internalAssert t != nil
-  if t.kind == tyTypeDesc and t.len == 0:
-    result = n
-  elif not containsGenericType(t):
-    result = evalTypeTrait(n[0], t, getCurrOwner())
+  internalAssert t != nil and t.kind == tyTypeDesc
+  if t.sonsLen > 0:
+    # This is either a type known to sem or a typedesc
+    # param to a regular proc (again, known at instantiation)
+    result = evalTypeTrait(n[0], t, GetCurrOwner())
   else:
     # a typedesc variable, pass unmodified to evals
     result = n
@@ -102,7 +101,7 @@ proc semLocals(c: PContext, n: PNode): PNode =
       #if it.owner != c.p.owner: return result
       if it.kind in skLocalVars and
           it.typ.skipTypes({tyGenericInst, tyVar}).kind notin
-              {tyVarargs, tyOpenArray, tyTypeDesc, tyExpr, tyStmt, tyEmpty}:
+            {tyVarargs, tyOpenArray, tyTypeDesc, tyStatic, tyExpr, tyStmt, tyEmpty}:
 
         var field = newSym(skField, it.name, getCurrOwner(), n.info)
         field.typ = it.typ.skipTypes({tyGenericInst, tyVar})
diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim
index 1766c4446..3cc338d8a 100644
--- a/compiler/semstmts.nim
+++ b/compiler/semstmts.nim
@@ -1037,12 +1037,16 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
     pushOwner(s)
   s.options = gOptions
   if sfDestructor in s.flags: doDestructorStuff(c, s, n)
-  if n.sons[bodyPos].kind != nkEmpty: 
+  if n.sons[bodyPos].kind != nkEmpty:
     # for DLL generation it is annoying to check for sfImportc!
-    if sfBorrow in s.flags: 
+    if sfBorrow in s.flags:
       localError(n.sons[bodyPos].info, errImplOfXNotAllowed, s.name.s)
-    if n.sons[genericParamsPos].kind == nkEmpty: 
-      paramsTypeCheck(c, s.typ)
+    let usePseudoGenerics = kind in {skMacro, skTemplate}
+    # Macros and Templates can have generic parameters, but they are
+    # only used for overload resolution (there is no instantiation of
+    # the symbol, so we must process the body now)
+    if n.sons[genericParamsPos].kind == nkEmpty or usePseudoGenerics:
+      if not usePseudoGenerics: paramsTypeCheck(c, s.typ)
       pushProcCon(c, s)
       maybeAddResult(c, s, n)
       if sfImportc notin s.flags:
@@ -1052,13 +1056,13 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
         # context as it may even be evaluated in 'system.compiles':
         n.sons[bodyPos] = transformBody(c.module, semBody, s)
       popProcCon(c)
-    else: 
+    else:
       if s.typ.sons[0] != nil and kind != skIterator:
         addDecl(c, newSym(skUnknown, getIdent"result", nil, n.info))
       var toBind = initIntSet()
       n.sons[bodyPos] = semGenericStmtScope(c, n.sons[bodyPos], {}, toBind)
       fixupInstantiatedSymbols(c, s)
-    if sfImportc in s.flags: 
+    if sfImportc in s.flags:
       # so we just ignore the body after semantic checking for importc:
       n.sons[bodyPos] = ast.emptyNode
   else:
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 4fdd84841..03d8b7095 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -18,7 +18,7 @@ proc newOrPrevType(kind: TTypeKind, prev: PType, c: PContext): PType =
     if result.kind == tyForward: result.kind = kind
 
 proc newConstraint(c: PContext, k: TTypeKind): PType = 
-  result = newTypeS(tyTypeClass, c)
+  result = newTypeS(tyBuiltInTypeClass, c)
   result.addSonSkipIntLit(newTypeS(k, c))
 
 proc semEnum(c: PContext, n: PNode, prev: PType): PType =
@@ -196,7 +196,7 @@ proc semArray(c: PContext, n: PNode, prev: PType): PType =
       let e = semExprWithType(c, n.sons[1], {efDetermineType})
       if e.kind in {nkIntLit..nkUInt64Lit}:
         indx = makeRangeType(c, 0, e.intVal-1, n.info, e.typ)
-      elif e.kind == nkSym and e.typ.kind == tyExpr:
+      elif e.kind == nkSym and e.typ.kind == tyStatic:
         if e.sym.ast != nil: return semArray(c, e.sym.ast, nil)
         internalAssert c.inGenericContext > 0
         if not isOrdinalType(e.typ.lastSon):
@@ -206,7 +206,7 @@ proc semArray(c: PContext, n: PNode, prev: PType): PType =
         indx = e.typ.skipTypes({tyTypeDesc})
     addSonSkipIntLit(result, indx)
     if indx.kind == tyGenericInst: indx = lastSon(indx)
-    if indx.kind notin {tyGenericParam, tyExpr}:
+    if indx.kind notin {tyGenericParam, tyStatic}:
       if not isOrdinalType(indx):
         localError(n.sons[1].info, errOrdinalTypeExpected)
       elif enumHasHoles(indx): 
@@ -579,9 +579,9 @@ proc semObjectNode(c: PContext, n: PNode, prev: PType): PType =
     pragma(c, s, n.sons[0], typePragmas)
   if base == nil and tfInheritable notin result.flags:
     incl(result.flags, tfFinal)
-  
+
 proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind) =
-  if kind == skMacro and param.typ.kind != tyTypeDesc:
+  if kind == skMacro and param.typ.kind notin {tyTypeDesc, tyStatic}:
     # within a macro, every param has the type PNimrodNode!
     # and param.typ.kind in {tyTypeDesc, tyExpr, tyStmt}:
     let nn = getSysSym"PNimrodNode"
@@ -593,18 +593,21 @@ proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind) =
 
 let typedescId = getIdent"typedesc"
 
+template shouldHaveMeta(t) =
+  InternalAssert tfHasMeta in result.lastSon.flags
+  # result.lastSon.flags.incl tfHasMeta
+
 proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
                    paramType: PType, paramName: string,
                    info: TLineInfo, anon = false): PType =
-  if procKind in {skMacro, skTemplate}:
-    # generic param types in macros and templates affect overload
-    # resolution, but don't work as generic params when it comes
-    # to proc instantiation. We don't need to lift such params here.  
-    return
-
+  
   proc addImplicitGenericImpl(typeClass: PType, typId: PIdent): PType =
     let finalTypId = if typId != nil: typId
                      else: getIdent(paramName & ":type")
+    if genericParams == nil:
+      # This happens with anonymous proc types appearing in signatures
+      # XXX: we need to lift these earlier
+      return
     # is this a bindOnce type class already present in the param list?
     for i in countup(0, genericParams.len - 1):
       if genericParams.sons[i].sym.name.id == finalTypId.id:
@@ -618,7 +621,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
     s.position = genericParams.len
     genericParams.addSon(newSymNode(s))
     result = typeClass
-
+        
   # XXX: There are codegen errors if this is turned into a nested proc
   template liftingWalk(typ: PType, anonFlag = false): expr =
     liftParamType(c, procKind, genericParams, typ, paramName, info, anonFlag)
@@ -631,25 +634,27 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
     addImplicitGenericImpl(e, paramTypId)
 
   case paramType.kind:
-  of tyExpr:
-    if paramType.sonsLen == 0:
-      # proc(a, b: expr)
-      # no constraints, treat like generic param
-      result = addImplicitGeneric(newTypeS(tyGenericParam, c))
-    else:
-      # proc(a: expr{string}, b: expr{nkLambda})
-      # overload on compile time values and AST trees
-      result = addImplicitGeneric(c.newTypeWithSons(tyExpr, paramType.sons))
+  of tyAnything:
+    result = addImplicitGeneric(newTypeS(tyGenericParam, c))
+  
+  of tyStatic:
+    # proc(a: expr{string}, b: expr{nkLambda})
+    # overload on compile time values and AST trees
+    result = addImplicitGeneric(c.newTypeWithSons(tyStatic, paramType.sons))
+    result.flags.incl tfHasStatic
+  
   of tyTypeDesc:
     if tfUnresolved notin paramType.flags:
       # naked typedescs are not bindOnce types
       if paramType.sonsLen == 0 and paramTypId != nil and
          paramTypId.id == typedescId.id: paramTypId = nil
       result = addImplicitGeneric(c.newTypeWithSons(tyTypeDesc, paramType.sons))
+  
   of tyDistinct:
     if paramType.sonsLen == 1:
       # disable the bindOnce behavior for the type class
       result = liftingWalk(paramType.sons[0], true)
+  
   of tySequence, tySet, tyArray, tyOpenArray:
     # XXX: this is a bit strange, but proc(s: seq)
     # produces tySequence(tyGenericParam, null).
@@ -658,7 +663,8 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
     # Maybe there is another better place to associate
     # the seq type class with the seq identifier.
     if paramType.lastSon == nil:
-      let typ = c.newTypeWithSons(tyTypeClass, @[newTypeS(paramType.kind, c)])
+      let typ = c.newTypeWithSons(tyBuiltInTypeClass,
+                                  @[newTypeS(paramType.kind, c)])
       result = addImplicitGeneric(typ)
     else:
       for i in 0 .. <paramType.sons.len:
@@ -666,29 +672,45 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
         if lifted != nil:
           paramType.sons[i] = lifted
           result = paramType
+  
   of tyGenericBody:
-    # type Foo[T] = object
-    # proc x(a: Foo, b: Foo) 
-    var typ = newTypeS(tyTypeClass, c)
-    typ.addSonSkipIntLit(paramType)
-    result = addImplicitGeneric(typ)
+    result = newTypeS(tyGenericInvokation, c)
+    result.rawAddSon(paramType)
+    for i in 0 .. paramType.sonsLen - 2:
+      result.rawAddSon(copyType(paramType.sons[i], getCurrOwner(), true))
+    result = instGenericContainer(c, paramType.sym.info, result,
+                                  allowMetaTypes = true)
+    result.lastSon.shouldHaveMeta
+    result = newTypeWithSons(c, tyCompositeTypeClass, @[paramType, result])
+    result = addImplicitGeneric(result)
+  
   of tyGenericInst:
     for i in 1 .. (paramType.sons.len - 2):
       var lifted = liftingWalk(paramType.sons[i])
       if lifted != nil:
         paramType.sons[i] = lifted
         result = paramType
+        result.lastSon.shouldHaveMeta
 
-    if paramType.lastSon.kind == tyTypeClass:
-      result = paramType
-      result.kind = tyParametricTypeClass
-      result = addImplicitGeneric(copyType(result,
-                                           getCurrOwner(), false))
-    elif result != nil:
-      result.kind = tyGenericInvokation
-      result.sons.setLen(result.sons.len - 1)
-  of tyTypeClass:
-    result = addImplicitGeneric(copyType(paramType, getCurrOwner(), false))
+    let liftBody = liftingWalk(paramType.lastSon)
+    if liftBody != nil:
+      result = liftBody
+      result.shouldHaveMeta
+    
+  of tyTypeClass, tyBuiltInTypeClass, tyAnd, tyOr, tyNot:
+    result = addImplicitGeneric(copyType(paramType, getCurrOwner(), true))
+  
+  of tyExpr:
+    if procKind notin {skMacro, skTemplate}:
+      result = addImplicitGeneric(newTypeS(tyGenericParam, c))
+  
+  of tyGenericParam:
+    if tfGenericTypeParam in paramType.flags and false:
+      if paramType.sonsLen > 0:
+        result = liftingWalk(paramType.lastSon)
+      else:
+        result = addImplicitGeneric(newTypeS(tyGenericParam, c))
+  
   else: nil
 
   # result = liftingWalk(paramType)
@@ -745,8 +767,9 @@ proc semProcTypeNode(c: PContext, n, genericParams: PNode,
         if not containsGenericType(typ):
           def = fitNode(c, typ, def)
     if not (hasType or hasDefault):
-      typ = newTypeS(tyExpr, c)
-      
+      let tdef = if kind in {skTemplate, skMacro}: tyExpr else: tyAnything
+      typ = newTypeS(tdef, c)
+
     if skipTypes(typ, {tyGenericInst}).kind == tyEmpty: continue
     for j in countup(0, length-3): 
       var arg = newSymG(skParam, a.sons[j], c)
@@ -842,7 +865,7 @@ proc semGeneric(c: PContext, n: PNode, s: PSym, prev: PType): PType =
   else:
     internalAssert s.typ.kind == tyGenericBody
 
-    var m = newCandidate(s, n)
+    var m = newCandidate(c, s, n)
     matches(c, n, copyTree(n), m)
     
     if m.state != csMatch:
@@ -867,12 +890,15 @@ proc semGeneric(c: PContext, n: PNode, s: PSym, prev: PType): PType =
         when oUseLateInstantiation:
           result = lateInstantiateGeneric(c, result, n.info)
         else:
-          result = instGenericContainer(c, n, result)
+          result = instGenericContainer(c, n.info, result,
+                                        allowMetaTypes = not isConcrete)
+          if not isConcrete and result.kind == tyGenericInst:
+            result.lastSon.shouldHaveMeta
 
 proc semTypeExpr(c: PContext, n: PNode): PType =
   var n = semExprWithType(c, n, {efDetermineType})
-  if n.kind == nkSym and n.sym.kind == skType:
-    result = n.sym.typ
+  if n.typ.kind == tyTypeDesc:
+    result = n.typ.base
   else:
     localError(n.info, errTypeExpected, n.renderTree)
 
@@ -921,24 +947,27 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
         var
           t1 = semTypeNode(c, n.sons[1], nil)
           t2 = semTypeNode(c, n.sons[2], nil)
-        if t1 == nil: 
+        if t1 == nil:
           localError(n.sons[1].info, errTypeExpected)
           result = newOrPrevType(tyError, prev, c)
-        elif t2 == nil: 
+        elif t2 == nil:
           localError(n.sons[2].info, errTypeExpected)
           result = newOrPrevType(tyError, prev, c)
         else:
-          result = newTypeS(tyTypeClass, c)
-          result.addSonSkipIntLit(t1)
-          result.addSonSkipIntLit(t2)
-          result.flags.incl(if op.id == ord(wAnd): tfAll else: tfAny)
-          result.flags.incl(tfHasMeta)
+          result = if op.id == ord(wAnd): makeAndType(c, t1, t2)
+                   else: makeOrType(c, t1, t2)
       elif op.id == ord(wNot):
-        checkSonsLen(n, 3)
-        result = semTypeNode(c, n.sons[1], prev)
-        if result.kind in NilableTypes and n.sons[2].kind == nkNilLit:
-          result = freshType(result, prev)
-          result.flags.incl(tfNotNil)
+        case n.len
+        of 3:
+          result = semTypeNode(c, n.sons[1], prev)
+          if result.kind in NilableTypes and n.sons[2].kind == nkNilLit:
+            result = freshType(result, prev)
+            result.flags.incl(tfNotNil)
+          else:
+            LocalError(n.info, errGenerated, "invalid type")
+        of 2:
+          let negated = semTypeNode(c, n.sons[1], prev)
+          result = makeNotType(c, negated)
         else:
           localError(n.info, errGenerated, "invalid type")
       else:
@@ -1004,6 +1033,11 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
   of nkPtrTy: result = semAnyRef(c, n, tyPtr, prev)
   of nkVarTy: result = semVarType(c, n, prev)
   of nkDistinctTy: result = semDistinct(c, n, prev)
+  of nkStaticTy:
+    result = newOrPrevType(tyStatic, prev, c)
+    var base = semTypeNode(c, n.sons[0], nil)
+    result.rawAddSon(base)
+    result.flags.incl tfHasStatic
   of nkProcTy, nkIteratorTy:
     if n.sonsLen == 0:
       result = newConstraint(c, tyProc)
@@ -1088,11 +1122,7 @@ proc processMagicType(c: PContext, m: PSym) =
   else: localError(m.info, errTypeExpected)
   
 proc semGenericConstraints(c: PContext, x: PType): PType =
-  if x.kind in StructuralEquivTypes and (
-      sonsLen(x) == 0 or x.sons[0].kind in {tyGenericParam, tyEmpty}):
-    result = newConstraint(c, x.kind)
-  else:
-    result = newTypeWithSons(c, tyGenericParam, @[x])
+  result = newTypeWithSons(c, tyGenericParam, @[x])
 
 proc semGenericParamList(c: PContext, n: PNode, father: PType = nil): PNode = 
   result = copyNode(n)
@@ -1109,7 +1139,7 @@ proc semGenericParamList(c: PContext, n: PNode, father: PType = nil): PNode =
     
     if constraint.kind != nkEmpty:
       typ = semTypeNode(c, constraint, nil)
-      if typ.kind != tyExpr or typ.len == 0:
+      if typ.kind != tyStatic or typ.len == 0:
         if typ.kind == tyTypeDesc:
           if typ.len == 0:
             typ = newTypeS(tyTypeDesc, c)
@@ -1120,14 +1150,16 @@ proc semGenericParamList(c: PContext, n: PNode, father: PType = nil): PNode =
       def = semConstExpr(c, def)
       if typ == nil:
         if def.typ.kind != tyTypeDesc:
-          typ = newTypeWithSons(c, tyExpr, @[def.typ])
+          typ = newTypeWithSons(c, tyStatic, @[def.typ])
       else:
         if not containsGenericType(def.typ):
           def = fitNode(c, typ, def)
     
     if typ == nil:
       typ = newTypeS(tyGenericParam, c)
-    
+
+    typ.flags.incl tfGenericTypeParam
+
     for j in countup(0, L-3):
       let finalType = if j == 0: typ
                       else: copyType(typ, typ.owner, false)
@@ -1136,7 +1168,7 @@ proc semGenericParamList(c: PContext, n: PNode, father: PType = nil): PNode =
                       # of the parameter will be stored in the
                       # attached symbol.
       var s = case finalType.kind
-        of tyExpr:
+        of tyStatic:
           newSymG(skGenericParam, a.sons[j], c).linkTo(finalType)
         else:
           newSymG(skType, a.sons[j], c).linkTo(finalType)
diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim
index 2e2d54b5b..0bb27946f 100644
--- a/compiler/semtypinst.nim
+++ b/compiler/semtypinst.nim
@@ -17,14 +17,14 @@ proc checkPartialConstructedType(info: TLineInfo, t: PType) =
   elif t.kind == tyVar and t.sons[0].kind == tyVar:
     localError(info, errVarVarTypeNotAllowed)
 
-proc checkConstructedType*(info: TLineInfo, typ: PType) = 
+proc checkConstructedType*(info: TLineInfo, typ: PType) =
   var t = typ.skipTypes({tyDistinct})
-  if t.kind in {tyTypeClass}: nil
+  if t.kind in tyTypeClasses: nil
   elif tfAcyclic in t.flags and skipTypes(t, abstractInst).kind != tyObject: 
     localError(info, errInvalidPragmaX, "acyclic")
   elif t.kind == tyVar and t.sons[0].kind == tyVar: 
     localError(info, errVarVarTypeNotAllowed)
-  elif computeSize(t) < 0:
+  elif computeSize(t) == szIllegalRecursion:
     localError(info, errIllegalRecursionInTypeX, typeToString(t))
   when false:
     if t.kind == tyObject and t.sons[0] != nil:
@@ -50,9 +50,10 @@ proc searchInstTypes*(key: PType): PType =
     block matchType:
       for j in 1 .. high(key.sons):
         # XXX sameType is not really correct for nested generics?
-        if not sameType(inst.sons[j], key.sons[j]):
+        if not compareTypes(inst.sons[j], key.sons[j],
+                            flags = {ExactGenericParams}):
           break matchType
-      
+       
       return inst
 
 proc cacheTypeInst*(inst: PType) =
@@ -67,6 +68,8 @@ type
     typeMap*: TIdTable        # map PType to PType
     symMap*: TIdTable         # map PSym to PSym
     info*: TLineInfo
+    allowMetaTypes*: bool     # allow types such as seq[Number]
+                              # i.e. the result contains unresolved generics
 
 proc replaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType
 proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym
@@ -132,11 +135,12 @@ proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym =
 proc lookupTypeVar(cl: TReplTypeVars, t: PType): PType = 
   result = PType(idTableGet(cl.typeMap, t))
   if result == nil:
+    if cl.allowMetaTypes or tfRetType in t.flags: return
     localError(t.sym.info, errCannotInstantiateX, typeToString(t))
     result = errorType(cl.c)
-  elif result.kind == tyGenericParam: 
+  elif result.kind == tyGenericParam and not cl.allowMetaTypes:
     internalError(cl.info, "substitution with generic parameter")
-  
+ 
 proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType = 
   # tyGenericInvokation[A, tyGenericInvokation[A, B]]
   # is difficult to handle: 
@@ -150,11 +154,11 @@ proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType =
     var x = t.sons[i]
     if x.kind == tyGenericParam:
       x = lookupTypeVar(cl, x)
-      if header == nil: header = copyType(t, t.owner, false)
-      header.sons[i] = x
-      propagateToOwner(header, x)
-      #idTablePut(cl.typeMap, body.sons[i-1], x)  
-
+      if x != nil:
+        if header == nil: header = copyType(t, t.owner, false)
+        header.sons[i] = x
+        propagateToOwner(header, x)
+  
   if header != nil:
     # search again after first pass:
     result = searchInstTypes(header)
@@ -166,7 +170,8 @@ proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType =
   # recursive instantions:
   result = newType(tyGenericInst, t.sons[0].owner)
   result.rawAddSon(header.sons[0])
-  cacheTypeInst(result)
+  if not cl.allowMetaTypes:
+    cacheTypeInst(result)
 
   for i in countup(1, sonsLen(t) - 1):
     var x = replaceTypeVarsT(cl, t.sons[i])
@@ -179,7 +184,7 @@ proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType =
     # if one of the params is not concrete, we cannot do anything
     # but we already raised an error!
     rawAddSon(result, header.sons[i])
-  
+ 
   var newbody = replaceTypeVarsT(cl, lastSon(body))
   newbody.flags = newbody.flags + t.flags + body.flags
   result.flags = result.flags + newbody.flags
@@ -194,28 +199,39 @@ proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType =
   
 proc replaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType = 
   result = t
-  if t == nil: return 
+  if t == nil: return
+  if t.kind == tyStatic and t.sym != nil and t.sym.kind == skGenericParam:
+    let s = lookupTypeVar(cl, t)
+    return if s != nil: s else: t
+
   case t.kind
-  of tyTypeClass: discard
-  of tyGenericParam:
-    result = lookupTypeVar(cl, t)
-    if result.kind == tyGenericInvokation:
-      result = handleGenericInvokation(cl, result)
-  of tyExpr:
-    if t.sym != nil and t.sym.kind == skGenericParam:
-      result = lookupTypeVar(cl, t)
-  of tyGenericInvokation: 
+  of tyGenericParam, tyTypeClasses:
+    let lookup = lookupTypeVar(cl, t)
+    if lookup != nil:
+      result = lookup
+      if result.kind == tyGenericInvokation:
+        result = handleGenericInvokation(cl, result)
+  of tyGenericInvokation:
     result = handleGenericInvokation(cl, t)
   of tyGenericBody:
-    internalError(cl.info, "ReplaceTypeVarsT: tyGenericBody")
+    internalError(cl.info, "ReplaceTypeVarsT: tyGenericBody" )
     result = replaceTypeVarsT(cl, lastSon(t))
   of tyInt:
     result = skipIntLit(t)
     # XXX now there are also float literals
+  of tyTypeDesc:
+    let lookup = PType(idTableGet(cl.typeMap, t)) # lookupTypeVar(cl, t)
+    if lookup != nil:
+      result = lookup
+      if tfUnresolved in t.flags: result = result.base
+  of tyGenericInst:
+    result = copyType(t, t.owner, true)
+    for i in 1 .. <result.sonsLen:
+      result.sons[i] = ReplaceTypeVarsT(cl, result.sons[i])
   else:
     if t.kind == tyArray:
       let idxt = t.sons[0]
-      if idxt.kind == tyExpr and 
+      if idxt.kind == tyStatic and 
          idxt.sym != nil and idxt.sym.kind == skGenericParam:
         let value = lookupTypeVar(cl, idxt).n
         t.sons[0] = makeRangeType(cl.c, 0, value.intVal - 1, value.info)
@@ -231,14 +247,19 @@ proc replaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType =
       if result.kind == tyProc and result.sons[0] != nil:
         if result.sons[0].kind == tyEmpty:
           result.sons[0] = nil
-  
-proc generateTypeInstance*(p: PContext, pt: TIdTable, arg: PNode, 
-                           t: PType): PType = 
+
+proc generateTypeInstance*(p: PContext, pt: TIdTable, info: TLineInfo,
+                           t: PType): PType =
   var cl: TReplTypeVars
   initIdTable(cl.symMap)
   copyIdTable(cl.typeMap, pt)
-  cl.info = arg.info
+  cl.info = info
   cl.c = p
-  pushInfoContext(arg.info)
+  pushInfoContext(info)
   result = replaceTypeVarsT(cl, t)
   popInfoContext()
+
+template generateTypeInstance*(p: PContext, pt: TIdTable, arg: PNode,
+                               t: PType): expr =
+  generateTypeInstance(p, pt, arg.info, t)
+
diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim
index 201f61dec..13546eae2 100644
--- a/compiler/sigmatch.nim
+++ b/compiler/sigmatch.nim
@@ -21,7 +21,8 @@ type
   TCandidateState* = enum 
     csEmpty, csMatch, csNoMatch
 
-  TCandidate* {.final.} = object 
+  TCandidate* {.final.} = object
+    c*: PContext
     exactMatches*: int       # also misused to prefer iters over procs
     genericMatches: int      # also misused to prefer constraints
     subtypeMatches: int
@@ -58,7 +59,9 @@ const
     
 proc markUsed*(n: PNode, s: PSym)
 
-proc initCandidateAux(c: var TCandidate, callee: PType) {.inline.} = 
+proc initCandidateAux(ctx: PContext,
+                      c: var TCandidate, callee: PType) {.inline.} =
+  c.c = ctx
   c.exactMatches = 0
   c.subtypeMatches = 0
   c.convMatches = 0
@@ -71,17 +74,17 @@ proc initCandidateAux(c: var TCandidate, callee: PType) {.inline.} =
   c.genericConverter = false
   c.inheritancePenalty = 0
 
-proc initCandidate*(c: var TCandidate, callee: PType) = 
-  initCandidateAux(c, callee)
+proc initCandidate*(ctx: PContext, c: var TCandidate, callee: PType) =
+  initCandidateAux(ctx, c, callee)
   c.calleeSym = nil
   initIdTable(c.bindings)
 
 proc put(t: var TIdTable, key, val: PType) {.inline.} =
   idTablePut(t, key, val)
 
-proc initCandidate*(c: var TCandidate, callee: PSym, binding: PNode, 
-                    calleeScope = -1) =
-  initCandidateAux(c, callee.typ)
+proc initCandidate*(ctx: PContext, c: var TCandidate, callee: PSym,
+                    binding: PNode, calleeScope = -1) =
+  initCandidateAux(ctx, c, callee.typ)
   c.calleeSym = callee
   c.calleeScope = calleeScope
   initIdTable(c.bindings)
@@ -90,13 +93,17 @@ proc initCandidate*(c: var TCandidate, callee: PSym, binding: PNode,
     var typeParams = callee.ast[genericParamsPos]
     for i in 1..min(sonsLen(typeParams), sonsLen(binding)-1):
       var formalTypeParam = typeParams.sons[i-1].typ
-      #debug(formalTypeParam)
-      put(c.bindings, formalTypeParam, binding[i].typ)
+      var bound = binding[i].typ
+      if formalTypeParam.kind != tyTypeDesc:
+        bound = bound.skipTypes({tyTypeDesc})
+      put(c.bindings, formalTypeParam, bound)
 
-proc newCandidate*(callee: PSym, binding: PNode, calleeScope = -1): TCandidate =
-  initCandidate(result, callee, binding, calleeScope)
+proc newCandidate*(ctx: PContext, callee: PSym,
+                   binding: PNode, calleeScope = -1): TCandidate =
+  initCandidate(ctx, result, callee, binding, calleeScope)
 
 proc copyCandidate(a: var TCandidate, b: TCandidate) = 
+  a.c = b.c
   a.exactMatches = b.exactMatches
   a.subtypeMatches = b.subtypeMatches
   a.convMatches = b.convMatches
@@ -124,7 +131,7 @@ proc sumGeneric(t: PType): int =
       result = ord(t.kind == tyGenericInvokation)
       for i in 0 .. <t.len: result += t.sons[i].sumGeneric
       break
-    of tyGenericParam, tyExpr, tyStmt, tyTypeDesc, tyTypeClass: break
+    of tyGenericParam, tyExpr, tyStatic, tyStmt, tyTypeDesc, tyTypeClass: break
     else: return 0
 
 proc complexDisambiguation(a, b: PType): int =
@@ -203,7 +210,7 @@ proc describeArgs*(c: PContext, n: PNode, startIdx = 1): string =
     add(result, argTypeToString(arg))
     if i != sonsLen(n) - 1: add(result, ", ")
 
-proc typeRel*(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation
+proc typeRel*(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation
 proc concreteType(c: TCandidate, t: PType): PType = 
   case t.kind
   of tyArrayConstr: 
@@ -296,24 +303,27 @@ proc minRel(a, b: TTypeRelation): TTypeRelation =
   if a <= b: result = a
   else: result = b
   
-proc tupleRel(c: var TCandidate, f, a: PType): TTypeRelation =
+proc recordRel(c: var TCandidate, f, a: PType): TTypeRelation =
   result = isNone
-  if sameType(f, a):
-    result = isEqual
+  if sameType(f, a): result = isEqual
   elif sonsLen(a) == sonsLen(f):
     result = isEqual
-    for i in countup(0, sonsLen(f) - 1):
+    let firstField = if f.kind == tyTuple: 0
+                     else: 1 
+    for i in countup(firstField, sonsLen(f) - 1):
       var m = typeRel(c, f.sons[i], a.sons[i])
       if m < isSubtype: return isNone
       result = minRel(result, m)
     if f.n != nil and a.n != nil:
       for i in countup(0, sonsLen(f.n) - 1):
         # check field names:
-        if f.n.sons[i].kind != nkSym: internalError(f.n.info, "tupleRel")
-        elif a.n.sons[i].kind != nkSym: internalError(a.n.info, "tupleRel")
+        if f.n.sons[i].kind != nkSym: internalError(f.n.info, "recordRel")
+        elif a.n.sons[i].kind != nkSym: internalError(a.n.info, "recordRel")
         else:
           var x = f.n.sons[i].sym
           var y = a.n.sons[i].sym
+          if f.kind == tyObject and typeRel(c, x.typ, y.typ) < isSubtype:
+            return isNone
           if x.name.id != y.name.id: return isNone
 
 proc allowsNil(f: PType): TTypeRelation {.inline.} =
@@ -365,10 +375,6 @@ proc procTypeRel(c: var TCandidate, f, a: PType): TTypeRelation =
   of tyNil: result = f.allowsNil
   else: nil
 
-proc matchTypeClass(c: var TCandidate, f, a: PType): TTypeRelation =
-  result = if matchTypeClass(c.bindings, f, a): isGeneric
-           else: isNone
-
 proc typeRangeRel(f, a: PType): TTypeRelation {.noinline.} =
   let
     a0 = firstOrd(a)
@@ -385,7 +391,7 @@ proc typeRangeRel(f, a: PType): TTypeRelation {.noinline.} =
   else:
     result = isNone
 
-proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
+proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation =
   # typeRel can be used to establish various relationships between types:
   #
   # 1) When used with concrete types, it will check for type equivalence
@@ -401,20 +407,22 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   # order to give preferrence to the most specific one:
   #
   # seq[seq[any]] is a strict subset of seq[any] and hence more specific.
-  
+
   result = isNone
   assert(f != nil)
-  assert(a != nil)
+  assert(aOrig != nil)
+
+  # var and static arguments match regular modifier-free types
+  let a = aOrig.skipTypes({tyStatic, tyVar})
+  
   if a.kind == tyGenericInst and
       skipTypes(f, {tyVar}).kind notin {
         tyGenericBody, tyGenericInvokation,
-        tyGenericParam, tyTypeClass}:
+        tyGenericInst, tyGenericParam} + tyTypeClasses:
     return typeRel(c, f, lastSon(a))
-  if a.kind == tyVar and f.kind != tyVar:
-    return typeRel(c, f, a.sons[0])
-  
+
   template bindingRet(res) =
-    when res == isGeneric: put(c.bindings, f, a)
+    when res == isGeneric: put(c.bindings, f, aOrig)
     return res
  
   case a.kind
@@ -457,10 +465,10 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   else: nil
 
   case f.kind
-  of tyEnum: 
+  of tyEnum:
     if a.kind == f.kind and sameEnumTypes(f, a): result = isEqual
     elif sameEnumTypes(f, skipTypes(a, {tyRange})): result = isSubtype
-  of tyBool, tyChar: 
+  of tyBool, tyChar:
     if a.kind == f.kind: result = isEqual
     elif skipTypes(a, {tyRange}).kind == f.kind: result = isSubtype
   of tyRange:
@@ -488,9 +496,9 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   of tyFloat32:  result = handleFloatRange(f, a)
   of tyFloat64:  result = handleFloatRange(f, a)
   of tyFloat128: result = handleFloatRange(f, a)
-  of tyVar: 
-    if a.kind == f.kind: result = typeRel(c, base(f), base(a))
-    else: result = typeRel(c, base(f), a)
+  of tyVar:
+    if aOrig.kind == tyVar: result = typeRel(c, f.base, aOrig.base)
+    else: result = typeRel(c, f.base, aOrig)
   of tyArray, tyArrayConstr:
     # tyArrayConstr cannot happen really, but
     # we wanna be safe here
@@ -544,7 +552,6 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   of tyOrdinal:
     if isOrdinalType(a):
       var x = if a.kind == tyOrdinal: a.sons[0] else: a
-     
       if f.sonsLen == 0:
         result = isGeneric
       else:
@@ -556,10 +563,11 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   of tyNil:
     if a.kind == f.kind: result = isEqual
   of tyTuple: 
-    if a.kind == tyTuple: result = tupleRel(c, f, a)
+    if a.kind == tyTuple: result = recordRel(c, f, a)
   of tyObject:
     if a.kind == tyObject:
       if sameObjectTypes(f, a): result = isEqual
+      elif tfHasMeta in f.flags: result = recordRel(c, f, a)
       else:
         var depth = isObjectSubtype(a, f)
         if depth > 0:
@@ -641,9 +649,18 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
     if a.kind == tyEmpty: result = isEqual
 
   of tyGenericInst:
-    result = typeRel(c, lastSon(f), a)
+    if a.kind == tyGenericInst:
+      if a.base != f.base: return isNone
+      for i in 1 .. f.sonsLen-2:
+        result = typeRel(c, f.sons[i], a.sons[i])
+        if result == isNone: return
+      result = isGeneric
+    else:
+      result = typeRel(c, lastSon(f), a)
 
   of tyGenericBody:
+    if a.kind == tyGenericInst and a.sons[0] == f:
+      return isGeneric
     let ff = lastSon(f)
     if ff != nil: result = typeRel(c, ff, a)
 
@@ -673,21 +690,21 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   
   of tyAnd:
     for branch in f.sons:
-      if typeRel(c, branch, a) == isNone:
+      if typeRel(c, branch, aOrig) == isNone:
         return isNone
 
     bindingRet isGeneric
 
   of tyOr:
     for branch in f.sons:
-      if typeRel(c, branch, a) != isNone:
+      if typeRel(c, branch, aOrig) != isNone:
         bindingRet isGeneric
-
+     
     return isNone
 
   of tyNot:
     for branch in f.sons:
-      if typeRel(c, branch, a) != isNone:
+      if typeRel(c, branch, aOrig) != isNone:
         return isNone
     
     bindingRet isGeneric
@@ -701,7 +718,31 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       return isGeneric
     else:
       return typeRel(c, prev, a)
-    
+
+  of tyBuiltInTypeClass:
+    var prev = PType(idTableGet(c.bindings, f))
+    if prev == nil:
+      let targetKind = f.sons[0].kind
+      if targetKind == a.skipTypes({tyRange, tyGenericInst}).kind or
+         (targetKind in {tyProc, tyPointer} and a.kind == tyNil):
+        put(c.bindings, f, a)
+        return isGeneric
+      else:
+        return isNone
+    else:
+      result = typeRel(c, prev, a)
+
+  of tyCompositeTypeClass:
+    var prev = PType(idTableGet(c.bindings, f))
+    if prev == nil:
+      if typeRel(c, f.sons[1], a) != isNone:
+        put(c.bindings, f, a)
+        return isGeneric
+      else:
+        return isNone
+    else:
+      result = typeRel(c, prev, a)
+
   of tyGenericParam, tyTypeClass:
     var x = PType(idTableGet(c.bindings, f))
     if x == nil:
@@ -722,11 +763,11 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         else:
           result = isNone
       else:
-        if a.kind == tyTypeClass:
-          result = isGeneric
+        if f.sonsLen > 0:
+          result = typeRel(c, f.lastSon, a)
         else:
-          result = matchTypeClass(c, f, a)
-        
+          result = isGeneric
+
       if result == isGeneric:
         var concrete = concreteType(c, a)
         if concrete == nil:
@@ -739,6 +780,14 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       result = isGeneric
     else:
       result = typeRel(c, x, a) # check if it fits
+  
+  of tyStatic:
+    if aOrig.kind == tyStatic:
+      result = typeRel(c, f.lastSon, a)
+      if result != isNone: put(c.bindings, f, aOrig)
+    else:
+      result = isNone
+
   of tyTypeDesc:
     var prev = PType(idTableGet(c.bindings, f))
     if prev == nil:
@@ -746,8 +795,8 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         if f.sonsLen == 0:
           result = isGeneric
         else:
-          result = matchTypeClass(c, f, a.sons[0])
-        if result == isGeneric:
+          result = typeRel(c, f.sons[0], a.sons[0])
+        if result != isNone:
           put(c.bindings, f, a)
       else:
         result = isNone
@@ -756,16 +805,19 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       let toMatch = if tfUnresolved in f.flags: a
                     else: a.sons[0]
       result = typeRel(c, prev.sons[0], toMatch)
+  
   of tyExpr, tyStmt:
     result = isGeneric
+  
   of tyProxy:
     result = isEqual
+  
   else: internalError("typeRel: " & $f.kind)
   
-proc cmpTypes*(f, a: PType): TTypeRelation = 
-  var c: TCandidate
-  initCandidate(c, f)
-  result = typeRel(c, f, a)
+proc cmpTypes*(c: PContext, f, a: PType): TTypeRelation = 
+  var m: TCandidate
+  initCandidate(c, m, f)
+  result = typeRel(m, f, a)
 
 proc getInstantiatedType(c: PContext, arg: PNode, m: TCandidate, 
                          f: PType): PType = 
@@ -887,47 +939,34 @@ proc matchUserTypeClass*(c: PContext, m: var TCandidate,
   result = arg
   put(m.bindings, f, a)
 
-proc paramTypesMatchAux(c: PContext, m: var TCandidate, f, argType: PType,
+proc paramTypesMatchAux(m: var TCandidate, f, argType: PType,
                         argSemantized, argOrig: PNode): PNode =
   var
-    r: TTypeRelation
+    fMaybeStatic = f.skipTypes({tyDistinct})
     arg = argSemantized
-
-  let
-    a = if c.inTypeClass > 0: argType.skipTypes({tyTypeDesc})
+    argType = argType
+    c = m.c
+
+  if tfHasStatic in fMaybeStatic.flags:
+    # XXX: When implicit statics are the default
+    # this will be done earlier - we just have to
+    # make sure that static types enter here
+    var evaluated = c.semTryConstExpr(c, arg)
+    if evaluated != nil:
+      arg.typ = newTypeS(tyStatic, c)
+      arg.typ.sons = @[evaluated.typ]
+      arg.typ.n = evaluated
+      argType = arg.typ
+ 
+  var
+    r: TTypeRelation
+    a = if c.InTypeClass > 0: argType.skipTypes({tyTypeDesc})
         else: argType
-    fMaybeExpr = f.skipTypes({tyDistinct})
-
-  case fMaybeExpr.kind
-  of tyExpr:
-    if fMaybeExpr.sonsLen == 0:
-      r = isGeneric
-    else:
-      if a.kind == tyExpr:
-        internalAssert a.len > 0
-        r = typeRel(m, f.lastSon, a.lastSon)
-      else:
-        let match = matchTypeClass(m.bindings, fMaybeExpr, a)
-        if not match: r = isNone
-        else:
-          # XXX: Ideally, this should happen much earlier somewhere near 
-          # semOpAux, but to do that, we need to be able to query the 
-          # overload set to determine whether compile-time value is expected
-          # for the param before entering the full-blown sigmatch algorithm.
-          # This is related to the immediate pragma since querying the
-          # overload set could help there too.
-          var evaluated = c.semConstExpr(c, arg)
-          if evaluated != nil:
-            r = isGeneric
-            arg.typ = newTypeS(tyExpr, c)
-            arg.typ.sons = @[evaluated.typ]
-            arg.typ.n = evaluated
-        
-    if r == isGeneric:
-      put(m.bindings, f, arg.typ)
+ 
+  case fMaybeStatic.kind
   of tyTypeClass, tyParametricTypeClass:
-    if fMaybeExpr.n != nil:
-      let match = matchUserTypeClass(c, m, arg, fMaybeExpr, a)
+    if fMaybeStatic.n != nil:
+      let match = matchUserTypeClass(c, m, arg, fMaybeStatic, a)
       if match != nil:
         r = isGeneric
         arg = match
@@ -935,11 +974,14 @@ proc paramTypesMatchAux(c: PContext, m: var TCandidate, f, argType: PType,
         r = isNone
     else:
       r = typeRel(m, f, a)
+  of tyExpr:
+    r = isGeneric
+    put(m.bindings, f, arg.typ)
   else:
     r = typeRel(m, f, a)
 
   case r
-  of isConvertible: 
+  of isConvertible:
     inc(m.convMatches)
     result = implicitConv(nkHiddenStdConv, f, copyTree(arg), m, c)
   of isIntConv:
@@ -961,6 +1003,8 @@ proc paramTypesMatchAux(c: PContext, m: var TCandidate, f, argType: PType,
         result = argOrig[bodyPos]
       elif f.kind == tyTypeDesc:
         result = arg
+      elif f.kind == tyStatic:
+        result = arg.typ.n
       else:
         result = argOrig
     else:
@@ -1003,19 +1047,20 @@ proc paramTypesMatchAux(c: PContext, m: var TCandidate, f, argType: PType,
         else:
           result = userConvMatch(c, m, base(f), a, arg)
 
-proc paramTypesMatch*(c: PContext, m: var TCandidate, f, a: PType, 
+proc paramTypesMatch*(m: var TCandidate, f, a: PType,
                       arg, argOrig: PNode): PNode =
   if arg == nil or arg.kind notin nkSymChoices:
-    result = paramTypesMatchAux(c, m, f, a, arg, argOrig)
+    result = paramTypesMatchAux(m, f, a, arg, argOrig)
   else: 
     # CAUTION: The order depends on the used hashing scheme. Thus it is
     # incorrect to simply use the first fitting match. However, to implement
     # this correctly is inefficient. We have to copy `m` here to be able to
     # roll back the side effects of the unification algorithm.
+    let c = m.c
     var x, y, z: TCandidate
-    initCandidate(x, m.callee)
-    initCandidate(y, m.callee)
-    initCandidate(z, m.callee)
+    initCandidate(c, x, m.callee)
+    initCandidate(c, y, m.callee)
+    initCandidate(c, z, m.callee)
     x.calleeSym = m.calleeSym
     y.calleeSym = m.calleeSym
     z.calleeSym = m.calleeSym
@@ -1047,7 +1092,7 @@ proc paramTypesMatch*(c: PContext, m: var TCandidate, f, a: PType,
     else: 
       # only one valid interpretation found:
       markUsed(arg, arg.sons[best].sym)
-      result = paramTypesMatchAux(c, m, f, arg.sons[best].typ, arg.sons[best],
+      result = paramTypesMatchAux(m, f, arg.sons[best].typ, arg.sons[best],
                                   argOrig)
 
 proc setSon(father: PNode, at: int, son: PNode) = 
@@ -1138,7 +1183,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
       m.baseTypeMatch = false
       n.sons[a].sons[1] = prepareOperand(c, formal.typ, n.sons[a].sons[1])
       n.sons[a].typ = n.sons[a].sons[1].typ
-      var arg = paramTypesMatch(c, m, formal.typ, n.sons[a].typ,
+      var arg = paramTypesMatch(m, formal.typ, n.sons[a].typ,
                                 n.sons[a].sons[1], nOrig.sons[a].sons[1])
       if arg == nil:
         m.state = csNoMatch
@@ -1168,7 +1213,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
         elif formal != nil:
           m.baseTypeMatch = false
           n.sons[a] = prepareOperand(c, formal.typ, n.sons[a])
-          var arg = paramTypesMatch(c, m, formal.typ, n.sons[a].typ,
+          var arg = paramTypesMatch(m, formal.typ, n.sons[a].typ,
                                     n.sons[a], nOrig.sons[a])
           if (arg != nil) and m.baseTypeMatch and (container != nil):
             addSon(container, arg)
@@ -1191,7 +1236,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
           return 
         m.baseTypeMatch = false
         n.sons[a] = prepareOperand(c, formal.typ, n.sons[a])
-        var arg = paramTypesMatch(c, m, formal.typ, n.sons[a].typ,
+        var arg = paramTypesMatch(m, formal.typ, n.sons[a].typ,
                                   n.sons[a], nOrig.sons[a])
         if arg == nil:
           m.state = csNoMatch
@@ -1245,8 +1290,8 @@ proc matches*(c: PContext, n, nOrig: PNode, m: var TCandidate) =
 
 proc argtypeMatches*(c: PContext, f, a: PType): bool =
   var m: TCandidate
-  initCandidate(m, f)
-  let res = paramTypesMatch(c, m, f, a, ast.emptyNode, nil)
+  initCandidate(c, m, f)
+  let res = paramTypesMatch(m, f, a, ast.emptyNode, nil)
   #instantiateGenericConverters(c, res, m)
   # XXX this is used by patterns.nim too; I think it's better to not
   # instantiate generic converters for that
@@ -1308,7 +1353,7 @@ tests:
 
     setup:
       var c: TCandidate
-      InitCandidate(c, nil)
+      InitCandidate(nil, c, nil)
 
     template yes(x, y) =
       test astToStr(x) & " is " & astToStr(y):
diff --git a/compiler/suggest.nim b/compiler/suggest.nim
index 06d1b28d2..1fde831b7 100644
--- a/compiler/suggest.nim
+++ b/compiler/suggest.nim
@@ -119,7 +119,7 @@ proc argsFit(c: PContext, candidate: PSym, n, nOrig: PNode): bool =
   case candidate.kind 
   of OverloadableSyms:
     var m: TCandidate
-    initCandidate(m, candidate, nil)
+    initCandidate(c, m, candidate, nil)
     sigmatch.partialMatch(c, n, nOrig, m)
     result = m.state != csNoMatch
   else:
diff --git a/compiler/types.nim b/compiler/types.nim
index 779a649a7..024cf4549 100644
--- a/compiler/types.nim
+++ b/compiler/types.nim
@@ -410,18 +410,8 @@ const
     "uint", "uint8", "uint16", "uint32", "uint64",
     "bignum", "const ",
     "!", "varargs[$1]", "iter[$1]", "Error Type", "TypeClass",
-    "ParametricTypeClass", "and", "or", "not", "any"]
-
-proc consToStr(t: PType): string =
-  if t.len > 0: result = t.typeToString
-  else: result = typeToStr[t.kind].strip
-
-proc constraintsToStr(t: PType): string =
-  let sep = if tfAny in t.flags: " or " else: " and "
-  result = ""
-  for i in countup(0, t.len - 1):
-    if i > 0: result.add(sep)
-    result.add(t.sons[i].consToStr)
+    "ParametricTypeClass", "BuiltInTypeClass", "CompositeTypeClass",
+    "and", "or", "not", "any", "static"]
 
 proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
   var t = typ
@@ -445,16 +435,24 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
     add(result, ']')
   of tyTypeDesc:
     if t.len == 0: result = "typedesc"
-    else: result = "typedesc[" & constraintsToStr(t) & "]"
+    else: result = "typedesc[" & typeToString(t.sons[0]) & "]"
+  of tyStatic:
+    InternalAssert t.len > 0
+    result = "static[" & typeToString(t.sons[0]) & "]"
   of tyTypeClass:
-    if t.n != nil: return t.sym.owner.name.s
-    case t.len
-    of 0: result = "typeclass[]"
-    of 1: result = "typeclass[" & consToStr(t.sons[0]) & "]"
-    else: result = constraintsToStr(t)
+    InternalAssert t.sym != nil and t.sym.owner != nil
+    return t.sym.owner.name.s
+  of tyBuiltInTypeClass:
+    return "TypeClass"
+  of tyAnd:
+    result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
+  of tyOr:
+    result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
+  of tyNot:
+    result = "not " & typeToString(t.sons[0])
   of tyExpr:
-    if t.len == 0: result = "expr"
-    else: result = "expr[" & constraintsToStr(t) & "]"
+    InternalAssert t.len == 0
+    result = "expr"
   of tyArray: 
     if t.sons[0].kind == tyRange: 
       result = "array[" & rangeToStr(t.sons[0].n) & ", " &
@@ -607,8 +605,9 @@ type
     dcEqOrDistinctOf       ## a equals b or a is distinct of b
 
   TTypeCmpFlag* = enum
-    IgnoreTupleFields,
-    TypeDescExactMatch,
+    IgnoreTupleFields
+    ExactTypeDescValues
+    ExactGenericParams
     AllowCommonBase
 
   TTypeCmpFlags* = set[TTypeCmpFlag]
@@ -649,7 +648,7 @@ proc sameTypeOrNil*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
       result = sameTypeAux(a, b, c)
 
 proc equalParam(a, b: PSym): TParamsEquality = 
-  if sameTypeOrNil(a.typ, b.typ, {TypeDescExactMatch}) and
+  if sameTypeOrNil(a.typ, b.typ, {ExactTypeDescValues}) and
       exprStructuralEquivalent(a.constraint, b.constraint):
     if a.ast == b.ast: 
       result = paramsEqual
@@ -685,7 +684,7 @@ proc equalParams(a, b: PNode): TParamsEquality =
         return paramsNotEqual # paramsIncompatible;
       # continue traversal! If not equal, we can return immediately; else
       # it stays incompatible
-    if not sameTypeOrNil(a.sons[0].typ, b.sons[0].typ, {TypeDescExactMatch}):
+    if not sameTypeOrNil(a.sons[0].typ, b.sons[0].typ, {ExactTypeDescValues}):
       if (a.sons[0].typ == nil) or (b.sons[0].typ == nil): 
         result = paramsNotEqual # one proc has a result, the other not is OK
       else: 
@@ -752,9 +751,9 @@ template ifFastObjectTypeCheckFailed(a, b: PType, body: stmt) {.immediate.} =
 
 proc sameObjectTypes*(a, b: PType): bool =
   # specialized for efficiency (sigmatch uses it)
-  ifFastObjectTypeCheckFailed(a, b):     
+  ifFastObjectTypeCheckFailed(a, b):
     var c = initSameTypeClosure()
-    result = sameTypeAux(a, b, c)    
+    result = sameTypeAux(a, b, c)
 
 proc sameDistinctTypes*(a, b: PType): bool {.inline.} =
   result = sameObjectTypes(a, b)
@@ -829,9 +828,9 @@ proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
       if a.kind != b.kind: return false  
   case a.kind
   of tyEmpty, tyChar, tyBool, tyNil, tyPointer, tyString, tyCString,
-     tyInt..tyBigNum, tyStmt:
+     tyInt..tyBigNum, tyStmt, tyExpr:
     result = sameFlags(a, b)
-  of tyExpr:
+  of tyStatic:
     result = exprStructuralEquivalent(a.n, b.n) and sameFlags(a, b)
   of tyObject:
     ifFastObjectTypeCheckFailed(a, b):
@@ -855,12 +854,15 @@ proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     result = sameTypeAux(lastSon(a), lastSon(b), c)
   of tyTypeDesc:
     if c.cmp == dcEqIgnoreDistinct: result = false
-    elif TypeDescExactMatch in c.flags:
+    elif ExactTypeDescValues in c.flags:
       cycleCheck()
       result = sameChildrenAux(x, y, c) and sameFlags(a, b)
     else:
       result = sameFlags(a, b)
-  of tyGenericParam, tyGenericInvokation, tyGenericBody, tySequence,
+  of tyGenericParam:
+    result = if ExactGenericParams in c.flags: a.id == b.id
+             else: sameChildrenAux(a, b, c) and sameFlags(a, b)
+  of tyGenericInvokation, tyGenericBody, tySequence,
      tyOpenArray, tySet, tyRef, tyPtr, tyVar, tyArrayConstr,
      tyArray, tyProc, tyConst, tyMutable, tyVarargs, tyIter,
      tyOrdinal, tyTypeClasses:
@@ -976,42 +978,6 @@ proc isGenericAlias*(t: PType): bool =
 proc skipGenericAlias*(t: PType): PType =
   return if t.isGenericAlias: t.lastSon else: t
 
-proc matchTypeClass*(bindings: var TIdTable, typeClass, t: PType): bool =
-  for i in countup(0, typeClass.sonsLen - 1):
-    let req = typeClass.sons[i]
-    var match = req.kind == skipTypes(t, {tyRange, tyGenericInst}).kind
-
-    if not match:
-      case req.kind
-      of tyGenericBody:
-        if t.kind == tyGenericInst and t.sons[0] == req:
-          match = true
-          idTablePut(bindings, typeClass, t)
-      of tyTypeClass:
-        match = matchTypeClass(bindings, req, t)
-      elif t.kind == tyTypeClass:
-        match = matchTypeClass(bindings, t, req)
-          
-    elif t.kind in {tyObject} and req.len != 0:
-      # empty 'object' is fine as constraint in a type class
-      match = sameType(t, req)
-
-    if tfAny in typeClass.flags:
-      if match: return true
-    else:
-      if not match: return false
-
-  # if the loop finished without returning, either all constraints matched
-  # or none of them matched.
-  result = if tfAny in typeClass.flags: false else: true
-  if result == true:
-    idTablePut(bindings, typeClass, t)
-
-proc matchTypeClass*(typeClass, typ: PType): bool =
-  var bindings: TIdTable
-  initIdTable(bindings)
-  result = matchTypeClass(bindings, typeClass, typ)
-
 proc typeAllowedAux(marker: var TIntSet, typ: PType, kind: TSymKind,
                     flags: TTypeAllowedFlags = {}): bool =
   assert(kind in {skVar, skLet, skConst, skParam, skResult})
@@ -1039,7 +1005,7 @@ proc typeAllowedAux(marker: var TIntSet, typ: PType, kind: TSymKind,
       if not result: break 
     if result and t.sons[0] != nil:
       result = typeAllowedAux(marker, t.sons[0], skResult, flags)
-  of tyExpr, tyStmt, tyTypeDesc:
+  of tyExpr, tyStmt, tyTypeDesc, tyStatic:
     result = true
     # XXX er ... no? these should not be allowed!
   of tyEmpty:
@@ -1133,18 +1099,22 @@ proc computeRecSizeAux(n: PNode, a, currOffset: var BiggestInt): BiggestInt =
     a = 1
     result = - 1
 
-proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt = 
+const 
+  szIllegalRecursion* = -2
+  szUnknownSize* = -1
+
+proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
   var res, maxAlign, length, currOffset: BiggestInt
-  if typ.size == - 2: 
+  if typ.size == szIllegalRecursion:
     # we are already computing the size of the type
     # --> illegal recursion in type
-    return - 2
-  if typ.size >= 0: 
+    return szIllegalRecursion
+  if typ.size >= 0:
     # size already computed
     result = typ.size
     a = typ.align
     return 
-  typ.size = - 2              # mark as being computed
+  typ.size = szIllegalRecursion # mark as being computed
   case typ.kind
   of tyInt, tyUInt: 
     result = intSize
@@ -1175,8 +1145,10 @@ proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
      tyBigNum: 
     result = ptrSize
     a = result
-  of tyArray, tyArrayConstr: 
-    result = lengthOrd(typ.sons[0]) * computeSizeAux(typ.sons[1], a)
+  of tyArray, tyArrayConstr:
+    let elemSize = computeSizeAux(typ.sons[1], a)
+    if elemSize < 0: return elemSize
+    result = lengthOrd(typ.sons[0]) * elemSize
   of tyEnum: 
     if firstOrd(typ) < 0: 
       result = 4              # use signed int32
@@ -1227,11 +1199,12 @@ proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
   of tyGenericInst, tyDistinct, tyGenericBody, tyMutable, tyConst, tyIter:
     result = computeSizeAux(lastSon(typ), a)
   of tyTypeDesc:
-    result = (if typ.len == 1: computeSizeAux(typ.sons[0], a) else: -1)
-  of tyProxy: result = 1
+    result = if typ.len == 1: computeSizeAux(typ.sons[0], a)
+             else: szUnknownSize
+  of tyForward: return szIllegalRecursion
   else:
     #internalError("computeSizeAux()")
-    result = - 1
+    result = szUnknownSize
   typ.size = result
   typ.align = int(a)
 
@@ -1248,9 +1221,9 @@ proc getSize(typ: PType): BiggestInt =
   result = computeSize(typ)
   if result < 0: internalError("getSize: " & $typ.kind)
 
-  
-proc containsGenericTypeIter(t: PType, closure: PObject): bool = 
-  result = t.kind in GenericTypes
+proc containsGenericTypeIter(t: PType, closure: PObject): bool =
+  result = t.kind in GenericTypes + tyTypeClasses +
+                     {tyTypeDesc, tyStatic}
 
 proc containsGenericType*(t: PType): bool = 
   result = iterOverType(t, containsGenericTypeIter, nil)
@@ -1315,7 +1288,7 @@ proc compatibleEffects*(formal, actual: PType): bool =
   result = true
 
 proc isCompileTimeOnly*(t: PType): bool {.inline.} =
-  result = t.kind in {tyTypeDesc, tyExpr}
+  result = t.kind in {tyTypeDesc, tyStatic}
 
 proc containsCompileTimeOnly*(t: PType): bool =
   if isCompileTimeOnly(t): return true
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 0a1ee0a1a..f7ca9ea7f 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -791,7 +791,8 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): PNode =
       decodeBC(nkIntLit)
       let t1 = regs[rb].typ.skipTypes({tyTypeDesc})
       let t2 = c.types[regs[rc].intVal.int]
-      let match = if t2.kind == tyTypeClass: matchTypeClass(t2, t1)
+      # XXX: This should use the standard isOpImpl
+      let match = if t2.kind == tyTypeClass: true
                   else: sameType(t1, t2)
       regs[ra].intVal = ord(match)
     of opcSetLenSeq:
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index 563dbc6d1..6389d0508 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -832,7 +832,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
 
 const
   atomicTypes = {tyBool, tyChar,
-    tyExpr, tyStmt, tyTypeDesc,
+    tyExpr, tyStmt, tyTypeDesc, tyStatic,
     tyEnum,
     tyOrdinal,
     tyRange,
@@ -1039,8 +1039,8 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
     result = newNodeIT(nkUIntLit, info, t)
   of tyFloat..tyFloat128: 
     result = newNodeIT(nkFloatLit, info, t)
-  of tyVar, tyPointer, tyPtr, tyCString, tySequence, tyString, tyExpr, 
-     tyStmt, tyTypeDesc, tyRef:
+  of tyVar, tyPointer, tyPtr, tyCString, tySequence, tyString, tyExpr,
+     tyStmt, tyTypeDesc, tyStatic, tyRef:
     result = newNodeIT(nkNilLit, info, t)
   of tyProc:
     if t.callConv != ccClosure:
diff --git a/doc/manual.txt b/doc/manual.txt
index 5024fffec..2d8feca17 100644
--- a/doc/manual.txt
+++ b/doc/manual.txt
@@ -3837,6 +3837,60 @@ This is a simple syntactic transformation into:
 Special Types
 =============
 
+static[T]
+---------
+
+As their name suggests, static params must be known at compile-time:
+
+.. code-block:: nimrod
+
+  proc precompiledRegex(pattern: static[string]): TRegEx =
+    var res {.global.} = re(pattern)
+    return res
+
+  precompiledRegex("/d+") # Replaces the call with a precompiled
+                          # regex, stored in a global variable
+
+  precompiledRegex(paramStr(1)) # Error, command-line options
+                                # are not known at compile-time
+
+
+For the purposes of code generation, all static params are treated as
+generic params - the proc will be compiled separately for each unique
+supplied value (or combination of values). 
+
+Furthermore, the system module defines a `semistatic[T]` type than can be
+used to declare procs accepting both static and run-time values, which can
+optimize their body according to the supplied param using the `isStatic(p)`
+predicate:
+
+.. code-block:: nimrod
+
+  # The following proc will be compiled once for each unique static
+  # value and also once for the case handling all run-time values:
+
+  proc re(pattern: semistatic[string]): TRegEx =
+    when isStatic(pattern):
+      return precompiledRegex(pattern)
+    else:
+      return compile(pattern)
+
+Static params can also appear in the signatures of generic types:
+
+.. code-block:: nimrod
+
+  type
+    Matrix[M,N: static[int]; T: Number] = array[0..(M*N - 1), T]
+      # Please, note how `Number` is just a type constraint here, while
+      # `static[int]` requires us to supply a compile-time int value
+
+    AffineTransform2D[T] = Matrix[3, 3, T]
+    AffineTransform3D[T] = Matrix[4, 4, T]
+
+  AffineTransform3D[float] # OK
+  AffineTransform2D[string] # Error, `string` is not a `Number`
+
+
 typedesc
 --------
 
diff --git a/lib/core/macros.nim b/lib/core/macros.nim
index f1f1c8ddb..0356067f1 100644
--- a/lib/core/macros.nim
+++ b/lib/core/macros.nim
@@ -59,7 +59,8 @@ type
     nnkBindStmt, nnkMixinStmt, nnkUsingStmt,
     nnkCommentStmt, nnkStmtListExpr, nnkBlockExpr,
     nnkStmtListType, nnkBlockType, nnkTypeOfExpr, nnkObjectTy,
-    nnkTupleTy, nnkTypeClassTy, nnkRecList, nnkRecCase, nnkRecWhen,
+    nnkTupleTy, nnkTypeClassTy, nnkStaticTy,
+    nnkRecList, nnkRecCase, nnkRecWhen,
     nnkRefTy, nnkPtrTy, nnkVarTy,
     nnkConstTy, nnkMutableTy,
     nnkDistinctTy,
@@ -293,16 +294,15 @@ proc quote*(bl: stmt, op = "``"): PNimrodNode {.magic: "QuoteAst".}
   ##       if not `ex`:
   ##         echo `info` & ": Check failed: " & `expString`
   
-template emit*(e: expr[string]): stmt =
-  ## accepts a single string argument and treats it as nimrod code
-  ## that should be inserted verbatim in the program
-  ## Example:
-  ##
-  ## .. code-block:: nimrod
-  ##
-  ##   emit("echo " & '"' & "hello world".toUpper & '"')
-  ##
-  eval: result = e.parseStmt
+when not defined(booting):
+  template emit*(e: static[string]): stmt =
+    ## accepts a single string argument and treats it as nimrod code
+    ## that should be inserted verbatim in the program
+    ## Example:
+    ##
+    ##   emit("echo " & '"' & "hello world".toUpper & '"')
+    ##
+    eval: result = e.parseStmt
 
 proc expectKind*(n: PNimrodNode, k: TNimrodNodeKind) {.compileTime.} =
   ## checks that `n` is of kind `k`. If this is not the case,
diff --git a/lib/system.nim b/lib/system.nim
index dddf77858..978fae1a6 100644
--- a/lib/system.nim
+++ b/lib/system.nim
@@ -2550,7 +2550,7 @@ proc raiseAssert*(msg: string) {.noinline.} =
   sysFatal(EAssertionFailed, msg)
 
 when true:
-  proc hiddenRaiseAssert(msg: string) {.raises: [], tags: [].} =
+  proc failedAssertImpl*(msg: string) {.raises: [], tags: [].} =
     # trick the compiler to not list ``EAssertionFailed`` when called
     # by ``assert``.
     type THide = proc (msg: string) {.noinline, raises: [], noSideEffect,
@@ -2563,11 +2563,11 @@ template assert*(cond: bool, msg = "") =
   ## raises an ``EAssertionFailure`` exception. However, the compiler may
   ## not generate any code at all for ``assert`` if it is advised to do so.
   ## Use ``assert`` for debugging purposes only.
-  bind instantiationInfo, hiddenRaiseAssert
+  bind instantiationInfo
+  mixin failedAssertImpl
   when compileOption("assertions"):
     {.line.}:
-      if not cond:
-        hiddenRaiseAssert(astToStr(cond) & ' ' & msg)
+      if not cond: failedAssertImpl(astToStr(cond) & ' ' & msg)
 
 template doAssert*(cond: bool, msg = "") =
   ## same as `assert` but is always turned on and not affected by the
@@ -2580,9 +2580,9 @@ template doAssert*(cond: bool, msg = "") =
 when not defined(nimhygiene):
   {.pragma: inject.}
 
-template onFailedAssert*(msg: expr, code: stmt): stmt =
-  ## Sets an assertion failure handler that will intercept any assert statements
-  ## following `onFailedAssert` in the current lexical scope.
+template onFailedAssert*(msg: expr, code: stmt): stmt {.dirty, immediate.} =
+  ## Sets an assertion failure handler that will intercept any assert
+  ## statements following `onFailedAssert` in the current lexical scope.
   ## Can be defined multiple times in a single function.
   ##  
   ## .. code-block:: nimrod
@@ -2599,8 +2599,8 @@ template onFailedAssert*(msg: expr, code: stmt): stmt =
   ##
   ##     assert(...)
   ##
-  template raiseAssert(msgIMPL: string): stmt =
-    let msg {.inject.} = msgIMPL
+  template failedAssertImpl(msgIMPL: string): stmt {.dirty, immediate.} =
+    let msg = msgIMPL
     code
 
 proc shallow*[T](s: var seq[T]) {.noSideEffect, inline.} =
@@ -2646,7 +2646,7 @@ when hostOS != "standalone":
       x[j+i] = item[j]
       inc(j)
 
-proc compiles*(x: expr): bool {.magic: "Compiles", noSideEffect.} =
+proc compiles*(x): bool {.magic: "Compiles", noSideEffect.} =
   ## Special compile-time procedure that checks whether `x` can be compiled
   ## without any semantic error.
   ## This can be used to check whether a type supports some operation:
@@ -2680,3 +2680,13 @@ proc locals*(): TObject {.magic: "Locals", noSideEffect.} =
   ## the official signature says, the return type is not ``TObject`` but a
   ## tuple of a structure that depends on the current scope.
   discard
+
+when not defined(booting):
+  type
+    semistatic*[T] = static[T] | T
+    # indicates a param of proc specialized for each static value,
+    # but also accepting run-time values
+
+  template isStatic*(x): expr = compiles(static(x))
+    # checks whether `x` is a value known at compile-time
+
diff --git a/tests/compile/tbindtypedesc.nim b/tests/compile/tbindtypedesc.nim
index 4ebfd12bb..5ea8cf063 100644
--- a/tests/compile/tbindtypedesc.nim
+++ b/tests/compile/tbindtypedesc.nim
@@ -16,10 +16,10 @@ type
   TBar = tuple
     x, y: int
 
-template good(e: expr) =
+template accept(e: expr) =
   static: assert(compiles(e))
 
-template bad(e: expr) =
+template reject(e: expr) =
   static: assert(not compiles(e))
 
 proc genericParamRepeated[T: typedesc](a: T, b: T) =
@@ -27,22 +27,22 @@ proc genericParamRepeated[T: typedesc](a: T, b: T) =
     echo a.name
     echo b.name
 
-good(genericParamRepeated(int, int))
-good(genericParamRepeated(float, float))
+accept genericParamRepeated(int, int)
+accept genericParamRepeated(float, float)
 
-bad(genericParamRepeated(string, int))
-bad(genericParamRepeated(int, float))
+reject genericParamRepeated(string, int)
+reject genericParamRepeated(int, float)
 
 proc genericParamOnce[T: typedesc](a, b: T) =
   static:
     echo a.name
     echo b.name
 
-good(genericParamOnce(int, int))
-good(genericParamOnce(TFoo, TFoo))
+accept genericParamOnce(int, int)
+accept genericParamOnce(TFoo, TFoo)
 
-bad(genericParamOnce(string, int))
-bad(genericParamOnce(TFoo, float))
+reject genericParamOnce(string, int)
+reject genericParamOnce(TFoo, float)
 
 type
   type1 = typedesc
@@ -50,42 +50,42 @@ type
 
 proc typePairs(A, B: type1; C, D: type2) = nil
 
-good(typePairs(int, int, TFoo, TFOO))
-good(typePairs(TBAR, TBar, TBAR, TBAR))
-good(typePairs(int, int, string, string))
+accept typePairs(int, int, TFoo, TFOO)
+accept typePairs(TBAR, TBar, TBAR, TBAR)
+accept typePairs(int, int, string, string)
 
-bad(typePairs(TBAR, TBar, TBar, TFoo))
-bad(typePairs(string, int, TBAR, TBAR))
+reject typePairs(TBAR, TBar, TBar, TFoo)
+reject typePairs(string, int, TBAR, TBAR)
 
 proc typePairs2[T: typedesc, U: typedesc](A, B: T; C, D: U) = nil
 
-good(typePairs2(int, int, TFoo, TFOO))
-good(typePairs2(TBAR, TBar, TBAR, TBAR))
-good(typePairs2(int, int, string, string))
+accept typePairs2(int, int, TFoo, TFOO)
+accept typePairs2(TBAR, TBar, TBAR, TBAR)
+accept typePairs2(int, int, string, string)
 
-bad(typePairs2(TBAR, TBar, TBar, TFoo))
-bad(typePairs2(string, int, TBAR, TBAR))
+reject typePairs2(TBAR, TBar, TBar, TFoo)
+reject typePairs2(string, int, TBAR, TBAR)
 
 proc dontBind(a: typedesc, b: typedesc) =
   static:
     echo a.name
     echo b.name
 
-good(dontBind(int, float))
-good(dontBind(TFoo, TFoo))
+accept dontBind(int, float)
+accept dontBind(TFoo, TFoo)
 
 proc dontBind2(a, b: typedesc) = nil
 
-good(dontBind2(int, float))
-good(dontBind2(TBar, int))
+accept dontBind2(int, float)
+accept dontBind2(TBar, int)
 
 proc bindArg(T: typedesc, U: typedesc, a, b: T, c, d: U) = nil
 
-good(bindArg(int, string, 10, 20, "test", "nest"))
-good(bindArg(int, int, 10, 20, 30, 40))
+accept bindArg(int, string, 10, 20, "test", "nest")
+accept bindArg(int, int, 10, 20, 30, 40)
 
-bad(bindArg(int, string, 10, "test", "test", "nest"))
-bad(bindArg(int, int, 10, 20, 30, "test"))
-bad(bindArg(int, string, 10.0, 20, "test", "nest"))
-bad(bindArg(int, string, "test", "nest", 10, 20))
+reject bindArg(int, string, 10, "test", "test", "nest")
+reject bindArg(int, int, 10, 20, 30, "test")
+reject bindArg(int, string, 10.0, 20, "test", "nest")
+reject bindArg(int, string, "test", "nest", 10, 20)
 
diff --git a/tests/compile/tcompositetypeclasses.nim b/tests/compile/tcompositetypeclasses.nim
new file mode 100644
index 000000000..4ba92fed1
--- /dev/null
+++ b/tests/compile/tcompositetypeclasses.nim
@@ -0,0 +1,35 @@
+template accept(e) =
+  static: assert(compiles(e))
+
+template reject(e) =
+  static: assert(not compiles(e))
+
+type
+  TFoo[T, U] = tuple
+    x: T
+    y: U
+
+  TBar[K] = TFoo[K, K]
+
+  TUserClass = int|string
+
+  TBaz = TBar[TUserClass]
+
+var
+  vfoo: TFoo[int, string]
+  vbar: TFoo[string, string]
+  vbaz: TFoo[int, int]
+  vnotbaz: TFoo[TObject, TObject]
+
+proc foo(x: TFoo) = echo "foo"
+proc bar(x: TBar) = echo "bar"
+proc baz(x: TBaz) = echo "baz"
+
+accept foo(vfoo)
+accept bar(vbar)
+accept baz(vbar)
+accept baz(vbaz)
+
+reject baz(vnotbaz)
+reject bar(vfoo)
+
diff --git a/tests/compile/tloops.nim b/tests/compile/tloops.nim
index 2b1765b00..f6f939769 100644
--- a/tests/compile/tloops.nim
+++ b/tests/compile/tloops.nim
@@ -1,67 +1,67 @@
-# Test nested loops and some other things

-

-proc andTest() =

-  var a = 0 == 5 and 6 == 6

-

-proc incx(x: var int) = # is built-in proc

-  x = x + 1

-

-proc decx(x: var int) =

-  x = x - 1

-

-proc First(y: var int) =

-  var x: int

-  i_ncx(x)

-  if x == 10:

-    y = 0

-  else:

-    if x == 0:

-      incx(x)

-    else:

-      x=11

-

-proc TestLoops() =

-  var i, j: int

-  while i >= 0:

-    if i mod 3 == 0:

-      break

-    i = i + 1

-    while j == 13:

-      j = 13

-      break

-    break

-

-  while True:

-    break

-

-

-proc Foo(n: int): int =

-    var

-        a, old: int

-        b, c: bool

-    F_irst(a)

-    if a == 10:

-        a = 30

-    elif a == 11:

-        a = 22

-    elif a == 12:

-        a = 23

-    elif b:

-        old = 12

-    else:

-        a = 40

-

-    #

-    b = false or 2 == 0 and 3 == 9

-    a = 0 + 3 * 5 + 6 + 7 + +8 # 36

-    while b:

-        a = a + 3

-    a = a + 5

-    write(stdout, "Hello!")

-

-

-# We should come till here :-)

-discard Foo(345)

+# Test nested loops and some other things
+
+proc andTest() =
+  var a = 0 == 5 and 6 == 6
+
+proc incx(x: var int) = # is built-in proc
+  x = x + 1
+
+proc decx(x: var int) =
+  x = x - 1
+
+proc First(y: var int) =
+  var x: int
+  i_ncx(x)
+  if x == 10:
+    y = 0
+  else:
+    if x == 0:
+      incx(x)
+    else:
+      x=11
+
+proc TestLoops() =
+  var i, j: int
+  while i >= 0:
+    if i mod 3 == 0:
+      break
+    i = i + 1
+    while j == 13:
+      j = 13
+      break
+    break
+
+  while True:
+    break
+
+
+proc Foo(n: int): int =
+    var
+        a, old: int
+        b, c: bool
+    F_irst(a)
+    if a == 10:
+        a = 30
+    elif a == 11:
+        a = 22
+    elif a == 12:
+        a = 23
+    elif b:
+        old = 12
+    else:
+        a = 40
+
+    #
+    b = false or 2 == 0 and 3 == 9
+    a = 0 + 3 * 5 + 6 + 7 + +8 # 36
+    while b:
+        a = a + 3
+    a = a + 5
+    write(stdout, "Hello!")
+
+
+# We should come till here :-)
+discard Foo(345)
 
 # test the new type symbol lookup feature:
 
diff --git a/tests/reject/tillrec.nim b/tests/reject/tillrec.nim
index 3f8fe60fc..1d1ec0622 100644
--- a/tests/reject/tillrec.nim
+++ b/tests/reject/tillrec.nim
@@ -3,15 +3,14 @@ discard """
   line: 13
   errormsg: "illegal recursion in type \'TIllegal\'"
 """
-# test illegal recursive types

-

-type

-  TLegal {.final.} = object

-    x: int

-    kids: seq[TLegal]

-

-  TIllegal {.final.} = object  #ERROR_MSG illegal recursion in type 'TIllegal'

-    y: Int

-    x: array[0..3, TIllegal]

+# test illegal recursive types
 
+type
+  TLegal {.final.} = object
+    x: int
+    kids: seq[TLegal]
+
+  TIllegal {.final.} = object  #ERROR_MSG illegal recursion in type 'TIllegal'
+    y: Int
+    x: array[0..3, TIllegal]
 
diff --git a/tests/reject/typredef.nim b/tests/reject/typredef.nim
index b2182d116..0b6aed875 100644
--- a/tests/reject/typredef.nim
+++ b/tests/reject/typredef.nim
@@ -3,8 +3,6 @@ discard """
   line: 7
   errormsg: "illegal recursion in type \'Uint8\'"
 """
-type

-  Uint8 = Uint8 #ERROR_MSG illegal recursion in type 'Uint8'

-

-
+type
+  Uint8 = Uint8 #ERROR_MSG illegal recursion in type 'Uint8'
 
diff --git a/tests/run/tfailedassert.nim b/tests/run/tfailedassert.nim
new file mode 100644
index 000000000..d99e6dc60
--- /dev/null
+++ b/tests/run/tfailedassert.nim
@@ -0,0 +1,51 @@
+discard """
+  output: '''
+WARNING: false first asseertion from bar
+ERROR: false second assertion from bar
+-1
+tests/run/tfailedassert.nim:27 false assertion from foo
+'''
+"""
+
+type
+  TLineInfo = tuple[filename: string, line: int]
+
+  TMyError = object of E_Base
+    lineinfo: TLineInfo
+
+  EMyError = ref TMyError
+
+# module-wide policy to change the failed assert
+# exception type in order to include a lineinfo
+onFailedAssert(msg):
+  var e = new(TMyError)
+  e.msg = msg
+  e.lineinfo = instantiationInfo(-2)
+  raise e
+
+proc foo =
+  assert(false, "assertion from foo")
+
+proc bar: int =
+  # local overrides that are active only
+  # in this proc
+  onFailedAssert(msg): echo "WARNING: " & msg
+    
+  assert(false, "first asseertion from bar")
+
+  onFailedAssert(msg):
+    echo "ERROR: " & msg
+    return -1
+
+  assert(false, "second assertion from bar")
+  return 10
+
+echo("")
+echo(bar())
+
+try:
+  foo()
+except:
+  let e = EMyError(getCurrentException())
+  echo e.lineinfo.filename, ":", e.lineinfo.line, " ", e.msg
+
diff --git a/tests/run/tmemoization.nim b/tests/run/tmemoization.nim
index 78f0515f3..180acd89b 100644
--- a/tests/run/tmemoization.nim
+++ b/tests/run/tmemoization.nim
@@ -1,17 +1,17 @@
 discard """
-  msg:    "test 1\ntest 2"
-  output: "TEST 1\nTEST 2\nTEST 2"
+  msg:    "test 1\ntest 2\ntest 3"
+  output: "TEST 1\nTEST 2\nTEST 3"
 """
 
 import strutils
 
-proc foo(s: expr[string]): string =
+proc foo(s: static[string]): string =
   static: echo s
 
   const R = s.toUpper
   return R
-  
+
 echo foo("test 1")
 echo foo("test 2")
-echo foo("test " & $2)
+echo foo("test " & $3)
 
diff --git a/tests/run/tsemistatic.nim b/tests/run/tsemistatic.nim
new file mode 100644
index 000000000..d187f153c
--- /dev/null
+++ b/tests/run/tsemistatic.nim
@@ -0,0 +1,24 @@
+discard """
+  msg: "static 10\ndynamic\nstatic 20\n"
+  output: "s\nd\nd\ns"
+"""
+
+proc foo(x: semistatic[int]) =
+  when isStatic(x):
+    static: echo "static ", x
+    echo "s"
+  else:
+    static: echo "dynamic"
+    echo "d"
+
+foo 10
+
+var
+  x = 10
+  y: int
+
+foo x
+foo y
+
+foo 20
+
diff --git a/tests/run/tstaticparams.nim b/tests/run/tstaticparams.nim
index f2d6e1dd6..b1377443b 100644
--- a/tests/run/tstaticparams.nim
+++ b/tests/run/tstaticparams.nim
@@ -4,15 +4,15 @@ discard """
 """
 
 type 
-  TFoo[T; Val: expr[string]] = object
+  TFoo[T; Val: static[string]] = object
     data: array[4, T]
 
-  TBar[T; I: expr[int]] = object
+  TBar[T; I: static[int]] = object
     data: array[I, T]
 
-  TA1[T; I: expr[int]] = array[I, T]
-  TA2[T; I: expr[int]] = array[0..I, T]
-  TA3[T; I: expr[int]] = array[I-1, T]
+  TA1[T; I: static[int]] = array[I, T]
+  # TA2[T; I: static[int]] = array[0..I, T]
+  # TA3[T; I: static[int]] = array[I-1, T]
 
 proc takeFoo(x: TFoo) =
   echo "abracadabra"
@@ -25,7 +25,7 @@ var y: TBar[float, 4]
 echo high(y.data)
 
 var
-  t1: TA1
-  t2: TA2
-  t3: TA3
+  t1: TA1[float, 1]
+  # t2: TA2[string, 4]
+  # t3: TA3[int, 10]
 
diff --git a/tests/run/ttypetraits.nim b/tests/run/ttypetraits.nim
index 9a4a7d0d3..4344855eb 100644
--- a/tests/run/ttypetraits.nim
+++ b/tests/run/ttypetraits.nim
@@ -1,6 +1,6 @@
 discard """
   msg:    "int\nstring\nTBar[int]"
-  output: "int\nstring\nTBar[int]\nint\nrange 0..2\nstring"
+  output: "int\nstring\nTBar[int]\nint\nrange 0..2(int)\nstring"
 """
 
 import typetraits
diff --git a/tests/run/tusingstatement.nim b/tests/run/tusingstatement.nim
index b9d466377..a33aced4c 100644
--- a/tests/run/tusingstatement.nim
+++ b/tests/run/tusingstatement.nim
@@ -8,25 +8,11 @@ import
 
 # This macro mimics the using statement from C#
 #
-# XXX: 
-#  It doen't match the C# version exactly yet.
-#  In particular, it's not recursive, which prevents it from dealing 
-#  with exceptions thrown from the variable initializers when multiple.
-#  variables are used.
+# It's kept only as a test for the macro system
+# Nimrod's destructors offer a mechanism for automatic 
+# disposal of resources.
 #
-#  Also, since nimrod relies less on exceptions in general, a more
-#  idiomatic definition could be:
-#  var x = init()
-#  if opened(x): 
-#    try:
-#      body
-#    finally:
-#      close(x)
-#
-#  `opened` here could be an overloaded proc which any type can define.
-#  A common practice can be returing an Optional[Resource] obj for which
-#  `opened` is defined to `optional.hasValue`
-macro using(e: expr): stmt {.immediate.} =
+macro autoClose(e: expr): stmt {.immediate.} =
   let e = callsite()
   if e.len != 3:
     error "Using statement: unexpected number of arguments. Got " &
@@ -97,7 +83,7 @@ proc close(r: var TResource) =
 proc use(r: var TResource) =
   write(stdout, "Using " & r.field & ".")
 
-using(r = openResource("test")):
+autoClose(r = openResource("test")):
   use r
 
 
diff --git a/todo.txt b/todo.txt
index 4a2ab4c70..d9069dd26 100644
--- a/todo.txt
+++ b/todo.txt
@@ -41,7 +41,6 @@ version 0.9.x
 - macros as type pragmas
 - implicit deref for parameter matching
 - lazy overloading resolution:
-  * get rid of ``expr[typ]``, use perhaps ``static[typ]`` instead
   * special case ``tyStmt``
 - FFI:
   * test libffi on windows
diff --git a/web/news.txt b/web/news.txt
index 7deda8dad..c518bfc95 100644
--- a/web/news.txt
+++ b/web/news.txt
@@ -33,6 +33,10 @@ Changes affecting backwards compatibility
 - The symbol binding rules for clean templates changed: ``bind`` for any
   symbol that's not a parameter is now the default. ``mixin`` can be used
   to require instantiation scope for a symbol.
+- ``quoteIfContainsWhite`` now escapes argument in such way that it can be safely
+  passed to shell, instead of just adding double quotes.
+- ``macros.dumpTree`` and ``macros.dumpLisp`` have been made ``immediate``,
+  ``dumpTreeImm`` and ``dumpLispImm`` are now deprecated.
 
 
 Compiler Additions
@@ -56,15 +60,15 @@ Language Additions
 
 - Arrays can now be declared with a single integer literal ``N`` instead of a
   range; the range is then ``0..N-1``.
-- ``macros.dumpTree`` and ``macros.dumpLisp`` have been made ``immediate``,
-  ``dumpTreeImm`` and ``dumpLispImm`` are now deprecated.
 - Added ``requiresInit`` pragma to enforce explicit initialization.
-- Added ``using statement`` for better authoring domain-specific languages and
-  OOP-like syntactic sugar.
-- Added ``delegator pragma`` for handling calls to missing procs and fields at
-  compile-time.
-- Support for user-defined type classes has been added.
 - Exported templates are allowed to access hidden fields.
+- The ``using statement`` enables you to more easily author domain-specific
+  languages and libraries providing OOP-like syntactic sugar.
+- Added a new ``delegator pragma`` for handling calls to missing procs and
+  fields at compile-time.
+- The overload resolution now supports ``static[T]`` params that must be
+  evaluatable at compile-time.
+- Support for user-defined type classes have been added.
 
 
 Tools improvements