summary refs log tree commit diff stats
diff options
context:
space:
mode:
authorZahary Karadjov <zahary@gmail.com>2013-12-19 01:06:38 +0200
committerZahary Karadjov <zahary@gmail.com>2013-12-19 01:06:38 +0200
commit027f30610e44633b661befcca1b5dd39e9eaa283 (patch)
tree45841cac06bf79c512b050791697ce68b36b58ed
parent7120491d055c04d838d9539fdf0c42003637ec2d (diff)
downloadNim-027f30610e44633b661befcca1b5dd39e9eaa283.tar.gz
static params: expr[T] is now static[T]
This introduces tyStatic and successfully bootstraps and handles
few simple test cases.  Static params within macros are no longer
treated as PNimrodNodes - they are now equivalent to constants
of the designated type.
-rw-r--r--compiler/ast.nim8
-rw-r--r--compiler/ccgutils.nim2
-rw-r--r--compiler/cgen.nim4
-rw-r--r--compiler/evalffi.nim2
-rw-r--r--compiler/evals.nim7
-rw-r--r--compiler/jsgen.nim2
-rw-r--r--compiler/parser.nim26
-rw-r--r--compiler/ropes.nim17
-rw-r--r--compiler/semexprs.nim9
-rw-r--r--compiler/semfold.nim2
-rw-r--r--compiler/seminst.nim8
-rw-r--r--compiler/semmagic.nim2
-rw-r--r--compiler/semtypes.nim38
-rw-r--r--compiler/semtypinst.nim4
-rw-r--r--compiler/sigmatch.nim62
-rw-r--r--compiler/types.nim13
-rw-r--r--compiler/vmgen.nim6
-rw-r--r--lib/core/macros.nim20
-rw-r--r--lib/system.nim2
-rw-r--r--tests/run/tmemoization.nim2
-rw-r--r--tests/run/tstaticparams.nim10
-rw-r--r--todo.txt1
22 files changed, 136 insertions, 111 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 1e5276d68..462bad24f 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,12 +337,13 @@ type
     tyIter, # unused
     tyProxy # used as errornous type (for idetools)
     tyTypeClass
+    tyParametricTypeClass # structured similarly to tyGenericInst
+                          # lastSon is the body of the type class
     tyAnd
     tyOr
     tyNot
     tyAnything
-    tyParametricTypeClass # structured similarly to tyGenericInst
-                          # lastSon is the body of the type class
+    tyStatic
 
 const
   tyPureObject* = tyTuple
@@ -1232,7 +1234,7 @@ proc propagateToOwner*(owner, elem: PType) =
   if tfShared in elem.flags:
     owner.flags.incl tfHasShared
   
-  if elem.kind in {tyExpr, tyTypeDesc}:
+  if elem.kind in {tyExpr, tyStatic, tyTypeDesc}:
     owner.flags.incl tfHasMeta
   elif elem.kind in {tyString, tyRef, tySequence} or
       elem.kind == tyProc and elem.callConv == ccClosure:
diff --git a/compiler/ccgutils.nim b/compiler/ccgutils.nim
index 310f7204a..01928b22c 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 b0c90de76..c2bba76b9 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 21a131996..848f706f2 100644
--- a/compiler/evalffi.nim
+++ b/compiler/evalffi.nim
@@ -78,7 +78,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..4a2586d5f 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): 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,
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index a3c88824d..9912115ee 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/parser.nim b/compiler/parser.nim
index fd51b04ec..c8c14780d 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/ropes.nim b/compiler/ropes.nim
index 707c29123..9a3647c0a 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/semexprs.nim b/compiler/semexprs.nim
index ccbb1e367..a7fd1eaa0 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:
@@ -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")
@@ -937,7 +938,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)
@@ -1882,7 +1883,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)
diff --git a/compiler/semfold.nim b/compiler/semfold.nim
index ca06ea1b6..ddbe3053c 100644
--- a/compiler/semfold.nim
+++ b/compiler/semfold.nim
@@ -587,7 +587,7 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
     of skType:
       result = newSymNodeTypeDesc(s, n.info)
     of skGenericParam:
-      if s.typ.kind == tyExpr:
+      if s.typ.kind == tyStatic:
         result = s.typ.n
         result.typ = s.typ.sons[0]
       else:
diff --git a/compiler/seminst.nim b/compiler/seminst.nim
index d7d64fd54..a76c673da 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}
@@ -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
@@ -200,7 +200,7 @@ proc fixupProcType(c: PContext, genericType: PType,
     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 tyOpenArray, tyArray, tySet, tySequence, tyTuple, tyProc,
      tyPtr, tyVar, tyRef, tyOrdinal, tyRange, tyVarargs:
diff --git a/compiler/semmagic.nim b/compiler/semmagic.nim
index 88567b10a..4c667e27e 100644
--- a/compiler/semmagic.nim
+++ b/compiler/semmagic.nim
@@ -88,7 +88,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/semtypes.nim b/compiler/semtypes.nim
index 6c9c476d9..d4d953757 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -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): 
@@ -577,9 +577,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"
@@ -629,15 +629,12 @@ 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))
   of tyTypeDesc:
     if tfUnresolved notin paramType.flags:
       # naked typedescs are not bindOnce types
@@ -743,8 +740,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)
@@ -1000,6 +998,10 @@ 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)
   of nkProcTy, nkIteratorTy:
     if n.sonsLen == 0:
       result = newConstraint(c, tyProc)
@@ -1105,7 +1107,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)
@@ -1116,7 +1118,7 @@ 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)
@@ -1132,7 +1134,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 61c31a4fe..d05d063aa 100644
--- a/compiler/semtypinst.nim
+++ b/compiler/semtypinst.nim
@@ -201,7 +201,7 @@ proc ReplaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType =
     result = lookupTypeVar(cl, t)
     if result.kind == tyGenericInvokation:
       result = handleGenericInvokation(cl, result)
-  of tyExpr:
+  of tyStatic:
     if t.sym != nil and t.sym.kind == skGenericParam:
       result = lookupTypeVar(cl, t)
   of tyGenericInvokation: 
@@ -215,7 +215,7 @@ proc ReplaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType =
   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)
diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim
index cacf4782e..87f1decf4 100644
--- a/compiler/sigmatch.nim
+++ b/compiler/sigmatch.nim
@@ -124,7 +124,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 =
@@ -894,40 +894,39 @@ proc ParamTypesMatchAux(c: PContext, m: var TCandidate, f, argType: PType,
     arg = argSemantized
 
   let
-    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
+    a0 = if c.InTypeClass > 0: argType.skipTypes({tyTypeDesc})
+         else: argType
+    a = if a0 != nil: a0.skipTypes({tyStatic}) else: a0
+    fMaybeStatic = f.skipTypes({tyDistinct})
+
+  case fMaybeStatic.kind
+  of tyStatic:
+    if a.kind == tyStatic:
+      InternalAssert a.len > 0
+      r = typeRel(m, f.lastSon, a.lastSon)
     else:
-      if a.kind == tyExpr:
-        InternalAssert a.len > 0
-        r = typeRel(m, f.lastSon, a.lastSon)
+      let match = matchTypeClass(m.bindings, fMaybeStatic, a)
+      if not match: r = isNone
       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
+        # 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(tyStatic, c)
+          arg.typ.sons = @[evaluated.typ]
+          arg.typ.n = evaluated
         
     if r == isGeneric:
       put(m.bindings, f, arg.typ)
+
   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,6 +934,9 @@ 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)
 
@@ -961,6 +963,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:
diff --git a/compiler/types.nim b/compiler/types.nim
index 7e07a0667..5fe128bbb 100644
--- a/compiler/types.nim
+++ b/compiler/types.nim
@@ -409,7 +409,7 @@ const
     "uint", "uint8", "uint16", "uint32", "uint64",
     "bignum", "const ",
     "!", "varargs[$1]", "iter[$1]", "Error Type", "TypeClass",
-    "ParametricTypeClass", "and", "or", "not", "any"]
+    "ParametricTypeClass", "and", "or", "not", "any", "static"]
 
 proc consToStr(t: PType): string =
   if t.len > 0: result = t.typeToString
@@ -445,6 +445,9 @@ proc TypeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
   of tyTypeDesc:
     if t.len == 0: result = "typedesc"
     else: result = "typedesc[" & constraintsToStr(t) & "]"
+  of tyStatic:
+    InternalAssert t.len > 0
+    result = "static[" & constraintsToStr(t) & "]"
   of tyTypeClass:
     if t.n != nil: return t.sym.owner.name.s
     case t.len
@@ -828,9 +831,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):
@@ -1038,7 +1041,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:
@@ -1314,7 +1317,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/vmgen.nim b/compiler/vmgen.nim
index 84d82e117..f5ea24aa2 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -777,7 +777,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
 
 const
   atomicTypes = {tyBool, tyChar,
-    tyExpr, tyStmt, tyTypeDesc,
+    tyExpr, tyStmt, tyTypeDesc, tyStatic,
     tyEnum,
     tyOrdinal,
     tyRange,
@@ -937,8 +937,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, tyProc, tyRef:
+  of tyVar, tyPointer, tyPtr, tyCString, tySequence, tyString, tyExpr,
+     tyStmt, tyTypeDesc, tyStatic, tyProc, tyRef:
     result = newNodeIT(nkNilLit, info, t)
   of tyObject: 
     result = newNodeIT(nkPar, info, t)
diff --git a/lib/core/macros.nim b/lib/core/macros.nim
index d01d4ebee..44a3a34c3 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,
@@ -285,14 +286,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:
-  ##
-  ##   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 dc5a406d1..e58378c05 100644
--- a/lib/system.nim
+++ b/lib/system.nim
@@ -2641,7 +2641,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:
diff --git a/tests/run/tmemoization.nim b/tests/run/tmemoization.nim
index 78f0515f3..b59ff44ea 100644
--- a/tests/run/tmemoization.nim
+++ b/tests/run/tmemoization.nim
@@ -5,7 +5,7 @@ discard """
 
 import strutils
 
-proc foo(s: expr[string]): string =
+proc foo(s: static[string]): string =
   static: echo s
 
   const R = s.toUpper
diff --git a/tests/run/tstaticparams.nim b/tests/run/tstaticparams.nim
index f2d6e1dd6..23d644bce 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"
diff --git a/todo.txt b/todo.txt
index da7585500..a0a8ce2b5 100644
--- a/todo.txt
+++ b/todo.txt
@@ -38,7 +38,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