summary refs log tree commit diff stats
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/aliases.nim14
-rw-r--r--compiler/ast.nim168
-rw-r--r--compiler/astalgo.nim275
-rw-r--r--compiler/babelcmd.nim10
-rw-r--r--compiler/bitsets.nim40
-rw-r--r--compiler/c2nim/c2nim.nim24
-rw-r--r--compiler/c2nim/clex.nim100
-rw-r--r--compiler/c2nim/cparse.nim789
-rw-r--r--compiler/c2nim/cpp.nim12
-rw-r--r--compiler/c2nim/tests/vincent.c33
-rw-r--r--compiler/c2nim/tests/vincent.h3
-rw-r--r--compiler/ccgcalls.nim14
-rw-r--r--compiler/ccgexprs.nim284
-rw-r--r--compiler/ccgmerge.nim33
-rw-r--r--compiler/ccgstmts.nim125
-rw-r--r--compiler/ccgthreadvars.nim6
-rw-r--r--compiler/ccgtrav.nim8
-rw-r--r--compiler/ccgtypes.nim96
-rw-r--r--compiler/ccgutils.nim49
-rw-r--r--compiler/cgen.nim298
-rw-r--r--compiler/cgendata.nim15
-rw-r--r--compiler/cgmeth.nim24
-rw-r--r--compiler/commands.nim209
-rw-r--r--compiler/condsyms.nim76
-rw-r--r--compiler/crc.nim14
-rw-r--r--compiler/depends.nim4
-rw-r--r--compiler/docgen.nim50
-rw-r--r--compiler/docgen2.nim4
-rw-r--r--compiler/evalffi.nim82
-rw-r--r--compiler/evals.nim17
-rw-r--r--compiler/evaltempl.nim59
-rw-r--r--compiler/extccomp.nim126
-rw-r--r--compiler/filter_tmpl.nim112
-rw-r--r--compiler/filters.nim30
-rw-r--r--compiler/guards.nim12
-rw-r--r--compiler/hlo.nim8
-rw-r--r--compiler/idents.nim2
-rw-r--r--compiler/idgen.nim14
-rw-r--r--compiler/importer.nim46
-rw-r--r--compiler/jsgen.nim143
-rw-r--r--compiler/jstypes.nim8
-rw-r--r--compiler/lambdalifting.nim512
-rw-r--r--compiler/lexer.nim232
-rw-r--r--compiler/lists.nim40
-rw-r--r--compiler/llstream.nim97
-rw-r--r--compiler/lookups.nim109
-rw-r--r--compiler/magicsys.nim33
-rw-r--r--compiler/main.nim156
-rw-r--r--compiler/modules.nim28
-rw-r--r--compiler/msgs.nim132
-rw-r--r--compiler/nimconf.nim32
-rw-r--r--compiler/nimlexbase.nim45
-rw-r--r--compiler/nimrod.dot591
-rw-r--r--compiler/nimrod.nim16
-rw-r--r--compiler/nimrod.nimrod.cfg5
-rw-r--r--compiler/nimsets.nim38
-rw-r--r--compiler/options.nim39
-rw-r--r--compiler/parampatterns.nim14
-rw-r--r--compiler/parser.nim230
-rw-r--r--compiler/pas2nim/pas2nim.nim2
-rw-r--r--compiler/pas2nim/paslex.nim74
-rw-r--r--compiler/pas2nim/pasparse.nim52
-rw-r--r--compiler/passaux.nim8
-rw-r--r--compiler/passes.nim8
-rw-r--r--compiler/patterns.nim16
-rw-r--r--compiler/pbraces.nim2
-rw-r--r--compiler/platform.nim20
-rw-r--r--compiler/pragmas.nim264
-rw-r--r--compiler/pretty.nim178
-rw-r--r--compiler/procfind.nim54
-rw-r--r--compiler/renderer.nim139
-rw-r--r--compiler/rodread.nim158
-rw-r--r--compiler/rodutils.nim6
-rw-r--r--compiler/rodwrite.nim54
-rw-r--r--compiler/ropes.nim67
-rw-r--r--compiler/saturate.nim12
-rw-r--r--compiler/sem.nim171
-rw-r--r--compiler/semcall.nim58
-rw-r--r--compiler/semdata.nim83
-rw-r--r--compiler/semdestruct.nim99
-rw-r--r--compiler/semexprs.nim377
-rw-r--r--compiler/semfold.nim115
-rw-r--r--compiler/semgnrc.nim33
-rw-r--r--compiler/seminst.nim181
-rw-r--r--compiler/semmacrosanity.nim89
-rw-r--r--compiler/semmagic.nim39
-rw-r--r--compiler/sempass2.nim30
-rw-r--r--compiler/semstmts.nim276
-rw-r--r--compiler/semtempl.nim142
-rw-r--r--compiler/semthreads.nim40
-rw-r--r--compiler/semtypes.nim408
-rw-r--r--compiler/semtypinst.nim351
-rw-r--r--compiler/service.nim12
-rw-r--r--compiler/sigmatch.nim529
-rw-r--r--compiler/suggest.nim55
-rw-r--r--compiler/syntaxes.nim60
-rw-r--r--compiler/transf.nim102
-rw-r--r--compiler/trees.nim40
-rw-r--r--compiler/treetab.nim36
-rw-r--r--compiler/types.nim422
-rw-r--r--compiler/vm.nim626
-rw-r--r--compiler/vmdef.nim40
-rw-r--r--compiler/vmdeps.nim61
-rw-r--r--compiler/vmgen.nim410
-rw-r--r--compiler/wordrecg.nim14
105 files changed, 6338 insertions, 5460 deletions
diff --git a/compiler/aliases.nim b/compiler/aliases.nim
index 7accb8ce3..a26b94303 100644
--- a/compiler/aliases.nim
+++ b/compiler/aliases.nim
@@ -42,7 +42,7 @@ proc isPartOfAux(n: PNode, b: PType, marker: var TIntSet): TAnalysisResult =
 proc isPartOfAux(a, b: PType, marker: var TIntSet): TAnalysisResult = 
   result = arNo
   if a == nil or b == nil: return 
-  if ContainsOrIncl(marker, a.id): return 
+  if containsOrIncl(marker, a.id): return 
   if compareTypes(a, b, dcEqIgnoreDistinct): return arYes
   case a.kind
   of tyObject: 
@@ -54,11 +54,11 @@ proc isPartOfAux(a, b: PType, marker: var TIntSet): TAnalysisResult =
     for i in countup(0, sonsLen(a) - 1): 
       result = isPartOfAux(a.sons[i], b, marker)
       if result == arYes: return 
-  else: nil
+  else: discard
 
 proc isPartOf(a, b: PType): TAnalysisResult = 
   ## checks iff 'a' can be part of 'b'. Iterates over VALUE types!
-  var marker = InitIntSet()
+  var marker = initIntSet()
   # watch out: parameters reversed because I'm too lazy to change the code...
   result = isPartOfAux(b, a, marker)
 
@@ -115,7 +115,7 @@ proc isPartOf*(a, b: PNode): TAnalysisResult =
           var x = if a[1].kind == nkHiddenStdConv: a[1][1] else: a[1]
           var y = if b[1].kind == nkHiddenStdConv: b[1][1] else: b[1]
           
-          if SameValue(x, y): result = arYes
+          if sameValue(x, y): result = arYes
           else: result = arNo
         # else: maybe and no are accurate
       else:
@@ -140,7 +140,7 @@ proc isPartOf*(a, b: PNode): TAnalysisResult =
       result = isPartOf(a[1], b[1])
     of nkObjUpConv, nkObjDownConv, nkCheckedFieldExpr:
       result = isPartOf(a[0], b[0])
-    else: nil
+    else: discard
     # Calls return a new location, so a default of ``arNo`` is fine.
   else:
     # go down recursively; this is quite demanding:
@@ -177,6 +177,6 @@ proc isPartOf*(a, b: PNode): TAnalysisResult =
         if isPartOf(a.typ, b.typ) != arNo:
           result = isPartOf(a[0], b)
           if result == arNo: result = arMaybe
-      else: nil
-    else: nil
+      else: discard
+    else: discard
 
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 1e5276d68..7138b5f52 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
@@ -238,7 +239,7 @@ type
     sfMainModule,     # module is the main module
     sfSystemModule,   # module is the system module
     sfNoReturn,       # proc never returns (an exit proc)
-    sfAddrTaken,      # the variable's address is taken (ex- or implicitely);
+    sfAddrTaken,      # the variable's address is taken (ex- or implicitly);
                       # *OR*: a proc is indirectly called (used as first class)
     sfCompilerProc,   # proc is a compiler proc, that is a C proc that is
                       # needed for the code generator
@@ -257,7 +258,7 @@ type
                       # for interfacing with C++, JS
     sfNamedParamCall, # symbol needs named parameter call syntax in target
                       # language; for interfacing with Objective C
-    sfDiscardable,    # returned value may be discarded implicitely
+    sfDiscardable,    # returned value may be discarded implicitly
     sfDestructor,     # proc is destructor
     sfGenSym          # symbol is 'gensym'ed; do not add to symbol table
 
@@ -335,20 +336,66 @@ type
     tyConst, tyMutable, tyVarargs, 
     tyIter, # unused
     tyProxy # used as errornous type (for idetools)
-    tyTypeClass
-    tyAnd
-    tyOr
-    tyNot
-    tyAnything
-    tyParametricTypeClass # structured similarly to tyGenericInst
-                          # lastSon is the body of the type class
+    
+    tyBuiltInTypeClass #\
+      # Type such as the catch-all object, tuple, seq, etc
+    
+    tyUserTypeClass #\
+      # the body of a user-defined type class
+
+    tyUserTypeClassInst #\
+      # Instance of a parametric user-defined type class.
+      # Structured similarly to tyGenericInst.
+      # tyGenericInst represents concrete types, while
+      # this is still a "generic param" that will bind types
+      # and resolves them during sigmatch and instantiation.
+    
+    tyCompositeTypeClass #\
+      # Type such as seq[Number]
+      # The notes for tyUserTypeClassInst apply here as well 
+      # sons[0]: the original expression used by the user.
+      # sons[1]: fully expanded and instantiated meta type
+      # (potentially following aliases)
+    
+    tyAnd, tyOr, tyNot #\
+      # boolean type classes such as `string|int`,`not seq`,
+      # `Sortable and Enumable`, etc
+    
+    tyAnything #\
+      # a type class matching any type
+    
+    tyStatic #\
+      # a value known at compile type (the underlying type is .base)
+    
+    tyFromExpr #\
+      # This is a type representing an expression that depends
+      # on generic parameters (the exprsesion is stored in t.n)
+      # It will be converted to a real type only during generic
+      # instantiation and prior to this it has the potential to
+      # be any type.
+
+    tyFieldAccessor #\
+      # Expressions such as Type.field (valid in contexts such
+      # as the `is` operator and magics like `high` and `low`).
+      # Could be lifted to a single argument proc returning the
+      # field value.
+      # sons[0]: type of containing object or tuple
+      # sons[1]: field type
+      # .n: nkDotExpr storing the field name
 
 const
   tyPureObject* = tyTuple
   GcTypeKinds* = {tyRef, tySequence, tyString}
   tyError* = tyProxy # as an errornous node should match everything
-  tyTypeClasses* = {tyTypeClass, tyParametricTypeClass, tyAnd, tyOr, tyNot, tyAnything}
 
+  tyUnknownTypes* = {tyError, tyFromExpr}
+
+  tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass,
+                    tyUserTypeClass, tyUserTypeClassInst,
+                    tyAnd, tyOr, tyNot, tyAnything}
+
+  tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyStatic, tyExpr} + tyTypeClasses
+ 
 type
   TTypeKinds* = set[TTypeKind]
 
@@ -364,6 +411,7 @@ type
     nfSem       # node has been checked for semantics
     nfDelegate  # the call can use a delegator
     nfExprCall  # this is an attempt to call a regular expression
+    nfIsRef     # this node is a 'ref' node; used for the VM
 
   TNodeFlags* = set[TNodeFlag]
   TTypeFlag* = enum   # keep below 32 for efficiency reasons (now: 23)
@@ -382,9 +430,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)
@@ -395,8 +440,12 @@ 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
+    tfHasStatic
+    tfGenericTypeParam
+    tfImplicitTypeParam
 
   TTypeFlags* = set[TTypeFlag]
 
@@ -545,11 +594,11 @@ type
     typ*: PType
     info*: TLineInfo
     flags*: TNodeFlags
-    case Kind*: TNodeKind
+    case kind*: TNodeKind
     of nkCharLit..nkUInt64Lit:
-      intVal*: biggestInt
+      intVal*: BiggestInt
     of nkFloatLit..nkFloat128Lit:
-      floatVal*: biggestFloat
+      floatVal*: BiggestFloat
     of nkStrLit..nkTripleStrLit:
       strVal*: string
     of nkSym: 
@@ -773,9 +822,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, 
@@ -792,7 +843,7 @@ const
   ExportableSymKinds* = {skVar, skConst, skProc, skMethod, skType, skIterator, 
     skMacro, skTemplate, skConverter, skEnumField, skLet, skStub}
   PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16,
-                                      nfAllConst, nfDelegate}
+                                      nfAllConst, nfDelegate, nfIsRef}
   namePos* = 0
   patternPos* = 1    # empty except for term rewriting macros
   genericParamsPos* = 2
@@ -821,7 +872,7 @@ const
     # imported via 'importc: "fullname"' and no format string.
 
 # creator procs:
-proc newSym*(symKind: TSymKind, Name: PIdent, owner: PSym,
+proc newSym*(symKind: TSymKind, name: PIdent, owner: PSym,
              info: TLineInfo): PSym
 proc newType*(kind: TTypeKind, owner: PSym): PType
 proc newNode*(kind: TNodeKind): PNode
@@ -894,6 +945,9 @@ template `{}=`*(n: PNode, i: int, s: PNode): stmt =
 var emptyNode* = newNode(nkEmpty)
 # There is a single empty node that is shared! Do not overwrite it!
 
+proc isMetaType*(t: PType): bool =
+  return t.kind in tyMetaTypes or tfHasMeta in t.flags
+
 proc linkTo*(t: PType, s: PSym): PType {.discardable.} =
   t.sym = s
   s.typ = t
@@ -910,7 +964,7 @@ template fileIdx*(c: PSym): int32 =
 
 template filename*(c: PSym): string =
   # XXX: this should be used only on module symbols
-  c.position.int32.toFileName
+  c.position.int32.toFilename
 
 proc appendToModule*(m: PSym, n: PNode) =
   ## The compiler will use this internally to add nodes that will be
@@ -929,7 +983,7 @@ const                         # for all kind of hash tables:
 proc copyStrTable(dest: var TStrTable, src: TStrTable) = 
   dest.counter = src.counter
   if isNil(src.data): return 
-  setlen(dest.data, len(src.data))
+  setLen(dest.data, len(src.data))
   for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
   
 proc copyIdTable(dest: var TIdTable, src: TIdTable) = 
@@ -941,13 +995,13 @@ proc copyIdTable(dest: var TIdTable, src: TIdTable) =
 proc copyTable(dest: var TTable, src: TTable) = 
   dest.counter = src.counter
   if isNil(src.data): return 
-  setlen(dest.data, len(src.data))
+  setLen(dest.data, len(src.data))
   for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
   
 proc copyObjectSet(dest: var TObjectSet, src: TObjectSet) = 
   dest.counter = src.counter
   if isNil(src.data): return 
-  setlen(dest.data, len(src.data))
+  setLen(dest.data, len(src.data))
   for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
   
 proc discardSons(father: PNode) = 
@@ -1067,7 +1121,7 @@ proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
                   pragmas, exceptions, body]
 
 
-proc NewType(kind: TTypeKind, owner: PSym): PType = 
+proc newType(kind: TTypeKind, owner: PSym): PType = 
   new(result)
   result.kind = kind
   result.owner = owner
@@ -1107,7 +1161,7 @@ proc assignType(dest, src: PType) =
   for i in countup(0, sonsLen(src) - 1): dest.sons[i] = src.sons[i]
   
 proc copyType(t: PType, owner: PSym, keepId: bool): PType = 
-  result = newType(t.Kind, owner)
+  result = newType(t.kind, owner)
   assignType(result, t)
   if keepId: 
     result.id = t.id
@@ -1147,12 +1201,12 @@ proc createModuleAlias*(s: PSym, newIdent: PIdent, info: TLineInfo): PSym =
   # XXX once usedGenerics is used, ensure module aliases keep working!
   assert s.usedGenerics == nil
   
-proc newSym(symKind: TSymKind, Name: PIdent, owner: PSym,
+proc newSym(symKind: TSymKind, name: PIdent, owner: PSym,
             info: TLineInfo): PSym = 
   # generates a symbol and initializes the hash field too
   new(result)
-  result.Name = Name
-  result.Kind = symKind
+  result.name = name
+  result.kind = symKind
   result.flags = {}
   result.info = info
   result.options = gOptions
@@ -1160,36 +1214,36 @@ proc newSym(symKind: TSymKind, Name: PIdent, owner: PSym,
   result.offset = - 1
   result.id = getID()
   when debugIds: 
-    RegisterId(result)
+    registerId(result)
   #if result.id < 2000:
   #  MessageOut(name.s & " has id: " & toString(result.id))
   
 proc initStrTable(x: var TStrTable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc newStrTable*: TStrTable =
   initStrTable(result)
 
 proc initTable(x: var TTable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc initIdTable(x: var TIdTable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc initObjectSet(x: var TObjectSet) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc initIdNodeTable(x: var TIdNodeTable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc initNodeTable(x: var TNodeTable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
+  newSeq(x.data, StartSize)
 
 proc sonsLen(n: PType): int = 
   if isNil(n.sons): result = 0
@@ -1203,7 +1257,7 @@ proc newSons(father: PType, length: int) =
   if isNil(father.sons): 
     newSeq(father.sons, length)
   else:
-    setlen(father.sons, length)
+    setLen(father.sons, length)
 
 proc sonsLen(n: PNode): int = 
   if isNil(n.sons): result = 0
@@ -1213,12 +1267,16 @@ proc newSons(father: PNode, length: int) =
   if isNil(father.sons): 
     newSeq(father.sons, length)
   else:
-    setlen(father.sons, length)
+    setLen(father.sons, length)
+
+proc skipTypes*(t: PType, kinds: TTypeKinds): PType =
+  result = t
+  while result.kind in kinds: result = lastSon(result)
 
 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
@@ -1226,15 +1284,19 @@ proc propagateToOwner*(owner, elem: PType) =
       owner.flags.incl tfNeedsInit
   
   if tfNeedsInit in elem.flags:
-    if owner.kind in HaveTheirOwnEmpty: nil
+    if owner.kind in HaveTheirOwnEmpty: discard
     else: owner.flags.incl tfNeedsInit
     
   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
 
@@ -1256,7 +1318,7 @@ proc delSon(father: PNode, idx: int) =
   if isNil(father.sons): return 
   var length = sonsLen(father)
   for i in countup(idx, length - 2): father.sons[i] = father.sons[i + 1]
-  setlen(father.sons, length - 1)
+  setLen(father.sons, length - 1)
 
 proc copyNode(src: PNode): PNode = 
   # does not copy its sons!
@@ -1269,13 +1331,13 @@ proc copyNode(src: PNode): PNode =
   when defined(useNodeIds):
     if result.id == nodeIdToDebug:
       echo "COMES FROM ", src.id
-  case src.Kind
+  case src.kind
   of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
   of nkFloatLit..nkFloat128Lit: result.floatVal = src.floatVal
   of nkSym: result.sym = src.sym
   of nkIdent: result.ident = src.ident
   of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
-  else: nil
+  else: discard
 
 proc shallowCopy*(src: PNode): PNode = 
   # does not copy its sons, but provides space for them:
@@ -1287,7 +1349,7 @@ proc shallowCopy*(src: PNode): PNode =
   when defined(useNodeIds):
     if result.id == nodeIdToDebug:
       echo "COMES FROM ", src.id
-  case src.Kind
+  case src.kind
   of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
   of nkFloatLit..nkFloat128Lit: result.floatVal = src.floatVal
   of nkSym: result.sym = src.sym
@@ -1306,7 +1368,7 @@ proc copyTree(src: PNode): PNode =
   when defined(useNodeIds):
     if result.id == nodeIdToDebug:
       echo "COMES FROM ", src.id
-  case src.Kind
+  case src.kind
   of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
   of nkFloatLit..nkFloat128Lit: result.floatVal = src.floatVal
   of nkSym: result.sym = src.sym
@@ -1364,14 +1426,14 @@ proc sonsNotNil(n: PNode): bool =
       return false
   result = true
 
-proc getInt*(a: PNode): biggestInt = 
+proc getInt*(a: PNode): BiggestInt = 
   case a.kind
   of nkIntLit..nkUInt64Lit: result = a.intVal
   else: 
     internalError(a.info, "getInt")
     result = 0
 
-proc getFloat*(a: PNode): biggestFloat = 
+proc getFloat*(a: PNode): BiggestFloat = 
   case a.kind
   of nkFloatLit..nkFloat128Lit: result = a.floatVal
   else: 
@@ -1398,16 +1460,20 @@ proc isGenericRoutine*(s: PSym): bool =
   of skProcKinds:
     result = sfFromGeneric in s.flags or
              (s.ast != nil and s.ast[genericParamsPos].kind != nkEmpty)
-  else: nil
+  else: discard
 
 proc skipGenericOwner*(s: PSym): PSym =
-  InternalAssert s.kind in skProcKinds
+  internalAssert s.kind in skProcKinds
   ## Generic instantiations are owned by their originating generic
   ## symbol. This proc skips such owners and goes straigh to the owner
   ## of the generic itself (the module or the enclosing proc).
   result = if sfFromGeneric in s.flags: s.owner.owner
            else: s.owner
 
+proc originatingModule*(s: PSym): PSym =
+  result = s.owner
+  while result.kind != skModule: result = result.owner
+
 proc isRoutine*(s: PSym): bool {.inline.} =
   result = s.kind in {skProc, skTemplate, skMacro, skIterator, skMethod,
                       skConverter}
diff --git a/compiler/astalgo.nim b/compiler/astalgo.nim
index 6c48dd00f..2505bc687 100644
--- a/compiler/astalgo.nim
+++ b/compiler/astalgo.nim
@@ -24,35 +24,35 @@ proc symToYaml*(n: PSym, indent: int = 0, maxRecDepth: int = - 1): PRope
 proc lineInfoToStr*(info: TLineInfo): PRope
   
 # ----------------------- node sets: ---------------------------------------
-proc ObjectSetContains*(t: TObjectSet, obj: PObject): bool
+proc objectSetContains*(t: TObjectSet, obj: PObject): bool
   # returns true whether n is in t
-proc ObjectSetIncl*(t: var TObjectSet, obj: PObject)
+proc objectSetIncl*(t: var TObjectSet, obj: PObject)
   # include an element n in the table t
-proc ObjectSetContainsOrIncl*(t: var TObjectSet, obj: PObject): bool
+proc objectSetContainsOrIncl*(t: var TObjectSet, obj: PObject): bool
   # more are not needed ...
 
 # ----------------------- (key, val)-Hashtables ----------------------------
-proc TablePut*(t: var TTable, key, val: PObject)
-proc TableGet*(t: TTable, key: PObject): PObject
+proc tablePut*(t: var TTable, key, val: PObject)
+proc tableGet*(t: TTable, key: PObject): PObject
 type 
   TCmpProc* = proc (key, closure: PObject): bool {.nimcall.} # true if found
 
-proc TableSearch*(t: TTable, key, closure: PObject, 
+proc tableSearch*(t: TTable, key, closure: PObject, 
                   comparator: TCmpProc): PObject
   # return val as soon as comparator returns true; if this never happens,
   # nil is returned
 
 # ----------------------- str table -----------------------------------------
-proc StrTableContains*(t: TStrTable, n: PSym): bool
-proc StrTableAdd*(t: var TStrTable, n: PSym)
-proc StrTableGet*(t: TStrTable, name: PIdent): PSym  
+proc strTableContains*(t: TStrTable, n: PSym): bool
+proc strTableAdd*(t: var TStrTable, n: PSym)
+proc strTableGet*(t: TStrTable, name: PIdent): PSym  
   
 type 
   TTabIter*{.final.} = object # consider all fields here private
     h*: THash                 # current hash
   
-proc InitTabIter*(ti: var TTabIter, tab: TStrTable): PSym
-proc NextIter*(ti: var TTabIter, tab: TStrTable): PSym
+proc initTabIter*(ti: var TTabIter, tab: TStrTable): PSym
+proc nextIter*(ti: var TTabIter, tab: TStrTable): PSym
   # usage:
   # var 
   #   i: TTabIter
@@ -69,8 +69,8 @@ type
     name*: PIdent
 
 
-proc InitIdentIter*(ti: var TIdentIter, tab: TStrTable, s: PIdent): PSym
-proc NextIdentIter*(ti: var TIdentIter, tab: TStrTable): PSym
+proc initIdentIter*(ti: var TIdentIter, tab: TStrTable, s: PIdent): PSym
+proc nextIdentIter*(ti: var TIdentIter, tab: TStrTable): PSym
 
 # these are for debugging only: They are not really deprecated, but I want
 # the warning so that release versions do not contain debugging statements:
@@ -79,15 +79,14 @@ proc debug*(n: PType) {.deprecated.}
 proc debug*(n: PNode) {.deprecated.}
 
 # --------------------------- ident tables ----------------------------------
-proc IdTableGet*(t: TIdTable, key: PIdObj): PObject
-proc IdTableGet*(t: TIdTable, key: int): PObject
-proc IdTablePut*(t: var TIdTable, key: PIdObj, val: PObject)
-proc IdTableHasObjectAsKey*(t: TIdTable, key: PIdObj): bool
+proc idTableGet*(t: TIdTable, key: PIdObj): PObject
+proc idTableGet*(t: TIdTable, key: int): PObject
+proc idTablePut*(t: var TIdTable, key: PIdObj, val: PObject)
+proc idTableHasObjectAsKey*(t: TIdTable, key: PIdObj): bool
   # checks if `t` contains the `key` (compared by the pointer value, not only
   # `key`'s id)
-proc IdNodeTableGet*(t: TIdNodeTable, key: PIdObj): PNode
-proc IdNodeTablePut*(t: var TIdNodeTable, key: PIdObj, val: PNode)
-proc writeIdNodeTable*(t: TIdNodeTable)
+proc idNodeTableGet*(t: TIdNodeTable, key: PIdObj): PNode
+proc idNodeTablePut*(t: var TIdNodeTable, key: PIdObj, val: PNode)
 
 # ---------------------------------------------------------------------------
 
@@ -111,9 +110,9 @@ type
     data*: TIIPairSeq
 
 
-proc initIITable*(x: var TIITable)
-proc IITableGet*(t: TIITable, key: int): int
-proc IITablePut*(t: var TIITable, key, val: int)
+proc initIiTable*(x: var TIITable)
+proc iiTableGet*(t: TIITable, key: int): int
+proc iiTablePut*(t: var TIITable, key, val: int)
 
 # implementation
 
@@ -129,7 +128,7 @@ proc skipConvTakeType*(n: PNode): PNode =
   result = n.skipConv
   result.typ = n.typ
 
-proc SameValue*(a, b: PNode): bool = 
+proc sameValue*(a, b: PNode): bool = 
   result = false
   case a.kind
   of nkCharLit..nkInt64Lit: 
@@ -141,7 +140,7 @@ proc SameValue*(a, b: PNode): bool =
   else:
     # don't raise an internal error for 'nimrod check':
     #InternalError(a.info, "SameValue")
-    nil
+    discard
 
 proc leValue*(a, b: PNode): bool = 
   # a <= b?
@@ -156,7 +155,7 @@ proc leValue*(a, b: PNode): bool =
   else: 
     # don't raise an internal error for 'nimrod check':
     #InternalError(a.info, "leValue")
-    nil
+    discard
 
 proc lookupInRecord(n: PNode, field: PIdent): PSym = 
   result = nil
@@ -166,7 +165,7 @@ proc lookupInRecord(n: PNode, field: PIdent): PSym =
       result = lookupInRecord(n.sons[i], field)
       if result != nil: return 
   of nkRecCase: 
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "lookupInRecord")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "lookupInRecord")
     result = lookupInRecord(n.sons[0], field)
     if result != nil: return 
     for i in countup(1, sonsLen(n) - 1): 
@@ -182,14 +181,14 @@ proc lookupInRecord(n: PNode, field: PIdent): PSym =
 proc getModule(s: PSym): PSym = 
   result = s
   assert((result.kind == skModule) or (result.owner != result))
-  while (result != nil) and (result.kind != skModule): result = result.owner
+  while result != nil and result.kind != skModule: result = result.owner
   
 proc getSymFromList(list: PNode, ident: PIdent, start: int = 0): PSym = 
   for i in countup(start, sonsLen(list) - 1): 
     if list.sons[i].kind == nkSym:
       result = list.sons[i].sym
       if result.name.id == ident.id: return 
-    else: InternalError(list.info, "getSymFromList")
+    else: internalError(list.info, "getSymFromList")
   result = nil
 
 proc hashNode(p: PObject): THash = 
@@ -203,7 +202,7 @@ proc spaces(x: int): PRope =
   # returns x spaces
   result = toRope(repeatChar(x))
 
-proc toYamlChar(c: Char): string = 
+proc toYamlChar(c: char): string = 
   case c
   of '\0'..'\x1F', '\x80'..'\xFF': result = "\\u" & strutils.toHex(ord(c), 4)
   of '\'', '\"', '\\': result = '\\' & c
@@ -216,7 +215,7 @@ proc makeYamlString*(s: string): PRope =
   const MaxLineLength = 64
   result = nil
   var res = "\""
-  for i in countup(0, len(s) - 1): 
+  for i in countup(0, if s.isNil: -1 else: (len(s)-1)): 
     if (i + 1) mod MaxLineLength == 0: 
       add(res, '\"')
       add(res, "\n")
@@ -262,7 +261,7 @@ proc strTableToYaml(n: TStrTable, marker: var TIntSet, indent: int,
   app(result, "]")
   assert(mycount == n.counter)
 
-proc ropeConstr(indent: int, c: openarray[PRope]): PRope = 
+proc ropeConstr(indent: int, c: openArray[PRope]): PRope = 
   # array of (name, value) pairs
   var istr = spaces(indent + 2)
   result = toRope("{")
@@ -277,7 +276,7 @@ proc symToYamlAux(n: PSym, marker: var TIntSet, indent: int,
                   maxRecDepth: int): PRope = 
   if n == nil: 
     result = toRope("null")
-  elif ContainsOrIncl(marker, n.id): 
+  elif containsOrIncl(marker, n.id): 
     result = ropef("\"$1 @$2\"", [toRope(n.name.s), toRope(
         strutils.toHex(cast[TAddress](n), sizeof(n) * 2))])
   else: 
@@ -298,7 +297,7 @@ proc typeToYamlAux(n: PType, marker: var TIntSet, indent: int,
                    maxRecDepth: int): PRope = 
   if n == nil: 
     result = toRope("null")
-  elif ContainsOrIncl(marker, n.id): 
+  elif containsOrIncl(marker, n.id): 
     result = ropef("\"$1 @$2\"", [toRope($n.kind), toRope(
         strutils.toHex(cast[TAddress](n), sizeof(n) * 2))])
   else: 
@@ -315,7 +314,7 @@ proc typeToYamlAux(n: PType, marker: var TIntSet, indent: int,
                                  makeYamlString($n.kind), 
                                  toRope("sym"), symToYamlAux(n.sym, marker, 
         indent + 2, maxRecDepth - 1), toRope("n"), treeToYamlAux(n.n, marker, 
-        indent + 2, maxRecDepth - 1), toRope("flags"), FlagsToStr(n.flags), 
+        indent + 2, maxRecDepth - 1), toRope("flags"), flagsToStr(n.flags), 
                                  toRope("callconv"), 
                                  makeYamlString(CallingConvToStr[n.callConv]), 
                                  toRope("size"), toRope(n.size), 
@@ -336,7 +335,7 @@ proc treeToYamlAux(n: PNode, marker: var TIntSet, indent: int,
         appf(result, ",$N$1\"intVal\": $2", [istr, toRope(n.intVal)])
       of nkFloatLit, nkFloat32Lit, nkFloat64Lit: 
         appf(result, ",$N$1\"floatVal\": $2", 
-            [istr, toRope(n.floatVal.ToStrMaxPrecision)])
+            [istr, toRope(n.floatVal.toStrMaxPrecision)])
       of nkStrLit..nkTripleStrLit: 
         appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
       of nkSym: 
@@ -360,15 +359,15 @@ proc treeToYamlAux(n: PNode, marker: var TIntSet, indent: int,
     appf(result, "$N$1}", [spaces(indent)])
 
 proc treeToYaml(n: PNode, indent: int = 0, maxRecDepth: int = - 1): PRope = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = treeToYamlAux(n, marker, indent, maxRecDepth)
 
 proc typeToYaml(n: PType, indent: int = 0, maxRecDepth: int = - 1): PRope = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = typeToYamlAux(n, marker, indent, maxRecDepth)
 
 proc symToYaml(n: PSym, indent: int = 0, maxRecDepth: int = - 1): PRope = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = symToYamlAux(n, marker, indent, maxRecDepth)
 
 proc debugTree(n: PNode, indent: int, maxRecDepth: int): PRope
@@ -406,7 +405,7 @@ proc debugTree(n: PNode, indent: int, maxRecDepth: int): PRope =
         appf(result, ",$N$1\"intVal\": $2", [istr, toRope(n.intVal)])
       of nkFloatLit, nkFloat32Lit, nkFloat64Lit: 
         appf(result, ",$N$1\"floatVal\": $2", 
-            [istr, toRope(n.floatVal.ToStrMaxPrecision)])
+            [istr, toRope(n.floatVal.toStrMaxPrecision)])
       of nkStrLit..nkTripleStrLit: 
         appf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)])
       of nkSym: 
@@ -433,6 +432,8 @@ proc debugTree(n: PNode, indent: int, maxRecDepth: int): PRope =
 proc debug(n: PSym) =
   if n == nil:
     writeln(stdout, "null")
+  elif n.kind == skUnknown:
+    writeln(stdout, "skUnknown")
   else:
     #writeln(stdout, ropeToStr(symToYaml(n, 0, 1)))
     writeln(stdout, ropeToStr(ropef("$1_$2: $3, $4", [
@@ -454,18 +455,18 @@ proc nextTry(h, maxHash: THash): THash =
   # generates each int in range(maxHash) exactly once (see any text on
   # random-number generation for proof).
   
-proc objectSetContains(t: TObjectSet, obj: PObject): bool = 
+proc objectSetContains(t: TObjectSet, obj: PObject): bool =
   # returns true whether n is in t
   var h: THash = hashNode(obj) and high(t.data) # start with real hash value
-  while t.data[h] != nil: 
-    if (t.data[h] == obj): 
+  while t.data[h] != nil:
+    if t.data[h] == obj:
       return true
     h = nextTry(h, high(t.data))
   result = false
 
-proc objectSetRawInsert(data: var TObjectSeq, obj: PObject) = 
-  var h: THash = HashNode(obj) and high(data)
-  while data[h] != nil: 
+proc objectSetRawInsert(data: var TObjectSeq, obj: PObject) =
+  var h: THash = hashNode(obj) and high(data)
+  while data[h] != nil:
     assert(data[h] != obj)
     h = nextTry(h, high(data))
   assert(data[h] == nil)
@@ -473,8 +474,8 @@ proc objectSetRawInsert(data: var TObjectSeq, obj: PObject) =
 
 proc objectSetEnlarge(t: var TObjectSet) = 
   var n: TObjectSeq
-  newSeq(n, len(t.data) * growthFactor)
-  for i in countup(0, high(t.data)): 
+  newSeq(n, len(t.data) * GrowthFactor)
+  for i in countup(0, high(t.data)):
     if t.data[i] != nil: objectSetRawInsert(n, t.data[i])
   swap(t.data, n)
 
@@ -485,7 +486,7 @@ proc objectSetIncl(t: var TObjectSet, obj: PObject) =
 
 proc objectSetContainsOrIncl(t: var TObjectSet, obj: PObject): bool = 
   # returns true if obj is already in the string table:
-  var h: THash = HashNode(obj) and high(t.data)
+  var h: THash = hashNode(obj) and high(t.data)
   while true: 
     var it = t.data[h]
     if it == nil: break 
@@ -501,7 +502,7 @@ proc objectSetContainsOrIncl(t: var TObjectSet, obj: PObject): bool =
   inc(t.counter)
   result = false
 
-proc TableRawGet(t: TTable, key: PObject): int = 
+proc tableRawGet(t: TTable, key: PObject): int = 
   var h: THash = hashNode(key) and high(t.data) # start with real hash value
   while t.data[h].key != nil: 
     if t.data[h].key == key: 
@@ -509,7 +510,7 @@ proc TableRawGet(t: TTable, key: PObject): int =
     h = nextTry(h, high(t.data))
   result = -1
 
-proc TableSearch(t: TTable, key, closure: PObject, 
+proc tableSearch(t: TTable, key, closure: PObject, 
                  comparator: TCmpProc): PObject = 
   var h: THash = hashNode(key) and high(t.data) # start with real hash value
   while t.data[h].key != nil: 
@@ -520,13 +521,13 @@ proc TableSearch(t: TTable, key, closure: PObject,
     h = nextTry(h, high(t.data))
   result = nil
 
-proc TableGet(t: TTable, key: PObject): PObject = 
-  var index = TableRawGet(t, key)
+proc tableGet(t: TTable, key: PObject): PObject = 
+  var index = tableRawGet(t, key)
   if index >= 0: result = t.data[index].val
   else: result = nil
   
-proc TableRawInsert(data: var TPairSeq, key, val: PObject) = 
-  var h: THash = HashNode(key) and high(data)
+proc tableRawInsert(data: var TPairSeq, key, val: PObject) = 
+  var h: THash = hashNode(key) and high(data)
   while data[h].key != nil: 
     assert(data[h].key != key)
     h = nextTry(h, high(data))
@@ -534,23 +535,23 @@ proc TableRawInsert(data: var TPairSeq, key, val: PObject) =
   data[h].key = key
   data[h].val = val
 
-proc TableEnlarge(t: var TTable) = 
+proc tableEnlarge(t: var TTable) = 
   var n: TPairSeq
-  newSeq(n, len(t.data) * growthFactor)
+  newSeq(n, len(t.data) * GrowthFactor)
   for i in countup(0, high(t.data)): 
-    if t.data[i].key != nil: TableRawInsert(n, t.data[i].key, t.data[i].val)
+    if t.data[i].key != nil: tableRawInsert(n, t.data[i].key, t.data[i].val)
   swap(t.data, n)
 
-proc TablePut(t: var TTable, key, val: PObject) = 
-  var index = TableRawGet(t, key)
+proc tablePut(t: var TTable, key, val: PObject) = 
+  var index = tableRawGet(t, key)
   if index >= 0: 
     t.data[index].val = val
   else: 
-    if mustRehash(len(t.data), t.counter): TableEnlarge(t)
-    TableRawInsert(t.data, key, val)
+    if mustRehash(len(t.data), t.counter): tableEnlarge(t)
+    tableRawInsert(t.data, key, val)
     inc(t.counter)
 
-proc StrTableContains(t: TStrTable, n: PSym): bool = 
+proc strTableContains(t: TStrTable, n: PSym): bool = 
   var h: THash = n.name.h and high(t.data) # start with real hash value
   while t.data[h] != nil: 
     if (t.data[h] == n): 
@@ -558,7 +559,7 @@ proc StrTableContains(t: TStrTable, n: PSym): bool =
     h = nextTry(h, high(t.data))
   result = false
 
-proc StrTableRawInsert(data: var TSymSeq, n: PSym) = 
+proc strTableRawInsert(data: var TSymSeq, n: PSym) = 
   var h: THash = n.name.h and high(data)
   while data[h] != nil: 
     if data[h] == n:
@@ -569,7 +570,7 @@ proc StrTableRawInsert(data: var TSymSeq, n: PSym) =
   assert(data[h] == nil)
   data[h] = n
 
-proc SymTabReplaceRaw(data: var TSymSeq, prevSym: PSym, newSym: PSym) =
+proc symTabReplaceRaw(data: var TSymSeq, prevSym: PSym, newSym: PSym) =
   assert prevSym.name.h == newSym.name.h
   var h: THash = prevSym.name.h and high(data)
   while data[h] != nil:
@@ -579,22 +580,22 @@ proc SymTabReplaceRaw(data: var TSymSeq, prevSym: PSym, newSym: PSym) =
     h = nextTry(h, high(data))
   assert false
  
-proc SymTabReplace*(t: var TStrTable, prevSym: PSym, newSym: PSym) =
-  SymTabReplaceRaw(t.data, prevSym, newSym)
+proc symTabReplace*(t: var TStrTable, prevSym: PSym, newSym: PSym) =
+  symTabReplaceRaw(t.data, prevSym, newSym)
 
-proc StrTableEnlarge(t: var TStrTable) = 
+proc strTableEnlarge(t: var TStrTable) = 
   var n: TSymSeq
-  newSeq(n, len(t.data) * growthFactor)
+  newSeq(n, len(t.data) * GrowthFactor)
   for i in countup(0, high(t.data)): 
-    if t.data[i] != nil: StrTableRawInsert(n, t.data[i])
+    if t.data[i] != nil: strTableRawInsert(n, t.data[i])
   swap(t.data, n)
 
-proc StrTableAdd(t: var TStrTable, n: PSym) = 
-  if mustRehash(len(t.data), t.counter): StrTableEnlarge(t)
-  StrTableRawInsert(t.data, n)
+proc strTableAdd(t: var TStrTable, n: PSym) = 
+  if mustRehash(len(t.data), t.counter): strTableEnlarge(t)
+  strTableRawInsert(t.data, n)
   inc(t.counter)
 
-proc StrTableIncl*(t: var TStrTable, n: PSym): bool {.discardable.} =
+proc strTableIncl*(t: var TStrTable, n: PSym): bool {.discardable.} =
   # returns true if n is already in the string table:
   # It is essential that `n` is written nevertheless!
   # This way the newest redefinition is picked by the semantic analyses!
@@ -608,15 +609,15 @@ proc StrTableIncl*(t: var TStrTable, n: PSym): bool {.discardable.} =
       return true             # found it
     h = nextTry(h, high(t.data))
   if mustRehash(len(t.data), t.counter):
-    StrTableEnlarge(t)
-    StrTableRawInsert(t.data, n)
+    strTableEnlarge(t)
+    strTableRawInsert(t.data, n)
   else:
     assert(t.data[h] == nil)
     t.data[h] = n
   inc(t.counter)
   result = false
 
-proc StrTableGet(t: TStrTable, name: PIdent): PSym = 
+proc strTableGet(t: TStrTable, name: PIdent): PSym = 
   var h: THash = name.h and high(t.data)
   while true: 
     result = t.data[h]
@@ -624,19 +625,19 @@ proc StrTableGet(t: TStrTable, name: PIdent): PSym =
     if result.name.id == name.id: break 
     h = nextTry(h, high(t.data))
 
-proc InitIdentIter(ti: var TIdentIter, tab: TStrTable, s: PIdent): PSym = 
+proc initIdentIter(ti: var TIdentIter, tab: TStrTable, s: PIdent): PSym = 
   ti.h = s.h
   ti.name = s
-  if tab.Counter == 0: result = nil
-  else: result = NextIdentIter(ti, tab)
+  if tab.counter == 0: result = nil
+  else: result = nextIdentIter(ti, tab)
   
-proc NextIdentIter(ti: var TIdentIter, tab: TStrTable): PSym = 
+proc nextIdentIter(ti: var TIdentIter, tab: TStrTable): PSym = 
   var h, start: THash
   h = ti.h and high(tab.data)
   start = h
   result = tab.data[h]
   while result != nil: 
-    if result.Name.id == ti.name.id: break 
+    if result.name.id == ti.name.id: break 
     h = nextTry(h, high(tab.data))
     if h == start: 
       result = nil
@@ -644,13 +645,13 @@ proc NextIdentIter(ti: var TIdentIter, tab: TStrTable): PSym =
     result = tab.data[h]
   ti.h = nextTry(h, high(tab.data))
   
-proc NextIdentExcluding*(ti: var TIdentIter, tab: TStrTable, 
+proc nextIdentExcluding*(ti: var TIdentIter, tab: TStrTable, 
                          excluding: TIntSet): PSym =
   var h: THash = ti.h and high(tab.data)
   var start = h
   result = tab.data[h]
   while result != nil: 
-    if result.Name.id == ti.name.id and not Contains(excluding, result.id): 
+    if result.name.id == ti.name.id and not contains(excluding, result.id): 
       break
     h = nextTry(h, high(tab.data))
     if h == start: 
@@ -658,35 +659,35 @@ proc NextIdentExcluding*(ti: var TIdentIter, tab: TStrTable,
       break 
     result = tab.data[h]
   ti.h = nextTry(h, high(tab.data))
-  if result != nil and Contains(excluding, result.id): result = nil
+  if result != nil and contains(excluding, result.id): result = nil
 
-proc FirstIdentExcluding*(ti: var TIdentIter, tab: TStrTable, s: PIdent,
+proc firstIdentExcluding*(ti: var TIdentIter, tab: TStrTable, s: PIdent,
                           excluding: TIntSet): PSym = 
   ti.h = s.h
   ti.name = s
-  if tab.Counter == 0: result = nil
-  else: result = NextIdentExcluding(ti, tab, excluding)
+  if tab.counter == 0: result = nil
+  else: result = nextIdentExcluding(ti, tab, excluding)
 
-proc InitTabIter(ti: var TTabIter, tab: TStrTable): PSym = 
+proc initTabIter(ti: var TTabIter, tab: TStrTable): PSym = 
   ti.h = 0                    # we start by zero ...
   if tab.counter == 0: 
     result = nil              # FIX 1: removed endless loop
   else: 
-    result = NextIter(ti, tab)
+    result = nextIter(ti, tab)
   
-proc NextIter(ti: var TTabIter, tab: TStrTable): PSym = 
+proc nextIter(ti: var TTabIter, tab: TStrTable): PSym = 
   result = nil
   while (ti.h <= high(tab.data)): 
     result = tab.data[ti.h]
-    Inc(ti.h)                 # ... and increment by one always
+    inc(ti.h)                 # ... and increment by one always
     if result != nil: break 
 
 iterator items*(tab: TStrTable): PSym = 
   var it: TTabIter
-  var s = InitTabIter(it, tab)
+  var s = initTabIter(it, tab)
   while s != nil: 
     yield s
-    s = NextIter(it, tab)
+    s = nextIter(it, tab)
 
 proc hasEmptySlot(data: TIdPairSeq): bool = 
   for h in countup(0, high(data)): 
@@ -694,27 +695,27 @@ proc hasEmptySlot(data: TIdPairSeq): bool =
       return true
   result = false
 
-proc IdTableRawGet(t: TIdTable, key: int): int = 
+proc idTableRawGet(t: TIdTable, key: int): int = 
   var h: THash
   h = key and high(t.data)    # start with real hash value
   while t.data[h].key != nil: 
-    if (t.data[h].key.id == key): 
+    if t.data[h].key.id == key:
       return h
     h = nextTry(h, high(t.data))
   result = - 1
 
-proc IdTableHasObjectAsKey(t: TIdTable, key: PIdObj): bool = 
-  var index = IdTableRawGet(t, key.id)
+proc idTableHasObjectAsKey(t: TIdTable, key: PIdObj): bool = 
+  var index = idTableRawGet(t, key.id)
   if index >= 0: result = t.data[index].key == key
   else: result = false
   
-proc IdTableGet(t: TIdTable, key: PIdObj): PObject = 
-  var index = IdTableRawGet(t, key.id)
+proc idTableGet(t: TIdTable, key: PIdObj): PObject = 
+  var index = idTableRawGet(t, key.id)
   if index >= 0: result = t.data[index].val
   else: result = nil
   
-proc IdTableGet(t: TIdTable, key: int): PObject = 
-  var index = IdTableRawGet(t, key)
+proc idTableGet(t: TIdTable, key: int): PObject = 
+  var index = idTableRawGet(t, key)
   if index >= 0: result = t.data[index].val
   else: result = nil
 
@@ -723,7 +724,7 @@ iterator pairs*(t: TIdTable): tuple[key: int, value: PObject] =
     if t.data[i].key != nil:
       yield (t.data[i].key.id, t.data[i].val)
   
-proc IdTableRawInsert(data: var TIdPairSeq, key: PIdObj, val: PObject) = 
+proc idTableRawInsert(data: var TIdPairSeq, key: PIdObj, val: PObject) = 
   var h: THash
   h = key.id and high(data)
   while data[h].key != nil: 
@@ -733,33 +734,30 @@ proc IdTableRawInsert(data: var TIdPairSeq, key: PIdObj, val: PObject) =
   data[h].key = key
   data[h].val = val
 
-proc IdTablePut(t: var TIdTable, key: PIdObj, val: PObject) = 
+proc idTablePut(t: var TIdTable, key: PIdObj, val: PObject) = 
   var 
     index: int
     n: TIdPairSeq
-  index = IdTableRawGet(t, key.id)
+  index = idTableRawGet(t, key.id)
   if index >= 0: 
     assert(t.data[index].key != nil)
     t.data[index].val = val
   else: 
     if mustRehash(len(t.data), t.counter): 
-      newSeq(n, len(t.data) * growthFactor)
+      newSeq(n, len(t.data) * GrowthFactor)
       for i in countup(0, high(t.data)): 
         if t.data[i].key != nil: 
-          IdTableRawInsert(n, t.data[i].key, t.data[i].val)
+          idTableRawInsert(n, t.data[i].key, t.data[i].val)
       assert(hasEmptySlot(n))
       swap(t.data, n)
-    IdTableRawInsert(t.data, key, val)
+    idTableRawInsert(t.data, key, val)
     inc(t.counter)
 
-iterator IdTablePairs*(t: TIdTable): tuple[key: PIdObj, val: PObject] =
+iterator idTablePairs*(t: TIdTable): tuple[key: PIdObj, val: PObject] =
   for i in 0 .. high(t.data):
     if not isNil(t.data[i].key): yield (t.data[i].key, t.data[i].val)
 
-proc writeIdNodeTable(t: TIdNodeTable) = 
-  nil
-
-proc IdNodeTableRawGet(t: TIdNodeTable, key: PIdObj): int = 
+proc idNodeTableRawGet(t: TIdNodeTable, key: PIdObj): int = 
   var h: THash
   h = key.id and high(t.data) # start with real hash value
   while t.data[h].key != nil:
@@ -768,17 +766,17 @@ proc IdNodeTableRawGet(t: TIdNodeTable, key: PIdObj): int =
     h = nextTry(h, high(t.data))
   result = - 1
 
-proc IdNodeTableGet(t: TIdNodeTable, key: PIdObj): PNode = 
+proc idNodeTableGet(t: TIdNodeTable, key: PIdObj): PNode = 
   var index: int
-  index = IdNodeTableRawGet(t, key)
+  index = idNodeTableRawGet(t, key)
   if index >= 0: result = t.data[index].val
   else: result = nil
 
-proc IdNodeTableGetLazy*(t: TIdNodeTable, key: PIdObj): PNode =
+proc idNodeTableGetLazy*(t: TIdNodeTable, key: PIdObj): PNode =
   if not isNil(t.data):
-    result = IdNodeTableGet(t, key)
+    result = idNodeTableGet(t, key)
   
-proc IdNodeTableRawInsert(data: var TIdNodePairSeq, key: PIdObj, val: PNode) = 
+proc idNodeTableRawInsert(data: var TIdNodePairSeq, key: PIdObj, val: PNode) = 
   var h: THash
   h = key.id and high(data)
   while data[h].key != nil: 
@@ -788,25 +786,25 @@ proc IdNodeTableRawInsert(data: var TIdNodePairSeq, key: PIdObj, val: PNode) =
   data[h].key = key
   data[h].val = val
 
-proc IdNodeTablePut(t: var TIdNodeTable, key: PIdObj, val: PNode) = 
-  var index = IdNodeTableRawGet(t, key)
+proc idNodeTablePut(t: var TIdNodeTable, key: PIdObj, val: PNode) = 
+  var index = idNodeTableRawGet(t, key)
   if index >= 0: 
     assert(t.data[index].key != nil)
     t.data[index].val = val
   else: 
     if mustRehash(len(t.data), t.counter): 
       var n: TIdNodePairSeq
-      newSeq(n, len(t.data) * growthFactor)
+      newSeq(n, len(t.data) * GrowthFactor)
       for i in countup(0, high(t.data)): 
         if t.data[i].key != nil: 
-          IdNodeTableRawInsert(n, t.data[i].key, t.data[i].val)
+          idNodeTableRawInsert(n, t.data[i].key, t.data[i].val)
       swap(t.data, n)
-    IdNodeTableRawInsert(t.data, key, val)
+    idNodeTableRawInsert(t.data, key, val)
     inc(t.counter)
 
-proc IdNodeTablePutLazy*(t: var TIdNodeTable, key: PIdObj, val: PNode) =
+proc idNodeTablePutLazy*(t: var TIdNodeTable, key: PIdObj, val: PNode) =
   if isNil(t.data): initIdNodeTable(t)
-  IdNodeTablePut(t, key, val)
+  idNodeTablePut(t, key, val)
 
 iterator pairs*(t: TIdNodeTable): tuple[key: PIdObj, val: PNode] =
   for i in 0 .. high(t.data):
@@ -814,24 +812,23 @@ iterator pairs*(t: TIdNodeTable): tuple[key: PIdObj, val: PNode] =
 
 proc initIITable(x: var TIITable) = 
   x.counter = 0
-  newSeq(x.data, startSize)
-  for i in countup(0, startSize - 1): x.data[i].key = InvalidKey
+  newSeq(x.data, StartSize)
+  for i in countup(0, StartSize - 1): x.data[i].key = InvalidKey
   
-proc IITableRawGet(t: TIITable, key: int): int = 
+proc iiTableRawGet(t: TIITable, key: int): int = 
   var h: THash
   h = key and high(t.data)    # start with real hash value
   while t.data[h].key != InvalidKey: 
-    if (t.data[h].key == key): 
-      return h
+    if t.data[h].key == key: return h
     h = nextTry(h, high(t.data))
-  result = - 1
+  result = -1
 
-proc IITableGet(t: TIITable, key: int): int = 
-  var index = IITableRawGet(t, key)
+proc iiTableGet(t: TIITable, key: int): int = 
+  var index = iiTableRawGet(t, key)
   if index >= 0: result = t.data[index].val
   else: result = InvalidKey
   
-proc IITableRawInsert(data: var TIIPairSeq, key, val: int) = 
+proc iiTableRawInsert(data: var TIIPairSeq, key, val: int) = 
   var h: THash
   h = key and high(data)
   while data[h].key != InvalidKey: 
@@ -841,19 +838,19 @@ proc IITableRawInsert(data: var TIIPairSeq, key, val: int) =
   data[h].key = key
   data[h].val = val
 
-proc IITablePut(t: var TIITable, key, val: int) = 
-  var index = IITableRawGet(t, key)
+proc iiTablePut(t: var TIITable, key, val: int) = 
+  var index = iiTableRawGet(t, key)
   if index >= 0: 
     assert(t.data[index].key != InvalidKey)
     t.data[index].val = val
   else: 
     if mustRehash(len(t.data), t.counter): 
       var n: TIIPairSeq
-      newSeq(n, len(t.data) * growthFactor)
+      newSeq(n, len(t.data) * GrowthFactor)
       for i in countup(0, high(n)): n[i].key = InvalidKey
       for i in countup(0, high(t.data)): 
         if t.data[i].key != InvalidKey: 
-          IITableRawInsert(n, t.data[i].key, t.data[i].val)
+          iiTableRawInsert(n, t.data[i].key, t.data[i].val)
       swap(t.data, n)
-    IITableRawInsert(t.data, key, val)
+    iiTableRawInsert(t.data, key, val)
     inc(t.counter)
diff --git a/compiler/babelcmd.nim b/compiler/babelcmd.nim
index b67a26040..7fa233732 100644
--- a/compiler/babelcmd.nim
+++ b/compiler/babelcmd.nim
@@ -13,7 +13,7 @@ import parseutils, strutils, strtabs, os, options, msgs, lists
 
 proc addPath*(path: string, info: TLineInfo) = 
   if not contains(options.searchPaths, path): 
-    lists.PrependStr(options.searchPaths, path)
+    lists.prependStr(options.searchPaths, path)
 
 proc versionSplitPos(s: string): int =
   result = s.len-2
@@ -45,9 +45,9 @@ proc `<.`(a, b: string): bool =
 
 proc addPackage(packages: PStringTable, p: string) =
   let x = versionSplitPos(p)
-  let name = p.subStr(0, x-1)
+  let name = p.substr(0, x-1)
   if x < p.len:
-    let version = p.subStr(x+1)
+    let version = p.substr(x+1)
     if packages[name] <. version:
       packages[name] = version
   else:
@@ -60,8 +60,8 @@ iterator chosen(packages: PStringTable): string =
 
 proc addBabelPath(p: string, info: TLineInfo) =
   if not contains(options.searchPaths, p):
-    if gVerbosity >= 1: Message(info, hintPath, p)
-    lists.PrependStr(options.lazyPaths, p)
+    if gVerbosity >= 1: message(info, hintPath, p)
+    lists.prependStr(options.lazyPaths, p)
 
 proc addPathWithNimFiles(p: string, info: TLineInfo) =
   proc hasNimFile(dir: string): bool =
diff --git a/compiler/bitsets.nim b/compiler/bitsets.nim
index dfb23b06d..740bdd5ef 100644
--- a/compiler/bitsets.nim
+++ b/compiler/bitsets.nim
@@ -18,53 +18,53 @@ type
 const 
   ElemSize* = sizeof(int8) * 8
 
-proc BitSetInit*(b: var TBitSet, length: int)
-proc BitSetUnion*(x: var TBitSet, y: TBitSet)
-proc BitSetDiff*(x: var TBitSet, y: TBitSet)
-proc BitSetSymDiff*(x: var TBitSet, y: TBitSet)
-proc BitSetIntersect*(x: var TBitSet, y: TBitSet)
-proc BitSetIncl*(x: var TBitSet, elem: BiggestInt)
-proc BitSetExcl*(x: var TBitSet, elem: BiggestInt)
-proc BitSetIn*(x: TBitSet, e: BiggestInt): bool
-proc BitSetEquals*(x, y: TBitSet): bool
-proc BitSetContains*(x, y: TBitSet): bool
+proc bitSetInit*(b: var TBitSet, length: int)
+proc bitSetUnion*(x: var TBitSet, y: TBitSet)
+proc bitSetDiff*(x: var TBitSet, y: TBitSet)
+proc bitSetSymDiff*(x: var TBitSet, y: TBitSet)
+proc bitSetIntersect*(x: var TBitSet, y: TBitSet)
+proc bitSetIncl*(x: var TBitSet, elem: BiggestInt)
+proc bitSetExcl*(x: var TBitSet, elem: BiggestInt)
+proc bitSetIn*(x: TBitSet, e: BiggestInt): bool
+proc bitSetEquals*(x, y: TBitSet): bool
+proc bitSetContains*(x, y: TBitSet): bool
 # implementation
 
-proc BitSetIn(x: TBitSet, e: BiggestInt): bool = 
+proc bitSetIn(x: TBitSet, e: BiggestInt): bool = 
   result = (x[int(e div ElemSize)] and toU8(int(1 shl (e mod ElemSize)))) !=
       toU8(0)
 
-proc BitSetIncl(x: var TBitSet, elem: BiggestInt) = 
+proc bitSetIncl(x: var TBitSet, elem: BiggestInt) = 
   assert(elem >= 0)
   x[int(elem div ElemSize)] = x[int(elem div ElemSize)] or
       toU8(int(1 shl (elem mod ElemSize)))
 
-proc BitSetExcl(x: var TBitSet, elem: BiggestInt) = 
+proc bitSetExcl(x: var TBitSet, elem: BiggestInt) = 
   x[int(elem div ElemSize)] = x[int(elem div ElemSize)] and
       not toU8(int(1 shl (elem mod ElemSize)))
 
-proc BitSetInit(b: var TBitSet, length: int) = 
+proc bitSetInit(b: var TBitSet, length: int) = 
   newSeq(b, length)
 
-proc BitSetUnion(x: var TBitSet, y: TBitSet) = 
+proc bitSetUnion(x: var TBitSet, y: TBitSet) = 
   for i in countup(0, high(x)): x[i] = x[i] or y[i]
   
-proc BitSetDiff(x: var TBitSet, y: TBitSet) = 
+proc bitSetDiff(x: var TBitSet, y: TBitSet) = 
   for i in countup(0, high(x)): x[i] = x[i] and not y[i]
   
-proc BitSetSymDiff(x: var TBitSet, y: TBitSet) = 
+proc bitSetSymDiff(x: var TBitSet, y: TBitSet) = 
   for i in countup(0, high(x)): x[i] = x[i] xor y[i]
   
-proc BitSetIntersect(x: var TBitSet, y: TBitSet) = 
+proc bitSetIntersect(x: var TBitSet, y: TBitSet) = 
   for i in countup(0, high(x)): x[i] = x[i] and y[i]
   
-proc BitSetEquals(x, y: TBitSet): bool = 
+proc bitSetEquals(x, y: TBitSet): bool = 
   for i in countup(0, high(x)): 
     if x[i] != y[i]: 
       return false
   result = true
 
-proc BitSetContains(x, y: TBitSet): bool = 
+proc bitSetContains(x, y: TBitSet): bool = 
   for i in countup(0, high(x)): 
     if (x[i] and not y[i]) != int8(0): 
       return false
diff --git a/compiler/c2nim/c2nim.nim b/compiler/c2nim/c2nim.nim
index df1e42f23..9b12b9e47 100644
--- a/compiler/c2nim/c2nim.nim
+++ b/compiler/c2nim/c2nim.nim
@@ -34,25 +34,36 @@ Options:
   --skipcomments         do not copy comments
   --ignoreRValueRefs     translate C++'s ``T&&`` to ``T`` instead ``of var T``
   --keepBodies           keep C++'s method bodies
+  --spliceHeader         parse and emit header before source file
   -v, --version          write c2nim's version
   -h, --help             show this help
 """
 
-proc main(infile, outfile: string, options: PParserOptions) =
-  var start = getTime()
-  var stream = LLStreamOpen(infile, fmRead)
+proc parse(infile: string, options: PParserOptions): PNode =
+  var stream = llStreamOpen(infile, fmRead)
   if stream == nil: rawMessage(errCannotOpenFile, infile)
   var p: TParser
   openParser(p, infile, stream, options)
-  var module = parseUnit(p)
+  result = parseUnit(p)
   closeParser(p)
-  renderModule(module, outfile)
+
+proc main(infile, outfile: string, options: PParserOptions, spliceHeader: bool) =
+  var start = getTime()
+  if spliceHeader and infile.splitFile.ext == ".c" and existsFile(infile.changeFileExt(".h")):
+    var header_module = parse(infile.changeFileExt(".h"), options)
+    var source_module = parse(infile, options)
+    for n in source_module:
+      addson(header_module, n)
+    renderModule(header_module, outfile)
+  else:
+    renderModule(parse(infile, options), outfile)
   rawMessage(hintSuccessX, [$gLinesCompiled, $(getTime() - start), 
                             formatSize(getTotalMem())])
 
 var
   infile = ""
   outfile = ""
+  spliceHeader = false
   parserOptions = newParserOptions()
 for kind, key, val in getopt():
   case kind
@@ -66,6 +77,7 @@ for kind, key, val in getopt():
       stdout.write(Version & "\n")
       quit(0)
     of "o", "out": outfile = val
+    of "spliceheader": spliceHeader = true
     else:
       if not parserOptions.setOption(key, val):
         stdout.writeln("[Error] unknown option: " & key)
@@ -77,4 +89,4 @@ else:
   if outfile.len == 0:
     outfile = changeFileExt(infile, "nim")
   infile = addFileExt(infile, "h")
-  main(infile, outfile, parserOptions)
+  main(infile, outfile, parserOptions, spliceHeader)
diff --git a/compiler/c2nim/clex.nim b/compiler/c2nim/clex.nim
index f949b97cb..3934eea63 100644
--- a/compiler/c2nim/clex.nim
+++ b/compiler/c2nim/clex.nim
@@ -103,7 +103,7 @@ type
     inDirective: bool
   
 proc getTok*(L: var TLexer, tok: var TToken)
-proc PrintTok*(tok: TToken)
+proc printTok*(tok: TToken)
 proc `$`*(tok: TToken): string
 # implementation
 
@@ -138,7 +138,7 @@ proc lexMessagePos(L: var TLexer, msg: TMsgKind, pos: int, arg = "") =
   var info = newLineInfo(L.fileIdx, L.linenumber, pos - L.lineStart)
   msgs.GlobalError(info, msg, arg)
 
-proc TokKindToStr*(k: TTokKind): string =
+proc tokKindToStr*(k: TTokKind): string =
   case k
   of pxEof: result = "[EOF]"
   of pxInvalid: result = "[invalid]"
@@ -211,9 +211,9 @@ proc `$`(tok: TToken): string =
   of pxSymbol, pxInvalid, pxStarComment, pxLineComment, pxStrLit: result = tok.s
   of pxIntLit, pxInt64Lit: result = $tok.iNumber
   of pxFloatLit: result = $tok.fNumber
-  else: result = TokKindToStr(tok.xkind)
+  else: result = tokKindToStr(tok.xkind)
   
-proc PrintTok(tok: TToken) = 
+proc printTok(tok: TToken) = 
   writeln(stdout, $tok)
   
 proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) = 
@@ -223,12 +223,12 @@ proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) =
   while true: 
     if buf[pos] in chars: 
       add(tok.s, buf[pos])
-      Inc(pos)
+      inc(pos)
     else: 
       break 
     if buf[pos] == '_': 
       add(tok.s, '_')
-      Inc(pos)
+      inc(pos)
   L.bufPos = pos
 
 proc isFloatLiteral(s: string): bool = 
@@ -239,7 +239,7 @@ proc isFloatLiteral(s: string): bool =
 proc getNumber2(L: var TLexer, tok: var TToken) = 
   var pos = L.bufpos + 2 # skip 0b
   tok.base = base2
-  var xi: biggestInt = 0
+  var xi: BiggestInt = 0
   var bits = 0
   while true: 
     case L.buf[pos]
@@ -264,7 +264,7 @@ proc getNumber2(L: var TLexer, tok: var TToken) =
 proc getNumber8(L: var TLexer, tok: var TToken) = 
   var pos = L.bufpos + 1 # skip 0
   tok.base = base8
-  var xi: biggestInt = 0
+  var xi: BiggestInt = 0
   var bits = 0
   while true: 
     case L.buf[pos]
@@ -289,7 +289,7 @@ proc getNumber8(L: var TLexer, tok: var TToken) =
 proc getNumber16(L: var TLexer, tok: var TToken) = 
   var pos = L.bufpos + 2          # skip 0x
   tok.base = base16
-  var xi: biggestInt = 0
+  var xi: BiggestInt = 0
   var bits = 0
   while true: 
     case L.buf[pos]
@@ -315,19 +315,34 @@ proc getNumber16(L: var TLexer, tok: var TToken) =
   else: tok.xkind = pxIntLit
   L.bufpos = pos
 
+proc getFloating(L: var TLexer, tok: var TToken) =
+  matchUnderscoreChars(L, tok, {'0'..'9'})
+  if L.buf[L.bufpos] in {'e', 'E'}:
+    add(tok.s, L.buf[L.bufpos])
+    inc(L.bufpos)
+    if L.buf[L.bufpos] in {'+', '-'}:
+      add(tok.s, L.buf[L.bufpos])
+      inc(L.bufpos)
+    matchUnderscoreChars(L, tok, {'0'..'9'})
+
 proc getNumber(L: var TLexer, tok: var TToken) = 
   tok.base = base10
-  matchUnderscoreChars(L, tok, {'0'..'9'})
-  if (L.buf[L.bufpos] == '.') and (L.buf[L.bufpos + 1] in {'0'..'9'}): 
-    add(tok.s, '.')
+  if L.buf[L.bufpos] == '.':
+    add(tok.s, "0.")
     inc(L.bufpos)
-    matchUnderscoreChars(L, tok, {'e', 'E', '+', '-', '0'..'9'})
+    getFloating(L, tok)
+  else:
+    matchUnderscoreChars(L, tok, {'0'..'9'})
+    if L.buf[L.bufpos] == '.':
+      add(tok.s, '.')
+      inc(L.bufpos)
+      getFloating(L, tok)
   try: 
     if isFloatLiteral(tok.s): 
       tok.fnumber = parseFloat(tok.s)
       tok.xkind = pxFloatLit
     else: 
-      tok.iNumber = ParseInt(tok.s)
+      tok.iNumber = parseInt(tok.s)
       if (tok.iNumber < low(int32)) or (tok.iNumber > high(int32)): 
         tok.xkind = pxInt64Lit
       else: 
@@ -339,10 +354,10 @@ proc getNumber(L: var TLexer, tok: var TToken) =
   # ignore type suffix:
   while L.buf[L.bufpos] in {'A'..'Z', 'a'..'z'}: inc(L.bufpos)
   
-proc HandleCRLF(L: var TLexer, pos: int): int = 
+proc handleCRLF(L: var TLexer, pos: int): int = 
   case L.buf[pos]
-  of CR: result = nimlexbase.HandleCR(L, pos)
-  of LF: result = nimlexbase.HandleLF(L, pos)
+  of CR: result = nimlexbase.handleCR(L, pos)
+  of LF: result = nimlexbase.handleLF(L, pos)
   else: result = pos
   
 proc escape(L: var TLexer, tok: var TToken, allowEmpty=false) = 
@@ -382,6 +397,23 @@ proc escape(L: var TLexer, tok: var TToken, allowEmpty=false) =
         xi = (xi shl 3) or (ord(L.buf[L.bufpos]) - ord('0'))
         inc(L.bufpos)
     add(tok.s, chr(xi))
+  of 'x':
+    var xi = 0
+    inc(L.bufpos)
+    while true: 
+      case L.buf[L.bufpos]
+      of '0'..'9': 
+        xi = `shl`(xi, 4) or (ord(L.buf[L.bufpos]) - ord('0'))
+        inc(L.bufpos)
+      of 'a'..'f': 
+        xi = `shl`(xi, 4) or (ord(L.buf[L.bufpos]) - ord('a') + 10)
+        inc(L.bufpos)
+      of 'A'..'F': 
+        xi = `shl`(xi, 4) or (ord(L.buf[L.bufpos]) - ord('A') + 10)
+        inc(L.bufpos)
+      else:
+        break 
+    add(tok.s, chr(xi))
   elif not allowEmpty:
     lexMessage(L, errInvalidCharacterConstant)
   
@@ -405,7 +437,7 @@ proc getString(L: var TLexer, tok: var TToken) =
   while true: 
     case buf[pos]
     of '\"': 
-      Inc(pos)
+      inc(pos)
       break
     of CR: 
       pos = nimlexbase.HandleCR(L, pos)
@@ -427,7 +459,7 @@ proc getString(L: var TLexer, tok: var TToken) =
       pos = L.bufpos
     else: 
       add(tok.s, buf[pos])
-      Inc(pos)
+      inc(pos)
   L.bufpos = pos
   tok.xkind = pxStrLit
 
@@ -438,7 +470,7 @@ proc getSymbol(L: var TLexer, tok: var TToken) =
     var c = buf[pos]
     if c notin SymChars: break
     add(tok.s, c)
-    Inc(pos)
+    inc(pos)
   L.bufpos = pos
   tok.xkind = pxSymbol
 
@@ -475,7 +507,7 @@ proc scanStarComment(L: var TLexer, tok: var TToken) =
   while true: 
     case buf[pos]
     of CR, LF: 
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
       add(tok.s, "\n#")
       # skip annoying stars as line prefix: (eg.
@@ -511,12 +543,12 @@ proc skip(L: var TLexer, tok: var TToken) =
       if L.inDirective:
         while buf[pos] in {' ', '\t'}: inc(pos)
         if buf[pos] in {CR, LF}:
-          pos = HandleCRLF(L, pos)
+          pos = handleCRLF(L, pos)
           buf = L.buf
     of ' ', Tabulator: 
-      Inc(pos)                # newline is special:
+      inc(pos)                # newline is special:
     of CR, LF: 
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
       if L.inDirective:
         tok.xkind = pxNewLine
@@ -559,13 +591,13 @@ proc getTok(L: var TLexer, tok: var TToken) =
     of 'b', 'B': getNumber2(L, tok)
     of '1'..'7': getNumber8(L, tok)
     else: getNumber(L, tok)
-  elif c in {'1'..'9'}: 
+  elif c in {'1'..'9'} or (c == '.' and L.buf[L.bufpos+1] in {'0'..'9'}): 
     getNumber(L, tok)
   else: 
     case c
     of ';': 
       tok.xkind = pxSemicolon
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '/': 
       if L.buf[L.bufpos + 1] == '/': 
         scanLineComment(L, tok)
@@ -580,9 +612,9 @@ proc getTok(L: var TLexer, tok: var TToken) =
         inc(L.bufpos)
     of ',': 
       tok.xkind = pxComma
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '(': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxParLe
     of '*': 
       inc(L.bufpos)
@@ -592,13 +624,13 @@ proc getTok(L: var TLexer, tok: var TToken) =
       else:
         tok.xkind = pxStar
     of ')': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxParRi
     of '[': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxBracketLe
     of ']': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxBracketRi
     of '.': 
       inc(L.bufpos)
@@ -608,10 +640,10 @@ proc getTok(L: var TLexer, tok: var TToken) =
       else: 
         tok.xkind = pxDot
     of '{': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxCurlyLe
     of '}': 
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxCurlyRi
     of '+': 
       inc(L.bufpos)
@@ -752,4 +784,4 @@ proc getTok(L: var TLexer, tok: var TToken) =
       tok.s = $c
       tok.xkind = pxInvalid
       lexMessage(L, errInvalidToken, c & " (\\" & $(ord(c)) & ')')
-      Inc(L.bufpos)
+      inc(L.bufpos)
diff --git a/compiler/c2nim/cparse.nim b/compiler/c2nim/cparse.nim
index 44be556db..ffab05788 100644
--- a/compiler/c2nim/cparse.nim
+++ b/compiler/c2nim/cparse.nim
@@ -61,6 +61,8 @@ type
   
   TReplaceTuple* = array[0..1, string]
 
+  ERetryParsing = object of ESynch
+
 proc newParserOptions*(): PParserOptions = 
   new(result)
   result.prefixes = @[]
@@ -93,16 +95,16 @@ proc setOption*(parserOptions: PParserOptions, key: string, val=""): bool =
   of "class": parserOptions.classes[val] = "true"
   else: result = false
 
-proc ParseUnit*(p: var TParser): PNode
+proc parseUnit*(p: var TParser): PNode
 proc openParser*(p: var TParser, filename: string, inputStream: PLLStream,
                  options = newParserOptions())
 proc closeParser*(p: var TParser)
 
 # implementation
 
-proc OpenParser(p: var TParser, filename: string, 
+proc openParser(p: var TParser, filename: string, 
                 inputStream: PLLStream, options = newParserOptions()) = 
-  OpenLexer(p.lex, filename, inputStream)
+  openLexer(p.lex, filename, inputStream)
   p.options = options
   p.backtrack = @[]
   new(p.tok)
@@ -111,7 +113,7 @@ proc parMessage(p: TParser, msg: TMsgKind, arg = "") =
   #assert false
   lexMessage(p.lex, msg, arg)
 
-proc CloseParser(p: var TParser) = CloseLexer(p.lex)
+proc closeParser(p: var TParser) = closeLexer(p.lex)
 proc saveContext(p: var TParser) = p.backtrack.add(p.tok)
 proc closeContext(p: var TParser) = discard p.backtrack.pop()
 proc backtrackContext(p: var TParser) = p.tok = p.backtrack.pop()
@@ -145,7 +147,7 @@ proc findMacro(p: TParser): int =
 
 proc rawEat(p: var TParser, xkind: TTokKind) = 
   if p.tok.xkind == xkind: rawGetTok(p)
-  else: parMessage(p, errTokenExpected, TokKindToStr(xkind))
+  else: parMessage(p, errTokenExpected, tokKindToStr(xkind))
 
 proc parseMacroArguments(p: var TParser): seq[seq[ref TToken]] = 
   result = @[]
@@ -228,7 +230,7 @@ proc skipComAux(p: var TParser, n: PNode) =
   getTok(p)
 
 proc skipCom(p: var TParser, n: PNode) = 
-  while p.tok.xkind in {pxLineComment, pxStarComment}: skipcomAux(p, n)
+  while p.tok.xkind in {pxLineComment, pxStarComment}: skipComAux(p, n)
 
 proc skipStarCom(p: var TParser, n: PNode) = 
   while p.tok.xkind == pxStarComment: skipComAux(p, n)
@@ -242,11 +244,11 @@ proc expectIdent(p: TParser) =
   
 proc eat(p: var TParser, xkind: TTokKind, n: PNode) = 
   if p.tok.xkind == xkind: getTok(p, n)
-  else: parMessage(p, errTokenExpected, TokKindToStr(xkind))
+  else: parMessage(p, errTokenExpected, tokKindToStr(xkind))
   
 proc eat(p: var TParser, xkind: TTokKind) = 
   if p.tok.xkind == xkind: getTok(p)
-  else: parMessage(p, errTokenExpected, TokKindToStr(xkind))
+  else: parMessage(p, errTokenExpected, tokKindToStr(xkind))
   
 proc eat(p: var TParser, tok: string, n: PNode) = 
   if p.tok.s == tok: getTok(p, n)
@@ -420,9 +422,9 @@ proc markTypeIdent(p: var TParser, typ: PNode) =
 # avoids to build a symbol table, which can't be done reliably anyway for our
 # purposes.
 
-proc expression(p: var TParser): PNode
-proc constantExpression(p: var TParser): PNode
-proc assignmentExpression(p: var TParser): PNode
+proc expression(p: var TParser, rbp: int = 0): PNode
+proc constantExpression(p: var TParser): PNode = expression(p, 40)
+proc assignmentExpression(p: var TParser): PNode = expression(p, 30)
 proc compoundStatement(p: var TParser): PNode
 proc statement(p: var TParser): PNode
 
@@ -605,7 +607,7 @@ proc addPragmas(father, pragmas: PNode) =
 proc addReturnType(params, rettyp: PNode) =
   if rettyp == nil: addSon(params, ast.emptyNode)
   elif rettyp.kind != nkNilLit: addSon(params, rettyp)
-  else: addson(params, ast.emptyNode)
+  else: addSon(params, ast.emptyNode)
 
 proc parseFormalParams(p: var TParser, params, pragmas: PNode)
 
@@ -651,6 +653,22 @@ proc parseTypeSuffix(p: var TParser, typ: PNode): PNode =
 proc typeDesc(p: var TParser): PNode = 
   result = pointer(p, typeAtom(p))
 
+proc abstractDeclarator(p: var TParser, a: PNode): PNode
+
+proc directAbstractDeclarator(p: var TParser, a: PNode): PNode =
+  if p.tok.xkind == pxParLe:
+    getTok(p, a)
+    if p.tok.xkind in {pxStar, pxAmp, pxAmpAmp}:
+      result = abstractDeclarator(p, a)
+      eat(p, pxParRi, result)
+  return parseTypeSuffix(p, a)
+
+proc abstractDeclarator(p: var TParser, a: PNode): PNode =
+  return directAbstractDeclarator(p, pointer(p, a))
+
+proc typeName(p: var TParser): PNode =
+  return abstractDeclarator(p, typeAtom(p))
+
 proc parseField(p: var TParser, kind: TNodeKind): PNode =
   if p.tok.xkind == pxParLe: 
     getTok(p, nil)
@@ -690,8 +708,8 @@ proc parseStructBody(p: var TParser, isUnion: bool,
 proc structPragmas(p: TParser, name: PNode, origName: string): PNode = 
   assert name.kind == nkIdent
   result = newNodeP(nkPragmaExpr, p)
-  addson(result, exportSym(p, name, origName))
-  var pragmas = newNodep(nkPragma, p)
+  addSon(result, exportSym(p, name, origName))
+  var pragmas = newNodeP(nkPragma, p)
   addSon(pragmas, newIdentNodeP("pure", p), newIdentNodeP("final", p))
   if p.options.header.len > 0:
     addSon(pragmas, newIdentStrLitPair("importc", origName, p),
@@ -700,8 +718,8 @@ proc structPragmas(p: TParser, name: PNode, origName: string): PNode =
 
 proc enumPragmas(p: TParser, name: PNode): PNode =
   result = newNodeP(nkPragmaExpr, p)
-  addson(result, name)
-  var pragmas = newNodep(nkPragma, p)
+  addSon(result, name)
+  var pragmas = newNodeP(nkPragma, p)
   var e = newNodeP(nkExprColonExpr, p)
   # HACK: sizeof(cint) should be constructed as AST
   addSon(e, newIdentNodeP("size", p), newIdentNodeP("sizeof(cint)", p))
@@ -716,18 +734,36 @@ proc parseStruct(p: var TParser, isUnion: bool): PNode =
   else: 
     addSon(result, newNodeP(nkRecList, p))
 
+proc declarator(p: var TParser, a: PNode, ident: ptr PNode): PNode
+
+proc directDeclarator(p: var TParser, a: PNode, ident: ptr PNode): PNode =
+  case p.tok.xkind
+  of pxSymbol:
+    ident[] = skipIdent(p)
+  of pxParLe:
+    getTok(p, a)
+    if p.tok.xkind in {pxStar, pxAmp, pxAmpAmp, pxSymbol}:
+      result = declarator(p, a, ident)
+      eat(p, pxParRi, result)
+  else:
+    nil
+  return parseTypeSuffix(p, a)
+
+proc declarator(p: var TParser, a: PNode, ident: ptr PNode): PNode =
+  return directDeclarator(p, pointer(p, a), ident)
+
+# parameter-declaration
+#   declaration-specifiers declarator
+#   declaration-specifiers asbtract-declarator(opt)
 proc parseParam(p: var TParser, params: PNode) = 
   var typ = typeDesc(p)
   # support for ``(void)`` parameter list: 
   if typ.kind == nkNilLit and p.tok.xkind == pxParRi: return
   var name: PNode
-  if p.tok.xkind == pxSymbol: 
-    name = skipIdent(p)
-  else:
-    # generate a name for the formal parameter:
+  typ = declarator(p, typ, addr name)
+  if name == nil:
     var idx = sonsLen(params)+1
     name = newIdentNodeP("a" & $idx, p)
-  typ = parseTypeSuffix(p, typ)
   var x = newNodeP(nkIdentDefs, p)
   addSon(x, name, typ)
   if p.tok.xkind == pxAsgn: 
@@ -1045,7 +1081,7 @@ proc declaration(p: var TParser): PNode =
     of pxSemicolon: 
       getTok(p)
       addSon(result, ast.emptyNode) # nobody
-      if p.scopeCounter == 0: DoImport(origName, pragmas, p)
+      if p.scopeCounter == 0: doImport(origName, pragmas, p)
     of pxCurlyLe:
       addSon(result, compoundStatement(p))
     else:
@@ -1134,224 +1170,27 @@ proc setBaseFlags(n: PNode, base: TNumericalBase) =
   of base8: incl(n.flags, nfBase8)
   of base16: incl(n.flags, nfBase16)
 
-proc unaryExpression(p: var TParser): PNode
-
-proc isDefinitelyAType(p: var TParser): bool = 
-  var starFound = false
-  var words = 0
-  while true:
-    case p.tok.xkind 
-    of pxSymbol:
-      if declKeyword(p, p.tok.s): return true
-      elif starFound: return false
-      else: inc(words)
-    of pxStar, pxAmp, pxAmpAmp:
-      starFound = true
-    of pxParRi: return words == 0 or words > 1 or starFound
-    else: return false
-    getTok(p, nil)
-
-proc castExpression(p: var TParser): PNode = 
-  if p.tok.xkind == pxParLe: 
-    saveContext(p)
-    result = newNodeP(nkCast, p)
-    getTok(p, result)
-    var t = isDefinitelyAType(p)
-    backtrackContext(p)
-    if t:
-      eat(p, pxParLe, result)
-      var a = typeDesc(p)
-      eat(p, pxParRi, result)
-      addSon(result, a)
-      addSon(result, castExpression(p))
-    else: 
-      # else it is just an expression in ():
-      result = newNodeP(nkPar, p)
-      eat(p, pxParLe, result)
-      addSon(result, expression(p))
-      if p.tok.xkind != pxParRi:  
-        # ugh, it is a cast, even though it does not look like one:
-        result.kind = nkCast
-        addSon(result, castExpression(p))
-      eat(p, pxParRi, result)
-      #result = unaryExpression(p)
-  else:
-    result = unaryExpression(p)
-  
-proc primaryExpression(p: var TParser): PNode = 
-  case p.tok.xkind
-  of pxSymbol: 
-    if p.tok.s == "NULL": 
-      result = newNodeP(nkNilLit, p)
-    else: 
-      result = mangledIdent(p.tok.s, p)
-    getTok(p, result)
-    result = optScope(p, result)
-  of pxIntLit: 
-    result = newIntNodeP(nkIntLit, p.tok.iNumber, p)
-    setBaseFlags(result, p.tok.base)
-    getTok(p, result)
-  of pxInt64Lit: 
-    result = newIntNodeP(nkInt64Lit, p.tok.iNumber, p)
-    setBaseFlags(result, p.tok.base)
-    getTok(p, result)
-  of pxFloatLit: 
-    result = newFloatNodeP(nkFloatLit, p.tok.fNumber, p)
-    setBaseFlags(result, p.tok.base)
-    getTok(p, result)
-  of pxStrLit: 
-    # Ansi C allows implicit string literal concatenations:
-    result = newStrNodeP(nkStrLit, p.tok.s, p)
-    getTok(p, result)
-    while p.tok.xkind == pxStrLit:
-      add(result.strVal, p.tok.s)
-      getTok(p, result)
-  of pxCharLit:
-    result = newIntNodeP(nkCharLit, ord(p.tok.s[0]), p)
-    getTok(p, result)
-  of pxParLe:
-    result = castExpression(p)
-  else:
-    result = ast.emptyNode
-
-proc multiplicativeExpression(p: var TParser): PNode = 
-  result = castExpression(p)
-  while true:
-    case p.tok.xkind
-    of pxStar:
-      var a = result
-      result = newNodeP(nkInfix, p)
-      addSon(result, newIdentNodeP("*", p), a)
-      getTok(p, result)
-      var b = castExpression(p)
-      addSon(result, b)
-    of pxSlash:
-      var a = result
-      result = newNodeP(nkInfix, p)
-      addSon(result, newIdentNodeP("div", p), a)
-      getTok(p, result)
-      var b = castExpression(p)
-      addSon(result, b)
-    of pxMod:
-      var a = result
-      result = newNodeP(nkInfix, p)
-      addSon(result, newIdentNodeP("mod", p), a)
-      getTok(p, result)
-      var b = castExpression(p)
-      addSon(result, b)
-    else: break 
-
-proc additiveExpression(p: var TParser): PNode = 
-  result = multiplicativeExpression(p)
-  while true:
-    case p.tok.xkind
-    of pxPlus:
-      var a = result
-      result = newNodeP(nkInfix, p)
-      addSon(result, newIdentNodeP("+", p), a)
-      getTok(p, result)
-      var b = multiplicativeExpression(p)
-      addSon(result, b)
-    of pxMinus:
-      var a = result
-      result = newNodeP(nkInfix, p)
-      addSon(result, newIdentNodeP("-", p), a)
-      getTok(p, result)
-      var b = multiplicativeExpression(p)
-      addSon(result, b)
-    else: break 
-  
-proc incdec(p: var TParser, opr: string): PNode = 
-  result = newNodeP(nkCall, p)
-  addSon(result, newIdentNodeP(opr, p))
-  gettok(p, result)
-  addSon(result, unaryExpression(p))
-
-proc unaryOp(p: var TParser, kind: TNodeKind): PNode = 
-  result = newNodeP(kind, p)
-  getTok(p, result)
-  addSon(result, castExpression(p))
-
-proc prefixCall(p: var TParser, opr: string): PNode = 
-  result = newNodeP(nkPrefix, p)
-  addSon(result, newIdentNodeP(opr, p))
-  gettok(p, result)
-  addSon(result, castExpression(p))
-
-proc postfixExpression(p: var TParser): PNode = 
-  result = primaryExpression(p)
-  while true:
-    case p.tok.xkind
-    of pxBracketLe:
-      var a = result
-      result = newNodeP(nkBracketExpr, p)
-      addSon(result, a)
-      getTok(p, result)
-      var b = expression(p)
-      addSon(result, b)
-      eat(p, pxBracketRi, result)
-    of pxParLe:
-      var a = result
-      result = newNodeP(nkCall, p)
-      addSon(result, a)
-      getTok(p, result)
-      if p.tok.xkind != pxParRi:
-        a = assignmentExpression(p)
-        addSon(result, a)
-        while p.tok.xkind == pxComma:
-          getTok(p, a)
-          a = assignmentExpression(p)
-          addSon(result, a)
-      eat(p, pxParRi, result)
-    of pxDot, pxArrow:
-      var a = result
-      result = newNodeP(nkDotExpr, p)
-      addSon(result, a)
-      getTok(p, result)
-      addSon(result, skipIdent(p))
-    of pxPlusPlus:
-      var a = result
-      result = newNodeP(nkCall, p)
-      addSon(result, newIdentNodeP("inc", p))
-      gettok(p, result)
-      addSon(result, a)
-    of pxMinusMinus:
-      var a = result
-      result = newNodeP(nkCall, p)
-      addSon(result, newIdentNodeP("dec", p))
-      gettok(p, result)
-      addSon(result, a)
-    of pxLt:
-      if isTemplateAngleBracket(p):
-        result = optAngle(p, result)
-      else: break
-    else: break
-
-proc unaryExpression(p: var TParser): PNode =
-  case p.tok.xkind
-  of pxPlusPlus: result = incdec(p, "inc")
-  of pxMinusMinus: result = incdec(p, "dec")
-  of pxAmp: result = unaryOp(p, nkAddr)
-  of pxStar: result = unaryOp(p, nkBracketExpr)
-  of pxPlus: result = prefixCall(p, "+")
-  of pxMinus: result = prefixCall(p, "-")
-  of pxTilde: result = prefixCall(p, "not")
-  of pxNot: result = prefixCall(p, "not")
+proc startExpression(p : var TParser, tok : TToken) : PNode =
+  #echo "nud ", $tok
+  case tok.xkind:
   of pxSymbol:
-    if p.tok.s == "sizeof": 
+    if tok.s == "NULL":
+      result = newNodeP(nkNilLit, p)
+    elif tok.s == "sizeof":
       result = newNodeP(nkCall, p)
       addSon(result, newIdentNodeP("sizeof", p))
-      getTok(p, result)
-      if p.tok.xkind == pxParLe:
-        getTok(p, result)
-        addSon(result, typeDesc(p))
-        eat(p, pxParRi, result)
-      else:
-        addSon(result, unaryExpression(p))
-    elif p.tok.s == "new" or p.tok.s == "delete" and pfCpp in p.options.flags:
-      var opr = p.tok.s
+      saveContext(p)
+      try:
+        addSon(result, expression(p, 139))
+        closeContext(p)
+      except ERetryParsing:
+        backtrackContext(p)
+        eat(p, pxParLe)
+        addSon(result, typeName(p))
+        eat(p, pxParRi)
+    elif (tok.s == "new" or tok.s == "delete") and pfCpp in p.options.flags:
+      var opr = tok.s
       result = newNodeP(nkCall, p)
-      getTok(p, result)
       if p.tok.xkind == pxBracketLe:
         getTok(p)
         eat(p, pxBracketRi)
@@ -1362,148 +1201,269 @@ proc unaryExpression(p: var TParser): PNode =
         addSon(result, typeDesc(p))
         eat(p, pxParRi, result)
       else:
-        addSon(result, unaryExpression(p))
+        addSon(result, expression(p, 139))
     else:
-      result = postfixExpression(p)
-  else: result = postfixExpression(p)
-
-proc expression(p: var TParser): PNode = 
-  # we cannot support C's ``,`` operator
-  result = assignmentExpression(p)
-  if p.tok.xkind == pxComma:
-    getTok(p, result)
-    parMessage(p, errOperatorExpected, ",")
-    
-proc conditionalExpression(p: var TParser): PNode
-
-proc constantExpression(p: var TParser): PNode = 
-  result = conditionalExpression(p)
-
-proc lvalue(p: var TParser): PNode = 
-  result = unaryExpression(p)
-
-proc asgnExpr(p: var TParser, opr: string, a: PNode): PNode = 
-  closeContext(p)
-  getTok(p, a)
-  var b = assignmentExpression(p)
-  result = newNodeP(nkAsgn, p)
-  addSon(result, a, newBinary(opr, copyTree(a), b, p))
-  
-proc incdec(p: var TParser, opr: string, a: PNode): PNode =
-  closeContext(p)
-  getTok(p, a)
-  var b = assignmentExpression(p)
-  result = newNodeP(nkCall, p)
-  addSon(result, newIdentNodeP(getIdent(opr), p), a, b)
-  
-proc assignmentExpression(p: var TParser): PNode = 
-  saveContext(p)
-  var a = lvalue(p)
-  case p.tok.xkind 
-  of pxAsgn:
-    closeContext(p)
-    getTok(p, a)
-    var b = assignmentExpression(p)
+      result = mangledIdent(tok.s, p)
+      result = optScope(p, result)
+      result = optAngle(p, result)
+  of pxIntLit: 
+    result = newIntNodeP(nkIntLit, tok.iNumber, p)
+    setBaseFlags(result, tok.base)
+  of pxInt64Lit: 
+    result = newIntNodeP(nkInt64Lit, tok.iNumber, p)
+    setBaseFlags(result, tok.base)
+  of pxFloatLit: 
+    result = newFloatNodeP(nkFloatLit, tok.fNumber, p)
+    setBaseFlags(result, tok.base)
+  of pxStrLit: 
+    result = newStrNodeP(nkStrLit, tok.s, p)
+    while p.tok.xkind == pxStrLit:
+      add(result.strVal, p.tok.s)
+      getTok(p, result)
+  of pxCharLit:
+    result = newIntNodeP(nkCharLit, ord(tok.s[0]), p)
+  of pxParLe:
+    try:
+      saveContext(p)
+      result = newNodeP(nkPar, p)
+      addSon(result, expression(p, 0))
+      if p.tok.xkind != pxParRi:
+        raise newException(ERetryParsing, "expected a ')'")
+      getTok(p, result)
+      if p.tok.xkind in {pxSymbol, pxIntLit, pxFloatLit, pxStrLit, pxCharLit}:
+        raise newException(ERetryParsing, "expected a non literal token")
+      closeContext(p)
+    except ERetryParsing:
+      backtrackContext(p)
+      result = newNodeP(nkCast, p)
+      addSon(result, typeName(p))
+      eat(p, pxParRi, result)
+      addSon(result, expression(p, 139))
+  of pxPlusPlus:
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP("inc", p))
+    addSon(result, expression(p, 139))
+  of pxMinusMinus:
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP("dec", p))
+    addSon(result, expression(p, 139))
+  of pxAmp:
+    result = newNodeP(nkAddr, p)
+    addSon(result, expression(p, 139))
+  of pxStar:
+    result = newNodeP(nkBracketExpr, p)
+    addSon(result, expression(p, 139))
+  of pxPlus:
+    result = newNodeP(nkPrefix, p)
+    addSon(result, newIdentNodeP("+", p))
+    addSon(result, expression(p, 139))
+  of pxMinus:
+    result = newNodeP(nkPrefix, p)
+    addSon(result, newIdentNodeP("-", p))
+    addSon(result, expression(p, 139))
+  of pxTilde:
+    result = newNodeP(nkPrefix, p)
+    addSon(result, newIdentNodeP("not", p))
+    addSon(result, expression(p, 139))
+  of pxNot:
+    result = newNodeP(nkPrefix, p)
+    addSon(result, newIdentNodeP("not", p))
+    addSon(result, expression(p, 139))
+  else:
+    # probably from a failed sub expression attempt, try a type cast
+    raise newException(ERetryParsing, "did not expect " & $tok)
+
+proc leftBindingPower(p : var TParser, tok : ref TToken) : int =
+  #echo "lbp ", $tok[]
+  case tok.xkind:
+  of pxComma:
+    return 10
+    # throw == 20
+  of pxAsgn, pxPlusAsgn, pxMinusAsgn, pxStarAsgn, pxSlashAsgn, pxModAsgn, pxShlAsgn, pxShrAsgn, pxAmpAsgn, pxHatAsgn, pxBarAsgn:
+    return 30
+  of pxConditional:
+    return 40
+  of pxBarBar:
+    return 50
+  of pxAmpAmp:
+    return 60
+  of pxBar:
+    return 70
+  of pxHat:
+    return 80
+  of pxAmp:
+    return 90
+  of pxEquals, pxNeq:
+    return 100
+  of pxLt, pxLe, pxGt, pxGe:
+    return 110
+  of pxShl, pxShr:
+    return 120
+  of pxPlus, pxMinus:
+    return 130
+  of pxStar, pxSlash, pxMod:
+    return 140
+    # .* ->* == 150
+  of pxPlusPlus, pxMinusMinus, pxParLe, pxDot, pxArrow, pxBracketLe:
+    return 160
+    # :: == 170
+  else:
+    return 0
+
+proc buildStmtList(a: PNode): PNode
+
+proc leftExpression(p : var TParser, tok : TToken, left : PNode) : PNode =
+  #echo "led ", $tok
+  case tok.xkind:
+  of pxComma: # 10
+    # not supported as an expression, turns into a statement list
+    result = buildStmtList(left)
+    addSon(result, expression(p, 0))
+    # throw == 20
+  of pxAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    addSon(result, left, expression(p, 29))
+  of pxPlusAsgn: # 30
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP(getIdent("inc"), p), left, expression(p, 29))
+  of pxMinusAsgn: # 30
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP(getIdent("dec"), p), left, expression(p, 29))
+  of pxStarAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("*", copyTree(left), right, p))
+  of pxSlashAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("/", copyTree(left), right, p))
+  of pxModAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("mod", copyTree(left), right, p))
+  of pxShlAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("shl", copyTree(left), right, p))
+  of pxShrAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("shr", copyTree(left), right, p))
+  of pxAmpAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("and", copyTree(left), right, p))
+  of pxHatAsgn: # 30
+    result = newNodeP(nkAsgn, p)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("xor", copyTree(left), right, p))
+  of pxBarAsgn: # 30
     result = newNodeP(nkAsgn, p)
-    addSon(result, a, b)
-  of pxPlusAsgn: result = incDec(p, "inc", a)    
-  of pxMinusAsgn: result = incDec(p, "dec", a)
-  of pxStarAsgn: result = asgnExpr(p, "*", a)
-  of pxSlashAsgn: result = asgnExpr(p, "/", a)
-  of pxModAsgn: result = asgnExpr(p, "mod", a)
-  of pxShlAsgn: result = asgnExpr(p, "shl", a)
-  of pxShrAsgn: result = asgnExpr(p, "shr", a)
-  of pxAmpAsgn: result = asgnExpr(p, "and", a)
-  of pxHatAsgn: result = asgnExpr(p, "xor", a)
-  of pxBarAsgn: result = asgnExpr(p, "or", a)
+    var right = expression(p, 29)
+    addSon(result, left, newBinary("or", copyTree(left), right, p))
+  of pxConditional: # 40
+    var a = expression(p, 0)
+    eat(p, pxColon, a)
+    var b = expression(p, 39)
+    result = newNodeP(nkIfExpr, p)
+    var branch = newNodeP(nkElifExpr, p)
+    addSon(branch, left, a)
+    addSon(result, branch)
+    branch = newNodeP(nkElseExpr, p)
+    addSon(branch, b)
+    addSon(result, branch)
+  of pxBarBar: # 50
+    result = newBinary("or", left, expression(p, 50), p)
+  of pxAmpAmp: # 60
+    result = newBinary("and", left, expression(p, 60), p)
+  of pxBar: # 70
+    result = newBinary("or", left, expression(p, 70), p)
+  of pxHat: # 80
+    result = newBinary("^", left, expression(p, 80), p)
+  of pxAmp: # 90
+    result = newBinary("and", left, expression(p, 90), p)
+  of pxEquals: # 100
+    result = newBinary("==", left, expression(p, 100), p)
+  of pxNeq: # 100
+    result = newBinary("!=", left, expression(p, 100), p)
+  of pxLt: # 110
+    result = newBinary("<", left, expression(p, 110), p)
+  of pxLe: # 110
+    result = newBinary("<=", left, expression(p, 110), p)
+  of pxGt: # 110
+    result = newBinary(">", left, expression(p, 110), p)
+  of pxGe: # 110
+    result = newBinary(">=", left, expression(p, 110), p)
+  of pxShl: # 120
+    result = newBinary("shl", left, expression(p, 120), p)
+  of pxShr: # 120
+    result = newBinary("shr", left, expression(p, 120), p)
+  of pxPlus: # 130
+    result = newNodeP(nkInfix, p)
+    addSon(result, newIdentNodeP("+", p), left)
+    addSon(result, expression(p, 130))
+  of pxMinus: # 130
+    result = newNodeP(nkInfix, p)
+    addSon(result, newIdentNodeP("+", p), left)
+    addSon(result, expression(p, 130))
+  of pxStar: # 140
+    result = newNodeP(nkInfix, p)
+    addSon(result, newIdentNodeP("*", p), left)
+    addSon(result, expression(p, 140))
+  of pxSlash: # 140
+    result = newNodeP(nkInfix, p)
+    addSon(result, newIdentNodeP("div", p), left)
+    addSon(result, expression(p, 140))
+  of pxMod: # 140
+    result = newNodeP(nkInfix, p)
+    addSon(result, newIdentNodeP("mod", p), left)
+    addSon(result, expression(p, 140))
+    # .* ->* == 150
+  of pxPlusPlus: # 160
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP("inc", p), left)
+  of pxMinusMinus: # 160
+    result = newNodeP(nkCall, p)
+    addSon(result, newIdentNodeP("dec", p), left)
+  of pxParLe: # 160
+    result = newNodeP(nkCall, p)
+    addSon(result, left)
+    while p.tok.xkind != pxParRi:
+      var a = expression(p, 29)
+      addSon(result, a)
+      while p.tok.xkind == pxComma:
+        getTok(p, a)
+        a = expression(p, 29)
+        addSon(result, a)
+    eat(p, pxParRi, result)
+  of pxDot: # 160
+    result = newNodeP(nkDotExpr, p)
+    addSon(result, left)
+    addSon(result, skipIdent(p))
+  of pxArrow: # 160
+    result = newNodeP(nkDotExpr, p)
+    addSon(result, left)
+    addSon(result, skipIdent(p))
+  of pxBracketLe: # 160
+    result = newNodeP(nkBracketExpr, p)
+    addSon(result, left, expression(p))
+    eat(p, pxBracketRi, result)
+    # :: == 170
   else:
-    backtrackContext(p)
-    result = conditionalExpression(p)
-  
-proc shiftExpression(p: var TParser): PNode = 
-  result = additiveExpression(p)
-  while p.tok.xkind in {pxShl, pxShr}:
-    var op = if p.tok.xkind == pxShl: "shl" else: "shr"
-    getTok(p, result)
-    var a = result 
-    var b = additiveExpression(p)
-    result = newBinary(op, a, b, p)
-
-proc relationalExpression(p: var TParser): PNode = 
-  result = shiftExpression(p)
-  # Nimrod uses ``<`` and ``<=``, etc. too:
-  while p.tok.xkind in {pxLt, pxLe, pxGt, pxGe}:
-    var op = TokKindToStr(p.tok.xkind)
-    getTok(p, result)
-    var a = result 
-    var b = shiftExpression(p)
-    result = newBinary(op, a, b, p)
-
-proc equalityExpression(p: var TParser): PNode =
-  result = relationalExpression(p)
-  # Nimrod uses ``==`` and ``!=`` too:
-  while p.tok.xkind in {pxEquals, pxNeq}:
-    var op = TokKindToStr(p.tok.xkind)
-    getTok(p, result)
-    var a = result 
-    var b = relationalExpression(p)
-    result = newBinary(op, a, b, p)
+    result = left
 
-proc andExpression(p: var TParser): PNode =
-  result = equalityExpression(p)
-  while p.tok.xkind == pxAmp:
-    getTok(p, result)
-    var a = result 
-    var b = equalityExpression(p)
-    result = newBinary("and", a, b, p)
+proc expression*(p : var TParser, rbp : int = 0) : PNode =
+  var tok : TToken
 
-proc exclusiveOrExpression(p: var TParser): PNode = 
-  result = andExpression(p)
-  while p.tok.xkind == pxHat:
-    getTok(p, result)
-    var a = result 
-    var b = andExpression(p)
-    result = newBinary("^", a, b, p)
+  tok = p.tok[]
+  getTok(p, result)
 
-proc inclusiveOrExpression(p: var TParser): PNode = 
-  result = exclusiveOrExpression(p)
-  while p.tok.xkind == pxBar:
-    getTok(p, result)
-    var a = result 
-    var b = exclusiveOrExpression(p)
-    result = newBinary("or", a, b, p)
-  
-proc logicalAndExpression(p: var TParser): PNode = 
-  result = inclusiveOrExpression(p)
-  while p.tok.xkind == pxAmpAmp:
-    getTok(p, result)
-    var a = result
-    var b = inclusiveOrExpression(p)
-    result = newBinary("and", a, b, p)
+  result = startExpression(p, tok)
 
-proc logicalOrExpression(p: var TParser): PNode = 
-  result = logicalAndExpression(p)
-  while p.tok.xkind == pxBarBar:
+  while rbp < leftBindingPower(p, p.tok):
+    tok = p.tok[]
     getTok(p, result)
-    var a = result
-    var b = logicalAndExpression(p)
-    result = newBinary("or", a, b, p)
-  
-proc conditionalExpression(p: var TParser): PNode =  
-  result = logicalOrExpression(p)
-  if p.tok.xkind == pxConditional: 
-    getTok(p, result) # skip '?'
-    var a = result
-    var b = expression(p)
-    eat(p, pxColon, b)
-    var c = conditionalExpression(p)
-    result = newNodeP(nkIfExpr, p)
-    var branch = newNodeP(nkElifExpr, p)
-    addSon(branch, a, b)
-    addSon(result, branch)
-    branch = newNodeP(nkElseExpr, p)
-    addSon(branch, c)
-    addSon(result, branch)
+    result = leftExpression(p, tok, result)
     
 # Statements
 
@@ -1549,12 +1509,12 @@ proc parseIf(p: var TParser): PNode =
   while true: 
     getTok(p) # skip ``if``
     var branch = newNodeP(nkElifBranch, p)
-    skipCom(p, branch)
     eat(p, pxParLe, branch)
     addSon(branch, expression(p))
     eat(p, pxParRi, branch)
     addSon(branch, nestedStatement(p))
     addSon(result, branch)
+    skipCom(p, branch)
     if p.tok.s == "else": 
       getTok(p, result)
       if p.tok.s != "if": 
@@ -1574,19 +1534,51 @@ proc parseWhile(p: var TParser): PNode =
   eat(p, pxParRi, result)
   addSon(result, nestedStatement(p))
 
+proc embedStmts(sl, a: PNode)
+
 proc parseDoWhile(p: var TParser): PNode =  
-  # we only support ``do stmt while (0)`` as an idiom for 
-  # ``block: stmt``
-  result = newNodeP(nkBlockStmt, p)
-  getTok(p, result) # skip "do"
-  addSon(result, ast.emptyNode, nestedStatement(p))
+  # parsing
+  result = newNodeP(nkWhileStmt, p)
+  getTok(p, result)
+  var stm = nestedStatement(p)
   eat(p, "while", result)
   eat(p, pxParLe, result)
-  if p.tok.xkind == pxIntLit and p.tok.iNumber == 0: getTok(p, result)
-  else: parMessage(p, errTokenExpected, "0")
+  var exp = expression(p)
   eat(p, pxParRi, result)
   if p.tok.xkind == pxSemicolon: getTok(p)
 
+  # while true:
+  #   stmt
+  #   if not expr:
+  #     break
+  addSon(result, newIdentNodeP("true", p))
+
+  stm = buildStmtList(stm)
+
+  # get the last exp if it is a stmtlist
+  var cleanedExp = exp
+  if exp.kind == nkStmtList:
+    cleanedExp = exp.sons[exp.len-1]
+    exp.sons = exp.sons[0..exp.len-2]
+    embedStmts(stm, exp)
+
+  var notExp = newNodeP(nkPrefix, p)
+  addSon(notExp, newIdentNodeP("not", p))
+  addSon(notExp, cleanedExp)
+
+  var brkStm = newNodeP(nkBreakStmt, p)
+  addSon(brkStm, ast.emptyNode)
+
+  var ifStm = newNodeP(nkIfStmt, p)
+  var ifBranch = newNodeP(nkElifBranch, p)
+  addSon(ifBranch, notExp)
+  addSon(ifBranch, brkStm)
+  addSon(ifStm, ifBranch)
+
+  embedStmts(stm, ifStm)
+
+  addSon(result, stm)
+
 proc declarationOrStatement(p: var TParser): PNode = 
   if p.tok.xkind != pxSymbol:
     result = expressionStatement(p)
@@ -1666,7 +1658,7 @@ proc parseFor(p: var TParser, result: PNode) =
   eat(p, pxParLe, result)
   var initStmt = declarationOrStatement(p)
   if initStmt.kind != nkEmpty:
-    addSon(result, initStmt)
+    embedStmts(result, initStmt)
   var w = newNodeP(nkWhileStmt, p)
   var condition = expressionStatement(p)
   if condition.kind == nkEmpty: condition = newIdentNodeP("true", p)
@@ -1676,7 +1668,7 @@ proc parseFor(p: var TParser, result: PNode) =
   var loopBody = nestedStatement(p)
   if step.kind != nkEmpty:
     loopBody = buildStmtList(loopBody)
-    addSon(loopBody, step)
+    embedStmts(loopBody, step)
   addSon(w, loopBody)
   addSon(result, w)
   
@@ -1818,7 +1810,7 @@ proc parseConstructor(p: var TParser, pragmas: PNode,
   else:
     parMessage(p, errTokenExpected, ";")
   if result.sons[bodyPos].kind == nkEmpty:
-    DoImport((if isDestructor: "~" else: "") & origName, pragmas, p)
+    doImport((if isDestructor: "~" else: "") & origName, pragmas, p)
   elif isDestructor:
     addSon(pragmas, newIdentNodeP("destructor", p))
   if sonsLen(result.sons[pragmasPos]) == 0:
@@ -1862,8 +1854,8 @@ proc parseMethod(p: var TParser, origName: string, rettyp, pragmas: PNode,
   else:
     parMessage(p, errTokenExpected, ";")
   if result.sons[bodyPos].kind == nkEmpty:
-    if isStatic: DoImport(origName, pragmas, p)
-    else: DoImportCpp(origName, pragmas, p)
+    if isStatic: doImport(origName, pragmas, p)
+    else: doImportCpp(origName, pragmas, p)
   if sonsLen(result.sons[pragmasPos]) == 0:
     result.sons[pragmasPos] = ast.emptyNode
 
@@ -1880,7 +1872,7 @@ proc parseOperator(p: var TParser, origName: var string): bool =
   case p.tok.xkind
   of pxAmp..pxArrow:
     # ordinary operator symbol:
-    origName.add(TokKindToStr(p.tok.xkind))
+    origName.add(tokKindToStr(p.tok.xkind))
     getTok(p)
   of pxSymbol:
     if p.tok.s == "new" or p.tok.s == "delete":
@@ -2048,6 +2040,10 @@ proc parseStandaloneClass(p: var TParser, isStruct: bool): PNode =
     result = declaration(p)
   p.currentClass = oldClass
 
+proc unwrap(a: PNode): PNode =
+  if a.kind == nkPar:
+    return a.sons[0]
+  return a
 
 include cpp
 
@@ -2082,16 +2078,10 @@ proc statement(p: var TParser): PNode =
     of "return":
       result = newNodeP(nkReturnStmt, p)
       getTok(p)
-      # special case for ``return (expr)`` because I hate the redundant
-      # parenthesis ;-)
-      if p.tok.xkind == pxParLe:
-        getTok(p, result)
-        addSon(result, expression(p))
-        eat(p, pxParRi, result)
-      elif p.tok.xkind != pxSemicolon:
-        addSon(result, expression(p))
-      else:
+      if p.tok.xkind == pxSemicolon:
         addSon(result, ast.emptyNode)
+      else:
+        addSon(result, unwrap(expression(p)))
       eat(p, pxSemicolon)
     of "enum": result = enumSpecifier(p)
     of "typedef": result = parseTypeDef(p)
@@ -2140,9 +2130,12 @@ proc statement(p: var TParser): PNode =
   assert result != nil
 
 proc parseUnit(p: var TParser): PNode =
-  result = newNodeP(nkStmtList, p)
-  getTok(p) # read first token
-  while p.tok.xkind != pxEof:
-    var s = statement(p)
-    if s.kind != nkEmpty: embedStmts(result, s)
+  try:
+    result = newNodeP(nkStmtList, p)
+    getTok(p) # read first token
+    while p.tok.xkind != pxEof:
+      var s = statement(p)
+      if s.kind != nkEmpty: embedStmts(result, s)
+  except ERetryParsing:
+    parMessage(p, errGenerated, "Uncaught parsing exception raised")
 
diff --git a/compiler/c2nim/cpp.nim b/compiler/c2nim/cpp.nim
index 2ce64e59b..1707b75db 100644
--- a/compiler/c2nim/cpp.nim
+++ b/compiler/c2nim/cpp.nim
@@ -226,7 +226,7 @@ proc skipUntilElifElseEndif(p: var TParser): TEndifMarker =
   
 proc parseIfdef(p: var TParser): PNode = 
   getTok(p) # skip #ifdef
-  ExpectIdent(p)
+  expectIdent(p)
   case p.tok.s
   of "__cplusplus":
     skipUntilEndif(p)
@@ -245,7 +245,7 @@ proc parseIfdef(p: var TParser): PNode =
 proc parseIfndef(p: var TParser): PNode = 
   result = ast.emptyNode
   getTok(p) # skip #ifndef
-  ExpectIdent(p)
+  expectIdent(p)
   if p.tok.s == c2nimSymbol: 
     skipLine(p)
     case skipUntilElifElseEndif(p)
@@ -282,11 +282,11 @@ proc parseIfDir(p: var TParser): PNode =
 proc parsePegLit(p: var TParser): TPeg =
   var col = getColumn(p.lex) + 2
   getTok(p)
-  if p.tok.xkind != pxStrLit: ExpectIdent(p)
+  if p.tok.xkind != pxStrLit: expectIdent(p)
   try:
     result = parsePeg(
       pattern = if p.tok.xkind == pxStrLit: p.tok.s else: escapePeg(p.tok.s), 
-      filename = p.lex.fileIdx.ToFilename, 
+      filename = p.lex.fileIdx.toFilename, 
       line = p.lex.linenumber, 
       col = col)
     getTok(p)
@@ -295,7 +295,7 @@ proc parsePegLit(p: var TParser): TPeg =
 
 proc parseMangleDir(p: var TParser) = 
   var pattern = parsePegLit(p)
-  if p.tok.xkind != pxStrLit: ExpectIdent(p)
+  if p.tok.xkind != pxStrLit: expectIdent(p)
   p.options.mangleRules.add((pattern, p.tok.s))
   getTok(p)
   eatNewLine(p, nil)
@@ -326,7 +326,7 @@ proc parseDir(p: var TParser): PNode =
   of "dynlib", "header", "prefix", "suffix", "class": 
     var key = p.tok.s
     getTok(p)
-    if p.tok.xkind != pxStrLit: ExpectIdent(p)
+    if p.tok.xkind != pxStrLit: expectIdent(p)
     discard setOption(p.options, key, p.tok.s)
     getTok(p)
     eatNewLine(p, nil)
diff --git a/compiler/c2nim/tests/vincent.c b/compiler/c2nim/tests/vincent.c
new file mode 100644
index 000000000..24c6d6425
--- /dev/null
+++ b/compiler/c2nim/tests/vincent.c
@@ -0,0 +1,33 @@
+#include <stdlib.h>
+#include <stdio.h>
+
+int rand(void);
+
+int id2(void) {
+    return (int *)1;
+}
+
+int id(void (*f)(void)) {
+    f();
+    ((void (*)(int))f)(10);
+    return 10;
+    return (20+1);
+    return (int *)id;
+}
+
+int main() {
+    float f = .2,
+          g = 2.,
+          h = 1.0+rand(),
+          i = 1.0e+3;
+    int j, a;
+    for(j = 0, a = 10; j < 0; j++, a++) ;
+    do {
+        printf("howdy");
+    } while(--i, 0);
+    if(1)
+        printf("1"); // error from this comment
+    else
+        printf("2");
+    return '\x00';
+}
diff --git a/compiler/c2nim/tests/vincent.h b/compiler/c2nim/tests/vincent.h
new file mode 100644
index 000000000..b4e761ee1
--- /dev/null
+++ b/compiler/c2nim/tests/vincent.h
@@ -0,0 +1,3 @@
+struct foo {
+    int x,y,z;
+};
diff --git a/compiler/ccgcalls.nim b/compiler/ccgcalls.nim
index 07fba95a3..84c5bf419 100644
--- a/compiler/ccgcalls.nim
+++ b/compiler/ccgcalls.nim
@@ -73,7 +73,7 @@ proc isInCurrentFrame(p: BProc, n: PNode): bool =
     result = false
   of nkObjUpConv, nkObjDownConv, nkCheckedFieldExpr:
     result = isInCurrentFrame(p, n.sons[0])
-  else: nil
+  else: discard
 
 proc openArrayLoc(p: BProc, n: PNode): PRope =
   var a: TLoc
@@ -88,7 +88,7 @@ proc openArrayLoc(p: BProc, n: PNode): PRope =
       result = ropef("$1->data, $1->$2", [a.rdLoc, lenField()])
   of tyArray, tyArrayConstr:
     result = ropef("$1, $2", [rdLoc(a), toRope(lengthOrd(a.t))])
-  else: InternalError("openArrayLoc: " & typeToString(a.t))
+  else: internalError("openArrayLoc: " & typeToString(a.t))
 
 proc genArgStringToCString(p: BProc, 
                            n: PNode): PRope {.inline.} =
@@ -146,7 +146,8 @@ proc genClosureCall(p: BProc, le, ri: PNode, d: var TLoc) =
   proc addComma(r: PRope): PRope =
     result = if r == nil: r else: con(r, ~", ")
 
-  const CallPattern = "$1.ClEnv? $1.ClPrc($3$1.ClEnv) : (($4)($1.ClPrc))($2)"
+  const PatProc = "$1.ClEnv? $1.ClPrc($3$1.ClEnv):(($4)($1.ClPrc))($2)"
+  const PatIter = "$1.ClPrc($3$1.ClEnv)" # we know the env exists
   var op: TLoc
   initLocExpr(p, ri.sons[0], op)
   var pl: PRope
@@ -164,9 +165,10 @@ proc genClosureCall(p: BProc, le, ri: PNode, d: var TLoc) =
     if i < length - 1: app(pl, ~", ")
   
   template genCallPattern {.dirty.} =
-    lineF(p, cpsStmts, CallPattern & ";$n", op.r, pl, pl.addComma, rawProc)
+    lineF(p, cpsStmts, callPattern & ";$n", op.r, pl, pl.addComma, rawProc)
 
   let rawProc = getRawProcType(p, typ)
+  let callPattern = if tfIterator in typ.flags: PatIter else: PatProc
   if typ.sons[0] != nil:
     if isInvalidReturnType(typ.sons[0]):
       if sonsLen(ri) > 1: app(pl, ~", ")
@@ -190,7 +192,7 @@ proc genClosureCall(p: BProc, le, ri: PNode, d: var TLoc) =
       assert(d.t != nil)        # generate an assignment to d:
       var list: TLoc
       initLoc(list, locCall, d.t, OnUnknown)
-      list.r = ropef(CallPattern, op.r, pl, pl.addComma, rawProc)
+      list.r = ropef(callPattern, op.r, pl, pl.addComma, rawProc)
       genAssignment(p, d, list, {}) # no need for deep copying
   else:
     genCallPattern()
@@ -243,7 +245,7 @@ proc genNamedParamCall(p: BProc, ri: PNode, d: var TLoc) =
   for i in countup(3, length-1):
     assert(sonsLen(typ) == sonsLen(typ.n))
     if i >= sonsLen(typ):
-      InternalError(ri.info, "varargs for objective C method?")
+      internalError(ri.info, "varargs for objective C method?")
     assert(typ.n.sons[i].kind == nkSym)
     var param = typ.n.sons[i].sym
     app(pl, ~" ")
diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim
index 873c61ed4..ba543039e 100644
--- a/compiler/ccgexprs.nim
+++ b/compiler/ccgexprs.nim
@@ -11,7 +11,7 @@
 
 # -------------------------- constant expressions ------------------------
 
-proc intLiteral(i: biggestInt): PRope =
+proc intLiteral(i: BiggestInt): PRope =
   if (i > low(int32)) and (i <= high(int32)):
     result = toRope(i)
   elif i == low(int32):
@@ -22,7 +22,7 @@ proc intLiteral(i: biggestInt): PRope =
   else:
     result = ~"(IL64(-9223372036854775807) - IL64(1))"
 
-proc int32Literal(i: Int): PRope =
+proc int32Literal(i: int): PRope =
   if i == int(low(int32)):
     result = ~"(-2147483647 -1)"
   else:
@@ -39,7 +39,7 @@ proc getStrLit(m: BModule, s: string): PRope =
   discard cgsym(m, "TGenericSeq")
   result = con("TMP", toRope(backendId()))
   appf(m.s[cfsData], "STRING_LITERAL($1, $2, $3);$n",
-       [result, makeCString(s), ToRope(len(s))])
+       [result, makeCString(s), toRope(len(s))])
 
 proc genLiteral(p: BProc, n: PNode, ty: PType): PRope =
   if ty == nil: internalError(n.info, "genLiteral: ty is nil")
@@ -62,7 +62,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): PRope =
   of nkNilLit:
     let t = skipTypes(ty, abstractVarRange)
     if t.kind == tyProc and t.callConv == ccClosure:
-      var id = NodeTableTestOrSet(p.module.dataCache, n, gBackendId)
+      var id = nodeTableTestOrSet(p.module.dataCache, n, gBackendId)
       result = con("TMP", toRope(id))
       if id == gBackendId:
         # not found in cache:
@@ -74,7 +74,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): PRope =
       result = toRope("NIM_NIL")
   of nkStrLit..nkTripleStrLit:
     if skipTypes(ty, abstractVarRange).kind == tyString:
-      var id = NodeTableTestOrSet(p.module.dataCache, n, gBackendId)
+      var id = nodeTableTestOrSet(p.module.dataCache, n, gBackendId)
       if id == gBackendId:
         # string literal not found in the cache:
         result = ropecg(p.module, "((#NimStringDesc*) &$1)", 
@@ -84,9 +84,9 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): PRope =
     else:
       result = makeCString(n.strVal)
   of nkFloatLit..nkFloat64Lit:
-    result = toRope(n.floatVal.ToStrMaxPrecision)
+    result = toRope(n.floatVal.toStrMaxPrecision)
   else:
-    InternalError(n.info, "genLiteral(" & $n.kind & ')')
+    internalError(n.info, "genLiteral(" & $n.kind & ')')
     result = nil
 
 proc genLiteral(p: BProc, n: PNode): PRope =
@@ -96,7 +96,7 @@ proc bitSetToWord(s: TBitSet, size: int): BiggestInt =
   result = 0
   when true:
     for j in countup(0, size - 1):
-      if j < len(s): result = result or `shl`(Ze64(s[j]), j * 8)
+      if j < len(s): result = result or `shl`(ze64(s[j]), j * 8)
   else:
     # not needed, too complex thinking:
     if CPU[platform.hostCPU].endian == CPU[targetCPU].endian:
@@ -117,7 +117,7 @@ proc genRawSetData(cs: TBitSet, size: int): PRope =
         else: frmt = "0x$1, "
       else:
         frmt = "0x$1}$n"
-      appf(result, frmt, [toRope(toHex(Ze64(cs[i]), 2))])
+      appf(result, frmt, [toRope(toHex(ze64(cs[i]), 2))])
   else:
     result = intLiteral(bitSetToWord(cs, size))
     #  result := toRope('0x' + ToHex(bitSetToWord(cs, size), size * 2))
@@ -127,7 +127,7 @@ proc genSetNode(p: BProc, n: PNode): PRope =
   var size = int(getSize(n.typ))
   toBitSet(n, cs)
   if size > 8:
-    var id = NodeTableTestOrSet(p.module.dataCache, n, gBackendId)
+    var id = nodeTableTestOrSet(p.module.dataCache, n, gBackendId)
     result = con("TMP", toRope(id))
     if id == gBackendId:
       # not found in cache:
@@ -155,7 +155,7 @@ proc getStorageLoc(n: PNode): TStorageLoc =
     of tyVar: result = OnUnknown
     of tyPtr: result = OnStack
     of tyRef: result = OnHeap
-    else: InternalError(n.info, "getStorageLoc")
+    else: internalError(n.info, "getStorageLoc")
   of nkBracketExpr, nkDotExpr, nkObjDownConv, nkObjUpConv:
     result = getStorageLoc(n.sons[0])
   else: result = OnUnknown
@@ -202,7 +202,7 @@ proc asgnComplexity(n: PNode): int =
     of nkRecList:
       for t in items(n):
         result += asgnComplexity(t)
-    else: nil
+    else: discard
 
 proc optAsgnLoc(a: TLoc, t: PType, field: PRope): TLoc =
   result.k = locField
@@ -228,7 +228,7 @@ proc genOptAsgnObject(p: BProc, dest, src: TLoc, flags: TAssignmentFlags,
                      optAsgnLoc(src, field.typ, field.loc.r), flags)
   of nkRecList:
     for child in items(t): genOptAsgnObject(p, dest, src, flags, child)
-  else: nil
+  else: discard
 
 proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   # Consider: 
@@ -343,7 +343,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   of tyPtr, tyPointer, tyChar, tyBool, tyEnum, tyCString,
      tyInt..tyUInt64, tyRange, tyVar:
     linefmt(p, cpsStmts, "$1 = $2;$n", rdLoc(dest), rdLoc(src))
-  else: InternalError("genAssignment(" & $ty.kind & ')')
+  else: internalError("genAssignment(" & $ty.kind & ')')
 
 proc getDestLoc(p: BProc, d: var TLoc, typ: PType) =
   if d.k == locNone: getTemp(p, typ, d)
@@ -373,62 +373,62 @@ proc putIntoDest(p: BProc, d: var TLoc, t: PType, r: PRope) =
 
 proc binaryStmt(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a, b: TLoc
-  if d.k != locNone: InternalError(e.info, "binaryStmt")
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  if d.k != locNone: internalError(e.info, "binaryStmt")
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   lineCg(p, cpsStmts, frmt, rdLoc(a), rdLoc(b))
 
 proc unaryStmt(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a: TLoc
-  if d.k != locNone: InternalError(e.info, "unaryStmt")
-  InitLocExpr(p, e.sons[1], a)
+  if d.k != locNone: internalError(e.info, "unaryStmt")
+  initLocExpr(p, e.sons[1], a)
   lineCg(p, cpsStmts, frmt, [rdLoc(a)])
 
 proc binaryStmtChar(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a, b: TLoc
-  if (d.k != locNone): InternalError(e.info, "binaryStmtChar")
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  if (d.k != locNone): internalError(e.info, "binaryStmtChar")
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   lineCg(p, cpsStmts, frmt, [rdCharLoc(a), rdCharLoc(b)])
 
 proc binaryExpr(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a, b: TLoc
   assert(e.sons[1].typ != nil)
   assert(e.sons[2].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   putIntoDest(p, d, e.typ, ropecg(p.module, frmt, [rdLoc(a), rdLoc(b)]))
 
 proc binaryExprChar(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a, b: TLoc
   assert(e.sons[1].typ != nil)
   assert(e.sons[2].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   putIntoDest(p, d, e.typ, ropecg(p.module, frmt, [a.rdCharLoc, b.rdCharLoc]))
 
 proc unaryExpr(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a: TLoc
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   putIntoDest(p, d, e.typ, ropecg(p.module, frmt, [rdLoc(a)]))
 
 proc unaryExprChar(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a: TLoc
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   putIntoDest(p, d, e.typ, ropecg(p.module, frmt, [rdCharLoc(a)]))
 
 proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
   const
-    prc: array[mAddi..mModi64, string] = ["addInt", "subInt", "mulInt",
+    prc: array[mAddI..mModI64, string] = ["addInt", "subInt", "mulInt",
       "divInt", "modInt", "addInt64", "subInt64", "mulInt64", "divInt64",
       "modInt64"]
-    opr: array[mAddi..mModi64, string] = ["+", "-", "*", "/", "%", "+", "-",
+    opr: array[mAddI..mModI64, string] = ["+", "-", "*", "/", "%", "+", "-",
       "*", "/", "%"]
   var a, b: TLoc
   assert(e.sons[1].typ != nil)
   assert(e.sons[2].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   var t = skipTypes(e.typ, abstractRange)
   if optOverflowCheck notin p.options:
     putIntoDest(p, d, e.typ, ropef("(NI$4)($2 $1 $3)", [toRope(opr[m]),
@@ -436,7 +436,7 @@ proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
   else:
     var storage: PRope
     var size = getSize(t)
-    if size < platform.IntSize:
+    if size < platform.intSize:
       storage = toRope("NI") 
     else:
       storage = getTypeDesc(p.module, t)
@@ -444,7 +444,7 @@ proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
     linefmt(p, cpsLocals, "$1 $2;$n", storage, tmp)
     lineCg(p, cpsStmts, "$1 = #$2($3, $4);$n",
                          tmp, toRope(prc[m]), rdLoc(a), rdLoc(b))
-    if size < platform.IntSize or t.kind in {tyRange, tyEnum, tySet}:
+    if size < platform.intSize or t.kind in {tyRange, tyEnum, tySet}:
       linefmt(p, cpsStmts, "if ($1 < $2 || $1 > $3) #raiseOverflow();$n",
               tmp, intLiteral(firstOrd(t)), intLiteral(lastOrd(t)))
     putIntoDest(p, d, e.typ, ropef("(NI$1)($2)", [toRope(getSize(t)*8), tmp]))
@@ -460,7 +460,7 @@ proc unaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
     a: TLoc
     t: PType
   assert(e.sons[1].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   t = skipTypes(e.typ, abstractRange)
   if optOverflowCheck in p.options:
     linefmt(p, cpsStmts, "if ($1 == $2) #raiseOverflow();$n",
@@ -526,11 +526,11 @@ proc binaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
       "($1 != $2)"]           # Xor
   var
     a, b: TLoc
-    s: biggestInt
+    s: BiggestInt
   assert(e.sons[1].typ != nil)
   assert(e.sons[2].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   # BUGFIX: cannot use result-type here, as it may be a boolean
   s = max(getSize(a.t), getSize(b.t)) * 8
   putIntoDest(p, d, e.typ,
@@ -541,8 +541,8 @@ proc genEqProc(p: BProc, e: PNode, d: var TLoc) =
   var a, b: TLoc
   assert(e.sons[1].typ != nil)
   assert(e.sons[2].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   if a.t.callConv == ccClosure:
     putIntoDest(p, d, e.typ, 
       ropef("($1.ClPrc == $2.ClPrc && $1.ClEnv == $2.ClEnv)", [
@@ -585,7 +585,7 @@ proc unaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
     a: TLoc
     t: PType
   assert(e.sons[1].typ != nil)
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   t = skipTypes(e.typ, abstractRange)
   putIntoDest(p, d, e.typ,
               ropef(unArithTab[op], [rdLoc(a), toRope(getSize(t) * 8),
@@ -606,21 +606,21 @@ proc genDeref(p: BProc, e: PNode, d: var TLoc) =
       d.s = OnUnknown
     of tyPtr:
       d.s = OnUnknown         # BUGFIX!
-    else: InternalError(e.info, "genDeref " & $a.t.kind)
+    else: internalError(e.info, "genDeref " & $a.t.kind)
     putIntoDest(p, d, a.t.sons[0], ropef("(*$1)", [rdLoc(a)]))
 
 proc genAddr(p: BProc, e: PNode, d: var TLoc) =
   # careful  'addr(myptrToArray)' needs to get the ampersand:
   if e.sons[0].typ.skipTypes(abstractInst).kind in {tyRef, tyPtr}:
     var a: TLoc
-    InitLocExpr(p, e.sons[0], a)
+    initLocExpr(p, e.sons[0], a)
     putIntoDest(p, d, e.typ, con("&", a.r))
     #Message(e.info, warnUser, "HERE NEW &")
   elif mapType(e.sons[0].typ) == ctArray:
     expr(p, e.sons[0], d)
   else:
     var a: TLoc
-    InitLocExpr(p, e.sons[0], a)
+    initLocExpr(p, e.sons[0], a)
     putIntoDest(p, d, e.typ, addrLoc(a))
 
 template inheritLocation(d: var TLoc, a: TLoc) =
@@ -630,7 +630,7 @@ template inheritLocation(d: var TLoc, a: TLoc) =
   
 proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc): PType =
   initLocExpr(p, e.sons[0], a)
-  if e.sons[1].kind != nkSym: InternalError(e.info, "genRecordFieldAux")
+  if e.sons[1].kind != nkSym: internalError(e.info, "genRecordFieldAux")
   d.inheritLocation(a)
   discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
   result = a.t
@@ -664,13 +664,13 @@ proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
     var field: PSym = nil
     while ty != nil:
       if ty.kind notin {tyTuple, tyObject}:
-        InternalError(e.info, "genRecordField")
+        internalError(e.info, "genRecordField")
       field = lookupInRecord(ty.n, f.name)
       if field != nil: break
       if gCmd != cmdCompileToCpp: app(r, ".Sup")
-      ty = GetUniqueType(ty.sons[0])
-    if field == nil: InternalError(e.info, "genRecordField 2 ")
-    if field.loc.r == nil: InternalError(e.info, "genRecordField 3")
+      ty = getUniqueType(ty.sons[0])
+    if field == nil: internalError(e.info, "genRecordField 2 ")
+    if field.loc.r == nil: internalError(e.info, "genRecordField 3")
     appf(r, ".$1", [field.loc.r])
     putIntoDest(p, d, field.typ, r)
 
@@ -686,11 +686,11 @@ proc genFieldCheck(p: BProc, e: PNode, obj: PRope, field: PSym) =
     if op.magic == mNot: it = it.sons[1]
     assert(it.sons[2].kind == nkSym)
     initLoc(test, locNone, it.typ, OnStack)
-    InitLocExpr(p, it.sons[1], u)
+    initLocExpr(p, it.sons[1], u)
     initLoc(v, locExpr, it.sons[2].typ, OnUnknown)
     v.r = ropef("$1.$2", [obj, it.sons[2].sym.loc.r])
     genInExprAux(p, it, u, v, test)
-    let id = NodeTableTestOrSet(p.module.dataCache,
+    let id = nodeTableTestOrSet(p.module.dataCache,
                                newStrNode(nkStrLit, field.name.s), gBackendId)
     let strLit = if id == gBackendId: getStrLit(p.module, field.name.s)
                  else: con("TMP", toRope(id))
@@ -720,9 +720,9 @@ proc genCheckedRecordField(p: BProc, e: PNode, d: var TLoc) =
       if field != nil: break
       if gCmd != cmdCompileToCpp: app(r, ".Sup")
       ty = getUniqueType(ty.sons[0])
-    if field == nil: InternalError(e.info, "genCheckedRecordField")
+    if field == nil: internalError(e.info, "genCheckedRecordField")
     if field.loc.r == nil:
-      InternalError(e.info, "genCheckedRecordField") # generate the checks:
+      internalError(e.info, "genCheckedRecordField") # generate the checks:
     genFieldCheck(p, e, r, field)
     app(r, rfmt(nil, ".$1", field.loc.r))
     putIntoDest(p, d, field.typ, r)
@@ -774,7 +774,7 @@ proc genOpenArrayElem(p: BProc, e: PNode, d: var TLoc) =
   putIntoDest(p, d, elemType(skipTypes(a.t, abstractVar)),
               rfmt(nil, "$1[$2]", rdLoc(a), rdCharLoc(b)))
 
-proc genSeqElem(p: BPRoc, e: PNode, d: var TLoc) =
+proc genSeqElem(p: BProc, e: PNode, d: var TLoc) =
   var a, b: TLoc
   initLocExpr(p, e.sons[0], a)
   initLocExpr(p, e.sons[1], b)
@@ -838,7 +838,7 @@ proc genAndOr(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
 proc genEcho(p: BProc, n: PNode) =
   # this unusal way of implementing it ensures that e.g. ``echo("hallo", 45)``
   # is threadsafe.
-  discard lists.IncludeStr(p.module.headerFiles, "<stdio.h>")
+  discard lists.includeStr(p.module.headerFiles, "<stdio.h>")
   var args: PRope = nil
   var a: TLoc
   for i in countup(1, n.len-1):
@@ -847,6 +847,9 @@ proc genEcho(p: BProc, n: PNode) =
   linefmt(p, cpsStmts, "printf($1$2);$n",
           makeCString(repeatStr(n.len-1, "%s") & tnl), args)
 
+proc gcUsage(n: PNode) =
+  if gSelectedGC == gcNone: message(n.info, warnGcMem, n.renderTree)
+
 proc genStrConcat(p: BProc, e: PNode, d: var TLoc) =
   #   <Nimrod code>
   #   s = 'Hello ' & name & ', how do you feel?' & 'z'
@@ -872,12 +875,12 @@ proc genStrConcat(p: BProc, e: PNode, d: var TLoc) =
   for i in countup(0, sonsLen(e) - 2):
     # compute the length expression:
     initLocExpr(p, e.sons[i + 1], a)
-    if skipTypes(e.sons[i + 1].Typ, abstractVarRange).kind == tyChar:
-      Inc(L)
+    if skipTypes(e.sons[i + 1].typ, abstractVarRange).kind == tyChar:
+      inc(L)
       app(appends, rfmt(p.module, "#appendChar($1, $2);$n", tmp.r, rdLoc(a)))
     else:
       if e.sons[i + 1].kind in {nkStrLit..nkTripleStrLit}:
-        Inc(L, len(e.sons[i + 1].strVal))
+        inc(L, len(e.sons[i + 1].strVal))
       else:
         appf(lens, "$1->$2 + ", [rdLoc(a), lenField()])
       app(appends, rfmt(p.module, "#appendString($1, $2);$n", tmp.r, rdLoc(a)))
@@ -888,6 +891,7 @@ proc genStrConcat(p: BProc, e: PNode, d: var TLoc) =
     keepAlive(p, tmp)
   else:
     genAssignment(p, d, tmp, {needToKeepAlive}) # no need for deep copying
+  gcUsage(e)
 
 proc genStrAppend(p: BProc, e: PNode, d: var TLoc) =
   #  <Nimrod code>
@@ -910,13 +914,13 @@ proc genStrAppend(p: BProc, e: PNode, d: var TLoc) =
   for i in countup(0, sonsLen(e) - 3):
     # compute the length expression:
     initLocExpr(p, e.sons[i + 2], a)
-    if skipTypes(e.sons[i + 2].Typ, abstractVarRange).kind == tyChar:
-      Inc(L)
+    if skipTypes(e.sons[i + 2].typ, abstractVarRange).kind == tyChar:
+      inc(L)
       app(appends, rfmt(p.module, "#appendChar($1, $2);$n",
                         rdLoc(dest), rdLoc(a)))
     else:
       if e.sons[i + 2].kind in {nkStrLit..nkTripleStrLit}:
-        Inc(L, len(e.sons[i + 2].strVal))
+        inc(L, len(e.sons[i + 2].strVal))
       else:
         appf(lens, "$1->$2 + ", [rdLoc(a), lenField()])
       app(appends, rfmt(p.module, "#appendString($1, $2);$n",
@@ -925,6 +929,7 @@ proc genStrAppend(p: BProc, e: PNode, d: var TLoc) =
           rdLoc(dest), lens, toRope(L))
   keepAlive(p, dest)
   app(p.s(cpsStmts), appends)
+  gcUsage(e)
 
 proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
   # seq &= x  -->
@@ -935,20 +940,21 @@ proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
                          else:
                            "$1 = ($2) #incrSeq($1, sizeof($3));$n"
   var a, b, dest: TLoc
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   lineCg(p, cpsStmts, seqAppendPattern, [
       rdLoc(a),
       getTypeDesc(p.module, skipTypes(e.sons[1].typ, abstractVar)),
-      getTypeDesc(p.module, skipTypes(e.sons[2].Typ, abstractVar))])
+      getTypeDesc(p.module, skipTypes(e.sons[2].typ, abstractVar))])
   keepAlive(p, a)
   initLoc(dest, locExpr, b.t, OnHeap)
   dest.r = rfmt(nil, "$1->data[$1->$2-1]", rdLoc(a), lenField())
   genAssignment(p, dest, b, {needToCopy, afDestIsNil})
+  gcUsage(e)
 
 proc genReset(p: BProc, n: PNode) = 
   var a: TLoc
-  InitLocExpr(p, n.sons[1], a)
+  initLocExpr(p, n.sons[1], a)
   linefmt(p, cpsStmts, "#genericReset((void*)$1, $2);$n",
           addrLoc(a), genTypeInfo(p.module, skipTypes(a.t, abstractVarRange)))
 
@@ -959,8 +965,8 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: PRope) =
   initLoc(b, locExpr, a.t, OnHeap)
   if sizeExpr.isNil:
     sizeExpr = ropef("sizeof($1)",
-        getTypeDesc(p.module, skipTypes(reftype.sons[0], abstractRange)))
-  let args = [getTypeDesc(p.module, reftype),
+        getTypeDesc(p.module, skipTypes(refType.sons[0], abstractRange)))
+  let args = [getTypeDesc(p.module, refType),
               genTypeInfo(p.module, refType),
               sizeExpr]
   if a.s == OnHeap and usesNativeGC():
@@ -979,19 +985,20 @@ proc rawGenNew(p: BProc, a: TLoc, sizeExpr: PRope) =
 
 proc genNew(p: BProc, e: PNode) =
   var a: TLoc
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   # 'genNew' also handles 'unsafeNew':
   if e.len == 3:
     var se: TLoc
-    InitLocExpr(p, e.sons[2], se)
+    initLocExpr(p, e.sons[2], se)
     rawGenNew(p, a, se.rdLoc)
   else:
     rawGenNew(p, a, nil)
+  gcUsage(e)
 
 proc genNewSeqAux(p: BProc, dest: TLoc, length: PRope) =
   let seqtype = skipTypes(dest.t, abstractVarRange)
   let args = [getTypeDesc(p.module, seqtype),
-              genTypeInfo(p.module, seqType), length]
+              genTypeInfo(p.module, seqtype), length]
   var call: TLoc
   initLoc(call, locExpr, dest.t, OnHeap)
   if dest.s == OnHeap and usesNativeGC():
@@ -1007,9 +1014,10 @@ proc genNewSeqAux(p: BProc, dest: TLoc, length: PRope) =
   
 proc genNewSeq(p: BProc, e: PNode) =
   var a, b: TLoc
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   genNewSeqAux(p, a, b.rdLoc)
+  gcUsage(e)
   
 proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
   var tmp: TLoc
@@ -1021,6 +1029,7 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
     rawGenNew(p, tmp, nil)
     t = t.sons[0].skipTypes(abstractInst)
     r = ropef("(*$1)", r)
+    gcUsage(e)
   discard getTypeDesc(p.module, t)
   for i in 1 .. <e.len:
     let it = e.sons[i]
@@ -1032,15 +1041,15 @@ proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
       field = lookupInRecord(ty.n, it.sons[0].sym.name)
       if field != nil: break
       if gCmd != cmdCompileToCpp: app(tmp2.r, ".Sup")
-      ty = GetUniqueType(ty.sons[0])
-    if field == nil or field.loc.r == nil: InternalError(e.info, "genObjConstr")
+      ty = getUniqueType(ty.sons[0])
+    if field == nil or field.loc.r == nil: internalError(e.info, "genObjConstr")
     if it.len == 3 and optFieldCheck in p.options:
       genFieldCheck(p, it.sons[2], r, field)
     app(tmp2.r, ".")
     app(tmp2.r, field.loc.r)
     tmp2.k = locTemp
     tmp2.t = field.loc.t
-    tmp2.s = onHeap
+    tmp2.s = OnHeap
     tmp2.heapRoot = tmp.r
     expr(p, it.sons[1], tmp2)
   if d.k == locNone:
@@ -1059,6 +1068,7 @@ proc genSeqConstr(p: BProc, t: PNode, d: var TLoc) =
     arr.r = rfmt(nil, "$1->data[$2]", rdLoc(d), intLiteral(i))
     arr.s = OnHeap            # we know that sequences are on the heap
     expr(p, t.sons[i], arr)
+  gcUsage(t)
 
 proc genArrToSeq(p: BProc, t: PNode, d: var TLoc) =
   var elem, a, arr: TLoc
@@ -1088,17 +1098,18 @@ proc genNewFinalize(p: BProc, e: PNode) =
     ti: PRope
     oldModule: BModule
   refType = skipTypes(e.sons[1].typ, abstractVarRange)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], f)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], f)
   initLoc(b, locExpr, a.t, OnHeap)
   ti = genTypeInfo(p.module, refType)
   appf(p.module.s[cfsTypeInit3], "$1->finalizer = (void*)$2;$n", [ti, rdLoc(f)])
   b.r = ropecg(p.module, "($1) #newObj($2, sizeof($3))", [
       getTypeDesc(p.module, refType),
-      ti, getTypeDesc(p.module, skipTypes(reftype.sons[0], abstractRange))])
+      ti, getTypeDesc(p.module, skipTypes(refType.sons[0], abstractRange))])
   genAssignment(p, a, b, {needToKeepAlive})  # set the object type:
   bt = skipTypes(refType.sons[0], abstractRange)
   genObjectInit(p, cpsStmts, bt, a, false)
+  gcUsage(e)
 
 proc genOf(p: BProc, x: PNode, typ: PType, d: var TLoc) =
   var a: TLoc
@@ -1116,7 +1127,7 @@ proc genOf(p: BProc, x: PNode, typ: PType, d: var TLoc) =
       app(r, ~".Sup")
       t = skipTypes(t.sons[0], typedescInst)
   if isObjLackingTypeField(t):
-    GlobalError(x.info, errGenerated, 
+    globalError(x.info, errGenerated, 
       "no 'of' operator available for pure objects")
   if nilCheck != nil:
     r = rfmt(p.module, "(($1) && #isObj($2.m_type, $3))",
@@ -1132,7 +1143,7 @@ proc genOf(p: BProc, n: PNode, d: var TLoc) =
 proc genRepr(p: BProc, e: PNode, d: var TLoc) =
   # XXX we don't generate keep alive info for now here
   var a: TLoc
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   var t = skipTypes(e.sons[1].typ, abstractVarRange)
   case t.kind
   of tyInt..tyInt64, tyUInt..tyUInt64:
@@ -1164,7 +1175,7 @@ proc genRepr(p: BProc, e: PNode, d: var TLoc) =
     of tyArray, tyArrayConstr:
       putIntoDest(p, b, e.typ,
                   ropef("$1, $2", [rdLoc(a), toRope(lengthOrd(a.t))]))
-    else: InternalError(e.sons[0].info, "genRepr()")
+    else: internalError(e.sons[0].info, "genRepr()")
     putIntoDest(p, d, e.typ, 
         ropecg(p.module, "#reprOpenArray($1, $2)", [rdLoc(b),
         genTypeInfo(p.module, elemType(t))]))
@@ -1176,6 +1187,7 @@ proc genRepr(p: BProc, e: PNode, d: var TLoc) =
   else:
     putIntoDest(p, d, e.typ, ropecg(p.module, "#reprAny($1, $2)",
                                    [addrLoc(a), genTypeInfo(p.module, t)]))
+  gcUsage(e)
 
 proc genGetTypeInfo(p: BProc, e: PNode, d: var TLoc) =
   var t = skipTypes(e.sons[1].typ, abstractVarRange)
@@ -1183,20 +1195,21 @@ proc genGetTypeInfo(p: BProc, e: PNode, d: var TLoc) =
 
 proc genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
   var a: TLoc
-  InitLocExpr(p, n.sons[1], a)
+  initLocExpr(p, n.sons[1], a)
   a.r = ropecg(p.module, frmt, [rdLoc(a)])
   if d.k == locNone: getTemp(p, n.typ, d)
   genAssignment(p, d, a, {needToKeepAlive})
+  gcUsage(n)
 
 proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
   var a = e.sons[1]
   if a.kind == nkHiddenAddr: a = a.sons[0]
-  var typ = skipTypes(a.Typ, abstractVar)
+  var typ = skipTypes(a.typ, abstractVar)
   case typ.kind
   of tyOpenArray, tyVarargs:
     if op == mHigh: unaryExpr(p, e, d, "($1Len0-1)")
     else: unaryExpr(p, e, d, "$1Len0")
-  of tyCstring:
+  of tyCString:
     if op == mHigh: unaryExpr(p, e, d, "(strlen($1)-1)")
     else: unaryExpr(p, e, d, "strlen($1)")
   of tyString, tySequence:
@@ -1208,15 +1221,15 @@ proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
       else: unaryExpr(p, e, d, "$1->len")
   of tyArray, tyArrayConstr:
     # YYY: length(sideeffect) is optimized away incorrectly?
-    if op == mHigh: putIntoDest(p, d, e.typ, toRope(lastOrd(Typ)))
+    if op == mHigh: putIntoDest(p, d, e.typ, toRope(lastOrd(typ)))
     else: putIntoDest(p, d, e.typ, toRope(lengthOrd(typ)))
-  else: InternalError(e.info, "genArrayLen()")
+  else: internalError(e.info, "genArrayLen()")
 
 proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
   var a, b: TLoc
   assert(d.k == locNone)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   var t = skipTypes(e.sons[1].typ, abstractVar)
   let setLenPattern = if gCmd != cmdCompileToCpp:
       "$1 = ($3) #setLengthSeq(&($1)->Sup, sizeof($4), $2);$n"
@@ -1227,10 +1240,12 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
       rdLoc(a), rdLoc(b), getTypeDesc(p.module, t),
       getTypeDesc(p.module, t.sons[0])])
   keepAlive(p, a)
+  gcUsage(e)
 
 proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) =
   binaryStmt(p, e, d, "$1 = #setLengthStr($1, $2);$n")
-  keepAlive(P, d)
+  keepAlive(p, d)
+  gcUsage(e)
 
 proc genSwap(p: BProc, e: PNode, d: var TLoc) =
   # swap(a, b) -->
@@ -1239,8 +1254,8 @@ proc genSwap(p: BProc, e: PNode, d: var TLoc) =
   # b = temp
   var a, b, tmp: TLoc
   getTemp(p, skipTypes(e.sons[1].typ, abstractVar), tmp)
-  InitLocExpr(p, e.sons[1], a) # eval a
-  InitLocExpr(p, e.sons[2], b) # eval b
+  initLocExpr(p, e.sons[1], a) # eval a
+  initLocExpr(p, e.sons[2], b) # eval b
   genAssignment(p, tmp, a, {})
   genAssignment(p, a, b, {})
   genAssignment(p, b, tmp, {})
@@ -1256,10 +1271,10 @@ proc rdSetElemLoc(a: TLoc, setType: PType): PRope =
 proc fewCmps(s: PNode): bool =
   # this function estimates whether it is better to emit code
   # for constructing the set or generating a bunch of comparisons directly
-  if s.kind != nkCurly: InternalError(s.info, "fewCmps")
+  if s.kind != nkCurly: internalError(s.info, "fewCmps")
   if (getSize(s.typ) <= platform.intSize) and (nfAllConst in s.flags):
     result = false            # it is better to emit the set generation code
-  elif elemType(s.typ).Kind in {tyInt, tyInt16..tyInt64}:
+  elif elemType(s.typ).kind in {tyInt, tyInt16..tyInt64}:
     result = true             # better not emit the set if int is basetype!
   else:
     result = sonsLen(s) <= 8  # 8 seems to be a good value
@@ -1278,13 +1293,13 @@ proc genInExprAux(p: BProc, e: PNode, a, b, d: var TLoc) =
 proc binaryStmtInExcl(p: BProc, e: PNode, d: var TLoc, frmt: string) =
   var a, b: TLoc
   assert(d.k == locNone)
-  InitLocExpr(p, e.sons[1], a)
-  InitLocExpr(p, e.sons[2], b)
+  initLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[2], b)
   lineF(p, cpsStmts, frmt, [rdLoc(a), rdSetElemLoc(b, a.t)])
 
 proc genInOp(p: BProc, e: PNode, d: var TLoc) =
   var a, b, x, y: TLoc
-  if (e.sons[1].Kind == nkCurly) and fewCmps(e.sons[1]):
+  if (e.sons[1].kind == nkCurly) and fewCmps(e.sons[1]):
     # a set constructor but not a constant set:
     # do not emit the set, but generate a bunch of comparisons; and if we do
     # so, we skip the unnecessary range check: This is a semantical extension
@@ -1298,13 +1313,13 @@ proc genInOp(p: BProc, e: PNode, d: var TLoc) =
     b.r = toRope("(")
     var length = sonsLen(e.sons[1])
     for i in countup(0, length - 1):
-      if e.sons[1].sons[i].Kind == nkRange:
-        InitLocExpr(p, e.sons[1].sons[i].sons[0], x)
-        InitLocExpr(p, e.sons[1].sons[i].sons[1], y)
+      if e.sons[1].sons[i].kind == nkRange:
+        initLocExpr(p, e.sons[1].sons[i].sons[0], x)
+        initLocExpr(p, e.sons[1].sons[i].sons[1], y)
         appf(b.r, "$1 >= $2 && $1 <= $3",
              [rdCharLoc(a), rdCharLoc(x), rdCharLoc(y)])
       else:
-        InitLocExpr(p, e.sons[1].sons[i], x)
+        initLocExpr(p, e.sons[1].sons[i], x)
         appf(b.r, "$1 == $2", [rdCharLoc(a), rdCharLoc(x)])
       if i < length - 1: app(b.r, " || ")
     app(b.r, ")")
@@ -1312,8 +1327,8 @@ proc genInOp(p: BProc, e: PNode, d: var TLoc) =
   else:
     assert(e.sons[1].typ != nil)
     assert(e.sons[2].typ != nil)
-    InitLocExpr(p, e.sons[1], a)
-    InitLocExpr(p, e.sons[2], b)
+    initLocExpr(p, e.sons[1], a)
+    initLocExpr(p, e.sons[2], b)
     genInExprAux(p, e, a, b, d)
 
 proc genSetOp(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
@@ -1326,7 +1341,7 @@ proc genSetOp(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
         "if ($3) $3 = (memcmp($4, $5, $2) != 0);$n",
       "&", "|", "& ~", "^"]
   var a, b, i: TLoc
-  var setType = skipTypes(e.sons[1].Typ, abstractVar)
+  var setType = skipTypes(e.sons[1].typ, abstractVar)
   var size = int(getSize(setType))
   case size
   of 1, 2, 4, 8:
@@ -1391,7 +1406,7 @@ proc genSomeCast(p: BProc, e: PNode, d: var TLoc) =
   # we use whatever C gives us. Except if we have a value-type, we need to go
   # through its address:
   var a: TLoc
-  InitLocExpr(p, e.sons[1], a)
+  initLocExpr(p, e.sons[1], a)
   let etyp = skipTypes(e.typ, abstractRange)
   if etyp.kind in ValueTypes and lfIndirect notin a.flags:
     putIntoDest(p, d, e.typ, ropef("(*($1*) ($2))",
@@ -1433,13 +1448,13 @@ proc genRangeChck(p: BProc, n: PNode, d: var TLoc, magic: string) =
   var dest = skipTypes(n.typ, abstractVar)
   # range checks for unsigned turned out to be buggy and annoying:
   if optRangeCheck notin p.options or dest.kind in {tyUInt..tyUInt64}:
-    InitLocExpr(p, n.sons[0], a)
+    initLocExpr(p, n.sons[0], a)
     putIntoDest(p, d, n.typ, ropef("(($1) ($2))",
         [getTypeDesc(p.module, dest), rdCharLoc(a)]))
   else:
-    InitLocExpr(p, n.sons[0], a)
+    initLocExpr(p, n.sons[0], a)
     if leValue(n.sons[2], n.sons[1]):
-      InternalError(n.info, "range check will always fail; empty range")
+      internalError(n.info, "range check will always fail; empty range")
     putIntoDest(p, d, dest, ropecg(p.module, "(($1)#$5($2, $3, $4))", [
         getTypeDesc(p.module, dest), rdCharLoc(a),
         genLiteral(p, n.sons[1], dest), genLiteral(p, n.sons[2], dest),
@@ -1462,6 +1477,7 @@ proc convCStrToStr(p: BProc, n: PNode, d: var TLoc) =
   initLocExpr(p, n.sons[0], a)
   putIntoDest(p, d, skipTypes(n.typ, abstractVar),
               ropecg(p.module, "#cstrToNimstr($1)", [rdLoc(a)]))
+  gcUsage(n)
 
 proc genStrEquals(p: BProc, e: PNode, d: var TLoc) =
   var x: TLoc
@@ -1481,17 +1497,17 @@ proc genStrEquals(p: BProc, e: PNode, d: var TLoc) =
     binaryExpr(p, e, d, "#eqStrings($1, $2)")
 
 proc binaryFloatArith(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
-  if {optNanCheck, optInfCheck} * p.options != {}:
+  if {optNaNCheck, optInfCheck} * p.options != {}:
     const opr: array[mAddF64..mDivF64, string] = ["+", "-", "*", "/"]
     var a, b: TLoc
     assert(e.sons[1].typ != nil)
     assert(e.sons[2].typ != nil)
-    InitLocExpr(p, e.sons[1], a)
-    InitLocExpr(p, e.sons[2], b)
+    initLocExpr(p, e.sons[1], a)
+    initLocExpr(p, e.sons[2], b)
     putIntoDest(p, d, e.typ, rfmt(nil, "(($4)($2) $1 ($4)($3))",
                                   toRope(opr[m]), rdLoc(a), rdLoc(b),
                                   getSimpleTypeDesc(p.module, e[1].typ)))
-    if optNanCheck in p.options:
+    if optNaNCheck in p.options:
       linefmt(p, cpsStmts, "#nanCheck($1);$n", rdLoc(d))
     if optInfCheck in p.options:
       linefmt(p, cpsStmts, "#infCheck($1);$n", rdLoc(d))
@@ -1507,30 +1523,30 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
   of mAddF64..mDivF64: binaryFloatArith(p, e, d, op)
   of mShrI..mXor: binaryArith(p, e, d, op)
   of mEqProc: genEqProc(p, e, d)
-  of mAddi..mModi64: binaryArithOverflow(p, e, d, op)
+  of mAddI..mModI64: binaryArithOverflow(p, e, d, op)
   of mRepr: genRepr(p, e, d)
   of mGetTypeInfo: genGetTypeInfo(p, e, d)
   of mSwap: genSwap(p, e, d)
   of mUnaryLt: 
-    if not (optOverflowCheck in p.Options): unaryExpr(p, e, d, "$1 - 1")
+    if not (optOverflowCheck in p.options): unaryExpr(p, e, d, "$1 - 1")
     else: unaryExpr(p, e, d, "#subInt($1, 1)")
   of mPred:
     # XXX: range checking?
-    if not (optOverflowCheck in p.Options): binaryExpr(p, e, d, "$1 - $2")
+    if not (optOverflowCheck in p.options): binaryExpr(p, e, d, "$1 - $2")
     else: binaryExpr(p, e, d, "#subInt($1, $2)")
   of mSucc:
     # XXX: range checking?
-    if not (optOverflowCheck in p.Options): binaryExpr(p, e, d, "$1 + $2")
+    if not (optOverflowCheck in p.options): binaryExpr(p, e, d, "$1 + $2")
     else: binaryExpr(p, e, d, "#addInt($1, $2)")
   of mInc:
-    if not (optOverflowCheck in p.Options):
+    if not (optOverflowCheck in p.options):
       binaryStmt(p, e, d, "$1 += $2;$n")
     elif skipTypes(e.sons[1].typ, abstractVar).kind == tyInt64:
       binaryStmt(p, e, d, "$1 = #addInt64($1, $2);$n")
     else:
       binaryStmt(p, e, d, "$1 = #addInt($1, $2);$n")
   of ast.mDec:
-    if not (optOverflowCheck in p.Options):
+    if not (optOverflowCheck in p.options):
       binaryStmt(p, e, d, "$1 -= $2;$n")
     elif skipTypes(e.sons[1].typ, abstractVar).kind == tyInt64:
       binaryStmt(p, e, d, "$1 = #subInt64($1, $2);$n")
@@ -1593,7 +1609,7 @@ proc handleConstExpr(p: BProc, n: PNode, d: var TLoc): bool =
   if (nfAllConst in n.flags) and (d.k == locNone) and (sonsLen(n) > 0):
     var t = getUniqueType(n.typ)
     discard getTypeDesc(p.module, t) # so that any fields are initialized
-    var id = NodeTableTestOrSet(p.module.dataCache, n, gBackendId)
+    var id = nodeTableTestOrSet(p.module.dataCache, n, gBackendId)
     fillLoc(d, locData, t, con("TMP", toRope(id)), OnHeap)
     if id == gBackendId:
       # expression not found in the cache:
@@ -1669,14 +1685,14 @@ proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
                       [rdLoc(d), mangleRecFieldName(t.n.sons[i].sym, t)])
         expr(p, it, rec)
 
-proc IsConstClosure(n: PNode): bool {.inline.} =
+proc isConstClosure(n: PNode): bool {.inline.} =
   result = n.sons[0].kind == nkSym and isRoutine(n.sons[0].sym) and
       n.sons[1].kind == nkNilLit
       
 proc genClosure(p: BProc, n: PNode, d: var TLoc) =
   assert n.kind == nkClosure
   
-  if IsConstClosure(n):
+  if isConstClosure(n):
     inc(p.labels)
     var tmp = con("LOC", toRope(p.labels))
     appf(p.module.s[cfsData], "NIM_CONST $1 $2 = $3;$n",
@@ -1760,7 +1776,7 @@ proc downConv(p: BProc, n: PNode, d: var TLoc) =
 proc exprComplexConst(p: BProc, n: PNode, d: var TLoc) =
   var t = getUniqueType(n.typ)
   discard getTypeDesc(p.module, t) # so that any fields are initialized
-  var id = NodeTableTestOrSet(p.module.dataCache, n, gBackendId)
+  var id = nodeTableTestOrSet(p.module.dataCache, n, gBackendId)
   var tmp = con("TMP", toRope(id))
   
   if id == gBackendId:
@@ -1778,7 +1794,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
   case n.kind
   of nkSym:
     var sym = n.sym
-    case sym.Kind
+    case sym.kind
     of skMethod:
       if sym.getBody.kind == nkEmpty or sfDispatcher in sym.flags:
         # we cannot produce code for the dispatcher yet:
@@ -1790,7 +1806,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
     of skProc, skConverter, skIterator:
       genProc(p.module, sym)
       if sym.loc.r == nil or sym.loc.t == nil:
-        InternalError(n.info, "expr: proc not init " & sym.name.s)
+        internalError(n.info, "expr: proc not init " & sym.name.s)
       putLocIntoDest(p, d, sym.loc)
     of skConst:
       if sfFakeConst in sym.flags:
@@ -1805,9 +1821,9 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
     of skVar, skForVar, skResult, skLet:
       if sfGlobal in sym.flags: genVarPrototype(p.module, sym)
       if sym.loc.r == nil or sym.loc.t == nil:
-        InternalError(n.info, "expr: var not init " & sym.name.s)
+        internalError(n.info, "expr: var not init " & sym.name.s)
       if sfThread in sym.flags:
-        AccessThreadLocalVar(p, sym)
+        accessThreadLocalVar(p, sym)
         if emulatedThreadVars(): 
           putIntoDest(p, d, sym.loc.t, con("NimTV->", sym.loc.r))
         else:
@@ -1816,13 +1832,13 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
         putLocIntoDest(p, d, sym.loc)
     of skTemp:
       if sym.loc.r == nil or sym.loc.t == nil:
-        InternalError(n.info, "expr: temp not init " & sym.name.s)
+        internalError(n.info, "expr: temp not init " & sym.name.s)
       putLocIntoDest(p, d, sym.loc)
     of skParam:
       if sym.loc.r == nil or sym.loc.t == nil:
-        InternalError(n.info, "expr: param not init " & sym.name.s)
+        internalError(n.info, "expr: param not init " & sym.name.s)
       putLocIntoDest(p, d, sym.loc)
-    else: InternalError(n.info, "expr(" & $sym.kind & "); unknown symbol")
+    else: internalError(n.info, "expr(" & $sym.kind & "); unknown symbol")
   of nkNilLit:
     if not isEmptyType(n.typ):
       putIntoDest(p, d, n.typ, genLiteral(p, n))
@@ -1876,7 +1892,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
     of tySequence, tyString: genSeqElem(p, n, d)
     of tyCString: genCStringElem(p, n, d)
     of tyTuple: genTupleElem(p, n, d)
-    else: InternalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
+    else: internalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
   of nkDerefExpr, nkHiddenDeref: genDeref(p, n, d)
   of nkDotExpr: genRecordField(p, n, d)
   of nkCheckedFieldExpr: genCheckedRecordField(p, n, d)
@@ -1896,12 +1912,12 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
     var sym = n.sons[namePos].sym
     genProc(p.module, sym)
     if sym.loc.r == nil or sym.loc.t == nil:
-      InternalError(n.info, "expr: proc not init " & sym.name.s)
+      internalError(n.info, "expr: proc not init " & sym.name.s)
     putLocIntoDest(p, d, sym.loc)
   of nkClosure: genClosure(p, n, d)
   of nkMetaNode: expr(p, n.sons[0], d)
 
-  of nkEmpty:  nil
+  of nkEmpty: discard
   of nkWhileStmt: genWhileStmt(p, n)
   of nkVarSection, nkLetSection: genVarStmt(p, n)
   of nkConstSection: genConstStmt(p, n)
@@ -1931,7 +1947,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
   of nkCommentStmt, nkIteratorDef, nkIncludeStmt, 
      nkImportStmt, nkImportExceptStmt, nkExportStmt, nkExportExceptStmt, 
      nkFromStmt, nkTemplateDef, nkMacroDef: 
-    nil
+    discard
   of nkPragma: genPragma(p, n)
   of nkProcDef, nkMethodDef, nkConverterDef: 
     if (n.sons[genericParamsPos].kind == nkEmpty):
@@ -1952,7 +1968,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc) =
   of nkState: genState(p, n)
   of nkGotoState: genGotoState(p, n)
   of nkBreakState: genBreakState(p, n)
-  else: InternalError(n.info, "expr(" & $n.kind & "); unknown node kind")
+  else: internalError(n.info, "expr(" & $n.kind & "); unknown node kind")
 
 proc genNamedConstExpr(p: BProc, n: PNode): PRope =
   if n.kind == nkExprColonExpr: result = genConstExpr(p, n.sons[1])
@@ -1990,7 +2006,7 @@ proc genConstSeq(p: BProc, n: PNode, t: PType): PRope =
   result = ropef("(($1)&$2)", [getTypeDesc(p.module, t), result])
 
 proc genConstExpr(p: BProc, n: PNode): PRope =
-  case n.Kind
+  case n.kind
   of nkHiddenStdConv, nkHiddenSubConv:
     result = genConstExpr(p, n.sons[1])
   of nkCurly:
diff --git a/compiler/ccgmerge.nim b/compiler/ccgmerge.nim
index c6c294b97..5b04f1358 100644
--- a/compiler/ccgmerge.nim
+++ b/compiler/ccgmerge.nim
@@ -108,7 +108,7 @@ proc genMergeInfo*(m: BModule): PRope =
   s.add("labels:")
   encodeVInt(m.labels, s)
   s.add(" hasframe:")
-  encodeVInt(ord(m.FrameDeclared), s)
+  encodeVInt(ord(m.frameDeclared), s)
   s.add(tnl)
   s.add("*/")
   result = s.toRope
@@ -119,8 +119,8 @@ proc skipWhite(L: var TBaseLexer) =
   var pos = L.bufpos
   while true:
     case ^pos
-    of CR: pos = nimlexbase.HandleCR(L, pos)
-    of LF: pos = nimlexbase.HandleLF(L, pos)
+    of CR: pos = nimlexbase.handleCR(L, pos)
+    of LF: pos = nimlexbase.handleLF(L, pos)
     of ' ': inc pos
     else: break
   L.bufpos = pos
@@ -129,8 +129,8 @@ proc skipUntilCmd(L: var TBaseLexer) =
   var pos = L.bufpos
   while true:
     case ^pos
-    of CR: pos = nimlexbase.HandleCR(L, pos)
-    of LF: pos = nimlexbase.HandleLF(L, pos)
+    of CR: pos = nimlexbase.handleCR(L, pos)
+    of LF: pos = nimlexbase.handleLF(L, pos)
     of '\0': break
     of '/': 
       if ^(pos+1) == '*' and ^(pos+2) == '\t':
@@ -179,15 +179,15 @@ proc readVerbatimSection(L: var TBaseLexer): PRope =
   while true:
     case buf[pos]
     of CR:
-      pos = nimlexbase.HandleCR(L, pos)
+      pos = nimlexbase.handleCR(L, pos)
       buf = L.buf
       r.add(tnl)
     of LF:
-      pos = nimlexbase.HandleLF(L, pos)
+      pos = nimlexbase.handleLF(L, pos)
       buf = L.buf
       r.add(tnl)
     of '\0':
-      InternalError("ccgmerge: expected: " & NimMergeEndMark)
+      internalError("ccgmerge: expected: " & NimMergeEndMark)
       break
     else: 
       if atEndMark(buf, pos):
@@ -208,7 +208,7 @@ proc readKey(L: var TBaseLexer, result: var string) =
   if buf[pos] != ':': internalError("ccgmerge: ':' expected")
   L.bufpos = pos + 1 # skip ':'
 
-proc NewFakeType(id: int): PType = 
+proc newFakeType(id: int): PType = 
   new(result)
   result.id = id
 
@@ -224,7 +224,7 @@ proc readTypeCache(L: var TBaseLexer, result: var TIdTable) =
     # XXX little hack: we create a "fake" type object with the correct Id
     # better would be to adapt the data structure to not even store the
     # object as key, but only the Id
-    IdTablePut(result, newFakeType(key), value.toRope)
+    idTablePut(result, newFakeType(key), value.toRope)
   inc L.bufpos
 
 proc readIntSet(L: var TBaseLexer, result: var TIntSet) =
@@ -249,14 +249,14 @@ proc processMergeInfo(L: var TBaseLexer, m: BModule) =
     of "declared":  readIntSet(L, m.declaredThings)
     of "typeInfo":  readIntSet(L, m.typeInfoMarker)
     of "labels":    m.labels = decodeVInt(L.buf, L.bufpos)
-    of "hasframe":  m.FrameDeclared = decodeVInt(L.buf, L.bufpos) != 0
-    else: InternalError("ccgmerge: unkown key: " & k)
+    of "hasframe":  m.frameDeclared = decodeVInt(L.buf, L.bufpos) != 0
+    else: internalError("ccgmerge: unkown key: " & k)
 
 when not defined(nimhygiene):
   {.pragma: inject.}
   
 template withCFile(cfilename: string, body: stmt) {.immediate.} = 
-  var s = LLStreamOpen(cfilename, fmRead)
+  var s = llStreamOpen(cfilename, fmRead)
   if s == nil: return
   var L {.inject.}: TBaseLexer
   openBaseLexer(L, s)
@@ -285,7 +285,7 @@ proc readMergeSections(cfilename: string, m: var TMergeSections) =
   withCFile(cfilename):
     readKey(L, k)
     if k == "NIM_merge_INFO":   
-      nil
+      discard
     elif ^L.bufpos == '*' and ^(L.bufpos+1) == '/':
       inc(L.bufpos, 2)
       # read back into section
@@ -300,9 +300,9 @@ proc readMergeSections(cfilename: string, m: var TMergeSections) =
         if sectionB >= 0 and sectionB <= high(TCProcSection).int:
           m.p[TCProcSection(sectionB)] = verbatim
         else:
-          InternalError("ccgmerge: unknown section: " & k)
+          internalError("ccgmerge: unknown section: " & k)
     else:
-      InternalError("ccgmerge: '*/' expected")
+      internalError("ccgmerge: '*/' expected")
 
 proc mergeRequired*(m: BModule): bool =
   for i in cfsHeaders..cfsProcs:
@@ -323,4 +323,3 @@ proc mergeFiles*(cfilename: string, m: BModule) =
     m.s[i] = con(old.f[i], m.s[i])
   for i in low(TCProcSection)..high(TCProcSection):
     m.initProc.s(i) = con(old.p[i], m.initProc.s(i))
-
diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim
index ac4bbb79f..af0d657f1 100644
--- a/compiler/ccgstmts.nim
+++ b/compiler/ccgstmts.nim
@@ -16,7 +16,7 @@ const
     # above X strings a hash-switch for strings is generated
 
 proc registerGcRoot(p: BProc, v: PSym) =
-  if gSelectedGc in {gcMarkAndSweep, gcGenerational} and
+  if gSelectedGC in {gcMarkAndSweep, gcGenerational} and
       containsGarbageCollectedRef(v.loc.t):
     # we register a specialized marked proc here; this has the advantage
     # that it works out of the box for thread local storage then :-)
@@ -26,7 +26,7 @@ proc registerGcRoot(p: BProc, v: PSym) =
 
 proc genVarTuple(p: BProc, n: PNode) = 
   var tup, field: TLoc
-  if n.kind != nkVarTuple: InternalError(n.info, "genVarTuple")
+  if n.kind != nkVarTuple: internalError(n.info, "genVarTuple")
   var L = sonsLen(n)
   genLineDir(p, n)
   initLocExpr(p, n.sons[L-1], tup)
@@ -45,7 +45,7 @@ proc genVarTuple(p: BProc, n: PNode) =
     if t.kind == tyTuple: 
       field.r = ropef("$1.Field$2", [rdLoc(tup), toRope(i)])
     else: 
-      if t.n.sons[i].kind != nkSym: InternalError(n.info, "genVarTuple")
+      if t.n.sons[i].kind != nkSym: internalError(n.info, "genVarTuple")
       field.r = ropef("$1.$2", 
                       [rdLoc(tup), mangleRecFieldName(t.n.sons[i].sym, t)])
     putLocIntoDest(p, v.loc, field)
@@ -62,7 +62,7 @@ proc startBlock(p: BProc, start: TFormatStr = "{$n",
   lineCg(p, cpsStmts, start, args)
   inc(p.labels)
   result = len(p.blocks)
-  setlen(p.blocks, result + 1)
+  setLen(p.blocks, result + 1)
   p.blocks[result].id = p.labels
   p.blocks[result].nestedTryStmts = p.nestedTryStmts.len.int16
 
@@ -81,7 +81,7 @@ proc endBlock(p: BProc, blockEnd: PRope) =
   let topBlock = p.blocks.len-1
   # the block is merged into the parent block
   app(p.blocks[topBlock-1].sections[cpsStmts], p.blocks[topBlock].blockBody)
-  setlen(p.blocks, topBlock)
+  setLen(p.blocks, topBlock)
   # this is done after the block is popped so $n is
   # properly indented when pretty printing is enabled
   line(p, cpsStmts, blockEnd)
@@ -126,7 +126,7 @@ proc genGotoState(p: BProc, n: PNode) =
   var a: TLoc
   initLocExpr(p, n.sons[0], a)
   lineF(p, cpsStmts, "switch ($1) {$n", [rdLoc(a)])
-  p.BeforeRetNeeded = true
+  p.beforeRetNeeded = true
   lineF(p, cpsStmts, "case -1: goto BeforeRet;$n", [])
   for i in 0 .. lastOrd(n.sons[0].typ):
     lineF(p, cpsStmts, "case $1: goto STATE$1;$n", [toRope(i)])
@@ -200,7 +200,7 @@ proc genConstStmt(p: BProc, t: PNode) =
   for i in countup(0, sonsLen(t) - 1): 
     var it = t.sons[i]
     if it.kind == nkCommentStmt: continue 
-    if it.kind != nkConstDef: InternalError(t.info, "genConstStmt")
+    if it.kind != nkConstDef: internalError(t.info, "genConstStmt")
     var c = it.sons[0].sym 
     if c.typ.containsCompileTimeOnly: continue
     if sfFakeConst in c.flags:
@@ -232,33 +232,33 @@ proc genIf(p: BProc, n: PNode, d: var TLoc) =
   #  Lend:
   var
     a: TLoc
-    Lelse: TLabel
+    lelse: TLabel
   if not isEmptyType(n.typ) and d.k == locNone:
     getTemp(p, n.typ, d)
   genLineDir(p, n)
-  let Lend = getLabel(p)
+  let lend = getLabel(p)
   for i in countup(0, sonsLen(n) - 1): 
     let it = n.sons[i]
     if it.len == 2: 
       when newScopeForIf: startBlock(p)
       initLocExpr(p, it.sons[0], a)
-      Lelse = getLabel(p)
+      lelse = getLabel(p)
       inc(p.labels)
       lineFF(p, cpsStmts, "if (!$1) goto $2;$n",
             "br i1 $1, label %LOC$3, label %$2$nLOC$3: $n",
-            [rdLoc(a), Lelse, toRope(p.labels)])
+            [rdLoc(a), lelse, toRope(p.labels)])
       when not newScopeForIf: startBlock(p)
       expr(p, it.sons[1], d)
       endBlock(p)
       if sonsLen(n) > 1:
-        lineFF(p, cpsStmts, "goto $1;$n", "br label %$1$n", [Lend])
-      fixLabel(p, Lelse)
+        lineFF(p, cpsStmts, "goto $1;$n", "br label %$1$n", [lend])
+      fixLabel(p, lelse)
     elif it.len == 1:
       startBlock(p)
       expr(p, it.sons[0], d)
       endBlock(p)
     else: internalError(n.info, "genIf()")
-  if sonsLen(n) > 1: fixLabel(p, Lend)
+  if sonsLen(n) > 1: fixLabel(p, lend)
 
 proc blockLeaveActions(p: BProc, howMany: int) = 
   var L = p.nestedTryStmts.len
@@ -296,7 +296,7 @@ proc genReturnStmt(p: BProc, t: PNode) =
 proc genComputedGoto(p: BProc; n: PNode) =
   # first pass: Generate array of computed labels:
   var casePos = -1
-  var arraySize: Int
+  var arraySize: int
   for i in 0 .. <n.len:
     let it = n.sons[i]
     if it.kind == nkCaseStmt:
@@ -322,8 +322,20 @@ proc genComputedGoto(p: BProc; n: PNode) =
     gotoArray.appf("&&TMP$#, ", (id+i).toRope)
   gotoArray.appf("&&TMP$#};$n", (id+arraySize).toRope)
   line(p, cpsLocals, gotoArray)
+
+  let topBlock = p.blocks.len-1
+  let oldBody = p.blocks[topBlock].sections[cpsStmts]
+  p.blocks[topBlock].sections[cpsStmts] = nil
   
+  for j in casePos+1 .. <n.len: genStmts(p, n.sons[j])
+  let tailB = p.blocks[topBlock].sections[cpsStmts]
+
+  p.blocks[topBlock].sections[cpsStmts] = nil
   for j in 0 .. casePos-1: genStmts(p, n.sons[j])
+  let tailA = p.blocks[topBlock].sections[cpsStmts]
+
+  p.blocks[topBlock].sections[cpsStmts] = oldBody.con(tailA)
+
   let caseStmt = n.sons[casePos]
   var a: TLoc
   initLocExpr(p, caseStmt.sons[0], a)
@@ -340,8 +352,11 @@ proc genComputedGoto(p: BProc; n: PNode) =
       let val = getOrdValue(it.sons[j])
       lineF(p, cpsStmts, "TMP$#:$n", intLiteral(val+id+1))
     genStmts(p, it.lastSon)
-    for j in casePos+1 .. <n.len: genStmts(p, n.sons[j])
-    for j in 0 .. casePos-1: genStmts(p, n.sons[j])
+    #for j in casePos+1 .. <n.len: genStmts(p, n.sons[j]) # tailB
+    #for j in 0 .. casePos-1: genStmts(p, n.sons[j])  # tailA
+    app(p.s(cpsStmts), tailB)
+    app(p.s(cpsStmts), tailA)
+
     var a: TLoc
     initLocExpr(p, caseStmt.sons[0], a)
     lineF(p, cpsStmts, "goto *$#[$#];$n", tmp, a.rdLoc)
@@ -352,7 +367,7 @@ proc genWhileStmt(p: BProc, t: PNode) =
   # significantly worse code
   var 
     a: TLoc
-    Labl: TLabel
+    labl: TLabel
   assert(sonsLen(t) == 2)
   inc(p.withinLoop)
   genLineDir(p, t)
@@ -366,7 +381,7 @@ proc genWhileStmt(p: BProc, t: PNode) =
       lineF(p, cpsStmts, "if (!$1) goto $2;$n", [rdLoc(a), label])
     var loopBody = t.sons[1]
     if loopBody.stmtsContainPragma(wComputedGoto) and
-        hasComputedGoto in CC[ccompiler].props:
+        hasComputedGoto in CC[cCompiler].props:
       # for closure support weird loop bodies are generated:
       if loopBody.len == 2 and loopBody.sons[0].kind == nkEmpty:
         loopBody = loopBody.sons[1]
@@ -401,7 +416,7 @@ proc genParForStmt(p: BProc, t: PNode) =
   preserveBreakIdx:
     let forLoopVar = t.sons[0].sym
     var rangeA, rangeB: TLoc
-    assignLocalVar(P, forLoopVar)
+    assignLocalVar(p, forLoopVar)
     #initLoc(forLoopVar.loc, locLocalVar, forLoopVar.typ, onStack)
     #discard mangleName(forLoopVar)
     let call = t.sons[1]
@@ -433,7 +448,7 @@ proc genBreakStmt(p: BProc, t: PNode) =
     # an unnamed 'break' can only break a loop after 'transf' pass:
     while idx >= 0 and not p.blocks[idx].isLoop: dec idx
     if idx < 0 or not p.blocks[idx].isLoop:
-      InternalError(t.info, "no loop to break")
+      internalError(t.info, "no loop to break")
   let label = assignLabel(p.blocks[idx])
   blockLeaveActions(p, p.nestedTryStmts.len - p.blocks[idx].nestedTryStmts)
   genLineDir(p, t)
@@ -454,7 +469,7 @@ proc genRaiseStmt(p: BProc, t: PNode) =
       genSimpleBlock(p, finallyBlock.sons[0])
   if t.sons[0].kind != nkEmpty: 
     var a: TLoc
-    InitLocExpr(p, t.sons[0], a)
+    initLocExpr(p, t.sons[0], a)
     var e = rdLoc(a)
     var typ = skipTypes(t.sons[0].typ, abstractPtrs)
     genLineDir(p, t)
@@ -484,16 +499,16 @@ proc genCaseGenericBranch(p: BProc, b: PNode, e: TLoc,
 
 proc genCaseSecondPass(p: BProc, t: PNode, d: var TLoc, 
                        labId, until: int): TLabel = 
-  var Lend = getLabel(p)
+  var lend = getLabel(p)
   for i in 1..until:
     lineF(p, cpsStmts, "LA$1: ;$n", [toRope(labId + i)])
     if t.sons[i].kind == nkOfBranch:
       var length = sonsLen(t.sons[i])
       exprBlock(p, t.sons[i].sons[length - 1], d)
-      lineF(p, cpsStmts, "goto $1;$n", [Lend])
+      lineF(p, cpsStmts, "goto $1;$n", [lend])
     else:
       exprBlock(p, t.sons[i].sons[0], d)
-  result = Lend
+  result = lend
 
 proc genIfForCaseUntil(p: BProc, t: PNode, d: var TLoc,
                        rangeFormat, eqFormat: TFormatStr,
@@ -520,8 +535,8 @@ proc genCaseGeneric(p: BProc, t: PNode, d: var TLoc,
                     rangeFormat, eqFormat: TFormatStr) = 
   var a: TLoc
   initLocExpr(p, t.sons[0], a)
-  var Lend = genIfForCaseUntil(p, t, d, rangeFormat, eqFormat, sonsLen(t)-1, a)
-  fixLabel(p, Lend)
+  var lend = genIfForCaseUntil(p, t, d, rangeFormat, eqFormat, sonsLen(t)-1, a)
+  fixLabel(p, lend)
 
 proc genCaseStringBranch(p: BProc, b: PNode, e: TLoc, labl: TLabel, 
                          branches: var openArray[PRope]) = 
@@ -565,25 +580,25 @@ proc genStringCase(p: BProc, t: PNode, d: var TLoc) =
     if t.sons[sonsLen(t)-1].kind != nkOfBranch: 
       lineF(p, cpsStmts, "goto LA$1;$n", [toRope(p.labels)]) 
     # third pass: generate statements
-    var Lend = genCaseSecondPass(p, t, d, labId, sonsLen(t)-1)
-    fixLabel(p, Lend)
+    var lend = genCaseSecondPass(p, t, d, labId, sonsLen(t)-1)
+    fixLabel(p, lend)
   else:
     genCaseGeneric(p, t, d, "", "if (#eqStrings($1, $2)) goto $3;$n")
   
 proc branchHasTooBigRange(b: PNode): bool = 
   for i in countup(0, sonsLen(b)-2): 
     # last son is block
-    if (b.sons[i].Kind == nkRange) and
+    if (b.sons[i].kind == nkRange) and
         b.sons[i].sons[1].intVal - b.sons[i].sons[0].intVal > RangeExpandLimit: 
       return true
 
-proc IfSwitchSplitPoint(p: BProc, n: PNode): int =
+proc ifSwitchSplitPoint(p: BProc, n: PNode): int =
   for i in 1..n.len-1:
     var branch = n[i]
     var stmtBlock = lastSon(branch)
     if stmtBlock.stmtsContainPragma(wLinearScanEnd):
       result = i
-    elif hasSwitchRange notin CC[ccompiler].props: 
+    elif hasSwitchRange notin CC[cCompiler].props: 
       if branch.kind == nkOfBranch and branchHasTooBigRange(branch): 
         result = i
 
@@ -591,7 +606,7 @@ proc genCaseRange(p: BProc, branch: PNode) =
   var length = branch.len
   for j in 0 .. length-2: 
     if branch[j].kind == nkRange: 
-      if hasSwitchRange in CC[ccompiler].props: 
+      if hasSwitchRange in CC[cCompiler].props: 
         lineF(p, cpsStmts, "case $1 ... $2:$n", [
             genLiteral(p, branch[j][0]), 
             genLiteral(p, branch[j][1])])
@@ -599,18 +614,18 @@ proc genCaseRange(p: BProc, branch: PNode) =
         var v = copyNode(branch[j][0])
         while v.intVal <= branch[j][1].intVal: 
           lineF(p, cpsStmts, "case $1:$n", [genLiteral(p, v)])
-          Inc(v.intVal)
+          inc(v.intVal)
     else:
       lineF(p, cpsStmts, "case $1:$n", [genLiteral(p, branch[j])])
 
 proc genOrdinalCase(p: BProc, n: PNode, d: var TLoc) =
   # analyse 'case' statement:
-  var splitPoint = IfSwitchSplitPoint(p, n)
+  var splitPoint = ifSwitchSplitPoint(p, n)
   
   # generate if part (might be empty):
   var a: TLoc
   initLocExpr(p, n.sons[0], a)
-  var Lend = if splitPoint > 0: genIfForCaseUntil(p, n, d,
+  var lend = if splitPoint > 0: genIfForCaseUntil(p, n, d,
                     rangeFormat = "if ($1 >= $2 && $1 <= $3) goto $4;$n",
                     eqFormat = "if ($1 == $2) goto $3;$n", 
                     splitPoint, a) else: nil
@@ -629,10 +644,10 @@ proc genOrdinalCase(p: BProc, n: PNode, d: var TLoc) =
         hasDefault = true
       exprBlock(p, branch.lastSon, d)
       lineF(p, cpsStmts, "break;$n")
-    if (hasAssume in CC[ccompiler].props) and not hasDefault: 
+    if (hasAssume in CC[cCompiler].props) and not hasDefault: 
       lineF(p, cpsStmts, "default: __assume(0);$n")
     lineF(p, cpsStmts, "}$n")
-  if Lend != nil: fixLabel(p, Lend)
+  if lend != nil: fixLabel(p, lend)
   
 proc genCase(p: BProc, t: PNode, d: var TLoc) = 
   genLineDir(p, t)
@@ -691,7 +706,7 @@ proc genTryCpp(p: BProc, t: PNode, d: var TLoc) =
   expr(p, t.sons[0], d)
   length = sonsLen(t)
   endBlock(p, ropecg(p.module, "} catch (NimException& $1) {$n", [exc]))
-  if optStackTrace in p.Options:
+  if optStackTrace in p.options:
     linefmt(p, cpsStmts, "#setFrame((TFrame*)&F);$n")
   inc p.inExceptBlock
   i = 1
@@ -764,7 +779,7 @@ proc genTry(p: BProc, t: PNode, d: var TLoc) =
   #
   if not isEmptyType(t.typ) and d.k == locNone:
     getTemp(p, t.typ, d)
-  discard lists.IncludeStr(p.module.headerFiles, "<setjmp.h>")
+  discard lists.includeStr(p.module.headerFiles, "<setjmp.h>")
   genLineDir(p, t)
   var safePoint = getTempName()
   discard cgsym(p.module, "E_Base")
@@ -779,7 +794,7 @@ proc genTry(p: BProc, t: PNode, d: var TLoc) =
   endBlock(p)
   startBlock(p, "else {$n")
   linefmt(p, cpsStmts, "#popSafePoint();$n")
-  if optStackTrace in p.Options:
+  if optStackTrace in p.options:
     linefmt(p, cpsStmts, "#setFrame((TFrame*)&F);$n")
   inc p.inExceptBlock
   var i = 1
@@ -818,7 +833,7 @@ proc genTry(p: BProc, t: PNode, d: var TLoc) =
 proc genAsmOrEmitStmt(p: BProc, t: PNode, isAsmStmt=false): PRope =
   var res = ""
   for i in countup(0, sonsLen(t) - 1):
-    case t.sons[i].Kind
+    case t.sons[i].kind
     of nkStrLit..nkTripleStrLit:
       res.add(t.sons[i].strVal)
     of nkSym:
@@ -835,9 +850,9 @@ proc genAsmOrEmitStmt(p: BProc, t: PNode, isAsmStmt=false): PRope =
           r = mangleName(sym)
           sym.loc.r = r       # but be consequent!
         res.add(r.ropeToStr)
-    else: InternalError(t.sons[i].info, "genAsmOrEmitStmt()")
+    else: internalError(t.sons[i].info, "genAsmOrEmitStmt()")
   
-  if isAsmStmt and hasGnuAsm in CC[ccompiler].props:
+  if isAsmStmt and hasGnuAsm in CC[cCompiler].props:
     for x in splitLines(res):
       var j = 0
       while x[j] in {' ', '\t'}: inc(j)
@@ -858,9 +873,9 @@ proc genAsmStmt(p: BProc, t: PNode) =
   var s = genAsmOrEmitStmt(p, t, isAsmStmt=true)
   if p.prc == nil:
     # top level asm statement?
-    appf(p.module.s[cfsProcHeaders], CC[ccompiler].asmStmtFrmt, [s])
+    appf(p.module.s[cfsProcHeaders], CC[cCompiler].asmStmtFrmt, [s])
   else:
-    lineF(p, cpsStmts, CC[ccompiler].asmStmtFrmt, [s])
+    lineF(p, cpsStmts, CC[cCompiler].asmStmtFrmt, [s])
 
 proc genEmit(p: BProc, t: PNode) = 
   genLineDir(p, t)
@@ -877,7 +892,7 @@ var
 
 proc genBreakPoint(p: BProc, t: PNode) = 
   var name: string
-  if optEndb in p.Options:
+  if optEndb in p.options:
     if t.kind == nkExprColonExpr: 
       assert(t.sons[1].kind in {nkStrLit..nkTripleStrLit})
       name = normalize(t.sons[1].strVal)
@@ -891,7 +906,7 @@ proc genBreakPoint(p: BProc, t: PNode) =
         makeCString(name)])
 
 proc genWatchpoint(p: BProc, n: PNode) =
-  if optEndb notin p.Options: return
+  if optEndb notin p.options: return
   var a: TLoc
   initLocExpr(p, n.sons[1], a)
   let typ = skipTypes(n.sons[1].typ, abstractVarRange)
@@ -905,7 +920,7 @@ proc genPragma(p: BProc, n: PNode) =
     case whichPragma(it)
     of wEmit: genEmit(p, it)
     of wBreakpoint: genBreakPoint(p, it)
-    of wWatchpoint: genWatchpoint(p, it)
+    of wWatchPoint: genWatchpoint(p, it)
     of wInjectStmt: 
       var p = newProc(nil, p.module)
       p.options = p.options - {optLineTrace, optStackTrace}
@@ -913,7 +928,7 @@ proc genPragma(p: BProc, n: PNode) =
       p.module.injectStmt = p.s(cpsStmts)
     else: discard
 
-proc FieldDiscriminantCheckNeeded(p: BProc, asgn: PNode): bool = 
+proc fieldDiscriminantCheckNeeded(p: BProc, asgn: PNode): bool = 
   if optFieldCheck in p.options:
     var le = asgn.sons[0]
     if le.kind == nkCheckedFieldExpr:
@@ -929,7 +944,7 @@ proc genDiscriminantCheck(p: BProc, a, tmp: TLoc, objtype: PType,
   assert t.kind == tyObject
   discard genTypeInfo(p.module, t)
   var L = lengthOrd(field.typ)
-  if not ContainsOrIncl(p.module.declaredThings, field.id):
+  if not containsOrIncl(p.module.declaredThings, field.id):
     appcg(p.module, cfsVars, "extern $1", 
           discriminatorTableDecl(p.module, t, field))
   lineCg(p, cpsStmts,
@@ -942,7 +957,7 @@ proc asgnFieldDiscriminant(p: BProc, e: PNode) =
   var dotExpr = e.sons[0]
   var d: PSym
   if dotExpr.kind == nkCheckedFieldExpr: dotExpr = dotExpr.sons[0]
-  InitLocExpr(p, e.sons[0], a)
+  initLocExpr(p, e.sons[0], a)
   getTemp(p, a.t, tmp)
   expr(p, e.sons[1], tmp)
   genDiscriminantCheck(p, a, tmp, dotExpr.sons[0].typ, dotExpr.sons[1].sym)
@@ -950,9 +965,9 @@ proc asgnFieldDiscriminant(p: BProc, e: PNode) =
   
 proc genAsgn(p: BProc, e: PNode, fastAsgn: bool) = 
   genLineDir(p, e)
-  if not FieldDiscriminantCheckNeeded(p, e):
+  if not fieldDiscriminantCheckNeeded(p, e):
     var a: TLoc
-    InitLocExpr(p, e.sons[0], a)
+    initLocExpr(p, e.sons[0], a)
     if fastAsgn: incl(a.flags, lfNoDeepCopy)
     assert(a.t != nil)
     loadInto(p, e.sons[0], e.sons[1], a)
@@ -962,4 +977,4 @@ proc genAsgn(p: BProc, e: PNode, fastAsgn: bool) =
 proc genStmts(p: BProc, t: PNode) = 
   var a: TLoc
   expr(p, t, a)
-  InternalAssert a.k in {locNone, locTemp, locLocalVar}
+  internalAssert a.k in {locNone, locTemp, locLocalVar}
diff --git a/compiler/ccgthreadvars.nim b/compiler/ccgthreadvars.nim
index d312ea027..c00b931ef 100644
--- a/compiler/ccgthreadvars.nim
+++ b/compiler/ccgthreadvars.nim
@@ -16,8 +16,8 @@ proc emulatedThreadVars(): bool =
   result = {optThreads, optTlsEmulation} <= gGlobalOptions
 
 proc accessThreadLocalVar(p: BProc, s: PSym) =
-  if emulatedThreadVars() and not p.ThreadVarAccessed:
-    p.ThreadVarAccessed = true
+  if emulatedThreadVars() and not p.threadVarAccessed:
+    p.threadVarAccessed = true
     p.module.usesThreadVars = true
     appf(p.procSec(cpsLocals), "\tNimThreadVars* NimTV;$n")
     app(p.procSec(cpsInit),
@@ -55,7 +55,7 @@ proc generateThreadLocalStorage(m: BModule) =
     for t in items(nimtvDeps): discard getTypeDesc(m, t)
     appf(m.s[cfsSeqTypes], "typedef struct {$1} NimThreadVars;$n", [nimtv])
 
-proc GenerateThreadVarsSize(m: BModule) =
+proc generateThreadVarsSize(m: BModule) =
   if nimtv != nil:
     app(m.s[cfsProcs], 
       "NI NimThreadVarsSize(){return (NI)sizeof(NimThreadVars);}" & tnl)
diff --git a/compiler/ccgtrav.nim b/compiler/ccgtrav.nim
index 9534eae91..26f474659 100644
--- a/compiler/ccgtrav.nim
+++ b/compiler/ccgtrav.nim
@@ -28,7 +28,7 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: PRope, n: PNode) =
     for i in countup(0, sonsLen(n) - 1):
       genTraverseProc(c, accessor, n.sons[i])
   of nkRecCase:
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "genTraverseProc")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "genTraverseProc")
     var p = c.p
     let disc = n.sons[0].sym
     lineF(p, cpsStmts, "switch ($1.$2) {$n", accessor, disc.loc.r)
@@ -74,7 +74,7 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: PRope, typ: PType) =
       genTraverseProc(c, accessor.parentObj, typ.sons[i])
     if typ.n != nil: genTraverseProc(c, accessor, typ.n)
   of tyTuple:
-    let typ = GetUniqueType(typ)
+    let typ = getUniqueType(typ)
     for i in countup(0, sonsLen(typ) - 1):
       genTraverseProc(c, rfmt(nil, "$1.Field$2", accessor, i.toRope), typ.sons[i])
   of tyRef, tyString, tySequence:
@@ -83,7 +83,7 @@ proc genTraverseProc(c: var TTraversalClosure, accessor: PRope, typ: PType) =
     if typ.callConv == ccClosure:
       lineCg(p, cpsStmts, c.visitorFrmt, rfmt(nil, "$1.ClEnv", accessor))
   else:
-    nil
+    discard
 
 proc genTraverseProcSeq(c: var TTraversalClosure, accessor: PRope, typ: PType) =
   var p = c.p
@@ -111,7 +111,7 @@ proc genTraverseProc(m: BModule, typ: PType, reason: TTypeInfoReason): PRope =
   lineF(p, cpsInit, "a = ($1)p;$n", t)
   
   c.p = p
-  assert typ.kind != tyTypedesc
+  assert typ.kind != tyTypeDesc
   if typ.kind == tySequence:
     genTraverseProcSeq(c, "a".toRope, typ)
   else:
diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim
index 4548ac641..c92c15fa9 100644
--- a/compiler/ccgtypes.nim
+++ b/compiler/ccgtypes.nim
@@ -25,7 +25,7 @@ proc mangleField(name: string): string =
     of 'A'..'Z': 
       add(result, chr(ord(name[i]) - ord('A') + ord('a')))
     of '_': 
-      nil
+      discard
     of 'a'..'z', '0'..'9': 
       add(result, name[i])
     else: 
@@ -48,7 +48,7 @@ proc mangle(name: string): string =
     of 'A'..'Z': 
       add(result, chr(ord(name[i]) - ord('A') + ord('a')))
     of '_': 
-      nil
+      discard
     of 'a'..'z', '0'..'9': 
       add(result, name[i])
     else: 
@@ -76,7 +76,7 @@ proc mangleName(s: PSym): PRope =
         else: result = ~"%"
       of skTemp, skParam, skType, skEnumField, skModule: 
         result = ~"%"
-      else: InternalError(s.info, "mangleName")
+      else: internalError(s.info, "mangleName")
     when oKeepVariableNames:
       let keepOrigName = s.kind in skLocalVars - {skForVar} and 
         {sfFromGeneric, sfGlobal, sfShadowed, sfGenSym} * s.flags == {} and
@@ -150,7 +150,7 @@ proc getTypeName(typ: PType): PRope =
       typ.loc.r = if gCmd != cmdCompileToLLVM: con(typ.typeName, typ.id.toRope)
                   else: con([~"%", typ.typeName, typ.id.toRope])
     result = typ.loc.r
-  if result == nil: InternalError("getTypeName: " & $typ.kind)
+  if result == nil: internalError("getTypeName: " & $typ.kind)
   
 proc mapSetType(typ: PType): TCTypeKind =
   case int(getSize(typ))
@@ -194,7 +194,7 @@ proc mapType(typ: PType): TCTypeKind =
   of tyCString: result = ctCString
   of tyInt..tyUInt64:
     result = TCTypeKind(ord(typ.kind) - ord(tyInt) + ord(ctInt))
-  else: InternalError("mapType")
+  else: internalError("mapType")
   
 proc mapReturnType(typ: PType): TCTypeKind = 
   if skipTypes(typ, typedescInst).kind == tyArray: result = ctPtr
@@ -229,11 +229,11 @@ const
     "stdcall $1", "ccc $1", "safecall $1", "syscall $1", "$1 alwaysinline", 
     "$1 noinline", "fastcc $1", "ccc $1", "$1"]
 
-proc CacheGetType(tab: TIdTable, key: PType): PRope = 
+proc cacheGetType(tab: TIdTable, key: PType): PRope = 
   # returns nil if we need to declare this type
   # since types are now unique via the ``GetUniqueType`` mechanism, this slow
   # linear search is not necessary anymore:
-  result = PRope(IdTableGet(tab, key))
+  result = PRope(idTableGet(tab, key))
 
 proc getTempName(): PRope = 
   result = rfmt(nil, "TMP$1", toRope(backendId()))
@@ -246,7 +246,7 @@ proc ccgIntroducedPtr(s: PSym): bool =
   assert skResult != s.kind
   if tfByRef in pt.flags: return true
   elif tfByCopy in pt.flags: return false
-  case pt.Kind
+  case pt.kind
   of tyObject:
     if (optByRef in s.options) or (getSize(pt) > platform.floatSize * 2): 
       result = true           # requested anyway
@@ -262,7 +262,7 @@ proc ccgIntroducedPtr(s: PSym): bool =
 proc fillResult(param: PSym) = 
   fillLoc(param.loc, locParam, param.typ, ~"Result",
           OnStack)
-  if (mapReturnType(param.typ) != ctArray) and IsInvalidReturnType(param.typ): 
+  if (mapReturnType(param.typ) != ctArray) and isInvalidReturnType(param.typ): 
     incl(param.loc.flags, lfIndirect)
     param.loc.s = OnUnknown
 
@@ -288,7 +288,7 @@ proc genProcParams(m: BModule, t: PType, rettype, params: var PRope,
   else: 
     rettype = getTypeDescAux(m, t.sons[0], check)
   for i in countup(1, sonsLen(t.n) - 1): 
-    if t.n.sons[i].kind != nkSym: InternalError(t.n.info, "genProcParams")
+    if t.n.sons[i].kind != nkSym: internalError(t.n.info, "genProcParams")
     var param = t.n.sons[i].sym
     if isCompileTimeOnly(param.typ): continue
     if params != nil: app(params, ~", ")
@@ -305,7 +305,7 @@ proc genProcParams(m: BModule, t: PType, rettype, params: var PRope,
     var arr = param.typ
     if arr.kind == tyVar: arr = arr.sons[0]
     var j = 0
-    while arr.Kind in {tyOpenArray, tyVarargs}:
+    while arr.kind in {tyOpenArray, tyVarargs}:
       # this fixes the 'sort' bug:
       if param.typ.kind == tyVar: param.loc.s = OnUnknown
       # need to pass hidden parameter:
@@ -344,7 +344,7 @@ proc getSimpleTypeDesc(m: BModule, typ: PType): PRope =
       "NI", "NI8", "NI16", "NI32", "NI64",
       "NF", "NF32", "NF64", "NF128",
       "NU", "NU8", "NU16", "NU32", "NU64",]
-  case typ.Kind
+  case typ.kind
   of tyPointer: 
     result = typeNameOrLiteral(typ, "void*")
   of tyEnum: 
@@ -362,12 +362,12 @@ proc getSimpleTypeDesc(m: BModule, typ: PType): PRope =
   of tyString: 
     discard cgsym(m, "NimStringDesc")
     result = typeNameOrLiteral(typ, "NimStringDesc*")
-  of tyCstring: result = typeNameOrLiteral(typ, "NCSTRING")
+  of tyCString: result = typeNameOrLiteral(typ, "NCSTRING")
   of tyBool: result = typeNameOrLiteral(typ, "NIM_BOOL")
   of tyChar: result = typeNameOrLiteral(typ, "NIM_CHAR")
   of tyNil: result = typeNameOrLiteral(typ, "0")
   of tyInt..tyUInt64: 
-    result = typeNameOrLiteral(typ, NumericalTypeToStr[typ.Kind])
+    result = typeNameOrLiteral(typ, NumericalTypeToStr[typ.kind])
   of tyRange: result = getSimpleTypeDesc(m, typ.sons[0])
   else: result = nil
   
@@ -375,14 +375,14 @@ proc getTypePre(m: BModule, typ: PType): PRope =
   if typ == nil: result = toRope("void")
   else: 
     result = getSimpleTypeDesc(m, typ)
-    if result == nil: result = CacheGetType(m.typeCache, typ)
+    if result == nil: result = cacheGetType(m.typeCache, typ)
   
 proc getForwardStructFormat(): string = 
   if gCmd == cmdCompileToCpp: result = "struct $1;$n"
   else: result = "typedef struct $1 $1;$n"
   
 proc getTypeForward(m: BModule, typ: PType): PRope = 
-  result = CacheGetType(m.forwTypeCache, typ)
+  result = cacheGetType(m.forwTypeCache, typ)
   if result != nil: return 
   result = getTypePre(m, typ)
   if result != nil: return 
@@ -391,8 +391,8 @@ proc getTypeForward(m: BModule, typ: PType): PRope =
     result = getTypeName(typ)
     if not isImportedType(typ): 
       appf(m.s[cfsForwardTypes], getForwardStructFormat(), [result])
-    IdTablePut(m.forwTypeCache, typ, result)
-  else: InternalError("getTypeForward(" & $typ.kind & ')')
+    idTablePut(m.forwTypeCache, typ, result)
+  else: internalError("getTypeForward(" & $typ.kind & ')')
   
 proc mangleRecFieldName(field: PSym, rectype: PType): PRope = 
   if (rectype.sym != nil) and
@@ -400,7 +400,7 @@ proc mangleRecFieldName(field: PSym, rectype: PType): PRope =
     result = field.loc.r
   else:
     result = toRope(mangleField(field.name.s))
-  if result == nil: InternalError(field.info, "mangleRecFieldName")
+  if result == nil: internalError(field.info, "mangleRecFieldName")
   
 proc genRecordFieldsAux(m: BModule, n: PNode, 
                         accessExpr: PRope, rectype: PType, 
@@ -415,7 +415,7 @@ proc genRecordFieldsAux(m: BModule, n: PNode,
     for i in countup(0, sonsLen(n) - 1): 
       app(result, genRecordFieldsAux(m, n.sons[i], accessExpr, rectype, check))
   of nkRecCase: 
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "genRecordFieldsAux")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "genRecordFieldsAux")
     app(result, genRecordFieldsAux(m, n.sons[0], accessExpr, rectype, check))
     uname = toRope(mangle(n.sons[0].sym.name.s) & 'U')
     if accessExpr != nil: ae = ropef("$1.$2", [accessExpr, uname])
@@ -497,49 +497,49 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var TIntSet): PRope =
   # returns only the type's name
   var 
     name, rettype, desc, recdesc: PRope
-    n: biggestInt
+    n: BiggestInt
     t, et: PType
   t = getUniqueType(typ)
-  if t == nil: InternalError("getTypeDescAux: t == nil")
+  if t == nil: internalError("getTypeDescAux: t == nil")
   if t.sym != nil: useHeader(m, t.sym)
   result = getTypePre(m, t)
   if result != nil: return 
-  if ContainsOrIncl(check, t.id): 
-    InternalError("cannot generate C type for: " & typeToString(typ)) 
+  if containsOrIncl(check, t.id): 
+    internalError("cannot generate C type for: " & typeToString(typ)) 
     # XXX: this BUG is hard to fix -> we need to introduce helper structs,
     # but determining when this needs to be done is hard. We should split
     # C type generation into an analysis and a code generation phase somehow.
-  case t.Kind
+  case t.kind
   of tyRef, tyPtr, tyVar: 
     et = getUniqueType(t.sons[0])
     if et.kind in {tyArrayConstr, tyArray, tyOpenArray, tyVarargs}: 
       # this is correct! sets have no proper base type, so we treat
       # ``var set[char]`` in `getParamTypeDesc`
       et = getUniqueType(elemType(et))
-    case et.Kind
+    case et.kind
     of tyObject, tyTuple: 
       # no restriction! We have a forward declaration for structs
       name = getTypeForward(m, et)
       result = con(name, "*")
-      IdTablePut(m.typeCache, t, result)
+      idTablePut(m.typeCache, t, result)
       pushType(m, et)
     of tySequence: 
       # no restriction! We have a forward declaration for structs
       name = getTypeForward(m, et)
       result = con(name, "**")
-      IdTablePut(m.typeCache, t, result)
+      idTablePut(m.typeCache, t, result)
       pushType(m, et)
     else: 
       # else we have a strong dependency  :-(
       result = con(getTypeDescAux(m, et, check), "*")
-      IdTablePut(m.typeCache, t, result)
+      idTablePut(m.typeCache, t, result)
   of tyOpenArray, tyVarargs: 
     et = getUniqueType(t.sons[0])
     result = con(getTypeDescAux(m, et, check), "*")
-    IdTablePut(m.typeCache, t, result)
+    idTablePut(m.typeCache, t, result)
   of tyProc: 
     result = getTypeName(t)
-    IdTablePut(m.typeCache, t, result)
+    idTablePut(m.typeCache, t, result)
     genProcParams(m, t, rettype, desc, check)
     if not isImportedType(t): 
       if t.callConv != ccClosure: # procedure vars may need a closure!
@@ -553,14 +553,14 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var TIntSet): PRope =
   of tySequence: 
     # we cannot use getTypeForward here because then t would be associated
     # with the name of the struct, not with the pointer to the struct:
-    result = CacheGetType(m.forwTypeCache, t)
+    result = cacheGetType(m.forwTypeCache, t)
     if result == nil: 
       result = getTypeName(t)
       if not isImportedType(t): 
         appf(m.s[cfsForwardTypes], getForwardStructFormat(), [result])
-      IdTablePut(m.forwTypeCache, t, result)
-    assert(CacheGetType(m.typeCache, t) == nil)
-    IdTablePut(m.typeCache, t, con(result, "*"))
+      idTablePut(m.forwTypeCache, t, result)
+    assert(cacheGetType(m.typeCache, t) == nil)
+    idTablePut(m.typeCache, t, con(result, "*"))
     if not isImportedType(t): 
       if skipTypes(t.sons[0], typedescInst).kind != tyEmpty: 
         const
@@ -579,18 +579,18 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var TIntSet): PRope =
     if n <= 0: 
       n = 1                   # make an array of at least one element
     result = getTypeName(t)
-    IdTablePut(m.typeCache, t, result)
+    idTablePut(m.typeCache, t, result)
     if not isImportedType(t): 
       appf(m.s[cfsTypes], "typedef $1 $2[$3];$n", 
-           [getTypeDescAux(m, t.sons[1], check), result, ToRope(n)])
+           [getTypeDescAux(m, t.sons[1], check), result, toRope(n)])
   of tyObject, tyTuple: 
-    result = CacheGetType(m.forwTypeCache, t)
+    result = cacheGetType(m.forwTypeCache, t)
     if result == nil: 
       result = getTypeName(t)
       if not isImportedType(t): 
         appf(m.s[cfsForwardTypes], getForwardStructFormat(), [result])
-      IdTablePut(m.forwTypeCache, t, result)
-    IdTablePut(m.typeCache, t, result) # always call for sideeffects:
+      idTablePut(m.forwTypeCache, t, result)
+    idTablePut(m.typeCache, t, result) # always call for sideeffects:
     if t.kind != tyTuple: recdesc = getRecordDesc(m, t, result, check)
     else: recdesc = getTupleDesc(m, t, result, check)
     if not isImportedType(t): app(m.s[cfsTypes], recdesc)
@@ -602,7 +602,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var TIntSet): PRope =
     of 8: result = toRope("NU64")
     else: 
       result = getTypeName(t)
-      IdTablePut(m.typeCache, t, result)
+      idTablePut(m.typeCache, t, result)
       if not isImportedType(t): 
         appf(m.s[cfsTypes], "typedef NU8 $1[$2];$n", 
              [result, toRope(getSize(t))])
@@ -610,7 +610,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var TIntSet): PRope =
       tyIter, tyTypeDesc:
     result = getTypeDescAux(m, lastSon(t), check)
   else:
-    InternalError("getTypeDescAux(" & $t.kind & ')')
+    internalError("getTypeDescAux(" & $t.kind & ')')
     result = nil
   # fixes bug #145:
   excl(check, t.id)
@@ -737,10 +737,10 @@ proc discriminatorTableName(m: BModule, objtype: PType, d: PSym): PRope =
   var objtype = objtype
   while lookupInRecord(objtype.n, d.name) == nil:
     objtype = objtype.sons[0]
-  if objType.sym == nil: 
-    InternalError(d.info, "anonymous obj with discriminator")
+  if objtype.sym == nil: 
+    internalError(d.info, "anonymous obj with discriminator")
   result = ropef("NimDT_$1_$2", [
-    toRope(objType.sym.name.s.mangle), toRope(d.name.s.mangle)])
+    toRope(objtype.sym.name.s.mangle), toRope(d.name.s.mangle)])
 
 proc discriminatorTableDecl(m: BModule, objtype: PType, d: PSym): PRope = 
   discard cgsym(m, "TNimNode")
@@ -911,7 +911,7 @@ include ccgtrav
 proc genTypeInfo(m: BModule, t: PType): PRope = 
   var t = getUniqueType(t)
   result = ropef("NTI$1", [toRope(t.id)])
-  if ContainsOrIncl(m.typeInfoMarker, t.id):
+  if containsOrIncl(m.typeInfoMarker, t.id):
     return con("(&".toRope, result, ")".toRope)
   let owner = t.skipTypes(typedescPtrs).owner.getModule
   if owner != m.module:
@@ -948,8 +948,8 @@ proc genTypeInfo(m: BModule, t: PType): PRope =
     # BUGFIX: use consistently RTTI without proper field names; otherwise
     # results are not deterministic!
     genTupleInfo(m, t, result)
-  else: InternalError("genTypeInfo(" & $t.kind & ')')
+  else: internalError("genTypeInfo(" & $t.kind & ')')
   result = con("(&".toRope, result, ")".toRope)
 
 proc genTypeSection(m: BModule, n: PNode) = 
-  nil
+  discard
diff --git a/compiler/ccgutils.nim b/compiler/ccgutils.nim
index 310f7204a..1129ecbef 100644
--- a/compiler/ccgutils.nim
+++ b/compiler/ccgutils.nim
@@ -22,19 +22,19 @@ proc getPragmaStmt*(n: PNode, w: TSpecialWord): PNode =
   of nkPragma:
     for i in 0 .. < n.len: 
       if whichPragma(n[i]) == w: return n[i]
-  else: nil
+  else: discard
 
 proc stmtsContainPragma*(n: PNode, w: TSpecialWord): bool =
   result = getPragmaStmt(n, w) != nil
 
-proc hashString*(s: string): biggestInt = 
+proc hashString*(s: string): BiggestInt = 
   # has to be the same algorithm as system.hashString!
   if CPU[targetCPU].bit == 64: 
     # we have to use the same bitwidth
     # as the target CPU
     var b = 0'i64
     for i in countup(0, len(s) - 1): 
-      b = b +% Ord(s[i])
+      b = b +% ord(s[i])
       b = b +% `shl`(b, 10)
       b = b xor `shr`(b, 6)
     b = b +% `shl`(b, 3)
@@ -44,7 +44,7 @@ proc hashString*(s: string): biggestInt =
   else: 
     var a = 0'i32
     for i in countup(0, len(s) - 1): 
-      a = a +% Ord(s[i]).int32
+      a = a +% ord(s[i]).int32
       a = a +% `shl`(a, 10'i32)
       a = a xor `shr`(a, 6'i32)
     a = a +% `shl`(a, 3'i32)
@@ -57,7 +57,7 @@ var
   gCanonicalTypes: array[TTypeKind, PType]
 
 proc initTypeTables() = 
-  for i in countup(low(TTypeKind), high(TTypeKind)): InitIdTable(gTypeTable[i])
+  for i in countup(low(TTypeKind), high(TTypeKind)): initIdTable(gTypeTable[i])
 
 proc resetCaches* =
   ## XXX: fix that more properly
@@ -70,7 +70,7 @@ when false:
     for i in countup(low(TTypeKind), high(TTypeKind)): 
       echo i, " ", gTypeTable[i].counter
   
-proc GetUniqueType*(key: PType): PType = 
+proc getUniqueType*(key: PType): PType = 
   # this is a hotspot in the compiler!
   if key == nil: return 
   var k = key.kind
@@ -86,12 +86,11 @@ proc GetUniqueType*(key: PType): PType =
     if result == nil:
       gCanonicalTypes[k] = key
       result = key
-  of tyTypeDesc, tyTypeClasses:
-    InternalError("value expected, but got a type")
-  of tyGenericParam:
-    InternalError("GetUniqueType")
+  of tyTypeDesc, tyTypeClasses, tyGenericParam,
+     tyFromExpr, tyStatic, tyFieldAccessor:
+    internalError("GetUniqueType")
   of tyGenericInst, tyDistinct, tyOrdinal, tyMutable, tyConst, tyIter:
-    result = GetUniqueType(lastSon(key))
+    result = getUniqueType(lastSon(key))
   of tyArrayConstr, tyGenericInvokation, tyGenericBody,
      tyOpenArray, tyArray, tySet, tyRange, tyTuple,
      tyPtr, tyRef, tySequence, tyForward, tyVarargs, tyProxy, tyVar:
@@ -102,33 +101,33 @@ proc GetUniqueType*(key: PType): PType =
 
     # we have to do a slow linear search because types may need
     # to be compared by their structure:
-    if IdTableHasObjectAsKey(gTypeTable[k], key): return key 
+    if idTableHasObjectAsKey(gTypeTable[k], key): return key 
     for h in countup(0, high(gTypeTable[k].data)): 
       var t = PType(gTypeTable[k].data[h].key)
       if t != nil and sameBackendType(t, key): 
         return t
-    IdTablePut(gTypeTable[k], key, key)
+    idTablePut(gTypeTable[k], key, key)
     result = key
   of tyObject:
     if tfFromGeneric notin key.flags:
       # fast case; lookup per id suffices:
-      result = PType(IdTableGet(gTypeTable[k], key))
+      result = PType(idTableGet(gTypeTable[k], key))
       if result == nil: 
-        IdTablePut(gTypeTable[k], key, key)
+        idTablePut(gTypeTable[k], key, key)
         result = key
     else:
       # ugly slow case: need to compare by structure
-      if IdTableHasObjectAsKey(gTypeTable[k], key): return key
+      if idTableHasObjectAsKey(gTypeTable[k], key): return key
       for h in countup(0, high(gTypeTable[k].data)): 
         var t = PType(gTypeTable[k].data[h].key)
         if t != nil and sameType(t, key): 
           return t
-      IdTablePut(gTypeTable[k], key, key)
+      idTablePut(gTypeTable[k], key, key)
       result = key
   of tyEnum:
-    result = PType(IdTableGet(gTypeTable[k], key))
+    result = PType(idTableGet(gTypeTable[k], key))
     if result == nil: 
-      IdTablePut(gTypeTable[k], key, key)
+      idTablePut(gTypeTable[k], key, key)
       result = key
   of tyProc:
     # tyVar is not 100% correct, but would speeds things up a little:
@@ -136,17 +135,17 @@ proc GetUniqueType*(key: PType): PType =
       result = key
     else:
       # ugh, we need the canon here:
-      if IdTableHasObjectAsKey(gTypeTable[k], key): return key 
+      if idTableHasObjectAsKey(gTypeTable[k], key): return key 
       for h in countup(0, high(gTypeTable[k].data)): 
         var t = PType(gTypeTable[k].data[h].key)
         if t != nil and sameBackendType(t, key): 
           return t
-      IdTablePut(gTypeTable[k], key, key)
+      idTablePut(gTypeTable[k], key, key)
       result = key
       
-proc TableGetType*(tab: TIdTable, key: PType): PObject = 
+proc tableGetType*(tab: TIdTable, key: PType): PObject = 
   # returns nil if we need to declare this type
-  result = IdTableGet(tab, key)
+  result = idTableGet(tab, key)
   if (result == nil) and (tab.counter > 0): 
     # we have to do a slow linear search because types may need
     # to be compared by their structure:
@@ -169,7 +168,7 @@ proc makeLLVMString*(s: string): PRope =
   for i in countup(0, len(s) - 1): 
     if (i + 1) mod MaxLineLength == 0: 
       app(result, toRope(res))
-      setlen(res, 0)
+      setLen(res, 0)
     case s[i]
     of '\0'..'\x1F', '\x80'..'\xFF', '\"', '\\': 
       add(res, '\\')
@@ -178,4 +177,4 @@ proc makeLLVMString*(s: string): PRope =
   add(res, "\\00\"")
   app(result, toRope(res))
 
-InitTypeTables()
+initTypeTables()
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index 6ccef5fde..5057ae558 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -52,7 +52,7 @@ proc emitLazily(s: PSym): bool {.inline.} =
 proc initLoc(result: var TLoc, k: TLocKind, typ: PType, s: TStorageLoc) = 
   result.k = k
   result.s = s
-  result.t = GetUniqueType(typ)
+  result.t = getUniqueType(typ)
   result.r = nil
   result.a = - 1
   result.flags = {}
@@ -75,12 +75,12 @@ proc isSimpleConst(typ: PType): bool =
 proc useStringh(m: BModule) =
   if not m.includesStringh:
     m.includesStringh = true
-    discard lists.IncludeStr(m.headerFiles, "<string.h>")
+    discard lists.includeStr(m.headerFiles, "<string.h>")
 
 proc useHeader(m: BModule, sym: PSym) = 
-  if lfHeader in sym.loc.Flags: 
+  if lfHeader in sym.loc.flags: 
     assert(sym.annex != nil)
-    discard lists.IncludeStr(m.headerFiles, getStr(sym.annex.path))
+    discard lists.includeStr(m.headerFiles, getStr(sym.annex.path))
 
 proc cgsym(m: BModule, name: string): PRope
 
@@ -103,7 +103,7 @@ proc ropecg(m: BModule, frmt: TFormatStr, args: varargs[PRope]): PRope =
       of '0'..'9': 
         var j = 0
         while true: 
-          j = (j * 10) + Ord(frmt[i]) - ord('0')
+          j = (j * 10) + ord(frmt[i]) - ord('0')
           inc(i)
           if i >= length or not (frmt[i] in {'0'..'9'}): break 
         num = j
@@ -116,7 +116,7 @@ proc ropecg(m: BModule, frmt: TFormatStr, args: varargs[PRope]): PRope =
       of 'N': 
         app(result, rnl)
         inc(i)
-      else: InternalError("ropes: invalid format string $" & frmt[i])
+      else: internalError("ropes: invalid format string $" & frmt[i])
     elif frmt[i] == '#' and frmt[i+1] in IdentStartChars:
       inc(i)
       var j = i
@@ -128,7 +128,7 @@ proc ropecg(m: BModule, frmt: TFormatStr, args: varargs[PRope]): PRope =
       inc(i, 2)
       var j = 0
       while frmt[i] in Digits: 
-        j = (j * 10) + Ord(frmt[i]) - ord('0')
+        j = (j * 10) + ord(frmt[i]) - ord('0')
         inc(i)
       app(result, cgsym(m, args[j-1].ropeToStr))
     var start = i
@@ -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, 
@@ -279,11 +279,11 @@ proc genLineDir(p: BProc, t: PNode) =
   if optEmbedOrigSrc in gGlobalOptions:
     app(p.s(cpsStmts), con(~"//", t.info.sourceLine, rnl))
   genCLineDir(p.s(cpsStmts), t.info.toFullPath, line)
-  if ({optStackTrace, optEndb} * p.Options == {optStackTrace, optEndb}) and
+  if ({optStackTrace, optEndb} * p.options == {optStackTrace, optEndb}) and
       (p.prc == nil or sfPure notin p.prc.flags):
     linefmt(p, cpsStmts, "#endb($1, $2);$n",
             line.toRope, makeCString(toFilename(t.info)))
-  elif ({optLineTrace, optStackTrace} * p.Options ==
+  elif ({optLineTrace, optStackTrace} * p.options ==
       {optLineTrace, optStackTrace}) and
       (p.prc == nil or sfPure notin p.prc.flags):
     linefmt(p, cpsStmts, "nimln($1, $2);$n",
@@ -319,7 +319,7 @@ proc genObjectInit(p: BProc, section: TCProcSection, t: PType, a: TLoc,
                    takeAddr: bool) =
   case analyseObjectWithTypeField(t)
   of frNone:
-    nil
+    discard
   of frHeader:
     var r = rdLoc(a)
     if not takeAddr: r = ropef("(*$1)", [r])
@@ -351,7 +351,7 @@ proc resetLoc(p: BProc, loc: var TLoc) =
   if not isComplexValueType(skipTypes(loc.t, abstractVarRange)):
     if containsGcRef:
       var nilLoc: TLoc
-      initLoc(nilLoc, locTemp, loc.t, onStack)
+      initLoc(nilLoc, locTemp, loc.t, OnStack)
       nilLoc.r = toRope("NIM_NIL")
       genRefAssign(p, loc, nilLoc, {afSrcIsNil})
     else:
@@ -513,7 +513,7 @@ proc assignLocalVar(p: BProc, s: PSym) =
 
 include ccgthreadvars
 
-proc VarInDynamicLib(m: BModule, sym: PSym)
+proc varInDynamicLib(m: BModule, sym: PSym)
 proc mangleDynLibProc(sym: PSym): PRope
 
 proc assignGlobalVar(p: BProc, s: PSym) = 
@@ -522,8 +522,8 @@ proc assignGlobalVar(p: BProc, s: PSym) =
   
   if lfDynamicLib in s.loc.flags:
     var q = findPendingModule(p.module, s)
-    if q != nil and not ContainsOrIncl(q.declaredThings, s.id): 
-      VarInDynamicLib(q, s)
+    if q != nil and not containsOrIncl(q.declaredThings, s.id): 
+      varInDynamicLib(q, s)
     else:
       s.loc.r = mangleDynLibProc(s)
     return
@@ -578,7 +578,7 @@ proc expr(p: BProc, n: PNode, d: var TLoc)
 proc genProcPrototype(m: BModule, sym: PSym)
 proc putLocIntoDest(p: BProc, d: var TLoc, s: TLoc)
 proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags)
-proc intLiteral(i: biggestInt): PRope
+proc intLiteral(i: BiggestInt): PRope
 proc genLiteral(p: BProc, n: PNode): PRope
 
 proc initLocExpr(p: BProc, e: PNode, result: var TLoc) =
@@ -610,7 +610,7 @@ proc loadDynamicLib(m: BModule, lib: PLib) =
       var s: TStringSeq = @[]
       libCandidates(lib.path.strVal, s)
       if gVerbosity >= 2:
-        MsgWriteln("Dependency: " & lib.path.strVal)
+        msgWriteln("Dependency: " & lib.path.strVal)
       var loadlib: PRope = nil
       for i in countup(0, high(s)): 
         inc(m.labels)
@@ -632,7 +632,7 @@ proc loadDynamicLib(m: BModule, lib: PLib) =
            "if (!($1 = #nimLoadLibrary($2))) #nimLoadLibraryError($2);$n", 
            [tmp, rdLoc(dest)])
       
-  if lib.name == nil: InternalError("loadDynamicLib")
+  if lib.name == nil: internalError("loadDynamicLib")
   
 proc mangleDynLibProc(sym: PSym): PRope =
   if sfCompilerProc in sym.flags: 
@@ -641,7 +641,7 @@ proc mangleDynLibProc(sym: PSym): PRope =
   else:
     result = ropef("Dl_$1", [toRope(sym.id)])
   
-proc SymInDynamicLib(m: BModule, sym: PSym) = 
+proc symInDynamicLib(m: BModule, sym: PSym) = 
   var lib = sym.annex
   let isCall = isGetProcAddr(lib)
   var extname = sym.loc.r
@@ -665,14 +665,14 @@ proc SymInDynamicLib(m: BModule, sym: PSym) =
         params, cstringLit(m, m.s[cfsDynLibInit], ropeToStr(extname))])
     var last = lastSon(n)
     if last.kind == nkHiddenStdConv: last = last.sons[1]
-    InternalAssert(last.kind == nkStrLit)
+    internalAssert(last.kind == nkStrLit)
     let idx = last.strVal
     if idx.len == 0:
       app(m.initProc.s(cpsStmts), load)
     elif idx.len == 1 and idx[0] in {'0'..'9'}:
       app(m.extensionLoaders[idx[0]], load)
     else:
-      InternalError(sym.info, "wrong index: " & idx)
+      internalError(sym.info, "wrong index: " & idx)
   else:
     appcg(m, m.s[cfsDynLibInit], 
         "\t$1 = ($2) #nimGetProcAddr($3, $4);$n", 
@@ -682,7 +682,7 @@ proc SymInDynamicLib(m: BModule, sym: PSym) =
       "$1 = linkonce global $2 zeroinitializer$n", 
       [sym.loc.r, getTypeDesc(m, sym.loc.t)])
 
-proc VarInDynamicLib(m: BModule, sym: PSym) = 
+proc varInDynamicLib(m: BModule, sym: PSym) = 
   var lib = sym.annex
   var extname = sym.loc.r
   loadDynamicLib(m, lib)
@@ -697,7 +697,7 @@ proc VarInDynamicLib(m: BModule, sym: PSym) =
   appf(m.s[cfsVars], "$2* $1;$n",
       [sym.loc.r, getTypeDesc(m, sym.loc.t)])
 
-proc SymInDynamicLibPartial(m: BModule, sym: PSym) =
+proc symInDynamicLibPartial(m: BModule, sym: PSym) =
   sym.loc.r = mangleDynLibProc(sym)
   sym.typ.sym = nil           # generate a new name
 
@@ -708,7 +708,7 @@ proc cgsym(m: BModule, name: string): PRope =
     of skProc, skMethod, skConverter, skIterator: genProc(m, sym)
     of skVar, skResult, skLet: genVarPrototype(m, sym)
     of skType: discard getTypeDesc(m, sym.typ)
-    else: InternalError("cgsym: " & name)
+    else: internalError("cgsym: " & name)
   else:
     # we used to exclude the system module from this check, but for DLL
     # generation support this sloppyness leads to hard to detect bugs, so
@@ -724,7 +724,7 @@ proc generateHeaders(m: BModule) =
       appf(m.s[cfsHeaders], "$N#include \"$1\"$N", [toRope(it.data)])
     else: 
       appf(m.s[cfsHeaders], "$N#include $1$N", [toRope(it.data)])
-    it = PStrEntry(it.Next)
+    it = PStrEntry(it.next)
 
 proc retIsNotVoid(s: PSym): bool = 
   result = (s.typ.sons[0] != nil) and not isInvalidReturnType(s.typ.sons[0])
@@ -747,7 +747,7 @@ proc closureSetup(p: BProc, prc: PSym) =
   # prc.ast[paramsPos].last contains the type we're after:
   var ls = lastSon(prc.ast[paramsPos])
   if ls.kind != nkSym:
-    InternalError(prc.info, "closure generation failed")
+    internalError(prc.info, "closure generation failed")
   var env = ls.sym
   #echo "created environment: ", env.id, " for ", prc.name.s
   assignLocalVar(p, env)
@@ -784,7 +784,7 @@ proc genProcAux(m: BModule, prc: PSym) =
   genStmts(p, prc.getBody) # modifies p.locals, p.init, etc.
   var generatedProc: PRope
   if sfPure in prc.flags:
-    if hasNakedDeclspec in extccomp.CC[extccomp.ccompiler].props:
+    if hasNakedDeclspec in extccomp.CC[extccomp.cCompiler].props:
       header = con("__declspec(naked) ", header)
     generatedProc = rfmt(nil, "$N$1 {$n$2$3$4}$N$N",
                          header, p.s(cpsLocals), p.s(cpsInit), p.s(cpsStmts))
@@ -793,7 +793,7 @@ proc genProcAux(m: BModule, prc: PSym) =
     app(generatedProc, initGCFrame(p))
     if optStackTrace in prc.options: 
       app(generatedProc, p.s(cpsLocals))
-      var procname = CStringLit(p, generatedProc, prc.name.s)
+      var procname = cstringLit(p, generatedProc, prc.name.s)
       app(generatedProc, initFrame(p, procname, prc.info.quotedFilename))
     else: 
       app(generatedProc, p.s(cpsLocals))
@@ -811,16 +811,16 @@ proc genProcAux(m: BModule, prc: PSym) =
   
 proc genProcPrototype(m: BModule, sym: PSym) = 
   useHeader(m, sym)
-  if lfNoDecl in sym.loc.Flags: return 
-  if lfDynamicLib in sym.loc.Flags:
+  if lfNoDecl in sym.loc.flags: return 
+  if lfDynamicLib in sym.loc.flags:
     if getModule(sym).id != m.module.id and
-        not ContainsOrIncl(m.declaredThings, sym.id): 
+        not containsOrIncl(m.declaredThings, sym.id): 
       app(m.s[cfsVars], rfmt(nil, "extern $1 $2;$n",
                         getTypeDesc(m, sym.loc.t), mangleDynLibProc(sym)))
       if gCmd == cmdCompileToLLVM: incl(sym.loc.flags, lfIndirect)
-  elif not ContainsOrIncl(m.declaredProtos, sym.id):
+  elif not containsOrIncl(m.declaredProtos, sym.id):
     var header = genProcHeader(m, sym)
-    if sfPure in sym.flags and hasNakedAttribute in CC[ccompiler].props:
+    if sfPure in sym.flags and hasNakedAttribute in CC[cCompiler].props:
       header.app(" __attribute__((naked))")
     app(m.s[cfsProcHeaders], rfmt(nil, "$1;$n", header))
 
@@ -832,21 +832,21 @@ proc genProcNoForward(m: BModule, prc: PSym) =
     discard cgsym(m, prc.name.s)
     return  
   genProcPrototype(m, prc)
-  if lfNoDecl in prc.loc.Flags: nil
+  if lfNoDecl in prc.loc.flags: discard
   elif prc.typ.callConv == ccInline:
     # We add inline procs to the calling module to enable C based inlining.
     # This also means that a check with ``q.declaredThings`` is wrong, we need
     # a check for ``m.declaredThings``.
-    if not ContainsOrIncl(m.declaredThings, prc.id): genProcAux(m, prc)
+    if not containsOrIncl(m.declaredThings, prc.id): genProcAux(m, prc)
   elif lfDynamicLib in prc.loc.flags:
     var q = findPendingModule(m, prc)
-    if q != nil and not ContainsOrIncl(q.declaredThings, prc.id): 
-      SymInDynamicLib(q, prc)
+    if q != nil and not containsOrIncl(q.declaredThings, prc.id): 
+      symInDynamicLib(q, prc)
     else:
-      SymInDynamicLibPartial(m, prc)
+      symInDynamicLibPartial(m, prc)
   elif sfImportc notin prc.flags:
     var q = findPendingModule(m, prc)
-    if q != nil and not ContainsOrIncl(q.declaredThings, prc.id): 
+    if q != nil and not containsOrIncl(q.declaredThings, prc.id): 
       genProcAux(q, prc)
 
 proc requestConstImpl(p: BProc, sym: PSym) =
@@ -854,15 +854,15 @@ proc requestConstImpl(p: BProc, sym: PSym) =
   useHeader(m, sym)
   if sym.loc.k == locNone:
     fillLoc(sym.loc, locData, sym.typ, mangleName(sym), OnUnknown)
-  if lfNoDecl in sym.loc.Flags: return
+  if lfNoDecl in sym.loc.flags: return
   # declare implementation:
   var q = findPendingModule(m, sym)
-  if q != nil and not ContainsOrIncl(q.declaredThings, sym.id):
+  if q != nil and not containsOrIncl(q.declaredThings, sym.id):
     assert q.initProc.module == q
     appf(q.s[cfsData], "NIM_CONST $1 $2 = $3;$n",
         [getTypeDesc(q, sym.typ), sym.loc.r, genConstExpr(q.initProc, sym.ast)])
   # declare header:
-  if q != m and not ContainsOrIncl(m.declaredThings, sym.id):
+  if q != m and not containsOrIncl(m.declaredThings, sym.id):
     assert(sym.loc.r != nil)
     let headerDecl = ropef("extern NIM_CONST $1 $2;$n",
         [getTypeDesc(m, sym.loc.t), sym.loc.r])
@@ -879,17 +879,17 @@ proc genProc(m: BModule, prc: PSym) =
   else:
     genProcNoForward(m, prc)
     if {sfExportc, sfCompilerProc} * prc.flags == {sfExportc} and
-        generatedHeader != nil and lfNoDecl notin prc.loc.Flags:
+        generatedHeader != nil and lfNoDecl notin prc.loc.flags:
       genProcPrototype(generatedHeader, prc)
       if prc.typ.callConv == ccInline:
-        if not ContainsOrIncl(generatedHeader.declaredThings, prc.id): 
+        if not containsOrIncl(generatedHeader.declaredThings, prc.id): 
           genProcAux(generatedHeader, prc)
 
 proc genVarPrototypeAux(m: BModule, sym: PSym) = 
   assert(sfGlobal in sym.flags)
   useHeader(m, sym)
   fillLoc(sym.loc, locGlobalVar, sym.typ, mangleName(sym), OnHeap)
-  if (lfNoDecl in sym.loc.Flags) or ContainsOrIncl(m.declaredThings, sym.id): 
+  if (lfNoDecl in sym.loc.flags) or containsOrIncl(m.declaredThings, sym.id): 
     return 
   if sym.owner.id != m.module.id: 
     # else we already have the symbol generated!
@@ -911,29 +911,29 @@ proc addIntTypes(result: var PRope) {.inline.} =
   appf(result, "#define NIM_INTBITS $1", [
     platform.CPU[targetCPU].intSize.toRope])
 
-proc getCopyright(cfilenoext: string): PRope = 
-  if optCompileOnly in gGlobalOptions: 
-    result = ropeff("/* Generated by Nimrod Compiler v$1 */$n" &
-        "/*   (c) 2012 Andreas Rumpf */$n" &
-        "/* The generated code is subject to the original license. */$n",
-        "; Generated by Nimrod Compiler v$1$n" &
-        ";   (c) 2012 Andreas Rumpf$n", [toRope(versionAsString)])
-  else: 
-    result = ropeff("/* Generated by Nimrod Compiler v$1 */$n" &
-        "/*   (c) 2012 Andreas Rumpf */$n" & 
-        "/* The generated code is subject to the original license. */$n" &
-        "/* Compiled for: $2, $3, $4 */$n" &
-        "/* Command for C compiler:$n   $5 */$n", 
-        "; Generated by Nimrod Compiler v$1$n" &
-        ";   (c) 2012 Andreas Rumpf$n" & 
-        "; Compiled for: $2, $3, $4$n" &
-        "; Command for LLVM compiler:$n   $5$n", [toRope(versionAsString), 
-        toRope(platform.OS[targetOS].name), 
-        toRope(platform.CPU[targetCPU].name), 
-        toRope(extccomp.CC[extccomp.ccompiler].name), 
+proc getCopyright(cfilenoext: string): PRope =
+  if optCompileOnly in gGlobalOptions:
+    result = ropeff("/* Generated by Nimrod Compiler v$1 */$N" &
+        "/*   (c) 2014 Andreas Rumpf */$N" &
+        "/* The generated code is subject to the original license. */$N",
+        "; Generated by Nimrod Compiler v$1$N" &
+        ";   (c) 2012 Andreas Rumpf$N", [toRope(VersionAsString)])
+  else:
+    result = ropeff("/* Generated by Nimrod Compiler v$1 */$N" &
+        "/*   (c) 2014 Andreas Rumpf */$N" &
+        "/* The generated code is subject to the original license. */$N" &
+        "/* Compiled for: $2, $3, $4 */$N" &
+        "/* Command for C compiler:$n   $5 */$N",
+        "; Generated by Nimrod Compiler v$1$N" &
+        ";   (c) 2014 Andreas Rumpf$N" &
+        "; Compiled for: $2, $3, $4$N" &
+        "; Command for LLVM compiler:$N   $5$N", [toRope(VersionAsString),
+        toRope(platform.OS[targetOS].name),
+        toRope(platform.CPU[targetCPU].name),
+        toRope(extccomp.CC[extccomp.cCompiler].name),
         toRope(getCompileCFileCmd(cfilenoext))])
 
-proc getFileHeader(cfilenoext: string): PRope = 
+proc getFileHeader(cfilenoext: string): PRope =
   result = getCopyright(cfilenoext)
   addIntTypes(result)
 
@@ -941,46 +941,72 @@ proc genFilenames(m: BModule): PRope =
   discard cgsym(m, "dbgRegisterFilename")
   result = nil
   for i in 0.. <fileInfos.len:
-    result.appf("dbgRegisterFilename($1);$n", fileInfos[i].projPath.makeCString)
+    result.appf("dbgRegisterFilename($1);$N", fileInfos[i].projPath.makeCString)
 
-proc genMainProc(m: BModule) = 
+proc genMainProc(m: BModule) =
   const 
-    CommonMainBody =
-        "\tsystemDatInit();$n" &
-        "\tsystemInit();$n" &
-        "$1" &
-        "$2" &
-        "$3" &
-        "$4"
-    PosixNimMain = 
-        "int cmdCount;$n" & 
-        "char** cmdLine;$n" & 
-        "char** gEnv;$n" &
-        "N_CDECL(void, NimMain)(void) {$n" &
-        CommonMainBody & "}$n"
-    PosixCMain = "int main(int argc, char** args, char** env) {$n" &
-        "\tcmdLine = args;$n" & "\tcmdCount = argc;$n" & "\tgEnv = env;$n" &
-        "\tNimMain();$n" & "\treturn nim_program_result;$n" & "}$n"
-    StandaloneCMain = "int main(void) {$n" &
-        "\tNimMain();$n" & 
-        "\treturn 0;$n" & "}$n"
-    WinNimMain = "N_CDECL(void, NimMain)(void) {$n" &
-        CommonMainBody & "}$n"
-    WinCMain = "N_STDCALL(int, WinMain)(HINSTANCE hCurInstance, $n" &
-        "                        HINSTANCE hPrevInstance, $n" &
-        "                        LPSTR lpCmdLine, int nCmdShow) {$n" &
-        "\tNimMain();$n" & "\treturn nim_program_result;$n" & "}$n"
-    WinNimDllMain = "N_LIB_EXPORT N_CDECL(void, NimMain)(void) {$n" &
-        CommonMainBody & "}$n"
-    WinCDllMain = 
-        "BOOL WINAPI DllMain(HINSTANCE hinstDLL, DWORD fwdreason, $n" &
-        "                    LPVOID lpvReserved) {$n" &
-          "\tif(fwdreason == DLL_PROCESS_ATTACH) NimMain();$n" &
-        "\treturn 1;$n" & "}$n"
+    PreMainBody =
+      "\tsystemDatInit();$N" &
+      "\tsystemInit();$N" &
+      "$1" &
+      "$2" &
+      "$3" &
+      "$4"
+
+    MainProcs =
+      "\tNimMain();$N"
+    
+    MainProcsWithResult =
+      MainProcs & "\treturn nim_program_result;$N"
+
+    NimMainBody =
+      "N_CDECL(void, NimMain)(void) {$N" &
+        "\tPreMain();$N" &
+        "$1$N" &
+      "}$N"
+
+    PosixNimMain =
+      "int cmdCount;$N" &
+      "char** cmdLine;$N" &
+      "char** gEnv;$N" &
+      NimMainBody
+  
+    PosixCMain =
+      "int main(int argc, char** args, char** env) {$N" &
+        "\tcmdLine = args;$N" &
+        "\tcmdCount = argc;$N" &
+        "\tgEnv = env;$N" &
+        MainProcsWithResult &
+      "}$N"
+  
+    StandaloneCMain =
+      "int main(void) {$N" &
+        MainProcs &
+        "\treturn 0;$N" &
+      "}$N"
+    
+    WinNimMain = NimMainBody
+    
+    WinCMain = "N_STDCALL(int, WinMain)(HINSTANCE hCurInstance, $N" &
+      "                        HINSTANCE hPrevInstance, $N" &
+      "                        LPSTR lpCmdLine, int nCmdShow) {$N" &
+      MainProcsWithResult & "}$N"
+  
+    WinNimDllMain = "N_LIB_EXPORT " & NimMainBody
+
+    WinCDllMain =
+      "BOOL WINAPI DllMain(HINSTANCE hinstDLL, DWORD fwdreason, $N" &
+      "                    LPVOID lpvReserved) {$N" &
+      "\tif(fwdreason == DLL_PROCESS_ATTACH) {$N" & MainProcs & "}$N" &
+      "\treturn 1;$N}$N"
+
     PosixNimDllMain = WinNimDllMain
-    PosixCDllMain = 
-        "void NIM_POSIX_INIT NimMainInit(void) {$n" &
-        "\tNimMain();$n}$n"
+    
+    PosixCDllMain =
+      "void NIM_POSIX_INIT NimMainInit(void) {$N" &
+        MainProcs &
+      "}$N"
+
   var nimMain, otherMain: TFormatStr
   if platform.targetOS == osWindows and
       gGlobalOptions * {optGenGuiApp, optGenDynLib} != {}: 
@@ -990,10 +1016,10 @@ proc genMainProc(m: BModule) =
     else: 
       nimMain = WinNimDllMain
       otherMain = WinCDllMain
-    discard lists.IncludeStr(m.headerFiles, "<windows.h>")
+    discard lists.includeStr(m.headerFiles, "<windows.h>")
   elif optGenDynLib in gGlobalOptions:
-    nimMain = posixNimDllMain
-    otherMain = posixCDllMain
+    nimMain = PosixNimDllMain
+    otherMain = PosixCDllMain
   elif platform.targetOS == osStandalone:
     nimMain = PosixNimMain
     otherMain = StandaloneCMain
@@ -1006,10 +1032,12 @@ proc genMainProc(m: BModule) =
   
   let initStackBottomCall = if emulatedThreadVars() or
                               platform.targetOS == osStandalone: "".toRope
-                            else: ropecg(m, "\t#initStackBottom();$n")
+                            else: ropecg(m, "\t#initStackBottom();$N")
   inc(m.labels)
-  appcg(m, m.s[cfsProcs], nimMain, [mainDatInit, initStackBottomCall,
-        gBreakpoints, mainModInit, toRope(m.labels)])
+  appcg(m, m.s[cfsProcs], "void PreMain() {$N" & PreMainBody & "}$N", [
+    mainDatInit, initStackBottomCall, gBreakpoints, otherModsInit])
+
+  appcg(m, m.s[cfsProcs], nimMain, [mainModInit, toRope(m.labels)])
   if optNoMain notin gGlobalOptions:
     appcg(m, m.s[cfsProcs], otherMain, [])
 
@@ -1030,13 +1058,17 @@ proc registerModuleToMain(m: PSym) =
                       "declare void $1() noinline$N", [init])
   appff(mainModProcs, "N_NOINLINE(void, $1)(void);$N",
                       "declare void $1() noinline$N", [datInit])
-  if not (sfSystemModule in m.flags):
-    appff(mainModInit, "\t$1();$n", "call void ()* $1$n", [init])
-    appff(mainDatInit, "\t$1();$n", "call void ()* $1$n", [datInit])
-  
+  if sfSystemModule notin m.flags:
+    appff(mainDatInit, "\t$1();$N", "call void ()* $1$n", [datInit])
+    let initCall = ropeff("\t$1();$N", "call void ()* $1$n", [init])
+    if sfMainModule in m.flags:
+      app(mainModInit, initCall)
+    else:
+      app(otherModsInit, initCall)
+    
 proc genInitCode(m: BModule) = 
   var initname = getInitName(m.module)
-  var prc = ropeff("N_NOINLINE(void, $1)(void) {$n", 
+  var prc = ropeff("N_NOINLINE(void, $1)(void) {$N", 
                    "define void $1() noinline {$n", [initname])
   if m.typeNodes > 0: 
     appcg(m, m.s[cfsTypeInit1], "static #TNimNode $1[$2];$n", 
@@ -1053,12 +1085,12 @@ proc genInitCode(m: BModule) =
   app(prc, m.postInitProc.s(cpsLocals))
   app(prc, genSectionEnd(cpsLocals))
 
-  if optStackTrace in m.initProc.options and not m.FrameDeclared:
+  if optStackTrace in m.initProc.options and not m.frameDeclared:
     # BUT: the generated init code might depend on a current frame, so
     # declare it nevertheless:
-    m.FrameDeclared = true
-    if not m.PreventStackTrace:
-      var procname = CStringLit(m.initProc, prc, m.module.name.s)
+    m.frameDeclared = true
+    if not m.preventStackTrace:
+      var procname = cstringLit(m.initProc, prc, m.module.name.s)
       app(prc, initFrame(m.initProc, procname, m.module.info.quotedFilename))
     else:
       app(prc, ~"\tTFrame F; F.len = 0;$N")
@@ -1074,12 +1106,12 @@ proc genInitCode(m: BModule) =
   app(prc, m.initProc.s(cpsStmts))
   app(prc, m.postInitProc.s(cpsStmts))
   app(prc, genSectionEnd(cpsStmts))
-  if optStackTrace in m.initProc.options and not m.PreventStackTrace:
+  if optStackTrace in m.initProc.options and not m.preventStackTrace:
     app(prc, deinitFrame(m.initProc))
   app(prc, deinitGCFrame(m.initProc))
   appf(prc, "}$N$N")
 
-  prc.appff("N_NOINLINE(void, $1)(void) {$n",
+  prc.appff("N_NOINLINE(void, $1)(void) {$N",
             "define void $1() noinline {$n", [getDatInitName(m.module)])
 
   for i in cfsTypeInit1..cfsDynLibInit:
@@ -1127,7 +1159,7 @@ proc initProcOptions(m: BModule): TOptions =
 
 proc rawNewModule(module: PSym, filename: string): BModule =
   new(result)
-  InitLinkedList(result.headerFiles)
+  initLinkedList(result.headerFiles)
   result.declaredThings = initIntSet()
   result.declaredProtos = initIntSet()
   result.cfilename = filename
@@ -1148,7 +1180,7 @@ proc rawNewModule(module: PSym, filename: string): BModule =
   # no line tracing for the init sections of the system module so that we
   # don't generate a TFrame which can confuse the stack botton initialization:
   if sfSystemModule in module.flags:
-    result.PreventStackTrace = true
+    result.preventStackTrace = true
     excl(result.preInitProc.options, optStackTrace)
     excl(result.postInitProc.options, optStackTrace)
 
@@ -1159,7 +1191,7 @@ proc nullify[T](arr: var T) =
 proc resetModule*(m: var BModule) =
   # between two compilations in CAAS mode, we can throw
   # away all the data that was written to disk
-  InitLinkedList(m.headerFiles)
+  initLinkedList(m.headerFiles)
   m.declaredProtos = initIntSet()
   initIdTable(m.forwTypeCache)
   m.initProc = newProc(nil, m)
@@ -1171,7 +1203,7 @@ proc resetModule*(m: var BModule) =
   m.forwardedProcs = @[]
   m.typeNodesName = getTempName()
   m.nimTypesName = getTempName()
-  m.PreventStackTrace = sfSystemModule in m.module.flags
+  m.preventStackTrace = sfSystemModule in m.module.flags
   nullify m.s
   m.usesThreadVars = false
   m.typeNodes = 0
@@ -1202,7 +1234,7 @@ proc rawNewModule(module: PSym): BModule =
 
 proc newModule(module: PSym): BModule =
   # we should create only one cgen module for each module sym
-  InternalAssert getCgenModule(module) == nil
+  internalAssert getCgenModule(module) == nil
 
   result = rawNewModule(module)
   growCache gModules, module.position
@@ -1210,7 +1242,7 @@ proc newModule(module: PSym): BModule =
 
   if (optDeadCodeElim in gGlobalOptions): 
     if (sfDeadCodeElim in module.flags): 
-      InternalError("added pending module twice: " & module.filename)
+      internalError("added pending module twice: " & module.filename)
 
 proc myOpen(module: PSym): PPassContext = 
   result = newModule(module)
@@ -1263,19 +1295,19 @@ proc finishModule(m: BModule) =
     # a ``for`` loop here
     var prc = m.forwardedProcs[i]
     if sfForward in prc.flags: 
-      InternalError(prc.info, "still forwarded: " & prc.name.s)
+      internalError(prc.info, "still forwarded: " & prc.name.s)
     genProcNoForward(m, prc)
     inc(i)
   assert(gForwardedProcsCounter >= i)
   dec(gForwardedProcsCounter, i)
-  setlen(m.forwardedProcs, 0)
+  setLen(m.forwardedProcs, 0)
 
 proc shouldRecompile(code: PRope, cfile, cfilenoext: string): bool = 
   result = true
   if optForceFullMake notin gGlobalOptions:
     var objFile = toObjFile(cfilenoext)
     if writeRopeIfNotEqual(code, cfile): return 
-    if ExistsFile(objFile) and os.FileNewer(objFile, cfile): result = false
+    if existsFile(objFile) and os.fileNewer(objFile, cfile): result = false
   else: 
     writeRope(code, cfile)
 
@@ -1296,7 +1328,7 @@ proc writeModule(m: BModule, pending: bool) =
     if sfMainModule in m.module.flags: 
       # generate main file:
       app(m.s[cfsProcHeaders], mainModProcs)
-      GenerateThreadVarsSize(m)
+      generateThreadVarsSize(m)
     
     var code = genModule(m, cfilenoext)
     when hasTinyCBackend:
@@ -1313,7 +1345,7 @@ proc writeModule(m: BModule, pending: bool) =
     var code = genModule(m, cfilenoext)
     writeRope(code, cfile)
     addFileToCompile(cfilenoext)
-  elif not ExistsFile(toObjFile(cfilenoext)):
+  elif not existsFile(toObjFile(cfilenoext)):
     # Consider: first compilation compiles ``system.nim`` and produces
     # ``system.c`` but then compilation fails due to an error. This means
     # that ``system.o`` is missing, so we need to call the C compiler for it:
diff --git a/compiler/cgendata.nim b/compiler/cgendata.nim
index a803c0ba1..9cd2c0d87 100644
--- a/compiler/cgendata.nim
+++ b/compiler/cgendata.nim
@@ -61,8 +61,8 @@ type
   
   TCProc{.final.} = object    # represents C proc that is currently generated
     prc*: PSym                # the Nimrod proc that this C proc belongs to
-    BeforeRetNeeded*: bool    # true iff 'BeforeRet' label for proc is needed
-    ThreadVarAccessed*: bool  # true if the proc already accessed some threadvar
+    beforeRetNeeded*: bool    # true iff 'BeforeRet' label for proc is needed
+    threadVarAccessed*: bool  # true if the proc already accessed some threadvar
     nestedTryStmts*: seq[PNode] # in how many nested try statements we are
                                 # (the vars must be volatile then)
     inExceptBlock*: int       # are we currently inside an except block?
@@ -78,7 +78,7 @@ type
     maxFrameLen*: int         # max length of frame descriptor
     module*: BModule          # used to prevent excessive parameter passing
     withinLoop*: int          # > 0 if we are within a loop
-    gcFrameId*: natural       # for the GC stack marking
+    gcFrameId*: Natural       # for the GC stack marking
     gcFrameType*: PRope       # the struct {} we put the GC markers into
   
   TTypeSeq* = seq[PType]
@@ -86,9 +86,9 @@ type
     module*: PSym
     filename*: string
     s*: TCFileSections        # sections of the C file
-    PreventStackTrace*: bool  # true if stack traces need to be prevented
+    preventStackTrace*: bool  # true if stack traces need to be prevented
     usesThreadVars*: bool     # true if the module uses a thread var
-    FrameDeclared*: bool      # hack for ROD support so that we don't declare
+    frameDeclared*: bool      # hack for ROD support so that we don't declare
                               # a frame var twice in an init proc
     isHeaderFile*: bool       # C source file is the header file
     includesStringh*: bool    # C source file already includes ``<string.h>``
@@ -108,13 +108,14 @@ type
     forwardedProcs*: TSymSeq  # keep forwarded procs here
     typeNodes*, nimTypes*: int # used for type info generation
     typeNodesName*, nimTypesName*: PRope # used for type info generation
-    labels*: natural          # for generating unique module-scope names
+    labels*: Natural          # for generating unique module-scope names
     extensionLoaders*: array['0'..'9', PRope] # special procs for the
                                               # OpenGL wrapper
     injectStmt*: PRope
 
 var
-  mainModProcs*, mainModInit*, mainDatInit*: PRope # parts of the main module
+  mainModProcs*, mainModInit*, otherModsInit*, mainDatInit*: PRope
+    # varuious parts of the main module
   gMapping*: PRope             # the generated mapping file (if requested)
   gModules*: seq[BModule] = @[] # list of all compiled modules
   gForwardedProcsCounter*: int = 0
diff --git a/compiler/cgmeth.nim b/compiler/cgmeth.nim
index 33bb94b38..1c5ce7a21 100644
--- a/compiler/cgmeth.nim
+++ b/compiler/cgmeth.nim
@@ -18,16 +18,16 @@ proc genConv(n: PNode, d: PType, downcast: bool): PNode =
   var source = skipTypes(n.typ, abstractPtrs)
   if (source.kind == tyObject) and (dest.kind == tyObject): 
     var diff = inheritanceDiff(dest, source)
-    if diff == high(int): InternalError(n.info, "cgmeth.genConv")
+    if diff == high(int): internalError(n.info, "cgmeth.genConv")
     if diff < 0: 
       result = newNodeIT(nkObjUpConv, n.info, d)
       addSon(result, n)
-      if downCast: InternalError(n.info, "cgmeth.genConv: no upcast allowed")
+      if downcast: internalError(n.info, "cgmeth.genConv: no upcast allowed")
     elif diff > 0: 
       result = newNodeIT(nkObjDownConv, n.info, d)
       addSon(result, n)
-      if not downCast: 
-        InternalError(n.info, "cgmeth.genConv: no downcast allowed")
+      if not downcast: 
+        internalError(n.info, "cgmeth.genConv: no downcast allowed")
     else: 
       result = n
   else: 
@@ -66,7 +66,7 @@ proc sameMethodBucket(a, b: PSym): bool =
     if sameType(aa, bb) or
         (aa.kind == tyObject) and (bb.kind == tyObject) and
         (inheritanceDiff(bb, aa) < 0):
-      nil
+      discard
     else:
       return
   result = true
@@ -112,12 +112,12 @@ proc relevantCol(methods: TSymSeq, col: int): bool =
   if t.kind == tyObject:
     for i in countup(1, high(methods)):
       let t2 = skipTypes(methods[i].typ.sons[col], skipPtrs)
-      if not SameType(t2, t):
+      if not sameType(t2, t):
         return true
   
 proc cmpSignatures(a, b: PSym, relevantCols: TIntSet): int = 
   for col in countup(1, sonsLen(a.typ) - 1): 
-    if Contains(relevantCols, col): 
+    if contains(relevantCols, col): 
       var aa = skipTypes(a.typ.sons[col], skipPtrs)
       var bb = skipTypes(b.typ.sons[col], skipPtrs)
       var d = inheritanceDiff(aa, bb)
@@ -126,14 +126,14 @@ proc cmpSignatures(a, b: PSym, relevantCols: TIntSet): int =
   
 proc sortBucket(a: var TSymSeq, relevantCols: TIntSet) = 
   # we use shellsort here; fast and simple
-  var N = len(a)
+  var n = len(a)
   var h = 1
   while true: 
     h = 3 * h + 1
-    if h > N: break 
+    if h > n: break 
   while true: 
     h = h div 3
-    for i in countup(h, N - 1): 
+    for i in countup(h, n - 1): 
       var v = a[i]
       var j = i
       while cmpSignatures(a[j - h], v, relevantCols) >= 0: 
@@ -154,7 +154,7 @@ proc genDispatcher(methods: TSymSeq, relevantCols: TIntSet): PSym =
     var curr = methods[meth]      # generate condition:
     var cond: PNode = nil
     for col in countup(1, paramLen - 1):
-      if Contains(relevantCols, col):
+      if contains(relevantCols, col):
         var isn = newNodeIT(nkCall, base.info, getSysType(tyBool))
         addSon(isn, newSymNode(iss))
         addSon(isn, newSymNode(base.typ.n.sons[col].sym))
@@ -195,7 +195,7 @@ proc generateMethodDispatchers*(): PNode =
   for bucket in countup(0, len(gMethods) - 1): 
     var relevantCols = initIntSet()
     for col in countup(1, sonsLen(gMethods[bucket][0].typ) - 1): 
-      if relevantCol(gMethods[bucket], col): Incl(relevantCols, col)
+      if relevantCol(gMethods[bucket], col): incl(relevantCols, col)
     sortBucket(gMethods[bucket], relevantCols)
     addSon(result, newSymNode(genDispatcher(gMethods[bucket], relevantCols)))
 
diff --git a/compiler/commands.nim b/compiler/commands.nim
index d3266930b..18bdb54d3 100644
--- a/compiler/commands.nim
+++ b/compiler/commands.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -21,40 +21,40 @@ type
     passCmd2,                 # second pass over the command line
     passPP                    # preprocessor called ProcessCommand()
 
-proc ProcessCommand*(switch: string, pass: TCmdLinePass)
-proc processSwitch*(switch, arg: string, pass: TCmdlinePass, info: TLineInfo)
+proc processCommand*(switch: string, pass: TCmdLinePass)
+proc processSwitch*(switch, arg: string, pass: TCmdLinePass, info: TLineInfo)
 
 # implementation
 
 const
-  HelpMessage = "Nimrod Compiler Version $1 (" & compileDate & ") [$2: $3]\n" &
-      "Copyright (c) 2004-2013 by Andreas Rumpf\n"
+  HelpMessage = "Nimrod Compiler Version $1 (" & CompileDate & ") [$2: $3]\n" &
+      "Copyright (c) 2006-2014 by Andreas Rumpf\n"
 
 const 
   Usage = slurp"doc/basicopt.txt".replace("//", "")
   AdvancedUsage = slurp"doc/advopt.txt".replace("//", "")
 
 proc getCommandLineDesc(): string = 
-  result = (HelpMessage % [VersionAsString, platform.os[platform.hostOS].name, 
-                           cpu[platform.hostCPU].name]) & Usage
+  result = (HelpMessage % [VersionAsString, platform.OS[platform.hostOS].name, 
+                           CPU[platform.hostCPU].name]) & Usage
 
-proc HelpOnError(pass: TCmdLinePass) = 
+proc helpOnError(pass: TCmdLinePass) = 
   if pass == passCmd1:
-    MsgWriteln(getCommandLineDesc())
+    msgWriteln(getCommandLineDesc())
     quit(0)
 
 proc writeAdvancedUsage(pass: TCmdLinePass) = 
   if pass == passCmd1:
-    MsgWriteln(`%`(HelpMessage, [VersionAsString, 
-                                 platform.os[platform.hostOS].name, 
-                                 cpu[platform.hostCPU].name]) & AdvancedUsage)
+    msgWriteln(`%`(HelpMessage, [VersionAsString, 
+                                 platform.OS[platform.hostOS].name, 
+                                 CPU[platform.hostCPU].name]) & AdvancedUsage)
     quit(0)
 
 proc writeVersionInfo(pass: TCmdLinePass) = 
   if pass == passCmd1:
-    MsgWriteln(`%`(HelpMessage, [VersionAsString, 
-                                 platform.os[platform.hostOS].name, 
-                                 cpu[platform.hostCPU].name]))
+    msgWriteln(`%`(HelpMessage, [VersionAsString, 
+                                 platform.OS[platform.hostOS].name, 
+                                 CPU[platform.hostCPU].name]))
     quit(0)
 
 var
@@ -62,16 +62,16 @@ var
 
 proc writeCommandLineUsage() = 
   if not helpWritten: 
-    MsgWriteln(getCommandLineDesc())
+    msgWriteln(getCommandLineDesc())
     helpWritten = true
 
 proc addPrefix(switch: string): string =
   if len(switch) == 1: result = "-" & switch
   else: result = "--" & switch
 
-proc InvalidCmdLineOption(pass: TCmdLinePass, switch: string, info: TLineInfo) = 
-  if switch == " ": LocalError(info, errInvalidCmdLineOption, "-")
-  else: LocalError(info, errInvalidCmdLineOption, addPrefix(switch))
+proc invalidCmdLineOption(pass: TCmdLinePass, switch: string, info: TLineInfo) = 
+  if switch == " ": localError(info, errInvalidCmdLineOption, "-")
+  else: localError(info, errInvalidCmdLineOption, addPrefix(switch))
 
 proc splitSwitch(switch: string, cmd, arg: var string, pass: TCmdLinePass, 
                  info: TLineInfo) = 
@@ -86,29 +86,29 @@ proc splitSwitch(switch: string, cmd, arg: var string, pass: TCmdLinePass,
     inc(i)
   if i >= len(switch): arg = ""
   elif switch[i] in {':', '=', '['}: arg = substr(switch, i + 1)
-  else: InvalidCmdLineOption(pass, switch, info)
+  else: invalidCmdLineOption(pass, switch, info)
   
-proc ProcessOnOffSwitch(op: TOptions, arg: string, pass: TCmdlinePass, 
+proc processOnOffSwitch(op: TOptions, arg: string, pass: TCmdLinePass, 
                         info: TLineInfo) = 
   case whichKeyword(arg)
   of wOn: gOptions = gOptions + op
   of wOff: gOptions = gOptions - op
-  else: LocalError(info, errOnOrOffExpectedButXFound, arg)
+  else: localError(info, errOnOrOffExpectedButXFound, arg)
   
-proc ProcessOnOffSwitchG(op: TGlobalOptions, arg: string, pass: TCmdlinePass, 
+proc processOnOffSwitchG(op: TGlobalOptions, arg: string, pass: TCmdLinePass, 
                          info: TLineInfo) = 
   case whichKeyword(arg)
   of wOn: gGlobalOptions = gGlobalOptions + op
   of wOff: gGlobalOptions = gGlobalOptions - op
-  else: LocalError(info, errOnOrOffExpectedButXFound, arg)
+  else: localError(info, errOnOrOffExpectedButXFound, arg)
   
-proc ExpectArg(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = 
-  if arg == "": LocalError(info, errCmdLineArgExpected, addPrefix(switch))
+proc expectArg(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = 
+  if arg == "": localError(info, errCmdLineArgExpected, addPrefix(switch))
   
-proc ExpectNoArg(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = 
-  if arg != "": LocalError(info, errCmdLineNoArgExpected, addPrefix(switch))
+proc expectNoArg(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = 
+  if arg != "": localError(info, errCmdLineNoArgExpected, addPrefix(switch))
   
-proc ProcessSpecificNote(arg: string, state: TSpecialWord, pass: TCmdlinePass, 
+proc processSpecificNote(arg: string, state: TSpecialWord, pass: TCmdLinePass, 
                          info: TLineInfo) = 
   var id = ""  # arg = "X]:on|off"
   var i = 0
@@ -117,21 +117,21 @@ proc ProcessSpecificNote(arg: string, state: TSpecialWord, pass: TCmdlinePass,
     add(id, arg[i])
     inc(i)
   if i < len(arg) and (arg[i] == ']'): inc(i)
-  else: InvalidCmdLineOption(pass, arg, info)
+  else: invalidCmdLineOption(pass, arg, info)
   if i < len(arg) and (arg[i] in {':', '='}): inc(i)
-  else: InvalidCmdLineOption(pass, arg, info)
+  else: invalidCmdLineOption(pass, arg, info)
   if state == wHint: 
     var x = findStr(msgs.HintsToStr, id)
     if x >= 0: n = TNoteKind(x + ord(hintMin))
-    else: InvalidCmdLineOption(pass, arg, info)
+    else: invalidCmdLineOption(pass, arg, info)
   else: 
     var x = findStr(msgs.WarningsToStr, id)
     if x >= 0: n = TNoteKind(x + ord(warnMin))
-    else: InvalidCmdLineOption(pass, arg, info)
+    else: invalidCmdLineOption(pass, arg, info)
   case whichKeyword(substr(arg, i))
   of wOn: incl(gNotes, n)
   of wOff: excl(gNotes, n)
-  else: LocalError(info, errOnOrOffExpectedButXFound, arg)
+  else: localError(info, errOnOrOffExpectedButXFound, arg)
 
 proc processCompile(filename: string) = 
   var found = findFile(filename)
@@ -150,14 +150,14 @@ proc testCompileOptionArg*(switch, arg: string, info: TLineInfo): bool =
     of "markandsweep": result = gSelectedGC == gcMarkAndSweep
     of "generational": result = gSelectedGC == gcGenerational
     of "none":         result = gSelectedGC == gcNone
-    else: LocalError(info, errNoneBoehmRefcExpectedButXFound, arg)
+    else: localError(info, errNoneBoehmRefcExpectedButXFound, arg)
   of "opt":
     case arg.normalize
     of "speed": result = contains(gOptions, optOptimizeSpeed)
     of "size": result = contains(gOptions, optOptimizeSize)
     of "none": result = gOptions * {optOptimizeSpeed, optOptimizeSize} == {}
-    else: LocalError(info, errNoneSpeedOrSizeExpectedButXFound, arg)
-  else: InvalidCmdLineOption(passCmd1, switch, info)
+    else: localError(info, errNoneSpeedOrSizeExpectedButXFound, arg)
+  else: invalidCmdLineOption(passCmd1, switch, info)
 
 proc testCompileOption*(switch: string, info: TLineInfo): bool = 
   case switch.normalize
@@ -173,11 +173,11 @@ proc testCompileOption*(switch: string, info: TLineInfo): bool =
   of "linetrace": result = contains(gOptions, optLineTrace)
   of "debugger": result = contains(gOptions, optEndb)
   of "profiler": result = contains(gOptions, optProfiler)
-  of "checks", "x": result = gOptions * checksOptions == checksOptions
+  of "checks", "x": result = gOptions * ChecksOptions == ChecksOptions
   of "floatchecks":
-    result = gOptions * {optNanCheck, optInfCheck} == {optNanCheck, optInfCheck}
+    result = gOptions * {optNaNCheck, optInfCheck} == {optNaNCheck, optInfCheck}
   of "infchecks": result = contains(gOptions, optInfCheck)
-  of "nanchecks": result = contains(gOptions, optNanCheck)
+  of "nanchecks": result = contains(gOptions, optNaNCheck)
   of "objchecks": result = contains(gOptions, optObjCheck)
   of "fieldchecks": result = contains(gOptions, optFieldCheck)
   of "rangechecks": result = contains(gOptions, optRangeCheck)
@@ -194,7 +194,7 @@ proc testCompileOption*(switch: string, info: TLineInfo): bool =
   of "tlsemulation": result = contains(gGlobalOptions, optTlsEmulation)
   of "implicitstatic": result = contains(gOptions, optImplicitStatic)
   of "patterns": result = contains(gOptions, optPatterns)
-  else: InvalidCmdLineOption(passCmd1, switch, info)
+  else: invalidCmdLineOption(passCmd1, switch, info)
   
 proc processPath(path: string, notRelativeToProj = false): string =
   let p = if notRelativeToProj or os.isAbsolute(path) or
@@ -202,20 +202,20 @@ proc processPath(path: string, notRelativeToProj = false): string =
             path 
           else:
             options.gProjectPath / path
-  result = UnixToNativePath(p % ["nimrod", getPrefixDir(), "lib", libpath,
+  result = unixToNativePath(p % ["nimrod", getPrefixDir(), "lib", libpath,
     "home", removeTrailingDirSep(os.getHomeDir()),
     "projectname", options.gProjectName,
     "projectpath", options.gProjectPath])
 
 proc trackDirty(arg: string, info: TLineInfo) =
   var a = arg.split(',')
-  if a.len != 4: LocalError(info, errTokenExpected,
+  if a.len != 4: localError(info, errTokenExpected,
                             "DIRTY_BUFFER,ORIGINAL_FILE,LINE,COLUMN")
   var line, column: int
   if parseUtils.parseInt(a[2], line) <= 0:
-    LocalError(info, errInvalidNumber, a[1])
+    localError(info, errInvalidNumber, a[1])
   if parseUtils.parseInt(a[3], column) <= 0:
-    LocalError(info, errInvalidNumber, a[2])
+    localError(info, errInvalidNumber, a[2])
   
   gDirtyBufferIdx = a[0].fileInfoIdx
   gDirtyOriginalIdx = a[1].fileInfoIdx
@@ -225,21 +225,21 @@ proc trackDirty(arg: string, info: TLineInfo) =
 
 proc track(arg: string, info: TLineInfo) = 
   var a = arg.split(',')
-  if a.len != 3: LocalError(info, errTokenExpected, "FILE,LINE,COLUMN")
+  if a.len != 3: localError(info, errTokenExpected, "FILE,LINE,COLUMN")
   var line, column: int
   if parseUtils.parseInt(a[1], line) <= 0:
-    LocalError(info, errInvalidNumber, a[1])
+    localError(info, errInvalidNumber, a[1])
   if parseUtils.parseInt(a[2], column) <= 0:
-    LocalError(info, errInvalidNumber, a[2])
+    localError(info, errInvalidNumber, a[2])
   optTrackPos = newLineInfo(a[0], line, column)
   msgs.addCheckpoint(optTrackPos)
 
-proc dynlibOverride(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
+proc dynlibOverride(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) =
   if pass in {passCmd2, passPP}:
     expectArg(switch, arg, pass, info)
     options.inclDynlibOverride(arg)
 
-proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) = 
+proc processSwitch(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = 
   var 
     theOS: TSystemOS
     cpu: TSystemCPU
@@ -249,15 +249,18 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     expectArg(switch, arg, pass, info)
     addPath(processPath(arg), info)
   of "babelpath":
-    if pass in {passCmd2, passPP}:
+    if pass in {passCmd2, passPP} and not options.gNoBabelPath:
       expectArg(switch, arg, pass, info)
       let path = processPath(arg, notRelativeToProj=true)
       babelpath(path, info)
+  of "nobabelpath":
+    expectNoArg(switch, arg, pass, info)
+    options.gNoBabelPath = true
   of "excludepath":
     expectArg(switch, arg, pass, info)
     let path = processPath(arg)
-    lists.ExcludeStr(options.searchPaths, path)
-    lists.ExcludeStr(options.lazyPaths, path)
+    lists.excludeStr(options.searchPaths, path)
+    lists.excludeStr(options.lazyPaths, path)
   of "nimcache":
     expectArg(switch, arg, pass, info)
     options.nimcacheDir = processPath(arg)
@@ -269,10 +272,10 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     optMainModule = arg
   of "define", "d": 
     expectArg(switch, arg, pass, info)
-    DefineSymbol(arg)
+    defineSymbol(arg)
   of "undef", "u": 
     expectArg(switch, arg, pass, info)
-    UndefSymbol(arg)
+    undefSymbol(arg)
   of "compile": 
     expectArg(switch, arg, pass, info)
     if pass in {passCmd2, passPP}: processCompile(arg)
@@ -305,7 +308,7 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     case arg.normalize
     of "boehm": 
       gSelectedGC = gcBoehm
-      DefineSymbol("boehmgc")
+      defineSymbol("boehmgc")
     of "refc":
       gSelectedGC = gcRefc
     of "v2":
@@ -319,42 +322,42 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     of "none":
       gSelectedGC = gcNone
       defineSymbol("nogc")
-    else: LocalError(info, errNoneBoehmRefcExpectedButXFound, arg)
-  of "warnings", "w": ProcessOnOffSwitch({optWarns}, arg, pass, info)
-  of "warning": ProcessSpecificNote(arg, wWarning, pass, info)
-  of "hint": ProcessSpecificNote(arg, wHint, pass, info)
-  of "hints": ProcessOnOffSwitch({optHints}, arg, pass, info)
-  of "threadanalysis": ProcessOnOffSwitchG({optThreadAnalysis}, arg, pass, info)
-  of "stacktrace": ProcessOnOffSwitch({optStackTrace}, arg, pass, info)
-  of "linetrace": ProcessOnOffSwitch({optLineTrace}, arg, pass, info)
+    else: localError(info, errNoneBoehmRefcExpectedButXFound, arg)
+  of "warnings", "w": processOnOffSwitch({optWarns}, arg, pass, info)
+  of "warning": processSpecificNote(arg, wWarning, pass, info)
+  of "hint": processSpecificNote(arg, wHint, pass, info)
+  of "hints": processOnOffSwitch({optHints}, arg, pass, info)
+  of "threadanalysis": processOnOffSwitchG({optThreadAnalysis}, arg, pass, info)
+  of "stacktrace": processOnOffSwitch({optStackTrace}, arg, pass, info)
+  of "linetrace": processOnOffSwitch({optLineTrace}, arg, pass, info)
   of "debugger": 
-    ProcessOnOffSwitch({optEndb}, arg, pass, info)
-    if optEndb in gOptions: DefineSymbol("endb")
-    else: UndefSymbol("endb")
+    processOnOffSwitch({optEndb}, arg, pass, info)
+    if optEndb in gOptions: defineSymbol("endb")
+    else: undefSymbol("endb")
   of "profiler": 
-    ProcessOnOffSwitch({optProfiler}, arg, pass, info)
-    if optProfiler in gOptions: DefineSymbol("profiler")
-    else: UndefSymbol("profiler")
-  of "checks", "x": ProcessOnOffSwitch(checksOptions, arg, pass, info)
+    processOnOffSwitch({optProfiler}, arg, pass, info)
+    if optProfiler in gOptions: defineSymbol("profiler")
+    else: undefSymbol("profiler")
+  of "checks", "x": processOnOffSwitch(ChecksOptions, arg, pass, info)
   of "floatchecks":
-    ProcessOnOffSwitch({optNanCheck, optInfCheck}, arg, pass, info)
-  of "infchecks": ProcessOnOffSwitch({optInfCheck}, arg, pass, info)
-  of "nanchecks": ProcessOnOffSwitch({optNanCheck}, arg, pass, info)
-  of "objchecks": ProcessOnOffSwitch({optObjCheck}, arg, pass, info)
-  of "fieldchecks": ProcessOnOffSwitch({optFieldCheck}, arg, pass, info)
-  of "rangechecks": ProcessOnOffSwitch({optRangeCheck}, arg, pass, info)
-  of "boundchecks": ProcessOnOffSwitch({optBoundsCheck}, arg, pass, info)
-  of "overflowchecks": ProcessOnOffSwitch({optOverflowCheck}, arg, pass, info)
-  of "linedir": ProcessOnOffSwitch({optLineDir}, arg, pass, info)
-  of "assertions", "a": ProcessOnOffSwitch({optAssert}, arg, pass, info)
-  of "deadcodeelim": ProcessOnOffSwitchG({optDeadCodeElim}, arg, pass, info)
-  of "threads": ProcessOnOffSwitchG({optThreads}, arg, pass, info)
-  of "tlsemulation": ProcessOnOffSwitchG({optTlsEmulation}, arg, pass, info)
-  of "taintmode": ProcessOnOffSwitchG({optTaintMode}, arg, pass, info)
+    processOnOffSwitch({optNaNCheck, optInfCheck}, arg, pass, info)
+  of "infchecks": processOnOffSwitch({optInfCheck}, arg, pass, info)
+  of "nanchecks": processOnOffSwitch({optNaNCheck}, arg, pass, info)
+  of "objchecks": processOnOffSwitch({optObjCheck}, arg, pass, info)
+  of "fieldchecks": processOnOffSwitch({optFieldCheck}, arg, pass, info)
+  of "rangechecks": processOnOffSwitch({optRangeCheck}, arg, pass, info)
+  of "boundchecks": processOnOffSwitch({optBoundsCheck}, arg, pass, info)
+  of "overflowchecks": processOnOffSwitch({optOverflowCheck}, arg, pass, info)
+  of "linedir": processOnOffSwitch({optLineDir}, arg, pass, info)
+  of "assertions", "a": processOnOffSwitch({optAssert}, arg, pass, info)
+  of "deadcodeelim": processOnOffSwitchG({optDeadCodeElim}, arg, pass, info)
+  of "threads": processOnOffSwitchG({optThreads}, arg, pass, info)
+  of "tlsemulation": processOnOffSwitchG({optTlsEmulation}, arg, pass, info)
+  of "taintmode": processOnOffSwitchG({optTaintMode}, arg, pass, info)
   of "implicitstatic":
-    ProcessOnOffSwitch({optImplicitStatic}, arg, pass, info)
+    processOnOffSwitch({optImplicitStatic}, arg, pass, info)
   of "patterns":
-    ProcessOnOffSwitch({optPatterns}, arg, pass, info)
+    processOnOffSwitch({optPatterns}, arg, pass, info)
   of "opt":
     expectArg(switch, arg, pass, info)
     case arg.normalize
@@ -367,7 +370,7 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     of "none":
       excl(gOptions, optOptimizeSpeed)
       excl(gOptions, optOptimizeSize)
-    else: LocalError(info, errNoneSpeedOrSizeExpectedButXFound, arg)
+    else: localError(info, errNoneSpeedOrSizeExpectedButXFound, arg)
   of "app": 
     expectArg(switch, arg, pass, info)
     case arg.normalize
@@ -389,7 +392,7 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
       excl(gGlobalOptions, optGenGuiApp)
       defineSymbol("library")
       defineSymbol("staticlib")
-    else: LocalError(info, errGuiConsoleOrLibExpectedButXFound, arg)
+    else: localError(info, errGuiConsoleOrLibExpectedButXFound, arg)
   of "passc", "t": 
     expectArg(switch, arg, pass, info)
     if pass in {passCmd2, passPP}: extccomp.addCompileOption(arg)
@@ -398,18 +401,18 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     if pass in {passCmd2, passPP}: extccomp.addLinkOption(arg)
   of "cincludes":
     expectArg(switch, arg, pass, info)
-    if pass in {passCmd2, passPP}: cIncludes.add arg
+    if pass in {passCmd2, passPP}: cIncludes.add arg.processPath
   of "clibdir":
     expectArg(switch, arg, pass, info)
-    if pass in {passCmd2, passPP}: cLibs.add arg
+    if pass in {passCmd2, passPP}: cLibs.add arg.processPath
   of "clib":
     expectArg(switch, arg, pass, info)
-    if pass in {passCmd2, passPP}: cLinkedLibs.add arg
+    if pass in {passCmd2, passPP}: cLinkedLibs.add arg.processPath
   of "header":
     headerFile = arg
     incl(gGlobalOptions, optGenIndex)
   of "index":
-    ProcessOnOffSwitchG({optGenIndex}, arg, pass, info)
+    processOnOffSwitchG({optGenIndex}, arg, pass, info)
   of "import":
     expectArg(switch, arg, pass, info)
     if pass in {passCmd2, passPP}: implicitImports.add arg
@@ -425,19 +428,19 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
   of "os": 
     expectArg(switch, arg, pass, info)
     if pass in {passCmd1, passPP}: 
-      theOS = platform.NameToOS(arg)
-      if theOS == osNone: LocalError(info, errUnknownOS, arg)
+      theOS = platform.nameToOS(arg)
+      if theOS == osNone: localError(info, errUnknownOS, arg)
       elif theOS != platform.hostOS: 
         setTarget(theOS, targetCPU)
-        condsyms.InitDefines()
+        condsyms.initDefines()
   of "cpu": 
     expectArg(switch, arg, pass, info)
     if pass in {passCmd1, passPP}: 
-      cpu = platform.NameToCPU(arg)
-      if cpu == cpuNone: LocalError(info, errUnknownCPU, arg)
+      cpu = platform.nameToCPU(arg)
+      if cpu == cpuNone: localError(info, errUnknownCPU, arg)
       elif cpu != platform.hostCPU: 
         setTarget(targetOS, cpu)
-        condsyms.InitDefines()
+        condsyms.initDefines()
   of "run", "r": 
     expectNoArg(switch, arg, pass, info)
     incl(gGlobalOptions, optRun)
@@ -457,7 +460,7 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     expectNoArg(switch, arg, pass, info)
     helpOnError(pass)
   of "symbolfiles": 
-    ProcessOnOffSwitchG({optSymbolFiles}, arg, pass, info)
+    processOnOffSwitchG({optSymbolFiles}, arg, pass, info)
   of "skipcfg": 
     expectNoArg(switch, arg, pass, info)
     incl(gGlobalOptions, optSkipConfigFile)
@@ -517,13 +520,13 @@ proc processSwitch(switch, arg: string, pass: TCmdlinePass, info: TLineInfo) =
     case arg
     of "partial": idents.firstCharIsCS = true
     of "none": idents.firstCharIsCS = false
-    else: LocalError(info, errGenerated,
+    else: localError(info, errGenerated,
       "'partial' or 'none' expected, but found " & arg)
   else:
     if strutils.find(switch, '.') >= 0: options.setConfigVar(switch, arg)
-    else: InvalidCmdLineOption(pass, switch, info)
+    else: invalidCmdLineOption(pass, switch, info)
   
-proc ProcessCommand(switch: string, pass: TCmdLinePass) =
+proc processCommand(switch: string, pass: TCmdLinePass) =
   var cmd, arg: string
   splitSwitch(switch, cmd, arg, pass, gCmdLineInfo)
   processSwitch(cmd, arg, pass, gCmdLineInfo)
diff --git a/compiler/condsyms.nim b/compiler/condsyms.nim
index 21095072b..c79fda13e 100644
--- a/compiler/condsyms.nim
+++ b/compiler/condsyms.nim
@@ -16,10 +16,10 @@ import
 # to be style insensitive. Otherwise hell would break lose.
 var gSymbols: PStringTable
 
-proc DefineSymbol*(symbol: string) = 
+proc defineSymbol*(symbol: string) = 
   gSymbols[symbol] = "true"
 
-proc UndefSymbol*(symbol: string) = 
+proc undefSymbol*(symbol: string) = 
   gSymbols[symbol] = "false"
 
 proc isDefined*(symbol: string): bool = 
@@ -37,52 +37,52 @@ proc countDefinedSymbols*(): int =
   for key, val in pairs(gSymbols):
     if val == "true": inc(result)
 
-proc InitDefines*() = 
+proc initDefines*() = 
   gSymbols = newStringTable(modeStyleInsensitive)
-  DefineSymbol("nimrod") # 'nimrod' is always defined
+  defineSymbol("nimrod") # 'nimrod' is always defined
   # for bootstrapping purposes and old code:
-  DefineSymbol("nimhygiene")
-  DefineSymbol("niminheritable")
-  DefineSymbol("nimmixin")
-  DefineSymbol("nimeffects")
-  DefineSymbol("nimbabel")
-  DefineSymbol("nimcomputedgoto")
+  defineSymbol("nimhygiene")
+  defineSymbol("niminheritable")
+  defineSymbol("nimmixin")
+  defineSymbol("nimeffects")
+  defineSymbol("nimbabel")
+  defineSymbol("nimcomputedgoto")
   
   # add platform specific symbols:
   case targetCPU
-  of cpuI386: DefineSymbol("x86")
-  of cpuIa64: DefineSymbol("itanium")
-  of cpuAmd64: DefineSymbol("x8664")
+  of cpuI386: defineSymbol("x86")
+  of cpuIa64: defineSymbol("itanium")
+  of cpuAmd64: defineSymbol("x8664")
   else: discard
   case targetOS
-  of osDOS: 
-    DefineSymbol("msdos")
+  of osDos: 
+    defineSymbol("msdos")
   of osWindows: 
-    DefineSymbol("mswindows")
-    DefineSymbol("win32")
-  of osLinux, osMorphOS, osSkyOS, osIrix, osPalmOS, osQNX, osAtari, osAix, 
+    defineSymbol("mswindows")
+    defineSymbol("win32")
+  of osLinux, osMorphos, osSkyos, osIrix, osPalmos, osQnx, osAtari, osAix, 
      osHaiku:
     # these are all 'unix-like'
-    DefineSymbol("unix")
-    DefineSymbol("posix")
+    defineSymbol("unix")
+    defineSymbol("posix")
   of osSolaris: 
-    DefineSymbol("sunos")
-    DefineSymbol("unix")
-    DefineSymbol("posix")
-  of osNetBSD, osFreeBSD, osOpenBSD: 
-    DefineSymbol("unix")
-    DefineSymbol("bsd")
-    DefineSymbol("posix")
-  of osMacOS: 
-    DefineSymbol("macintosh")
-  of osMacOSX: 
-    DefineSymbol("macintosh")
-    DefineSymbol("unix")
-    DefineSymbol("posix")
+    defineSymbol("sunos")
+    defineSymbol("unix")
+    defineSymbol("posix")
+  of osNetbsd, osFreebsd, osOpenbsd: 
+    defineSymbol("unix")
+    defineSymbol("bsd")
+    defineSymbol("posix")
+  of osMacos: 
+    defineSymbol("macintosh")
+  of osMacosx: 
+    defineSymbol("macintosh")
+    defineSymbol("unix")
+    defineSymbol("posix")
   else: discard
-  DefineSymbol("cpu" & $cpu[targetCPU].bit)
-  DefineSymbol(normalize(endianToStr[cpu[targetCPU].endian]))
-  DefineSymbol(cpu[targetCPU].name)
-  DefineSymbol(platform.os[targetOS].name)
+  defineSymbol("cpu" & $CPU[targetCPU].bit)
+  defineSymbol(normalize(EndianToStr[CPU[targetCPU].endian]))
+  defineSymbol(CPU[targetCPU].name)
+  defineSymbol(platform.OS[targetOS].name)
   if platform.OS[targetOS].props.contains(ospLacksThreadVars):
-    DefineSymbol("emulatedthreadvars")
+    defineSymbol("emulatedthreadvars")
diff --git a/compiler/crc.nim b/compiler/crc.nim
index a3b181e20..ae1df3ff1 100644
--- a/compiler/crc.nim
+++ b/compiler/crc.nim
@@ -18,8 +18,8 @@ const
   InitAdler32* = int32(1)
 
 proc updateCrc32*(val: int8, crc: TCrc32): TCrc32 {.inline.}
-proc updateCrc32*(val: Char, crc: TCrc32): TCrc32 {.inline.}
-proc crcFromBuf*(buf: Pointer, length: int): TCrc32
+proc updateCrc32*(val: char, crc: TCrc32): TCrc32 {.inline.}
+proc crcFromBuf*(buf: pointer, length: int): TCrc32
 proc strCrc32*(s: string): TCrc32
 proc crcFromFile*(filename: string): TCrc32
 proc updateAdler32*(adler: int32, buf: pointer, length: int): int32
@@ -75,10 +75,10 @@ const
     755167117]
 
 proc updateCrc32(val: int8, crc: TCrc32): TCrc32 = 
-  result = TCrc32(crc32Table[(int(crc) xor (int(val) and 0x000000FF)) and
+  result = TCrc32(crc32table[(int(crc) xor (int(val) and 0x000000FF)) and
       0x000000FF]) xor (crc shr TCrc32(8))
 
-proc updateCrc32(val: Char, crc: TCrc32): TCrc32 = 
+proc updateCrc32(val: char, crc: TCrc32): TCrc32 = 
   result = updateCrc32(toU8(ord(val)), crc)
 
 proc strCrc32(s: string): TCrc32 = 
@@ -93,7 +93,7 @@ type
   TByteArray = array[0..10000000, int8]
   PByteArray = ref TByteArray
 
-proc crcFromBuf(buf: Pointer, length: int): TCrc32 = 
+proc crcFromBuf(buf: pointer, length: int): TCrc32 = 
   var p = cast[PByteArray](buf)
   result = InitCrc32
   for i in countup(0, length - 1): result = updateCrc32(p[i], result)
@@ -102,11 +102,11 @@ proc crcFromFile(filename: string): TCrc32 =
   const 
     bufSize = 8000 # don't use 8K for the memory allocator!
   var 
-    bin: tfile
+    bin: TFile
   result = InitCrc32
   if not open(bin, filename): 
     return                    # not equal if file does not exist
-  var buf = alloc(BufSize)
+  var buf = alloc(bufSize)
   var p = cast[PByteArray](buf)
   while true: 
     var readBytes = readBuffer(bin, buf, bufSize)
diff --git a/compiler/depends.nim b/compiler/depends.nim
index 1468cbdb9..a43eaf844 100644
--- a/compiler/depends.nim
+++ b/compiler/depends.nim
@@ -39,11 +39,11 @@ proc addDotDependency(c: PPassContext, n: PNode): PNode =
   of nkStmtList, nkBlockStmt, nkStmtListExpr, nkBlockExpr: 
     for i in countup(0, sonsLen(n) - 1): discard addDotDependency(c, n.sons[i])
   else: 
-    nil
+    discard
 
 proc generateDot(project: string) = 
   writeRope(ropef("digraph $1 {$n$2}$n", [
-      toRope(changeFileExt(extractFileName(project), "")), gDotGraph]), 
+      toRope(changeFileExt(extractFilename(project), "")), gDotGraph]), 
             changeFileExt(project, "dot"))
 
 proc myOpen(module: PSym): PPassContext =
diff --git a/compiler/docgen.nim b/compiler/docgen.nim
index d44018a2b..343f415b3 100644
--- a/compiler/docgen.nim
+++ b/compiler/docgen.nim
@@ -40,33 +40,33 @@ proc compilerMsgHandler(filename: string, line, col: int,
   of mwRedefinitionOfLabel: k = warnRedefinitionOfLabel
   of mwUnknownSubstitution: k = warnUnknownSubstitutionX
   of mwUnsupportedLanguage: k = warnLanguageXNotSupported
-  GlobalError(newLineInfo(filename, line, col), k, arg)
+  globalError(newLineInfo(filename, line, col), k, arg)
 
 proc parseRst(text, filename: string,
               line, column: int, hasToc: var bool,
               rstOptions: TRstParseOptions): PRstNode =
   result = rstParse(text, filename, line, column, hasToc, rstOptions,
-                    options.FindFile, compilerMsgHandler)
+                    options.findFile, compilerMsgHandler)
 
 proc newDocumentor*(filename: string, config: PStringTable): PDoc =
   new(result)
-  initRstGenerator(result[], (if gCmd != cmdRst2Tex: outHtml else: outLatex),
+  initRstGenerator(result[], (if gCmd != cmdRst2tex: outHtml else: outLatex),
                    options.gConfigVars, filename, {roSupportRawDirective},
-                   options.FindFile, compilerMsgHandler)
+                   options.findFile, compilerMsgHandler)
   result.id = 100
 
-proc dispA(dest: var PRope, xml, tex: string, args: openarray[PRope]) =
-  if gCmd != cmdRst2Tex: appf(dest, xml, args)
+proc dispA(dest: var PRope, xml, tex: string, args: openArray[PRope]) =
+  if gCmd != cmdRst2tex: appf(dest, xml, args)
   else: appf(dest, tex, args)
 
-proc getVarIdx(varnames: openarray[string], id: string): int =
+proc getVarIdx(varnames: openArray[string], id: string): int =
   for i in countup(0, high(varnames)):
     if cmpIgnoreStyle(varnames[i], id) == 0:
       return i
   result = -1
 
-proc ropeFormatNamedVars(frmt: TFormatStr, varnames: openarray[string],
-                         varvalues: openarray[PRope]): PRope =
+proc ropeFormatNamedVars(frmt: TFormatStr, varnames: openArray[string],
+                         varvalues: openArray[PRope]): PRope =
   var i = 0
   var L = len(frmt)
   result = nil
@@ -85,7 +85,7 @@ proc ropeFormatNamedVars(frmt: TFormatStr, varnames: openarray[string],
       of '0'..'9':
         var j = 0
         while true:
-          j = (j * 10) + Ord(frmt[i]) - ord('0')
+          j = (j * 10) + ord(frmt[i]) - ord('0')
           inc(i)
           if (i > L + 0 - 1) or not (frmt[i] in {'0'..'9'}): break
         if j > high(varvalues) + 1: internalError("ropeFormatNamedVars")
@@ -112,7 +112,7 @@ proc ropeFormatNamedVars(frmt: TFormatStr, varnames: openarray[string],
         var idx = getVarIdx(varnames, id)
         if idx >= 0: app(result, varvalues[idx])
         else: rawMessage(errUnkownSubstitionVar, id)
-      else: InternalError("ropeFormatNamedVars")
+      else: internalError("ropeFormatNamedVars")
     var start = i
     while i < L:
       if frmt[i] != '$': inc(i)
@@ -124,7 +124,7 @@ proc genComment(d: PDoc, n: PNode): string =
   var dummyHasToc: bool
   if n.comment != nil and startsWith(n.comment, "##"):
     renderRstToOut(d[], parseRst(n.comment, toFilename(n.info),
-                               toLineNumber(n.info), toColumn(n.info),
+                               toLinenumber(n.info), toColumn(n.info),
                                dummyHasToc, d.options + {roSkipPounds}), result)
 
 proc genRecComment(d: PDoc, n: PNode): PRope =
@@ -152,7 +152,7 @@ proc extractDocComment*(s: PSym, d: PDoc = nil): string =
     if not d.isNil:
       var dummyHasToc: bool
       renderRstToOut(d[], parseRst(n.comment, toFilename(n.info),
-                                   toLineNumber(n.info), toColumn(n.info),
+                                   toLinenumber(n.info), toColumn(n.info),
                                    dummyHasToc, d.options + {roSkipPounds}),
                      result)
     else:
@@ -272,7 +272,7 @@ proc genJSONItem(d: PDoc, n, nameNode: PNode, k: TSymKind): PJsonNode =
     result["code"] = %r.buf
 
 proc checkForFalse(n: PNode): bool =
-  result = n.kind == nkIdent and IdentEq(n.ident, "false")
+  result = n.kind == nkIdent and identEq(n.ident, "false")
 
 proc traceDeps(d: PDoc, n: PNode) =
   const k = skModule
@@ -313,7 +313,7 @@ proc generateDoc*(d: PDoc, n: PNode) =
   of nkImportStmt:
     for i in 0 .. sonsLen(n)-1: traceDeps(d, n.sons[i])
   of nkFromStmt, nkImportExceptStmt: traceDeps(d, n.sons[0])
-  else: nil
+  else: discard
 
 proc generateJson(d: PDoc, n: PNode, jArray: PJsonNode = nil): PJsonNode =
   case n.kind
@@ -355,7 +355,7 @@ proc generateJson(d: PDoc, n: PNode, jArray: PJsonNode = nil): PJsonNode =
     # generate documentation for the first branch only:
     if not checkForFalse(n.sons[0].sons[0]) and jArray != nil:
       discard generateJson(d, lastSon(n.sons[0]), jArray)
-  else: nil
+  else: discard
 
 proc genSection(d: PDoc, kind: TSymKind) =
   const sectionNames: array[skModule..skTemplate, string] = [
@@ -408,7 +408,7 @@ proc genOutFile(d: PDoc): PRope =
 proc generateIndex*(d: PDoc) =
   if optGenIndex in gGlobalOptions:
     writeIndexFile(d[], splitFile(options.outFile).dir /
-                        splitFile(d.filename).name & indexExt)
+                        splitFile(d.filename).name & IndexExt)
 
 proc writeOutput*(d: PDoc, filename, outExt: string, useWarning = false) =
   var content = genOutFile(d)
@@ -417,7 +417,7 @@ proc writeOutput*(d: PDoc, filename, outExt: string, useWarning = false) =
   else:
     writeRope(content, getOutFile(filename, outExt), useWarning)
 
-proc CommandDoc*() =
+proc commandDoc*() =
   var ast = parseFile(gProjectMainIdx)
   if ast == nil: return
   var d = newDocumentor(gProjectFull, options.gConfigVars)
@@ -426,7 +426,7 @@ proc CommandDoc*() =
   writeOutput(d, gProjectFull, HtmlExt)
   generateIndex(d)
 
-proc CommandRstAux(filename, outExt: string) =
+proc commandRstAux(filename, outExt: string) =
   var filen = addFileExt(filename, "txt")
   var d = newDocumentor(filen, options.gConfigVars)
   var rst = parseRst(readFile(filen), filen, 0, 1, d.hasToc,
@@ -439,14 +439,14 @@ proc CommandRstAux(filename, outExt: string) =
   writeOutput(d, filename, outExt)
   generateIndex(d)
 
-proc CommandRst2Html*() =
-  CommandRstAux(gProjectFull, HtmlExt)
+proc commandRst2Html*() =
+  commandRstAux(gProjectFull, HtmlExt)
 
-proc CommandRst2TeX*() =
+proc commandRst2TeX*() =
   splitter = "\\-"
-  CommandRstAux(gProjectFull, TexExt)
+  commandRstAux(gProjectFull, TexExt)
 
-proc CommandJSON*() =
+proc commandJSON*() =
   var ast = parseFile(gProjectMainIdx)
   if ast == nil: return
   var d = newDocumentor(gProjectFull, options.gConfigVars)
@@ -460,7 +460,7 @@ proc CommandJSON*() =
     echo getOutFile(gProjectFull, JsonExt)
     writeRope(content, getOutFile(gProjectFull, JsonExt), useWarning = false)
 
-proc CommandBuildIndex*() =
+proc commandBuildIndex*() =
   var content = mergeIndexes(gProjectFull).toRope
 
   let code = ropeFormatNamedVars(getConfigVar("doc.file"), ["title",
diff --git a/compiler/docgen2.nim b/compiler/docgen2.nim
index d48f53d15..d76be8e3c 100644
--- a/compiler/docgen2.nim
+++ b/compiler/docgen2.nim
@@ -27,7 +27,7 @@ proc close(p: PPassContext, n: PNode): PNode =
     try:
       generateIndex(g.doc)
     except EIO:
-      nil
+      discard
 
 proc processNode(c: PPassContext, n: PNode): PNode = 
   result = n
@@ -46,4 +46,4 @@ proc myOpen(module: PSym): PPassContext =
 const docgen2Pass* = makePass(open = myOpen, process = processNode, close = close)
 
 proc finishDoc2Pass*(project: string) = 
-  nil
+  discard
diff --git a/compiler/evalffi.nim b/compiler/evalffi.nim
index 21a131996..74f0663f3 100644
--- a/compiler/evalffi.nim
+++ b/compiler/evalffi.nim
@@ -9,7 +9,7 @@
 
 ## This file implements the FFI part of the evaluator for Nimrod code.
 
-import ast, astalgo, ropes, types, options, tables, dynlib, libffi, msgs
+import ast, astalgo, ropes, types, options, tables, dynlib, libffi, msgs, os
 
 when defined(windows):
   const libcDll = "msvcrt.dll"
@@ -20,7 +20,11 @@ type
   TDllCache = tables.TTable[string, TLibHandle]
 var
   gDllCache = initTable[string, TLibHandle]()
-  gExeHandle = LoadLib()
+
+when defined(windows):
+  var gExeHandle = loadLib(os.getAppFilename())
+else:
+  var gExeHandle = loadLib()
 
 proc getDll(cache: var TDllCache; dll: string; info: TLineInfo): pointer =
   result = cache[dll]
@@ -28,15 +32,17 @@ proc getDll(cache: var TDllCache; dll: string; info: TLineInfo): pointer =
     var libs: seq[string] = @[]
     libCandidates(dll, libs)
     for c in libs:
-      result = LoadLib(c)
+      result = loadLib(c)
       if not result.isNil: break
     if result.isNil:
-      GlobalError(info, "cannot load: " & dll)
+      globalError(info, "cannot load: " & dll)
     cache[dll] = result
 
 const
   nkPtrLit = nkIntLit # hopefully we can get rid of this hack soon
 
+var myerrno {.importc: "errno", header: "<errno.h>".}: cint ## error variable
+
 proc importcSymbol*(sym: PSym): PNode =
   let name = ropeToStr(sym.loc.r)
   
@@ -47,10 +53,11 @@ proc importcSymbol*(sym: PSym): PNode =
   of "stdin":  result.intVal = cast[TAddress](system.stdin)
   of "stdout": result.intVal = cast[TAddress](system.stdout)
   of "stderr": result.intVal = cast[TAddress](system.stderr)
+  of "vmErrnoWrapper": result.intVal = cast[TAddress](myerrno)
   else:
     let lib = sym.annex
     if lib != nil and lib.path.kind notin {nkStrLit..nkTripleStrLit}:
-      GlobalError(sym.info, "dynlib needs to be a string lit for the REPL")
+      globalError(sym.info, "dynlib needs to be a string lit for the REPL")
     var theAddr: pointer
     if lib.isNil and not gExehandle.isNil:
       # first try this exe itself:
@@ -58,10 +65,12 @@ proc importcSymbol*(sym: PSym): PNode =
       # then try libc:
       if theAddr.isNil:
         let dllhandle = gDllCache.getDll(libcDll, sym.info)
-        theAddr = dllhandle.checkedSymAddr(name)
-    else:
-      let dllhandle = gDllCache.getDll(lib.path.strVal, sym.info)
-      theAddr = dllhandle.checkedSymAddr(name)
+        theAddr = dllhandle.symAddr(name)
+    elif not lib.isNil:
+      let dllhandle = gDllCache.getDll(if lib.kind == libHeader: libcDll 
+                                       else: lib.path.strVal, sym.info)
+      theAddr = dllhandle.symAddr(name)
+    if theAddr.isNil: globalError(sym.info, "cannot import: " & sym.name.s)
     result.intVal = cast[TAddress](theAddr)
 
 proc mapType(t: ast.PType): ptr libffi.TType =
@@ -78,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])
@@ -139,7 +148,7 @@ proc getField(n: PNode; position: int): PSym =
       else: internalError(n.info, "getField(record case branch)")
   of nkSym:
     if n.sym.position == position: result = n.sym
-  else: nil
+  else: discard
 
 proc packObject(x: PNode, typ: PType, res: pointer) =
   InternalAssert x.kind in {nkObjConstr, nkPar}
@@ -192,7 +201,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
   of tyPointer, tyProc,  tyCString, tyString:
     if v.kind == nkNilLit:
       # nothing to do since the memory is 0 initialized anyway
-      nil
+      discard
     elif v.kind == nkPtrLit:
       awr(pointer, cast[pointer](v.intVal))
     elif v.kind in {nkStrLit..nkTripleStrLit}:
@@ -202,7 +211,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
   of tyPtr, tyRef, tyVar:
     if v.kind == nkNilLit:
       # nothing to do since the memory is 0 initialized anyway
-      nil
+      discard
     elif v.kind == nkPtrLit:
       awr(pointer, cast[pointer](v.intVal))
     else:
@@ -220,7 +229,7 @@ proc pack(v: PNode, typ: PType, res: pointer) =
   of tyObject, tyTuple:
     packObject(v, typ, res)
   of tyNil:
-    nil
+    discard
   of tyDistinct, tyGenericInst:
     pack(v, typ.sons[0], res)
   else:
@@ -241,7 +250,7 @@ proc unpackObjectAdd(x: pointer, n, result: PNode) =
     pair.sons[1] = unpack(x +! n.sym.offset, n.sym.typ, nil)
     #echo "offset: ", n.sym.name.s, " ", n.sym.offset
     result.add pair
-  else: nil
+  else: discard
 
 proc unpackObject(x: pointer, typ: PType, n: PNode): PNode =
   # compute the field's offsets:
@@ -441,3 +450,46 @@ proc callForeignFunction*(call: PNode): PNode =
   for i in 1 .. call.len-1:
     call.sons[i] = unpack(args[i-1], typ.sons[i], call[i])
     dealloc args[i-1]
+
+proc callForeignFunction*(fn: PNode, fntyp: PType,
+                          args: var TNodeSeq, start, len: int,
+                          info: TLineInfo): PNode =
+  internalAssert fn.kind == nkPtrLit
+  
+  var cif: TCif
+  var sig: TParamList
+  for i in 0..len-1:
+    var aTyp = args[i+start].typ
+    if aTyp.isNil:
+      internalAssert i+1 < fntyp.len
+      aTyp = fntyp.sons[i+1]
+      args[i+start].typ = aTyp
+    sig[i] = mapType(aTyp)
+    if sig[i].isNil: globalError(info, "cannot map FFI type")
+  
+  if prep_cif(cif, mapCallConv(fntyp.callConv, info), cuint(len),
+              mapType(fntyp.sons[0]), sig) != OK:
+    globalError(info, "error in FFI call")
+  
+  var cargs: TArgList
+  let fn = cast[pointer](fn.intVal)
+  for i in 0 .. len-1:
+    let t = args[i+start].typ
+    cargs[i] = alloc0(packSize(args[i+start], t))
+    pack(args[i+start], t, cargs[i])
+  let retVal = if isEmptyType(fntyp.sons[0]): pointer(nil)
+               else: alloc(fntyp.sons[0].getSize.int)
+
+  libffi.call(cif, fn, retVal, cargs)
+  
+  if retVal.isNil: 
+    result = emptyNode
+  else:
+    result = unpack(retVal, fntyp.sons[0], nil)
+    result.info = info
+
+  if retVal != nil: dealloc retVal
+  for i in 0 .. len-1:
+    let t = args[i+start].typ
+    args[i+start] = unpack(cargs[i], t, args[i+start])
+    dealloc cargs[i]
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/evaltempl.nim b/compiler/evaltempl.nim
index 05be0e9d3..78cdbb45f 100644
--- a/compiler/evaltempl.nim
+++ b/compiler/evaltempl.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2012 Andreas Rumpf
+#        (c) Copyright 2013 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -16,9 +16,14 @@ import
 type
   TemplCtx {.pure, final.} = object
     owner, genSymOwner: PSym
+    instLines: bool   # use the instantiation lines numbers
     mapping: TIdTable # every gensym'ed symbol needs to be mapped to some
                       # new symbol
 
+proc copyNode(ctx: TemplCtx, a, b: PNode): PNode =
+  result = copyNode(a)
+  if ctx.instLines: result.info = b.info
+
 proc evalTemplateAux(templ, actual: PNode, c: var TemplCtx, result: PNode) =
   case templ.kind
   of nkSym:
@@ -31,49 +36,23 @@ proc evalTemplateAux(templ, actual: PNode, c: var TemplCtx, result: PNode) =
         else:
           result.add copyTree(x)
       else:
-        InternalAssert sfGenSym in s.flags
-        var x = PSym(IdTableGet(c.mapping, s))
+        internalAssert sfGenSym in s.flags
+        var x = PSym(idTableGet(c.mapping, s))
         if x == nil:
           x = copySym(s, false)
           x.owner = c.genSymOwner
-          IdTablePut(c.mapping, s, x)
-        result.add newSymNode(x, templ.info)
+          idTablePut(c.mapping, s, x)
+        result.add newSymNode(x, if c.instLines: actual.info else: templ.info)
     else:
-      result.add copyNode(templ)
+      result.add copyNode(c, templ, actual)
   of nkNone..nkIdent, nkType..nkNilLit: # atom
-    result.add copyNode(templ)
+    result.add copyNode(c, templ, actual)
   else:
-    var res = copyNode(templ)
+    var res = copyNode(c, templ, actual)
     for i in countup(0, sonsLen(templ) - 1): 
       evalTemplateAux(templ.sons[i], actual, c, res)
     result.add res
 
-when false:
-  proc evalTemplateAux(templ, actual: PNode, c: var TemplCtx): PNode =
-    case templ.kind
-    of nkSym:
-      var s = templ.sym
-      if s.owner.id == c.owner.id:
-        if s.kind == skParam:
-          result = copyTree(actual.sons[s.position])
-        else:
-          InternalAssert sfGenSym in s.flags
-          var x = PSym(IdTableGet(c.mapping, s))
-          if x == nil:
-            x = copySym(s, false)
-            x.owner = c.genSymOwner
-            IdTablePut(c.mapping, s, x)
-          result = newSymNode(x, templ.info)
-      else:
-        result = copyNode(templ)
-    of nkNone..nkIdent, nkType..nkNilLit: # atom
-      result = copyNode(templ)
-    else:
-      result = copyNode(templ)
-      newSons(result, sonsLen(templ))
-      for i in countup(0, sonsLen(templ) - 1): 
-        result.sons[i] = evalTemplateAux(templ.sons[i], actual, c)
-
 proc evalTemplateArgs(n: PNode, s: PSym): PNode =
   # if the template has zero arguments, it can be called without ``()``
   # `n` is then a nkSym or something similar
@@ -83,13 +62,13 @@ proc evalTemplateArgs(n: PNode, s: PSym): PNode =
     a = sonsLen(n)
   else: a = 0
   var f = s.typ.sonsLen
-  if a > f: GlobalError(n.info, errWrongNumberOfArguments)
+  if a > f: globalError(n.info, errWrongNumberOfArguments)
 
   result = newNodeI(nkArgList, n.info)
   for i in countup(1, f - 1):
     var arg = if i < a: n.sons[i] else: copyTree(s.typ.n.sons[i].sym.ast)
     if arg == nil or arg.kind == nkEmpty:
-      LocalError(n.info, errWrongNumberOfArguments)
+      localError(n.info, errWrongNumberOfArguments)
     addSon(result, arg)
 
 var evalTemplateCounter* = 0
@@ -98,7 +77,7 @@ var evalTemplateCounter* = 0
 proc evalTemplate*(n: PNode, tmpl, genSymOwner: PSym): PNode =
   inc(evalTemplateCounter)
   if evalTemplateCounter > 100:
-    GlobalError(n.info, errTemplateInstantiationTooNested)
+    globalError(n.info, errTemplateInstantiationTooNested)
     result = n
 
   # replace each param by the corresponding node:
@@ -114,11 +93,13 @@ proc evalTemplate*(n: PNode, tmpl, genSymOwner: PSym): PNode =
     evalTemplateAux(body, args, ctx, result)
     if result.len == 1: result = result.sons[0]
     else:
-      GlobalError(result.info, errIllFormedAstX,
+      globalError(result.info, errIllFormedAstX,
                   renderTree(result, {renderNoComments}))
   else:
     result = copyNode(body)
-    #evalTemplateAux(body, args, ctx, result)
+    ctx.instLines = body.kind notin {nkStmtList, nkStmtListExpr,
+                                     nkBlockStmt, nkBlockExpr}
+    if ctx.instLines: result.info = n.info
     for i in countup(0, safeLen(body) - 1):
       evalTemplateAux(body.sons[i], args, ctx, result)
   
diff --git a/compiler/extccomp.nim b/compiler/extccomp.nim
index d3b3cee75..12761f1d4 100644
--- a/compiler/extccomp.nim
+++ b/compiler/extccomp.nim
@@ -324,7 +324,7 @@ var
   compileOptions: string = ""
   ccompilerpath: string = ""
 
-proc NameToCC*(name: string): TSystemCC = 
+proc nameToCC*(name: string): TSystemCC = 
   for i in countup(succ(ccNone), high(TSystemCC)): 
     if cmpIgnoreStyle(name, CC[i].name) == 0: 
       return i
@@ -335,8 +335,8 @@ proc getConfigVar(c: TSystemCC, suffix: string): string =
   # for niminst support
   if (platform.hostOS != targetOS or platform.hostCPU != targetCPU) and
       optCompileOnly notin gGlobalOptions:
-    let fullCCname = platform.cpu[targetCPU].name & '.' & 
-                     platform.os[targetOS].name & '.' & 
+    let fullCCname = platform.CPU[targetCPU].name & '.' & 
+                     platform.OS[targetOS].name & '.' & 
                      CC[c].name & suffix
     result = getConfigVar(fullCCname)
     if result.len == 0:
@@ -346,13 +346,13 @@ proc getConfigVar(c: TSystemCC, suffix: string): string =
     result = getConfigVar(CC[c].name & suffix)
 
 proc setCC*(ccname: string) = 
-  ccompiler = nameToCC(ccname)
-  if ccompiler == ccNone: rawMessage(errUnknownCcompiler, ccname)
-  compileOptions = getConfigVar(ccompiler, ".options.always")
-  linkOptions = getConfigVar(ccompiler, ".options.linker")
-  ccompilerpath = getConfigVar(ccompiler, ".path")
+  cCompiler = nameToCC(ccname)
+  if cCompiler == ccNone: rawMessage(errUnknownCcompiler, ccname)
+  compileOptions = getConfigVar(cCompiler, ".options.always")
+  linkOptions = getConfigVar(cCompiler, ".options.linker")
+  ccompilerpath = getConfigVar(cCompiler, ".path")
   for i in countup(low(CC), high(CC)): undefSymbol(CC[i].name)
-  defineSymbol(CC[ccompiler].name)
+  defineSymbol(CC[cCompiler].name)
 
 proc addOpt(dest: var string, src: string) = 
   if len(dest) == 0 or dest[len(dest)-1] != ' ': add(dest, " ")
@@ -368,20 +368,20 @@ proc addCompileOption*(option: string) =
 proc initVars*() = 
   # we need to define the symbol here, because ``CC`` may have never been set!
   for i in countup(low(CC), high(CC)): undefSymbol(CC[i].name)
-  defineSymbol(CC[ccompiler].name)
+  defineSymbol(CC[cCompiler].name)
   if gCmd == cmdCompileToCpp: cExt = ".cpp"
   elif gCmd == cmdCompileToOC: cExt = ".m"
-  addCompileOption(getConfigVar(ccompiler, ".options.always"))
-  addLinkOption(getConfigVar(ccompiler, ".options.linker"))
-  if len(ccompilerPath) == 0:
-    ccompilerpath = getConfigVar(ccompiler, ".path")
+  addCompileOption(getConfigVar(cCompiler, ".options.always"))
+  addLinkOption(getConfigVar(cCompiler, ".options.linker"))
+  if len(ccompilerpath) == 0:
+    ccompilerpath = getConfigVar(cCompiler, ".path")
 
 proc completeCFilePath*(cfile: string, createSubDir: bool = true): string = 
   result = completeGeneratedFilePath(cfile, createSubDir)
 
 proc toObjFile*(filenameWithoutExt: string): string = 
   # Object file for compilation
-  result = changeFileExt(filenameWithoutExt, cc[ccompiler].objExt)
+  result = changeFileExt(filenameWithoutExt, CC[cCompiler].objExt)
 
 proc addFileToCompile*(filename: string) =
   appendStr(toCompile, filename)
@@ -400,28 +400,28 @@ proc addFileToLink*(filename: string) =
   # BUGFIX: was ``appendStr``
 
 proc execExternalProgram*(cmd: string) = 
-  if optListCmd in gGlobalOptions or gVerbosity > 0: MsgWriteln(cmd)
+  if optListCmd in gGlobalOptions or gVerbosity > 0: msgWriteln(cmd)
   if execCmd(cmd) != 0: rawMessage(errExecutionOfProgramFailed, "")
 
 proc generateScript(projectFile: string, script: PRope) = 
   let (dir, name, ext) = splitFile(projectFile)
-  WriteRope(script, dir / addFileExt("compile_" & name, 
-                                     platform.os[targetOS].scriptExt))
+  writeRope(script, dir / addFileExt("compile_" & name, 
+                                     platform.OS[targetOS].scriptExt))
 
 proc getOptSpeed(c: TSystemCC): string = 
   result = getConfigVar(c, ".options.speed")
   if result == "":
-    result = cc[c].optSpeed   # use default settings from this file
+    result = CC[c].optSpeed   # use default settings from this file
 
 proc getDebug(c: TSystemCC): string = 
   result = getConfigVar(c, ".options.debug")
   if result == "":
-    result = cc[c].debug      # use default settings from this file
+    result = CC[c].debug      # use default settings from this file
 
 proc getOptSize(c: TSystemCC): string = 
   result = getConfigVar(c, ".options.size")
   if result == "":
-    result = cc[c].optSize    # use default settings from this file
+    result = CC[c].optSize    # use default settings from this file
 
 proc noAbsolutePaths: bool {.inline.} =
   # We used to check current OS != specified OS, but this makes no sense
@@ -436,78 +436,78 @@ const
 
 var fileCounter: int
 
-proc add(s: var string, many: openarray[string]) =
+proc add(s: var string, many: openArray[string]) =
   s.add many.join
 
-proc CFileSpecificOptions(cfilename: string): string =
+proc cFileSpecificOptions(cfilename: string): string =
   result = compileOptions
   var trunk = splitFile(cfilename).name
   if optCDebug in gGlobalOptions: 
     var key = trunk & ".debug"
     if existsConfigVar(key): addOpt(result, getConfigVar(key))
-    else: addOpt(result, getDebug(ccompiler))
+    else: addOpt(result, getDebug(cCompiler))
   if optOptimizeSpeed in gOptions:
     var key = trunk & ".speed"
     if existsConfigVar(key): addOpt(result, getConfigVar(key))
-    else: addOpt(result, getOptSpeed(ccompiler))
+    else: addOpt(result, getOptSpeed(cCompiler))
   elif optOptimizeSize in gOptions:
     var key = trunk & ".size"
     if existsConfigVar(key): addOpt(result, getConfigVar(key))
-    else: addOpt(result, getOptSize(ccompiler))
+    else: addOpt(result, getOptSize(cCompiler))
   var key = trunk & ".always"
   if existsConfigVar(key): addOpt(result, getConfigVar(key))
 
 proc getCompileOptions: string =
-  result = CFileSpecificOptions("__dummy__")
+  result = cFileSpecificOptions("__dummy__")
 
 proc getLinkOptions: string =
   result = linkOptions
   for linkedLib in items(cLinkedLibs):
-    result.add(cc[ccompiler].linkLibCmd % linkedLib.quoteShell)
+    result.add(CC[cCompiler].linkLibCmd % linkedLib.quoteShell)
   for libDir in items(cLibs):
-    result.add([cc[ccompiler].linkDirCmd, libDir.quoteShell])
+    result.add([CC[cCompiler].linkDirCmd, libDir.quoteShell])
 
 proc needsExeExt(): bool {.inline.} =
   result = (optGenScript in gGlobalOptions and targetOS == osWindows) or
                                        (platform.hostOS == osWindows)
 
 proc getCompileCFileCmd*(cfilename: string, isExternal = false): string = 
-  var c = ccompiler
-  var options = CFileSpecificOptions(cfilename)
+  var c = cCompiler
+  var options = cFileSpecificOptions(cfilename)
   var exe = getConfigVar(c, ".exe")
-  if exe.len == 0: exe = cc[c].compilerExe
+  if exe.len == 0: exe = CC[c].compilerExe
   
   if needsExeExt(): exe = addFileExt(exe, "exe")
   if optGenDynLib in gGlobalOptions and
       ospNeedsPIC in platform.OS[targetOS].props: 
-    add(options, ' ' & cc[c].pic)
+    add(options, ' ' & CC[c].pic)
   
   var includeCmd, compilePattern: string
   if not noAbsolutePaths(): 
     # compute include paths:
-    includeCmd = cc[c].includeCmd & quoteShell(libpath)
+    includeCmd = CC[c].includeCmd & quoteShell(libpath)
 
     for includeDir in items(cIncludes):
-      includeCmd.add([cc[c].includeCmd, includeDir.quoteShell])
+      includeCmd.add([CC[c].includeCmd, includeDir.quoteShell])
 
-    compilePattern = JoinPath(ccompilerpath, exe)
+    compilePattern = joinPath(ccompilerpath, exe)
   else: 
     includeCmd = ""
-    compilePattern = cc[c].compilerExe
+    compilePattern = CC[c].compilerExe
   
-  var cfile = if noAbsolutePaths(): extractFileName(cfilename) 
+  var cfile = if noAbsolutePaths(): extractFilename(cfilename) 
               else: cfilename
   var objfile = if not isExternal or noAbsolutePaths(): 
                   toObjFile(cfile) 
                 else: 
                   completeCFilePath(toObjFile(cfile))
-  cfile = quoteShell(AddFileExt(cfile, cExt))
+  cfile = quoteShell(addFileExt(cfile, cExt))
   objfile = quoteShell(objfile)
   result = quoteShell(compilePattern % [
     "file", cfile, "objfile", objfile, "options", options, 
     "include", includeCmd, "nimrod", getPrefixDir(), "lib", libpath])
   add(result, ' ')
-  addf(result, cc[c].compileTmpl, [
+  addf(result, CC[c].compileTmpl, [
     "file", cfile, "objfile", objfile, 
     "options", options, "include", includeCmd, 
     "nimrod", quoteShell(getPrefixDir()), 
@@ -517,7 +517,7 @@ proc footprint(filename: string): TCrc32 =
   result = crcFromFile(filename) ><
       platform.OS[targetOS].name ><
       platform.CPU[targetCPU].name ><
-      extccomp.CC[extccomp.ccompiler].name ><
+      extccomp.CC[extccomp.cCompiler].name ><
       getCompileCFileCmd(filename, true)
 
 proc externalFileChanged(filename: string): bool = 
@@ -541,7 +541,7 @@ proc addExternalFileToCompile*(filename: string) =
   if optForceFullMake in gGlobalOptions or externalFileChanged(filename):
     appendStr(externalToCompile, filename)
 
-proc CompileCFile(list: TLinkedList, script: var PRope, cmds: var TStringSeq, 
+proc compileCFile(list: TLinkedList, script: var PRope, cmds: var TStringSeq, 
                   isExternal: bool) = 
   var it = PStrEntry(list.head)
   while it != nil: 
@@ -554,18 +554,18 @@ proc CompileCFile(list: TLinkedList, script: var PRope, cmds: var TStringSeq,
       app(script, tnl)
     it = PStrEntry(it.next)
 
-proc CallCCompiler*(projectfile: string) =
+proc callCCompiler*(projectfile: string) =
   var 
     linkCmd, buildgui, builddll: string
   if gGlobalOptions * {optCompileOnly, optGenScript} == {optCompileOnly}: 
     return # speed up that call if only compiling and no script shall be
            # generated
   fileCounter = 0
-  var c = ccompiler
+  var c = cCompiler
   var script: PRope = nil
   var cmds: TStringSeq = @[]
-  CompileCFile(toCompile, script, cmds, false)
-  CompileCFile(externalToCompile, script, cmds, true)
+  compileCFile(toCompile, script, cmds, false)
+  compileCFile(externalToCompile, script, cmds, true)
   if optCompileOnly notin gGlobalOptions: 
     if gNumberOfProcessors == 0: gNumberOfProcessors = countProcessors()
     var res = 0
@@ -591,40 +591,40 @@ proc CallCCompiler*(projectfile: string) =
       let objFile = if noAbsolutePaths(): it.data.extractFilename else: it.data
       add(objfiles, ' ')
       add(objfiles, quoteShell(
-          addFileExt(objFile, cc[ccompiler].objExt)))
+          addFileExt(objFile, CC[cCompiler].objExt)))
       it = PStrEntry(it.next)
 
     if optGenStaticLib in gGlobalOptions:
-      linkcmd = cc[c].buildLib % ["libfile", (libNameTmpl() % gProjectName),
+      linkCmd = CC[c].buildLib % ["libfile", (libNameTmpl() % gProjectName),
                                   "objfiles", objfiles]
       if optCompileOnly notin gGlobalOptions: execExternalProgram(linkCmd)
     else:
       var linkerExe = getConfigVar(c, ".linkerexe")
-      if len(linkerExe) == 0: linkerExe = cc[c].linkerExe
+      if len(linkerExe) == 0: linkerExe = CC[c].linkerExe
       if needsExeExt(): linkerExe = addFileExt(linkerExe, "exe")
       if noAbsolutePaths(): linkCmd = quoteShell(linkerExe)
-      else: linkCmd = quoteShell(JoinPath(ccompilerpath, linkerExe))
-      if optGenGuiApp in gGlobalOptions: buildGui = cc[c].buildGui
-      else: buildGui = ""
+      else: linkCmd = quoteShell(joinPath(ccompilerpath, linkerExe))
+      if optGenGuiApp in gGlobalOptions: buildgui = CC[c].buildGui
+      else: buildgui = ""
       var exefile: string
       if optGenDynLib in gGlobalOptions:
-        exefile = platform.os[targetOS].dllFrmt % splitFile(projectFile).name
-        buildDll = cc[c].buildDll
+        exefile = platform.OS[targetOS].dllFrmt % splitFile(projectfile).name
+        builddll = CC[c].buildDll
       else:
-        exefile = splitFile(projectFile).name & platform.os[targetOS].exeExt
-        buildDll = ""
+        exefile = splitFile(projectfile).name & platform.OS[targetOS].exeExt
+        builddll = ""
       if options.outFile.len > 0: 
-        exefile = options.outFile
+        exefile = options.outFile.expandTilde
       if not noAbsolutePaths():
-        if not exeFile.isAbsolute():
-          exefile = joinPath(splitFile(projectFile).dir, exefile)
+        if not exefile.isAbsolute():
+          exefile = joinPath(splitFile(projectfile).dir, exefile)
       exefile = quoteShell(exefile)
       let linkOptions = getLinkOptions()
       linkCmd = quoteShell(linkCmd % ["builddll", builddll,
           "buildgui", buildgui, "options", linkOptions, "objfiles", objfiles,
           "exefile", exefile, "nimrod", getPrefixDir(), "lib", libpath])
       linkCmd.add ' '
-      addf(linkCmd, cc[c].linkTmpl, ["builddll", builddll,
+      addf(linkCmd, CC[c].linkTmpl, ["builddll", builddll,
           "buildgui", buildgui, "options", linkOptions,
           "objfiles", objfiles, "exefile", exefile,
           "nimrod", quoteShell(getPrefixDir()),
@@ -635,12 +635,12 @@ proc CallCCompiler*(projectfile: string) =
   if optGenScript in gGlobalOptions:
     app(script, linkCmd)
     app(script, tnl)
-    generateScript(projectFile, script)
+    generateScript(projectfile, script)
 
 proc genMappingFiles(list: TLinkedList): PRope = 
   var it = PStrEntry(list.head)
   while it != nil: 
-    appf(result, "--file:r\"$1\"$N", [toRope(AddFileExt(it.data, cExt))])
+    appf(result, "--file:r\"$1\"$N", [toRope(addFileExt(it.data, cExt))])
     it = PStrEntry(it.next)
 
 proc writeMapping*(gSymbolMapping: PRope) = 
@@ -658,5 +658,5 @@ proc writeMapping*(gSymbolMapping: PRope) =
   app(code, strutils.escape(libpath))
   
   appf(code, "\n[Symbols]$n$1", [gSymbolMapping])
-  WriteRope(code, joinPath(gProjectPath, "mapping.txt"))
+  writeRope(code, joinPath(gProjectPath, "mapping.txt"))
   
diff --git a/compiler/filter_tmpl.nim b/compiler/filter_tmpl.nim
index d16639d08..0014e9c78 100644
--- a/compiler/filter_tmpl.nim
+++ b/compiler/filter_tmpl.nim
@@ -27,7 +27,7 @@ type
     indent, emitPar: int
     x: string                # the current input line
     outp: PLLStream          # the ouput will be parsed by pnimsyn
-    subsChar, NimDirective: Char
+    subsChar, nimDirective: char
     emit, conc, toStr: string
     curly, bracket, par: int
     pendingExprLine: bool
@@ -37,11 +37,11 @@ const
   PatternChars = {'a'..'z', 'A'..'Z', '0'..'9', '\x80'..'\xFF', '.', '_'}
 
 proc newLine(p: var TTmplParser) = 
-  LLStreamWrite(p.outp, repeatChar(p.emitPar, ')'))
+  llStreamWrite(p.outp, repeatChar(p.emitPar, ')'))
   p.emitPar = 0
-  if p.info.line > int16(1): LLStreamWrite(p.outp, "\n")
+  if p.info.line > int16(1): llStreamWrite(p.outp, "\n")
   if p.pendingExprLine:
-    LLStreamWrite(p.outp, repeatChar(2))
+    llStreamWrite(p.outp, repeatChar(2))
     p.pendingExprLine = false
   
 proc scanPar(p: var TTmplParser, d: int) = 
@@ -55,7 +55,7 @@ proc scanPar(p: var TTmplParser, d: int) =
     of ']': dec(p.bracket)
     of '{': inc(p.curly)
     of '}': dec(p.curly)
-    else: nil
+    else: discard
     inc(i)
 
 proc withInExpr(p: TTmplParser): bool {.inline.} = 
@@ -67,9 +67,9 @@ proc parseLine(p: var TTmplParser) =
     keyw: string
   j = 0
   while p.x[j] == ' ': inc(j)
-  if (p.x[0] == p.NimDirective) and (p.x[0 + 1] == '!'): 
+  if (p.x[0] == p.nimDirective) and (p.x[0 + 1] == '!'): 
     newLine(p)
-  elif (p.x[j] == p.NimDirective): 
+  elif (p.x[j] == p.nimDirective): 
     newLine(p)
     inc(j)
     while p.x[j] == ' ': inc(j)
@@ -87,26 +87,26 @@ proc parseLine(p: var TTmplParser) =
         dec(p.indent, 2)
       else: 
         p.info.col = int16(j)
-        LocalError(p.info, errXNotAllowedHere, "end")
-      LLStreamWrite(p.outp, repeatChar(p.indent))
-      LLStreamWrite(p.outp, "#end")
+        localError(p.info, errXNotAllowedHere, "end")
+      llStreamWrite(p.outp, repeatChar(p.indent))
+      llStreamWrite(p.outp, "#end")
     of wIf, wWhen, wTry, wWhile, wFor, wBlock, wCase, wProc, wIterator, 
        wConverter, wMacro, wTemplate, wMethod: 
-      LLStreamWrite(p.outp, repeatChar(p.indent))
-      LLStreamWrite(p.outp, substr(p.x, d))
+      llStreamWrite(p.outp, repeatChar(p.indent))
+      llStreamWrite(p.outp, substr(p.x, d))
       inc(p.indent, 2)
     of wElif, wOf, wElse, wExcept, wFinally: 
-      LLStreamWrite(p.outp, repeatChar(p.indent - 2))
-      LLStreamWrite(p.outp, substr(p.x, d))
+      llStreamWrite(p.outp, repeatChar(p.indent - 2))
+      llStreamWrite(p.outp, substr(p.x, d))
     of wLet, wVar, wConst, wType:
-      LLStreamWrite(p.outp, repeatChar(p.indent))
-      LLStreamWrite(p.outp, substr(p.x, d))
+      llStreamWrite(p.outp, repeatChar(p.indent))
+      llStreamWrite(p.outp, substr(p.x, d))
       if not p.x.contains({':', '='}):
         # no inline element --> treat as block:
         inc(p.indent, 2)
     else:
-      LLStreamWrite(p.outp, repeatChar(p.indent))
-      LLStreamWrite(p.outp, substr(p.x, d))
+      llStreamWrite(p.outp, repeatChar(p.indent))
+      llStreamWrite(p.outp, substr(p.x, d))
     p.state = psDirective
   else: 
     # data line
@@ -118,15 +118,15 @@ proc parseLine(p: var TTmplParser) =
     case p.state
     of psTempl: 
       # next line of string literal:
-      LLStreamWrite(p.outp, p.conc)
-      LLStreamWrite(p.outp, "\n")
-      LLStreamWrite(p.outp, repeatChar(p.indent + 2))
-      LLStreamWrite(p.outp, "\"")
+      llStreamWrite(p.outp, p.conc)
+      llStreamWrite(p.outp, "\n")
+      llStreamWrite(p.outp, repeatChar(p.indent + 2))
+      llStreamWrite(p.outp, "\"")
     of psDirective: 
       newLine(p)
-      LLStreamWrite(p.outp, repeatChar(p.indent))
-      LLStreamWrite(p.outp, p.emit)
-      LLStreamWrite(p.outp, "(\"")
+      llStreamWrite(p.outp, repeatChar(p.indent))
+      llStreamWrite(p.outp, p.emit)
+      llStreamWrite(p.outp, "(\"")
       inc(p.emitPar)
     p.state = psTempl
     while true: 
@@ -134,17 +134,17 @@ proc parseLine(p: var TTmplParser) =
       of '\0': 
         break 
       of '\x01'..'\x1F', '\x80'..'\xFF': 
-        LLStreamWrite(p.outp, "\\x")
-        LLStreamWrite(p.outp, toHex(ord(p.x[j]), 2))
+        llStreamWrite(p.outp, "\\x")
+        llStreamWrite(p.outp, toHex(ord(p.x[j]), 2))
         inc(j)
       of '\\': 
-        LLStreamWrite(p.outp, "\\\\")
+        llStreamWrite(p.outp, "\\\\")
         inc(j)
       of '\'': 
-        LLStreamWrite(p.outp, "\\\'")
+        llStreamWrite(p.outp, "\\\'")
         inc(j)
       of '\"': 
-        LLStreamWrite(p.outp, "\\\"")
+        llStreamWrite(p.outp, "\\\"")
         inc(j)
       else: 
         if p.x[j] == p.subsChar: 
@@ -153,59 +153,59 @@ proc parseLine(p: var TTmplParser) =
           case p.x[j]
           of '{': 
             p.info.col = int16(j)
-            LLStreamWrite(p.outp, '\"')
-            LLStreamWrite(p.outp, p.conc)
-            LLStreamWrite(p.outp, p.toStr)
-            LLStreamWrite(p.outp, '(')
+            llStreamWrite(p.outp, '\"')
+            llStreamWrite(p.outp, p.conc)
+            llStreamWrite(p.outp, p.toStr)
+            llStreamWrite(p.outp, '(')
             inc(j)
             curly = 0
             while true: 
               case p.x[j]
               of '\0': 
-                LocalError(p.info, errXExpected, "}")
+                localError(p.info, errXExpected, "}")
                 break
               of '{': 
                 inc(j)
                 inc(curly)
-                LLStreamWrite(p.outp, '{')
+                llStreamWrite(p.outp, '{')
               of '}': 
                 inc(j)
                 if curly == 0: break 
                 if curly > 0: dec(curly)
-                LLStreamWrite(p.outp, '}')
+                llStreamWrite(p.outp, '}')
               else: 
-                LLStreamWrite(p.outp, p.x[j])
+                llStreamWrite(p.outp, p.x[j])
                 inc(j)
-            LLStreamWrite(p.outp, ')')
-            LLStreamWrite(p.outp, p.conc)
-            LLStreamWrite(p.outp, '\"')
+            llStreamWrite(p.outp, ')')
+            llStreamWrite(p.outp, p.conc)
+            llStreamWrite(p.outp, '\"')
           of 'a'..'z', 'A'..'Z', '\x80'..'\xFF': 
-            LLStreamWrite(p.outp, '\"')
-            LLStreamWrite(p.outp, p.conc)
-            LLStreamWrite(p.outp, p.toStr)
-            LLStreamWrite(p.outp, '(')
+            llStreamWrite(p.outp, '\"')
+            llStreamWrite(p.outp, p.conc)
+            llStreamWrite(p.outp, p.toStr)
+            llStreamWrite(p.outp, '(')
             while p.x[j] in PatternChars: 
-              LLStreamWrite(p.outp, p.x[j])
+              llStreamWrite(p.outp, p.x[j])
               inc(j)
-            LLStreamWrite(p.outp, ')')
-            LLStreamWrite(p.outp, p.conc)
-            LLStreamWrite(p.outp, '\"')
+            llStreamWrite(p.outp, ')')
+            llStreamWrite(p.outp, p.conc)
+            llStreamWrite(p.outp, '\"')
           else: 
             if p.x[j] == p.subsChar: 
-              LLStreamWrite(p.outp, p.subsChar)
+              llStreamWrite(p.outp, p.subsChar)
               inc(j)
             else: 
               p.info.col = int16(j)
-              LocalError(p.info, errInvalidExpression, "$")
+              localError(p.info, errInvalidExpression, "$")
         else: 
-          LLStreamWrite(p.outp, p.x[j])
+          llStreamWrite(p.outp, p.x[j])
           inc(j)
-    LLStreamWrite(p.outp, "\\n\"")
+    llStreamWrite(p.outp, "\\n\"")
 
 proc filterTmpl(stdin: PLLStream, filename: string, call: PNode): PLLStream = 
   var p: TTmplParser
   p.info = newLineInfo(filename, 0, 0)
-  p.outp = LLStreamOpen("")
+  p.outp = llStreamOpen("")
   p.inp = stdin
   p.subsChar = charArg(call, "subschar", 1, '$')
   p.nimDirective = charArg(call, "metachar", 2, '#')
@@ -213,9 +213,9 @@ proc filterTmpl(stdin: PLLStream, filename: string, call: PNode): PLLStream =
   p.conc = strArg(call, "conc", 4, " & ")
   p.toStr = strArg(call, "tostring", 5, "$")
   p.x = newStringOfCap(120)
-  while LLStreamReadLine(p.inp, p.x):
+  while llStreamReadLine(p.inp, p.x):
     p.info.line = p.info.line + int16(1)
     parseLine(p)
   newLine(p)
   result = p.outp
-  LLStreamClose(p.inp)
+  llStreamClose(p.inp)
diff --git a/compiler/filters.nim b/compiler/filters.nim
index 19da11bca..ce0ffd196 100644
--- a/compiler/filters.nim
+++ b/compiler/filters.nim
@@ -16,13 +16,13 @@ import
 proc filterReplace*(stdin: PLLStream, filename: string, call: PNode): PLLStream
 proc filterStrip*(stdin: PLLStream, filename: string, call: PNode): PLLStream
   # helpers to retrieve arguments:
-proc charArg*(n: PNode, name: string, pos: int, default: Char): Char
+proc charArg*(n: PNode, name: string, pos: int, default: char): char
 proc strArg*(n: PNode, name: string, pos: int, default: string): string
 proc boolArg*(n: PNode, name: string, pos: int, default: bool): bool
 # implementation
 
 proc invalidPragma(n: PNode) = 
-  LocalError(n.info, errXNotAllowedHere, renderTree(n, {renderNoComments}))
+  localError(n.info, errXNotAllowedHere, renderTree(n, {renderNoComments}))
 
 proc getArg(n: PNode, name: string, pos: int): PNode = 
   result = nil
@@ -30,12 +30,12 @@ proc getArg(n: PNode, name: string, pos: int): PNode =
   for i in countup(1, sonsLen(n) - 1): 
     if n.sons[i].kind == nkExprEqExpr: 
       if n.sons[i].sons[0].kind != nkIdent: invalidPragma(n)
-      if IdentEq(n.sons[i].sons[0].ident, name): 
+      if identEq(n.sons[i].sons[0].ident, name): 
         return n.sons[i].sons[1]
     elif i == pos: 
       return n.sons[i]
   
-proc charArg(n: PNode, name: string, pos: int, default: Char): Char = 
+proc charArg(n: PNode, name: string, pos: int, default: char): char = 
   var x = getArg(n, name, pos)
   if x == nil: result = default
   elif x.kind == nkCharLit: result = chr(int(x.intVal))
@@ -50,30 +50,30 @@ proc strArg(n: PNode, name: string, pos: int, default: string): string =
 proc boolArg(n: PNode, name: string, pos: int, default: bool): bool = 
   var x = getArg(n, name, pos)
   if x == nil: result = default
-  elif (x.kind == nkIdent) and IdentEq(x.ident, "true"): result = true
-  elif (x.kind == nkIdent) and IdentEq(x.ident, "false"): result = false
+  elif (x.kind == nkIdent) and identEq(x.ident, "true"): result = true
+  elif (x.kind == nkIdent) and identEq(x.ident, "false"): result = false
   else: invalidPragma(n)
   
 proc filterStrip(stdin: PLLStream, filename: string, call: PNode): PLLStream = 
   var pattern = strArg(call, "startswith", 1, "")
   var leading = boolArg(call, "leading", 2, true)
   var trailing = boolArg(call, "trailing", 3, true)
-  result = LLStreamOpen("")
+  result = llStreamOpen("")
   var line = newStringOfCap(80)
-  while LLStreamReadLine(stdin, line):
+  while llStreamReadLine(stdin, line):
     var stripped = strip(line, leading, trailing)
     if (len(pattern) == 0) or startsWith(stripped, pattern): 
-      LLStreamWriteln(result, stripped)
+      llStreamWriteln(result, stripped)
     else: 
-      LLStreamWriteln(result, line)
-  LLStreamClose(stdin)
+      llStreamWriteln(result, line)
+  llStreamClose(stdin)
 
 proc filterReplace(stdin: PLLStream, filename: string, call: PNode): PLLStream = 
   var sub = strArg(call, "sub", 1, "")
   if len(sub) == 0: invalidPragma(call)
   var by = strArg(call, "by", 2, "")
-  result = LLStreamOpen("")
+  result = llStreamOpen("")
   var line = newStringOfCap(80)
-  while LLStreamReadLine(stdin, line):
-    LLStreamWriteln(result, replace(line, sub, by))
-  LLStreamClose(stdin)
+  while llStreamReadLine(stdin, line):
+    llStreamWriteln(result, replace(line, sub, by))
+  llStreamClose(stdin)
diff --git a/compiler/guards.nim b/compiler/guards.nim
index 8d271fa6d..607bb074a 100644
--- a/compiler/guards.nim
+++ b/compiler/guards.nim
@@ -251,10 +251,10 @@ proc invalidateFacts*(m: var TModel, n: PNode) =
 
 proc valuesUnequal(a, b: PNode): bool =
   if a.isValue and b.isValue:
-    result = not SameValue(a, b)
+    result = not sameValue(a, b)
 
 proc pred(n: PNode): PNode =
-  if n.kind in {nkCharLit..nkUInt64Lit} and n.intVal != low(biggestInt):
+  if n.kind in {nkCharLit..nkUInt64Lit} and n.intVal != low(BiggestInt):
     result = copyNode(n)
     dec result.intVal
   else:
@@ -366,7 +366,7 @@ proc impliesIsNil(fact, eq: PNode): TImplication =
   else: discard
 
 proc impliesGe(fact, x, c: PNode): TImplication =
-  InternalAssert isLocation(x)
+  internalAssert isLocation(x)
   case fact.sons[0].sym.magic
   of someEq:
     if sameTree(fact.sons[1], x):
@@ -439,7 +439,7 @@ proc impliesLe(fact, x, c: PNode): TImplication =
         if leValue(c, fact.sons[1].pred): result = impNo
 
   of mNot, mOr, mAnd: internalError(x.info, "impliesLe")
-  else: nil
+  else: discard
 
 proc impliesLt(fact, x, c: PNode): TImplication =
   # x < 3  same as x <= 2:
@@ -484,7 +484,7 @@ proc factImplies(fact, prop: PNode): TImplication =
       if a == b: return ~a
       return impUnknown
     else:
-      InternalError(fact.info, "invalid fact")
+      internalError(fact.info, "invalid fact")
   of mAnd:
     result = factImplies(fact.sons[1], prop)
     if result != impUnknown: return result
@@ -575,4 +575,4 @@ proc checkFieldAccess*(m: TModel, n: PNode) =
   for i in 1..n.len-1:
     let check = buildProperFieldCheck(n.sons[0], n.sons[i])
     if m.doesImply(check) != impYes:
-      Message(n.info, warnProveField, renderTree(n.sons[0])); break
+      message(n.info, warnProveField, renderTree(n.sons[0])); break
diff --git a/compiler/hlo.nim b/compiler/hlo.nim
index 1492ed76f..7982d4aa1 100644
--- a/compiler/hlo.nim
+++ b/compiler/hlo.nim
@@ -12,7 +12,7 @@
 proc hlo(c: PContext, n: PNode): PNode
 
 proc evalPattern(c: PContext, n, orig: PNode): PNode =
-  InternalAssert n.kind == nkCall and n.sons[0].kind == nkSym
+  internalAssert n.kind == nkCall and n.sons[0].kind == nkSym
   # we need to ensure that the resulting AST is semchecked. However, it's
   # aweful to semcheck before macro invocation, so we don't and treat
   # templates and macros as immediate in this context.
@@ -28,7 +28,7 @@ proc evalPattern(c: PContext, n, orig: PNode): PNode =
   else:
     result = semDirectOp(c, n, {})
   if optHints in gOptions and hintPattern in gNotes:
-    Message(orig.info, hintPattern, rule & " --> '" & 
+    message(orig.info, hintPattern, rule & " --> '" & 
       renderTree(result, {renderNoComments}) & "'")
 
 proc applyPatterns(c: PContext, n: PNode): PNode =
@@ -45,7 +45,7 @@ proc applyPatterns(c: PContext, n: PNode): PNode =
         # better be safe than sorry, so check evalTemplateCounter too:
         inc(evalTemplateCounter)
         if evalTemplateCounter > 100:
-          GlobalError(n.info, errTemplateInstantiationTooNested)
+          globalError(n.info, errTemplateInstantiationTooNested)
         # deactivate this pattern:
         c.patterns[i] = nil
         if x.kind == nkStmtList:
@@ -81,7 +81,7 @@ proc hlo(c: PContext, n: PNode): PNode =
     else:
       # perform type checking, so that the replacement still fits:
       if isEmptyType(n.typ) and isEmptyType(result.typ):
-        nil
+        discard
       else:
         result = fitNode(c, n.typ, result)
       # optimization has been applied so check again:
diff --git a/compiler/idents.nim b/compiler/idents.nim
index 1e6f9d2fd..ec903826a 100644
--- a/compiler/idents.nim
+++ b/compiler/idents.nim
@@ -102,7 +102,7 @@ proc getIdent*(identifier: string): PIdent =
 proc getIdent*(identifier: string, h: THash): PIdent = 
   result = getIdent(cstring(identifier), len(identifier), h)
 
-proc IdentEq*(id: PIdent, name: string): bool = 
+proc identEq*(id: PIdent, name: string): bool = 
   result = id.id == getIdent(name).id
 
 var idAnon* = getIdent":anonymous"
diff --git a/compiler/idgen.nim b/compiler/idgen.nim
index fbf450c90..c4f5f2a9e 100644
--- a/compiler/idgen.nim
+++ b/compiler/idgen.nim
@@ -22,9 +22,9 @@ when debugIds:
   var usedIds = InitIntSet()
 
 proc registerID*(id: PIdObj) = 
-  when debugIDs: 
-    if id.id == -1 or ContainsOrIncl(usedIds, id.id): 
-      InternalError("ID already used: " & $id.id)
+  when debugIds: 
+    if id.id == -1 or containsOrIncl(usedIds, id.id): 
+      internalError("ID already used: " & $id.id)
 
 proc getID*(): int {.inline.} = 
   result = gFrontEndId
@@ -37,8 +37,8 @@ proc backendId*(): int {.inline.} =
 proc setId*(id: int) {.inline.} = 
   gFrontEndId = max(gFrontEndId, id + 1)
 
-proc IDsynchronizationPoint*(idRange: int) = 
-  gFrontEndId = (gFrontEndId div IdRange + 1) * IdRange + 1
+proc idSynchronizationPoint*(idRange: int) = 
+  gFrontEndId = (gFrontEndId div idRange + 1) * idRange + 1
 
 proc toGid(f: string): string =
   # we used to use ``f.addFileExt("gid")`` (aka ``$project.gid``), but this
@@ -49,7 +49,7 @@ proc toGid(f: string): string =
 proc saveMaxIds*(project: string) =
   var f = open(project.toGid, fmWrite)
   f.writeln($gFrontEndId)
-  f.writeln($gBackEndId)
+  f.writeln($gBackendId)
   f.close()
   
 proc loadMaxIds*(project: string) =
@@ -61,5 +61,5 @@ proc loadMaxIds*(project: string) =
       if f.readLine(line):
         var backEndId = parseInt(line)
         gFrontEndId = max(gFrontEndId, frontEndId)
-        gBackEndId = max(gBackEndId, backEndId)
+        gBackendId = max(gBackendId, backEndId)
     f.close()
diff --git a/compiler/importer.nim b/compiler/importer.nim
index 8b854bcc6..078a90c98 100644
--- a/compiler/importer.nim
+++ b/compiler/importer.nim
@@ -22,7 +22,7 @@ proc getModuleName*(n: PNode): string =
   # The proc won't perform any checks that the path is actually valid
   case n.kind
   of nkStrLit, nkRStrLit, nkTripleStrLit:
-    result = UnixToNativePath(n.strVal)
+    result = unixToNativePath(n.strVal)
   of nkIdent:
     result = n.ident.s
   of nkSym:
@@ -50,7 +50,7 @@ proc checkModuleName*(n: PNode): int32 =
   let modulename = n.getModuleName
   let fullPath = findModule(modulename, n.info.toFullPath)
   if fullPath.len == 0:
-    LocalError(n.info, errCannotOpenFile, modulename)
+    localError(n.info, errCannotOpenFile, modulename)
     result = InvalidFileIDX
   else:
     result = fullPath.fileInfoIdx
@@ -59,32 +59,32 @@ proc rawImportSymbol(c: PContext, s: PSym) =
   # This does not handle stubs, because otherwise loading on demand would be
   # pointless in practice. So importing stubs is fine here!
   # check if we have already a symbol of the same name:
-  var check = StrTableGet(c.importTable.symbols, s.name)
+  var check = strTableGet(c.importTable.symbols, s.name)
   if check != nil and check.id != s.id:
     if s.kind notin OverloadableSyms:
       # s and check need to be qualified:
-      Incl(c.AmbiguousSymbols, s.id)
-      Incl(c.AmbiguousSymbols, check.id)
+      incl(c.ambiguousSymbols, s.id)
+      incl(c.ambiguousSymbols, check.id)
   # thanks to 'export' feature, it could be we import the same symbol from
   # multiple sources, so we need to call 'StrTableAdd' here:
-  StrTableAdd(c.importTable.symbols, s)
+  strTableAdd(c.importTable.symbols, s)
   if s.kind == skType:
     var etyp = s.typ
     if etyp.kind in {tyBool, tyEnum} and sfPure notin s.flags:
       for j in countup(0, sonsLen(etyp.n) - 1):
         var e = etyp.n.sons[j].sym
-        if e.Kind != skEnumField: 
-          InternalError(s.info, "rawImportSymbol") 
+        if e.kind != skEnumField: 
+          internalError(s.info, "rawImportSymbol") 
           # BUGFIX: because of aliases for enums the symbol may already
           # have been put into the symbol table
           # BUGFIX: but only iff they are the same symbols!
         var it: TIdentIter 
-        check = InitIdentIter(it, c.importTable.symbols, e.name)
+        check = initIdentIter(it, c.importTable.symbols, e.name)
         while check != nil:
           if check.id == e.id:
             e = nil
             break
-          check = NextIdentIter(it, c.importTable.symbols)
+          check = nextIdentIter(it, c.importTable.symbols)
         if e != nil:
           rawImportSymbol(c, e)
   else:
@@ -94,36 +94,36 @@ proc rawImportSymbol(c: PContext, s: PSym) =
 
 proc importSymbol(c: PContext, n: PNode, fromMod: PSym) = 
   let ident = lookups.considerAcc(n)
-  let s = StrTableGet(fromMod.tab, ident)
+  let s = strTableGet(fromMod.tab, ident)
   if s == nil:
-    LocalError(n.info, errUndeclaredIdentifier, ident.s)
+    localError(n.info, errUndeclaredIdentifier, ident.s)
   else:
     if s.kind == skStub: loadStub(s)
-    if s.Kind notin ExportableSymKinds:
-      InternalError(n.info, "importSymbol: 2")
+    if s.kind notin ExportableSymKinds:
+      internalError(n.info, "importSymbol: 2")
     # for an enumeration we have to add all identifiers
-    case s.Kind
+    case s.kind
     of skProc, skMethod, skIterator, skMacro, skTemplate, skConverter:
       # for a overloadable syms add all overloaded routines
       var it: TIdentIter
-      var e = InitIdentIter(it, fromMod.tab, s.name)
+      var e = initIdentIter(it, fromMod.tab, s.name)
       while e != nil:
-        if e.name.id != s.Name.id: InternalError(n.info, "importSymbol: 3")
+        if e.name.id != s.name.id: internalError(n.info, "importSymbol: 3")
         rawImportSymbol(c, e)
-        e = NextIdentIter(it, fromMod.tab)
+        e = nextIdentIter(it, fromMod.tab)
     else: rawImportSymbol(c, s)
 
 proc importAllSymbolsExcept(c: PContext, fromMod: PSym, exceptSet: TIntSet) =
   var i: TTabIter
-  var s = InitTabIter(i, fromMod.tab)
+  var s = initTabIter(i, fromMod.tab)
   while s != nil:
     if s.kind != skModule:
       if s.kind != skEnumField:
-        if s.Kind notin ExportableSymKinds:
-          InternalError(s.info, "importAllSymbols: " & $s.kind)
+        if s.kind notin ExportableSymKinds:
+          internalError(s.info, "importAllSymbols: " & $s.kind)
         if exceptSet.empty or s.name.id notin exceptSet:
           rawImportSymbol(c, s)
-    s = NextIter(i, fromMod.tab)
+    s = nextIter(i, fromMod.tab)
 
 proc importAllSymbols*(c: PContext, fromMod: PSym) =
   var exceptSet: TIntSet
@@ -160,7 +160,7 @@ proc myImportModule(c: PContext, n: PNode): PSym =
   if f != InvalidFileIDX:
     result = importModuleAs(n, gImportModule(c.module, f))
     if sfDeprecated in result.flags:
-      Message(n.info, warnDeprecated, result.name.s)
+      message(n.info, warnDeprecated, result.name.s)
 
 proc evalImport(c: PContext, n: PNode): PNode = 
   result = n
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index a3c88824d..c0fc4131a 100644
--- a/compiler/jsgen.nim
+++ b/compiler/jsgen.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -64,7 +64,7 @@ type
     options: TOptions
     module: BModule
     g: PGlobals
-    BeforeRetNeeded: bool
+    beforeRetNeeded: bool
     target: TTarget # duplicated here for faster dispatching
     unique: int    # for temp identifier generation
     blocks: seq[TBlock]
@@ -111,7 +111,7 @@ proc mapType(typ: PType): TJSTypeKind =
   let t = skipTypes(typ, abstractInst)
   case t.kind
   of tyVar, tyRef, tyPtr: 
-    if skipTypes(t.sons[0], abstractInst).kind in mappedToObject: 
+    if skipTypes(t.sons[0], abstractInst).kind in MappedToObject: 
       result = etyObject
     else: 
       result = etyBaseIndex
@@ -129,8 +129,9 @@ proc mapType(typ: PType): TJSTypeKind =
      tyVarargs:
     result = etyObject
   of tyNil: result = etyNull
-  of tyGenericInst, tyGenericParam, tyGenericBody, tyGenericInvokation, tyNone, 
-     tyForward, tyEmpty, tyExpr, tyStmt, tyTypeDesc, tyTypeClasses: 
+  of tyGenericInst, tyGenericParam, tyGenericBody, tyGenericInvokation,
+     tyNone, tyFromExpr, tyForward, tyEmpty, tyFieldAccessor,
+     tyExpr, tyStmt, tyStatic, tyTypeDesc, tyTypeClasses:
     result = etyNone
   of tyProc: result = etyProc
   of tyCString: result = etyString
@@ -142,7 +143,7 @@ proc mangle(name: string): string =
     of 'A'..'Z': 
       add(result, chr(ord(name[i]) - ord('A') + ord('a')))
     of '_': 
-      nil
+      discard
     of 'a'..'z', '0'..'9': 
       add(result, name[i])
     else: add(result, 'X' & toHex(ord(name[i]), 2))
@@ -175,7 +176,7 @@ proc useMagic(p: PProc, name: string) =
     # we used to exclude the system module from this check, but for DLL
     # generation support this sloppyness leads to hard to detect bugs, so
     # we're picky here for the system module too:
-    if p.prc != nil: GlobalError(p.prc.info, errSystemNeeds, name)
+    if p.prc != nil: globalError(p.prc.info, errSystemNeeds, name)
     else: rawMessage(errSystemNeeds, name)
 
 proc isSimpleExpr(n: PNode): bool =
@@ -240,7 +241,7 @@ proc genOr(p: PProc, a, b: PNode, r: var TCompRes) =
 
 type
   TMagicFrmt = array[0..3, string]
-  TMagicOps = array[mAddi..mStrToStr, TMagicFrmt]
+  TMagicOps = array[mAddI..mStrToStr, TMagicFrmt]
 
 const # magic checked op; magic unchecked op; checked op; unchecked op
   jsOps: TMagicOps = [
@@ -485,14 +486,14 @@ proc arith(p: PProc, n: PNode, r: var TCompRes, op: TMagic) =
 
 proc genLineDir(p: PProc, n: PNode) =
   let line = toLinenumber(n.info)
-  if optLineDir in p.Options:
+  if optLineDir in p.options:
     appf(p.body, "// line $2 \"$1\"$n" | "-- line $2 \"$1\"$n",
          [toRope(toFilename(n.info)), toRope(line)])
-  if {optStackTrace, optEndb} * p.Options == {optStackTrace, optEndb} and
+  if {optStackTrace, optEndb} * p.options == {optStackTrace, optEndb} and
       ((p.prc == nil) or sfPure notin p.prc.flags):
     useMagic(p, "endb")
     appf(p.body, "endb($1);$n", [toRope(line)])
-  elif ({optLineTrace, optStackTrace} * p.Options ==
+  elif ({optLineTrace, optStackTrace} * p.options ==
       {optLineTrace, optStackTrace}) and
       ((p.prc == nil) or not (sfPure in p.prc.flags)): 
     appf(p.body, "F.line = $1;$n", [toRope(line)])
@@ -504,7 +505,7 @@ proc genWhileStmt(p: PProc, n: PNode) =
   genLineDir(p, n)
   inc(p.unique)
   var length = len(p.blocks)
-  setlen(p.blocks, length + 1)
+  setLen(p.blocks, length + 1)
   p.blocks[length].id = -p.unique
   p.blocks[length].isLoop = true
   let labl = p.unique.toRope
@@ -514,7 +515,7 @@ proc genWhileStmt(p: PProc, n: PNode) =
        [cond.res, labl])
   genStmt(p, n.sons[1])
   appf(p.body, "}$n" | "end ::L$#::$n", [labl])
-  setlen(p.blocks, length)
+  setLen(p.blocks, length)
 
 proc moveInto(p: PProc, src: var TCompRes, dest: TCompRes) =
   if src.kind != resNone:
@@ -555,7 +556,7 @@ proc genTry(p: PProc, n: PNode, r: var TCompRes) =
        "var $1 = {prev: excHandler, exc: null};$nexcHandler = $1;$n" | 
        "local $1 = pcall(", 
        [safePoint])
-  if optStackTrace in p.Options: app(p.body, "framePtr = F;" & tnl)
+  if optStackTrace in p.options: app(p.body, "framePtr = F;" & tnl)
   appf(p.body, "try {$n" | "function()$n")
   var length = sonsLen(n)
   var a: TCompRes
@@ -579,7 +580,7 @@ proc genTry(p: PProc, n: PNode, r: var TCompRes) =
       useMagic(p, "isObj")
       for j in countup(0, blen - 2): 
         if n.sons[i].sons[j].kind != nkType: 
-          InternalError(n.info, "genTryStmt")
+          internalError(n.info, "genTryStmt")
         if orExpr != nil: app(orExpr, "||" | " or ")
         appf(orExpr, "isObj($1.exc.m_type, $2)", 
              [safePoint, genTypeInfo(p, n.sons[i].sons[j].typ)])
@@ -641,13 +642,13 @@ proc genCaseJS(p: PProc, n: PNode, r: var TCompRes) =
           while v.intVal <= e.sons[1].intVal: 
             gen(p, v, cond)
             appf(p.body, "case $1: ", [cond.rdLoc])
-            Inc(v.intVal)
+            inc(v.intVal)
         else:
           if stringSwitch: 
             case e.kind
             of nkStrLit..nkTripleStrLit: appf(p.body, "case $1: ", 
                 [makeJSString(e.strVal)])
-            else: InternalError(e.info, "jsgen.genCaseStmt: 2")
+            else: internalError(e.info, "jsgen.genCaseStmt: 2")
           else: 
             gen(p, e, cond)
             appf(p.body, "case $1: ", [cond.rdLoc])
@@ -694,7 +695,7 @@ proc genCaseLua(p: PProc, n: PNode, r: var TCompRes) =
             case e.kind
             of nkStrLit..nkTripleStrLit: appf(p.body, "eqStr($1, $2)",
                 [tmp, makeJSString(e.strVal)])
-            else: InternalError(e.info, "jsgen.genCaseStmt: 2")
+            else: internalError(e.info, "jsgen.genCaseStmt: 2")
           else:
             gen(p, e, cond)
             appf(p.body, "$1 == $2", [tmp, cond.rdLoc])
@@ -713,17 +714,17 @@ proc genBlock(p: PProc, n: PNode, r: var TCompRes) =
   let idx = len(p.blocks)
   if n.sons[0].kind != nkEmpty: 
     # named block?
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "genBlock")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "genBlock")
     var sym = n.sons[0].sym
     sym.loc.k = locOther
     sym.loc.a = idx
-  setlen(p.blocks, idx + 1)
+  setLen(p.blocks, idx + 1)
   p.blocks[idx].id = - p.unique # negative because it isn't used yet
   let labl = p.unique
   appf(p.body, "L$1: do {$n" | "", labl.toRope)
   gen(p, n.sons[1], r)
   appf(p.body, "} while(false);$n" | "$n::L$#::$n", labl.toRope)
-  setlen(p.blocks, idx)
+  setLen(p.blocks, idx)
 
 proc genBreakStmt(p: PProc, n: PNode) = 
   var idx: int
@@ -739,7 +740,7 @@ proc genBreakStmt(p: PProc, n: PNode) =
     idx = len(p.blocks) - 1
     while idx >= 0 and not p.blocks[idx].isLoop: dec idx
     if idx < 0 or not p.blocks[idx].isLoop:
-      InternalError(n.info, "no loop to break")
+      internalError(n.info, "no loop to break")
   p.blocks[idx].id = abs(p.blocks[idx].id) # label is used
   appf(p.body, "break L$1;$n" | "goto ::L$1::;$n", [toRope(p.blocks[idx].id)])
 
@@ -747,10 +748,10 @@ proc genAsmStmt(p: PProc, n: PNode) =
   genLineDir(p, n)
   assert(n.kind == nkAsmStmt)
   for i in countup(0, sonsLen(n) - 1): 
-    case n.sons[i].Kind
+    case n.sons[i].kind
     of nkStrLit..nkTripleStrLit: app(p.body, n.sons[i].strVal)
     of nkSym: app(p.body, mangleName(n.sons[i].sym))
-    else: InternalError(n.sons[i].info, "jsgen: genAsmStmt()")
+    else: internalError(n.sons[i].info, "jsgen: genAsmStmt()")
   
 proc genIf(p: PProc, n: PNode, r: var TCompRes) = 
   var cond, stmt: TCompRes
@@ -851,7 +852,7 @@ proc getFieldPosition(f: PNode): int =
   case f.kind
   of nkIntLit..nkUInt64Lit: result = int(f.intVal)
   of nkSym: result = f.sym.position
-  else: InternalError(f.info, "genFieldPosition")
+  else: internalError(f.info, "genFieldPosition")
 
 proc genFieldAddr(p: PProc, n: PNode, r: var TCompRes) = 
   var a: TCompRes
@@ -861,11 +862,11 @@ proc genFieldAddr(p: PProc, n: PNode, r: var TCompRes) =
   if skipTypes(b.sons[0].typ, abstractVarRange).kind == tyTuple:
     r.res = makeJSString("Field" & $getFieldPosition(b.sons[1]))
   else:
-    if b.sons[1].kind != nkSym: InternalError(b.sons[1].info, "genFieldAddr")
+    if b.sons[1].kind != nkSym: internalError(b.sons[1].info, "genFieldAddr")
     var f = b.sons[1].sym
     if f.loc.r == nil: f.loc.r = mangleName(f)
     r.res = makeJSString(ropeToStr(f.loc.r))
-  InternalAssert a.typ != etyBaseIndex
+  internalAssert a.typ != etyBaseIndex
   r.address = a.res
   r.kind = resExpr
 
@@ -875,7 +876,7 @@ proc genFieldAccess(p: PProc, n: PNode, r: var TCompRes) =
   if skipTypes(n.sons[0].typ, abstractVarRange).kind == tyTuple:
     r.res = ropef("$1.Field$2", [r.res, getFieldPosition(n.sons[1]).toRope])
   else:
-    if n.sons[1].kind != nkSym: InternalError(n.sons[1].info, "genFieldAddr")
+    if n.sons[1].kind != nkSym: internalError(n.sons[1].info, "genFieldAddr")
     var f = n.sons[1].sym
     if f.loc.r == nil: f.loc.r = mangleName(f)
     r.res = ropef("$1.$2", [r.res, f.loc.r])
@@ -890,14 +891,14 @@ proc genCheckedFieldAccess(p: PProc, n: PNode, r: var TCompRes) =
 proc genArrayAddr(p: PProc, n: PNode, r: var TCompRes) = 
   var 
     a, b: TCompRes
-    first: biggestInt
+    first: BiggestInt
   r.typ = etyBaseIndex
   gen(p, n.sons[0], a)
   gen(p, n.sons[1], b)
-  InternalAssert a.typ != etyBaseIndex and b.typ != etyBaseIndex
+  internalAssert a.typ != etyBaseIndex and b.typ != etyBaseIndex
   r.address = a.res
   var typ = skipTypes(n.sons[0].typ, abstractPtrs)
-  if typ.kind in {tyArray, tyArrayConstr}: first = FirstOrd(typ.sons[0])
+  if typ.kind in {tyArray, tyArrayConstr}: first = firstOrd(typ.sons[0])
   else: first = 0
   if optBoundsCheck in p.options and not isConstExpr(n.sons[1]): 
     useMagic(p, "chckIndx")
@@ -918,9 +919,9 @@ proc genArrayAccess(p: PProc, n: PNode, r: var TCompRes) =
     genArrayAddr(p, n, r)
   of tyTuple: 
     genFieldAddr(p, n, r)
-  else: InternalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
+  else: internalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
   r.typ = etyNone
-  if r.res == nil: InternalError(n.info, "genArrayAccess")
+  if r.res == nil: internalError(n.info, "genArrayAccess")
   r.res = ropef("$1[$2]", [r.address, r.res])
   r.address = nil
   r.kind = resExpr
@@ -929,7 +930,7 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) =
   case n.sons[0].kind
   of nkSym:
     let s = n.sons[0].sym
-    if s.loc.r == nil: InternalError(n.info, "genAddr: 3")
+    if s.loc.r == nil: internalError(n.info, "genAddr: 3")
     case s.kind
     of skVar, skLet, skResult:
       r.kind = resExpr
@@ -948,8 +949,8 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) =
         r.address = s.loc.r
         r.res = toRope("0")
       else:
-        InternalError(n.info, "genAddr: 4")
-    else: InternalError(n.info, "genAddr: 2")
+        internalError(n.info, "genAddr: 4")
+    else: internalError(n.info, "genAddr: 2")
   of nkCheckedFieldExpr:
     genCheckedFieldAddr(p, n, r)
   of nkDotExpr:
@@ -963,15 +964,15 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) =
       genArrayAddr(p, n, r)
     of tyTuple: 
       genFieldAddr(p, n, r)
-    else: InternalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
-  else: InternalError(n.info, "genAddr")
+    else: internalError(n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
+  else: internalError(n.info, "genAddr")
   
 proc genSym(p: PProc, n: PNode, r: var TCompRes) = 
   var s = n.sym
   case s.kind
   of skVar, skLet, skParam, skTemp, skResult:
     if s.loc.r == nil:
-      InternalError(n.info, "symbol has no generated name: " & s.name.s)
+      internalError(n.info, "symbol has no generated name: " & s.name.s)
     var k = mapType(s.typ)
     if k == etyBaseIndex:
       r.typ = etyBaseIndex
@@ -988,17 +989,17 @@ proc genSym(p: PProc, n: PNode, r: var TCompRes) =
   of skConst:
     genConstant(p, s)
     if s.loc.r == nil:
-      InternalError(n.info, "symbol has no generated name: " & s.name.s)
+      internalError(n.info, "symbol has no generated name: " & s.name.s)
     r.res = s.loc.r
   of skProc, skConverter, skMethod:
     discard mangleName(s)
     r.res = s.loc.r
     if lfNoDecl in s.loc.flags or s.magic != mNone or
        {sfImportc, sfInfixCall} * s.flags != {}:
-      nil
+      discard
     elif s.kind == skMethod and s.getBody.kind == nkEmpty:
       # we cannot produce code for the dispatcher yet:
-      nil
+      discard
     elif sfForward in s.flags:
       p.g.forwarded.add(s)
     elif not p.g.generatedSyms.containsOrIncl(s.id):
@@ -1010,7 +1011,7 @@ proc genSym(p: PProc, n: PNode, r: var TCompRes) =
       else: app(p.g.code, newp)
   else:
     if s.loc.r == nil:
-      InternalError(n.info, "symbol has no generated name: " & s.name.s)
+      internalError(n.info, "symbol has no generated name: " & s.name.s)
     r.res = s.loc.r
   r.kind = resVal
   
@@ -1020,7 +1021,7 @@ proc genDeref(p: PProc, n: PNode, r: var TCompRes) =
   else:
     var a: TCompRes
     gen(p, n.sons[0], a)
-    if a.typ != etyBaseIndex: InternalError(n.info, "genDeref")
+    if a.typ != etyBaseIndex: internalError(n.info, "genDeref")
     r.res = ropef("$1[$2]", [a.address, a.res])
 
 proc genArg(p: PProc, n: PNode, r: var TCompRes) =
@@ -1051,7 +1052,7 @@ proc genInfixCall(p: PProc, n: PNode, r: var TCompRes) =
   gen(p, n.sons[1], r)
   if r.typ == etyBaseIndex:
     if r.address == nil:
-      GlobalError(n.info, "cannot invoke with infix syntax")
+      globalError(n.info, "cannot invoke with infix syntax")
     r.res = ropef("$1[$2]", [r.address, r.res])
     r.address = nil
     r.typ = etyNone
@@ -1093,7 +1094,7 @@ proc createRecordVarAux(p: PProc, rec: PNode, c: var int): PRope =
     app(result, ": ")
     app(result, createVar(p, rec.sym.typ, false))
     inc(c)
-  else: InternalError(rec.info, "createRecordVarAux")
+  else: internalError(rec.info, "createRecordVarAux")
   
 proc createVar(p: PProc, typ: PType, indirect: bool): PRope = 
   var t = skipTypes(typ, abstractInst)
@@ -1125,7 +1126,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): PRope =
       app(result, "]")
   of tyTuple: 
     result = toRope("{")
-    for i in 0.. <t.sonslen:
+    for i in 0.. <t.sonsLen:
       if i > 0: app(result, ", ")
       appf(result, "Field$1: $2" | "Field$# = $#", i.toRope, 
            createVar(p, t.sons[i], false))
@@ -1173,7 +1174,7 @@ proc genVarInit(p: PProc, v: PSym, n: PNode) =
         useMagic(p, "NimCopy")
         s = ropef("NimCopy($1, $2)", [a.res, genTypeInfo(p, n.typ)])
     of etyBaseIndex: 
-      if (a.typ != etyBaseIndex): InternalError(n.info, "genVarInit")
+      if (a.typ != etyBaseIndex): internalError(n.info, "genVarInit")
       if {sfAddrTaken, sfGlobal} * v.flags != {}: 
         appf(p.body, "var $1 = [$2, $3];$n" | "local $1 = {$2, $3};$n", 
             [v.loc.r, a.address, a.res])
@@ -1227,7 +1228,7 @@ proc genOrd(p: PProc, n: PNode, r: var TCompRes) =
   case skipTypes(n.sons[1].typ, abstractVar).kind
   of tyEnum, tyInt..tyInt64, tyChar: gen(p, n.sons[1], r)
   of tyBool: unaryExpr(p, n, r, "", "($1 ? 1:0)" | "toBool($#)")
-  else: InternalError(n.info, "genOrd")
+  else: internalError(n.info, "genOrd")
   
 proc genConStrStr(p: PProc, n: PNode, r: var TCompRes) =
   var a: TCompRes
@@ -1293,20 +1294,20 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) =
   case op
   of mOr: genOr(p, n.sons[1], n.sons[2], r)
   of mAnd: genAnd(p, n.sons[1], n.sons[2], r)
-  of mAddi..mStrToStr: arith(p, n, r, op)
+  of mAddI..mStrToStr: arith(p, n, r, op)
   of mRepr: genRepr(p, n, r)
   of mSwap: genSwap(p, n)
   of mUnaryLt:
     # XXX: range checking?
-    if not (optOverflowCheck in p.Options): unaryExpr(p, n, r, "", "$1 - 1")
+    if not (optOverflowCheck in p.options): unaryExpr(p, n, r, "", "$1 - 1")
     else: unaryExpr(p, n, r, "subInt", "subInt($1, 1)")
   of mPred:
     # XXX: range checking?
-    if not (optOverflowCheck in p.Options): binaryExpr(p, n, r, "", "$1 - $2")
+    if not (optOverflowCheck in p.options): binaryExpr(p, n, r, "", "$1 - $2")
     else: binaryExpr(p, n, r, "subInt", "subInt($1, $2)")
   of mSucc:
     # XXX: range checking?
-    if not (optOverflowCheck in p.Options): binaryExpr(p, n, r, "", "$1 - $2")
+    if not (optOverflowCheck in p.options): binaryExpr(p, n, r, "", "$1 - $2")
     else: binaryExpr(p, n, r, "addInt", "addInt($1, $2)")
   of mAppendStrCh: binaryExpr(p, n, r, "addChar", "addChar($1, $2)")
   of mAppendStrStr:
@@ -1335,10 +1336,10 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) =
     else:
       unaryExpr(p, n, r, "", "($1.length-1)")
   of mInc:
-    if not (optOverflowCheck in p.Options): binaryExpr(p, n, r, "", "$1 += $2")
+    if optOverflowCheck notin p.options: binaryExpr(p, n, r, "", "$1 += $2")
     else: binaryExpr(p, n, r, "addInt", "$1 = addInt($1, $2)")
   of ast.mDec:
-    if not (optOverflowCheck in p.Options): binaryExpr(p, n, r, "", "$1 -= $2")
+    if optOverflowCheck notin p.options: binaryExpr(p, n, r, "", "$1 -= $2")
     else: binaryExpr(p, n, r, "subInt", "$1 = subInt($1, $2)")
   of mSetLengthStr: binaryExpr(p, n, r, "", "$1.length = ($2)-1")
   of mSetLengthSeq: binaryExpr(p, n, r, "", "$1.length = $2")
@@ -1416,7 +1417,7 @@ proc genObjConstr(p: PProc, n: PNode, r: var TCompRes) =
   for i in countup(1, sonsLen(n) - 1):
     if i > 0: app(r.res, ", ")
     var it = n.sons[i]
-    InternalAssert it.kind == nkExprColonExpr
+    internalAssert it.kind == nkExprColonExpr
     gen(p, it.sons[1], a)
     var f = it.sons[0].sym
     if f.loc.r == nil: f.loc.r = mangleName(f)
@@ -1451,7 +1452,7 @@ proc convStrToCStr(p: PProc, n: PNode, r: var TCompRes) =
     gen(p, n.sons[0].sons[0], r)
   else:
     gen(p, n.sons[0], r)
-    if r.res == nil: InternalError(n.info, "convStrToCStr")
+    if r.res == nil: internalError(n.info, "convStrToCStr")
     useMagic(p, "toJSStr")
     r.res = ropef("toJSStr($1)", [r.res])
     r.kind = resExpr
@@ -1463,14 +1464,14 @@ proc convCStrToStr(p: PProc, n: PNode, r: var TCompRes) =
     gen(p, n.sons[0].sons[0], r)
   else: 
     gen(p, n.sons[0], r)
-    if r.res == nil: InternalError(n.info, "convCStrToStr")
+    if r.res == nil: internalError(n.info, "convCStrToStr")
     useMagic(p, "cstrToNimstr")
     r.res = ropef("cstrToNimstr($1)", [r.res])
     r.kind = resExpr
 
 proc genReturnStmt(p: PProc, n: PNode) = 
-  if p.procDef == nil: InternalError(n.info, "genReturnStmt")
-  p.BeforeRetNeeded = true
+  if p.procDef == nil: internalError(n.info, "genReturnStmt")
+  p.beforeRetNeeded = true
   if (n.sons[0].kind != nkEmpty): 
     genStmt(p, n.sons[0])
   else:
@@ -1543,7 +1544,7 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
     r.res = toRope(n.intVal)
   of nkNilLit:
     if isEmptyType(n.typ):
-      nil
+      discard
     elif mapType(n.typ) == etyBaseIndex:
       r.typ = etyBaseIndex
       r.address = toRope"null" | toRope"nil"
@@ -1564,7 +1565,7 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
     elif f == 0.5 * f: 
       if f > 0.0: r.res = toRope"Infinity"
       else: r.res = toRope"-Infinity"
-    else: r.res = toRope(f.ToStrMaxPrecision)
+    else: r.res = toRope(f.toStrMaxPrecision)
   of nkCallKinds:
     if (n.sons[0].kind == nkSym) and (n.sons[0].sym.magic != mNone): 
       genMagic(p, n, r)
@@ -1591,12 +1592,12 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
   of nkChckRange: genRangeChck(p, n, r, "chckRange")
   of nkStringToCString: convStrToCStr(p, n, r)
   of nkCStringToString: convCStrToStr(p, n, r)
-  of nkEmpty: nil
+  of nkEmpty: discard
   of nkLambdaKinds: 
     let s = n.sons[namePos].sym
     discard mangleName(s)
     r.res = s.loc.r
-    if lfNoDecl in s.loc.flags or s.magic != mNone: nil
+    if lfNoDecl in s.loc.flags or s.magic != mNone: discard
     elif not p.g.generatedSyms.containsOrIncl(s.id):
       app(p.locals, genProc(p, s))
   of nkMetaNode: gen(p, n.sons[0], r)
@@ -1613,7 +1614,7 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
   of nkIfStmt, nkIfExpr: genIf(p, n, r)
   of nkWhileStmt: genWhileStmt(p, n)
   of nkVarSection, nkLetSection: genVarStmt(p, n)
-  of nkConstSection: nil
+  of nkConstSection: discard
   of nkForStmt, nkParForStmt: 
     internalError(n.info, "for statement not eliminated")
   of nkCaseStmt: 
@@ -1632,7 +1633,7 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
   of nkRaiseStmt: genRaiseStmt(p, n)
   of nkTypeSection, nkCommentStmt, nkIteratorDef, nkIncludeStmt, 
      nkImportStmt, nkImportExceptStmt, nkExportStmt, nkExportExceptStmt, 
-     nkFromStmt, nkTemplateDef, nkMacroDef, nkPragma: nil
+     nkFromStmt, nkTemplateDef, nkMacroDef, nkPragma: discard
   of nkProcDef, nkMethodDef, nkConverterDef:
     var s = n.sons[namePos].sym
     if {sfExportc, sfCompilerProc} * s.flags == {sfExportc}:
@@ -1640,7 +1641,7 @@ proc gen(p: PProc, n: PNode, r: var TCompRes) =
       r.res = nil
   of nkGotoState, nkState:
     internalError(n.info, "first class iterators not implemented")
-  else: InternalError(n.info, "gen: unknown node type: " & $n.kind)
+  else: internalError(n.info, "gen: unknown node type: " & $n.kind)
   
 var globals: PGlobals
 
@@ -1651,11 +1652,11 @@ proc newModule(module: PSym): BModule =
   
 proc genHeader(): PRope =
   result = ropef("/* Generated by the Nimrod Compiler v$1 */$n" &
-                 "/*   (c) 2013 Andreas Rumpf */$n$n" & 
+                 "/*   (c) 2014 Andreas Rumpf */$n$n" & 
                  "$nvar Globals = this;$n" &
                  "var framePtr = null;$n" & 
                  "var excHandler = null;$n", 
-                 [toRope(versionAsString)])
+                 [toRope(VersionAsString)])
 
 proc genModule(p: PProc, n: PNode) = 
   if optStackTrace in p.options:
@@ -1671,7 +1672,7 @@ proc myProcess(b: PPassContext, n: PNode): PNode =
   if passes.skipCodegen(n): return n
   result = n
   var m = BModule(b)
-  if m.module == nil: InternalError(n.info, "myProcess")
+  if m.module == nil: internalError(n.info, "myProcess")
   var p = newProc(globals, m, nil, m.module.options)
   genModule(p, n)
   app(p.g.code, p.locals)
@@ -1702,7 +1703,7 @@ proc myClose(b: PPassContext, n: PNode): PNode =
     discard writeRopeIfNotEqual(con(genHeader(), code), outfile)
 
 proc myOpenCached(s: PSym, rd: PRodReader): PPassContext = 
-  InternalError("symbol files are not possible with the JS code generator")
+  internalError("symbol files are not possible with the JS code generator")
   result = nil
 
 proc myOpen(s: PSym): PPassContext = 
diff --git a/compiler/jstypes.nim b/compiler/jstypes.nim
index 0be1e99dc..6d14076e1 100644
--- a/compiler/jstypes.nim
+++ b/compiler/jstypes.nim
@@ -37,7 +37,7 @@ proc genObjectFields(p: PProc, typ: PType, n: PNode): PRope =
                    [mangleName(field), s, makeJSString(field.name.s)])
   of nkRecCase: 
     length = sonsLen(n)
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "genObjectFields")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "genObjectFields")
     field = n.sons[0].sym
     s = genTypeInfo(p, field.typ)
     for i in countup(1, length - 1): 
@@ -98,7 +98,7 @@ proc genEnumInfo(p: PProc, typ: PType, name: PRope) =
   let length = sonsLen(typ.n)
   var s: PRope = nil
   for i in countup(0, length - 1): 
-    if (typ.n.sons[i].kind != nkSym): InternalError(typ.n.info, "genEnumInfo")
+    if (typ.n.sons[i].kind != nkSym): internalError(typ.n.info, "genEnumInfo")
     let field = typ.n.sons[i].sym
     if i > 0: app(s, ", " & tnl)
     let extName = if field.ast == nil: field.name.s else: field.ast.strVal
@@ -119,7 +119,7 @@ proc genTypeInfo(p: PProc, typ: PType): PRope =
   var t = typ
   if t.kind == tyGenericInst: t = lastSon(t)
   result = ropef("NTI$1", [toRope(t.id)])
-  if ContainsOrIncl(p.g.TypeInfoGenerated, t.id): return 
+  if containsOrIncl(p.g.typeInfoGenerated, t.id): return 
   case t.kind
   of tyDistinct: 
     result = genTypeInfo(p, typ.sons[0])
@@ -145,4 +145,4 @@ proc genTypeInfo(p: PProc, typ: PType): PRope =
   of tyEnum: genEnumInfo(p, t, result)
   of tyObject: genObjectInfo(p, t, result)
   of tyTuple: genTupleInfo(p, t, result)
-  else: InternalError("genTypeInfo(" & $t.kind & ')')
+  else: internalError("genTypeInfo(" & $t.kind & ')')
diff --git a/compiler/lambdalifting.nim b/compiler/lambdalifting.nim
index 96eb3a5f4..00fa04556 100644
--- a/compiler/lambdalifting.nim
+++ b/compiler/lambdalifting.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -116,9 +116,9 @@ type
   TDep = tuple[e: PEnv, field: PSym]
   TEnv {.final.} = object of TObject
     attachedNode: PNode
-    closure: PSym   # if != nil it is a used environment
+    createdVar: PSym         # if != nil it is a used environment
     capturedVars: seq[PSym] # captured variables in this environment
-    deps: seq[TDep] # dependencies
+    deps: seq[TDep]         # dependencies
     up: PEnv
     tup: PType
   
@@ -130,12 +130,99 @@ type
   TOuterContext {.final.} = object
     fn: PSym # may also be a module!
     currentEnv: PEnv
+    isIter: bool   # first class iterator?
     capturedVars, processed: TIntSet
     localsToEnv: TIdTable # PSym->PEnv mapping
     localsToAccess: TIdNodeTable
     lambdasToEnv: TIdTable # PSym->PEnv mapping
     up: POuterContext
 
+    closureParam, state, resultSym: PSym # only if isIter
+    tup: PType # only if isIter
+
+
+proc getStateType(iter: PSym): PType =
+  var n = newNodeI(nkRange, iter.info)
+  addSon(n, newIntNode(nkIntLit, -1))
+  addSon(n, newIntNode(nkIntLit, 0))
+  result = newType(tyRange, iter)
+  result.n = n
+  rawAddSon(result, getSysType(tyInt))
+
+proc createStateField(iter: PSym): PSym =
+  result = newSym(skField, getIdent(":state"), iter, iter.info)
+  result.typ = getStateType(iter)
+
+proc newIterResult(iter: PSym): PSym =
+  if resultPos < iter.ast.len:
+    result = iter.ast.sons[resultPos].sym
+  else:
+    # XXX a bit hacky:
+    result = newSym(skResult, getIdent":result", iter, iter.info)
+    result.typ = iter.typ.sons[0]
+    incl(result.flags, sfUsed)
+    iter.ast.add newSymNode(result)
+
+proc addHiddenParam(routine: PSym, param: PSym) =
+  var params = routine.ast.sons[paramsPos]
+  # -1 is correct here as param.position is 0 based but we have at position 0
+  # some nkEffect node:
+  param.position = params.len-1
+  addSon(params, newSymNode(param))
+  incl(routine.typ.flags, tfCapturesEnv)
+  #echo "produced environment: ", param.id, " for ", routine.name.s
+
+proc getHiddenParam(routine: PSym): PSym =
+  let params = routine.ast.sons[paramsPos]
+  let hidden = lastSon(params)
+  assert hidden.kind == nkSym
+  result = hidden.sym
+
+proc getEnvParam(routine: PSym): PSym =
+  let params = routine.ast.sons[paramsPos]
+  let hidden = lastSon(params)
+  if hidden.kind == nkSym and hidden.sym.name.s == paramName:
+    result = hidden.sym
+    
+proc addField(tup: PType, s: PSym) =
+  var field = newSym(skField, s.name, s.owner, s.info)
+  let t = skipIntLit(s.typ)
+  field.typ = t
+  field.position = sonsLen(tup)
+  addSon(tup.n, newSymNode(field))
+  rawAddSon(tup, t)
+
+proc initIterContext(c: POuterContext, iter: PSym) =
+  c.fn = iter
+  c.capturedVars = initIntSet()
+
+  var cp = getEnvParam(iter)
+  if cp == nil:
+    c.tup = newType(tyTuple, iter)
+    c.tup.n = newNodeI(nkRecList, iter.info)
+
+    cp = newSym(skParam, getIdent(paramName), iter, iter.info)
+    incl(cp.flags, sfFromGeneric)
+    cp.typ = newType(tyRef, iter)
+    rawAddSon(cp.typ, c.tup)
+    addHiddenParam(iter, cp)
+
+    c.state = createStateField(iter)
+    addField(c.tup, c.state)
+  else:
+    c.tup = cp.typ.sons[0]
+    assert c.tup.kind == tyTuple
+    if c.tup.len > 0:
+      c.state = c.tup.n[0].sym
+    else:
+      c.state = createStateField(iter)
+      addField(c.tup, c.state)
+
+  c.closureParam = cp
+  if iter.typ.sons[0] != nil:
+    c.resultSym = newIterResult(iter)
+    #iter.ast.add(newSymNode(c.resultSym))
+
 proc newOuterContext(fn: PSym, up: POuterContext = nil): POuterContext =
   new(result)
   result.fn = fn
@@ -144,12 +231,14 @@ proc newOuterContext(fn: PSym, up: POuterContext = nil): POuterContext =
   initIdNodeTable(result.localsToAccess)
   initIdTable(result.localsToEnv)
   initIdTable(result.lambdasToEnv)
+  result.isIter = fn.kind == skIterator and fn.typ.callConv == ccClosure
+  if result.isIter: initIterContext(result, fn)
   
 proc newInnerContext(fn: PSym): PInnerContext =
   new(result)
   result.fn = fn
   initIdNodeTable(result.localsToAccess)
-  
+
 proc newEnv(outerProc: PSym, up: PEnv, n: PNode): PEnv =
   new(result)
   result.deps = @[]
@@ -159,17 +248,12 @@ proc newEnv(outerProc: PSym, up: PEnv, n: PNode): PEnv =
   result.up = up
   result.attachedNode = n
 
-proc addField(tup: PType, s: PSym) =
-  var field = newSym(skField, s.name, s.owner, s.info)
-  let t = skipIntLit(s.typ)
-  field.typ = t
-  field.position = sonsLen(tup)
-  addSon(tup.n, newSymNode(field))
-  rawAddSon(tup, t)
-  
 proc addCapturedVar(e: PEnv, v: PSym) =
   for x in e.capturedVars:
     if x == v: return
+  # XXX meh, just add the state field for every closure for now, it's too
+  # hard to figure out if it comes from a closure iterator:
+  if e.tup.len == 0: addField(e.tup, createStateField(v.owner))
   e.capturedVars.add(v)
   addField(e.tup, v)
   
@@ -189,6 +273,7 @@ proc indirectAccess(a: PNode, b: PSym, info: TLineInfo): PNode =
   # returns a[].b as a node
   var deref = newNodeI(nkHiddenDeref, info)
   deref.typ = a.typ.sons[0]
+  assert deref.typ.kind == tyTuple
   let field = getSymFromList(deref.typ.n, b.name)
   assert field != nil, b.name.s
   addSon(deref, a)
@@ -205,37 +290,30 @@ proc newCall(a, b: PSym): PNode =
   result.add newSymNode(a)
   result.add newSymNode(b)
 
-proc addHiddenParam(routine: PSym, param: PSym) =
-  var params = routine.ast.sons[paramsPos]
-  param.position = params.len
-  addSon(params, newSymNode(param))
-  incl(routine.typ.flags, tfCapturesEnv)
-  #echo "produced environment: ", param.id, " for ", routine.name.s
-
-proc getHiddenParam(routine: PSym): PSym =
-  let params = routine.ast.sons[paramsPos]
-  let hidden = lastSon(params)
-  assert hidden.kind == nkSym
-  result = hidden.sym
-
 proc isInnerProc(s, outerProc: PSym): bool {.inline.} =
-  result = s.kind in {skProc, skMethod, skConverter} and 
+  result = (s.kind in {skProc, skMethod, skConverter} or
+            s.kind == skIterator and s.typ.callConv == ccClosure) and
            s.skipGenericOwner == outerProc
   #s.typ.callConv == ccClosure
 
 proc addClosureParam(i: PInnerContext, e: PEnv) =
-  var cp = newSym(skParam, getIdent(paramname), i.fn, i.fn.info)
-  incl(cp.flags, sfFromGeneric)
-  cp.typ = newType(tyRef, i.fn)
-  rawAddSon(cp.typ, e.tup)
+  var cp = getEnvParam(i.fn)
+  if cp == nil:
+    cp = newSym(skParam, getIdent(paramName), i.fn, i.fn.info)
+    incl(cp.flags, sfFromGeneric)
+    cp.typ = newType(tyRef, i.fn)
+    rawAddSon(cp.typ, e.tup)
+    addHiddenParam(i.fn, cp)
+  else:
+    e.tup = cp.typ.sons[0]
+    assert e.tup.kind == tyTuple
   i.closureParam = cp
-  addHiddenParam(i.fn, i.closureParam)
   #echo "closure param added for ", i.fn.name.s, " ", i.fn.id
 
 proc dummyClosureParam(o: POuterContext, i: PInnerContext) =
   var e = o.currentEnv
-  if IdTableGet(o.lambdasToEnv, i.fn) == nil:
-    IdTablePut(o.lambdasToEnv, i.fn, e)
+  if idTableGet(o.lambdasToEnv, i.fn) == nil:
+    idTablePut(o.lambdasToEnv, i.fn, e)
   if i.closureParam == nil: addClosureParam(i, e)
 
 proc illegalCapture(s: PSym): bool {.inline.} =
@@ -247,13 +325,13 @@ proc captureVar(o: POuterContext, i: PInnerContext, local: PSym,
                 info: TLineInfo) =
   # for inlined variables the owner is still wrong, so it can happen that it's
   # not a captured variable at all ... *sigh* 
-  var it = PEnv(IdTableGet(o.localsToEnv, local))
+  var it = PEnv(idTableGet(o.localsToEnv, local))
   if it == nil: return
   
   if illegalCapture(local) or o.fn.id != local.owner.id or 
       i.fn.typ.callConv notin {ccClosure, ccDefault}:
     # Currently captures are restricted to a single level of nesting:
-    LocalError(info, errIllegalCaptureX, local.name.s)
+    localError(info, errIllegalCaptureX, local.name.s)
   i.fn.typ.callConv = ccClosure
   #echo "captureVar ", i.fn.name.s, i.fn.id, " ", local.name.s, local.id
 
@@ -261,11 +339,11 @@ proc captureVar(o: POuterContext, i: PInnerContext, local: PSym,
 
   # we need to remember which inner most closure belongs to this lambda:
   var e = o.currentEnv
-  if IdTableGet(o.lambdasToEnv, i.fn) == nil:
-    IdTablePut(o.lambdasToEnv, i.fn, e)
+  if idTableGet(o.lambdasToEnv, i.fn) == nil:
+    idTablePut(o.lambdasToEnv, i.fn, e)
 
   # variable already captured:
-  if IdNodeTableGet(i.localsToAccess, local) != nil: return
+  if idNodeTableGet(i.localsToAccess, local) != nil: return
   if i.closureParam == nil: addClosureParam(i, e)
   
   # check which environment `local` belongs to:
@@ -273,13 +351,13 @@ proc captureVar(o: POuterContext, i: PInnerContext, local: PSym,
   addCapturedVar(it, local)
   if it == e:
     # common case: local directly in current environment:
-    nil
+    discard
   else:
     # it's in some upper environment:
     access = indirectAccess(access, addDep(e, it, i.fn), info)
   access = indirectAccess(access, local, info)
   incl(o.capturedVars, local.id)
-  IdNodeTablePut(i.localsToAccess, local, access)
+  idNodeTablePut(i.localsToAccess, local, access)
 
 proc interestingVar(s: PSym): bool {.inline.} =
   result = s.kind in {skVar, skLet, skTemp, skForVar, skParam, skResult} and
@@ -304,15 +382,17 @@ proc gatherVars(o: POuterContext, i: PInnerContext, n: PNode) =
     var s = n.sym
     if interestingVar(s) and i.fn.id != s.owner.id:
       captureVar(o, i, s, n.info)
-    elif isInnerProc(s, o.fn) and tfCapturesEnv in s.typ.flags and s != i.fn:
+    elif s.kind in {skProc, skMethod, skConverter} and
+            s.skipGenericOwner == o.fn and 
+            tfCapturesEnv in s.typ.flags and s != i.fn:
       # call to some other inner proc; we need to track the dependencies for
       # this:
-      let env = PEnv(IdTableGet(o.lambdasToEnv, i.fn))
-      if env == nil: InternalError(n.info, "no environment computed")
+      let env = PEnv(idTableGet(o.lambdasToEnv, i.fn))
+      if env == nil: internalError(n.info, "no environment computed")
       if o.currentEnv != env:
         discard addDep(o.currentEnv, env, i.fn)
-        InternalError(n.info, "too complex environment handling required")
-  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: nil
+        internalError(n.info, "too complex environment handling required")
+  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit, nkClosure: discard
   else:
     for k in countup(0, sonsLen(n) - 1): 
       gatherVars(o, i, n.sons[k])
@@ -349,7 +429,7 @@ proc makeClosure(prc, env: PSym, info: TLineInfo): PNode =
 
 proc transformInnerProc(o: POuterContext, i: PInnerContext, n: PNode): PNode =
   case n.kind
-  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: nil
+  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: discard
   of nkSym:
     let s = n.sym
     if s == i.fn: 
@@ -363,13 +443,14 @@ proc transformInnerProc(o: POuterContext, i: PInnerContext, n: PNode): PNode =
       result = makeClosure(s, i.closureParam, n.info)
     else:
       # captured symbol?
-      result = IdNodeTableGet(i.localsToAccess, n.sym)
-  of nkLambdaKinds:
-    result = transformInnerProc(o, i, n.sons[namePos])
+      result = idNodeTableGet(i.localsToAccess, n.sym)
+  of nkLambdaKinds, nkIteratorDef:
+    if n.typ != nil:
+      result = transformInnerProc(o, i, n.sons[namePos])
   of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef, nkTemplateDef,
-     nkIteratorDef:
+      nkClosure:
     # don't recurse here:
-    nil
+    discard
   else:
     for j in countup(0, sonsLen(n) - 1):
       let x = transformInnerProc(o, i, n.sons[j])
@@ -384,7 +465,7 @@ proc searchForInnerProcs(o: POuterContext, n: PNode) =
   if n == nil: return
   case n.kind
   of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: 
-    nil
+    discard
   of nkSym:
     if isInnerProc(n.sym, o.fn) and not containsOrIncl(o.processed, n.sym.id):
       var inner = newInnerContext(n.sym)
@@ -398,8 +479,9 @@ proc searchForInnerProcs(o: POuterContext, n: PNode) =
       if inner.closureParam != nil:
         let ti = transformInnerProc(o, inner, body)
         if ti != nil: n.sym.ast.sons[bodyPos] = ti
-  of nkLambdaKinds:
-    searchForInnerProcs(o, n.sons[namePos])
+  of nkLambdaKinds, nkIteratorDef:
+    if n.typ != nil:
+      searchForInnerProcs(o, n.sons[namePos])
   of nkWhileStmt, nkForStmt, nkParForStmt, nkBlockStmt:
     # some nodes open a new scope, so they are candidates for the insertion
     # of closure creation; however for simplicity we merge closures between
@@ -420,26 +502,26 @@ proc searchForInnerProcs(o: POuterContext, n: PNode) =
     # counts, not the block where it is captured!
     for i in countup(0, sonsLen(n) - 1):
       var it = n.sons[i]
-      if it.kind == nkCommentStmt: nil
+      if it.kind == nkCommentStmt: discard
       elif it.kind == nkIdentDefs:
         var L = sonsLen(it)
-        if it.sons[0].kind != nkSym: InternalError(it.info, "transformOuter")
+        if it.sons[0].kind != nkSym: internalError(it.info, "transformOuter")
         #echo "set: ", it.sons[0].sym.name.s, " ", o.currentBlock == nil
-        IdTablePut(o.localsToEnv, it.sons[0].sym, o.currentEnv)
+        idTablePut(o.localsToEnv, it.sons[0].sym, o.currentEnv)
         searchForInnerProcs(o, it.sons[L-1])
       elif it.kind == nkVarTuple:
         var L = sonsLen(it)
         for j in countup(0, L-3):
           #echo "set: ", it.sons[j].sym.name.s, " ", o.currentBlock == nil
-          IdTablePut(o.localsToEnv, it.sons[j].sym, o.currentEnv)
+          idTablePut(o.localsToEnv, it.sons[j].sym, o.currentEnv)
         searchForInnerProcs(o, it.sons[L-1])
       else:
-        InternalError(it.info, "transformOuter")
+        internalError(it.info, "transformOuter")
   of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef, nkTemplateDef, 
-     nkIteratorDef:
+     nkClosure:
     # don't recurse here:
     # XXX recurse here and setup 'up' pointers
-    nil
+    discard
   else:
     for i in countup(0, sonsLen(n) - 1):
       searchForInnerProcs(o, n.sons[i])
@@ -461,19 +543,20 @@ proc addVar*(father, v: PNode) =
   addSon(vpart, ast.emptyNode)
   addSon(father, vpart)
 
-proc getClosureVar(o: POuterContext, e: PEnv): PSym =
-  if e.closure == nil:
-    result = newSym(skVar, getIdent(envName), o.fn, e.attachedNode.info)
-    incl(result.flags, sfShadowed)
-    result.typ = newType(tyRef, o.fn)
-    result.typ.rawAddSon(e.tup)
-    e.closure = result
-  else:
-    result = e.closure
+proc newClosureCreationVar(o: POuterContext; e: PEnv): PSym =
+  result = newSym(skVar, getIdent(envName), o.fn, e.attachedNode.info)
+  incl(result.flags, sfShadowed)
+  result.typ = newType(tyRef, o.fn)
+  result.typ.rawAddSon(e.tup)
 
-proc generateClosureCreation(o: POuterContext, scope: PEnv): PNode =
-  var env = getClosureVar(o, scope)
+proc getClosureVar(o: POuterContext; e: PEnv): PSym =
+  if e.createdVar == nil:
+    result = newClosureCreationVar(o, e)
+    e.createdVar = result
+  else:
+    result = e.createdVar
 
+proc rawClosureCreation(o: POuterContext, scope: PEnv; env: PSym): PNode =
   result = newNodeI(nkStmtList, env.info)
   var v = newNodeI(nkVarSection, env.info)
   addVar(v, newSymNode(env))
@@ -488,23 +571,97 @@ proc generateClosureCreation(o: POuterContext, scope: PEnv): PNode =
       # maybe later: (sfByCopy in local.flags)
       # add ``env.param = param``
       result.add(newAsgnStmt(fieldAccess, newSymNode(local), env.info))
-    IdNodeTablePut(o.localsToAccess, local, fieldAccess)
+    idNodeTablePut(o.localsToAccess, local, fieldAccess)
   # add support for 'up' references:
   for e, field in items(scope.deps):
     # add ``env.up = env2``
     result.add(newAsgnStmt(indirectAccess(env, field, env.info),
                newSymNode(getClosureVar(o, e)), env.info))
+  
+proc generateClosureCreation(o: POuterContext, scope: PEnv): PNode =
+  var env = getClosureVar(o, scope)
+  result = rawClosureCreation(o, scope, env)
+
+proc generateIterClosureCreation(o: POuterContext; env: PEnv;
+                                 scope: PNode): PSym =
+  result = newClosureCreationVar(o, env)
+  let cc = rawClosureCreation(o, env, result)
+  var insertPoint = scope.sons[0]
+  if insertPoint.kind == nkEmpty: scope.sons[0] = cc
+  else:
+    assert cc.kind == nkStmtList and insertPoint.kind == nkStmtList
+    for x in cc: insertPoint.add(x)
+  if env.createdVar == nil: env.createdVar = result
+
+proc interestingIterVar(s: PSym): bool {.inline.} =
+  result = s.kind in {skVar, skLet, skTemp, skForVar} and sfGlobal notin s.flags
+
+proc transformOuterProc(o: POuterContext, n: PNode): PNode
+
+proc transformYield(c: POuterContext, n: PNode): PNode =
+  inc c.state.typ.n.sons[1].intVal
+  let stateNo = c.state.typ.n.sons[1].intVal
+
+  var stateAsgnStmt = newNodeI(nkAsgn, n.info)
+  stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),c.state,n.info))
+  stateAsgnStmt.add(newIntTypeNode(nkIntLit, stateNo, getSysType(tyInt)))
+
+  var retStmt = newNodeI(nkReturnStmt, n.info)
+  if n.sons[0].kind != nkEmpty:
+    var a = newNodeI(nkAsgn, n.sons[0].info)
+    var retVal = transformOuterProc(c, n.sons[0])
+    addSon(a, newSymNode(c.resultSym))
+    addSon(a, if retVal.isNil: n.sons[0] else: retVal)
+    retStmt.add(a)
+  else:
+    retStmt.add(emptyNode)
+  
+  var stateLabelStmt = newNodeI(nkState, n.info)
+  stateLabelStmt.add(newIntTypeNode(nkIntLit, stateNo, getSysType(tyInt)))
+  
+  result = newNodeI(nkStmtList, n.info)
+  result.add(stateAsgnStmt)
+  result.add(retStmt)
+  result.add(stateLabelStmt)
+
+proc transformReturn(c: POuterContext, n: PNode): PNode =
+  result = newNodeI(nkStmtList, n.info)
+  var stateAsgnStmt = newNodeI(nkAsgn, n.info)
+  stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),c.state,n.info))
+  stateAsgnStmt.add(newIntTypeNode(nkIntLit, -1, getSysType(tyInt)))
+  result.add(stateAsgnStmt)
+  result.add(n)
+
+proc outerProcSons(o: POuterContext, n: PNode) =
+  for i in countup(0, sonsLen(n) - 1):
+    let x = transformOuterProc(o, n.sons[i])
+    if x != nil: n.sons[i] = x
 
 proc transformOuterProc(o: POuterContext, n: PNode): PNode =
   if n == nil: return nil
   case n.kind
-  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: nil
+  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: discard
   of nkSym:
     var local = n.sym
-    var closure = PEnv(IdTableGet(o.lambdasToEnv, local))
+
+    if o.isIter and interestingIterVar(local) and o.fn.id == local.owner.id:
+      if not containsOrIncl(o.capturedVars, local.id): addField(o.tup, local)
+      return indirectAccess(newSymNode(o.closureParam), local, n.info)
+
+    var closure = PEnv(idTableGet(o.lambdasToEnv, local))
     if closure != nil:
-      # we need to replace the lambda with '(lambda, env)': 
-      let a = closure.closure
+      # we need to replace the lambda with '(lambda, env)':
+      if local.kind == skIterator and local.typ.callConv == ccClosure:
+        # consider: [i1, i2, i1]  Since we merged the iterator's closure
+        # with the captured owning variables, we need to generate the
+        # closure generation code again:
+        #if local == o.fn: message(n.info, errRecursiveDependencyX, local.name.s)
+        # XXX why doesn't this work?
+        let createdVar = generateIterClosureCreation(o, closure,
+                                                     closure.attachedNode)
+        return makeClosure(local, createdVar, n.info)
+      
+      let a = closure.createdVar
       if a != nil:
         return makeClosure(local, a, n.info)
       else:
@@ -514,12 +671,12 @@ proc transformOuterProc(o: POuterContext, n: PNode): PNode =
         if scope.sons[0].kind == nkEmpty:
           # change the empty node to contain the closure construction:
           scope.sons[0] = generateClosureCreation(o, closure)
-        let x = closure.closure
+        let x = closure.createdVar
         assert x != nil
         return makeClosure(local, x, n.info)
     
     if not contains(o.capturedVars, local.id): return
-    var env = PEnv(IdTableGet(o.localsToEnv, local))
+    var env = PEnv(idTableGet(o.localsToEnv, local))
     if env == nil: return
     var scope = env.attachedNode
     assert scope.kind == nkStmtList
@@ -529,26 +686,55 @@ proc transformOuterProc(o: POuterContext, n: PNode): PNode =
     
     # change 'local' to 'closure.local', unless it's a 'byCopy' variable:
     # if sfByCopy notin local.flags:
-    result = IdNodeTableGet(o.localsToAccess, local)
+    result = idNodeTableGet(o.localsToAccess, local)
     assert result != nil, "cannot find: " & local.name.s
     # else it is captured by copy and this means that 'outer' should continue
     # to access the local as a local.
-  of nkLambdaKinds:
-    result = transformOuterProc(o, n.sons[namePos])
-  of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef, nkTemplateDef, 
-     nkIteratorDef: 
+  of nkLambdaKinds, nkIteratorDef:
+    if n.typ != nil:
+      result = transformOuterProc(o, n.sons[namePos])
+  of nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef, nkTemplateDef,
+      nkClosure:
     # don't recurse here:
-    nil
+    discard
   of nkHiddenStdConv, nkHiddenSubConv, nkConv:
     let x = transformOuterProc(o, n.sons[1])
     if x != nil: n.sons[1] = x
     result = transformOuterConv(n)
+  of nkYieldStmt:
+    if o.isIter: result = transformYield(o, n)
+    else: outerProcSons(o, n)
+  of nkReturnStmt:
+    if o.isIter: result = transformReturn(o, n)
+    else: outerProcSons(o, n)
   else:
-    for i in countup(0, sonsLen(n) - 1):
-      let x = transformOuterProc(o, n.sons[i])
-      if x != nil: n.sons[i] = x
+    outerProcSons(o, n)
+
+proc liftIterator(c: POuterContext, body: PNode): PNode =
+  let iter = c.fn
+  result = newNodeI(nkStmtList, iter.info)
+  var gs = newNodeI(nkGotoState, iter.info)
+  gs.add(indirectAccess(newSymNode(c.closureParam), c.state, iter.info))
+  result.add(gs)
+  var state0 = newNodeI(nkState, iter.info)
+  state0.add(newIntNode(nkIntLit, 0))
+  result.add(state0)
+  
+  let newBody = transformOuterProc(c, body)
+  if newBody != nil:
+    result.add(newBody)
+  else:
+    result.add(body)
+
+  var stateAsgnStmt = newNodeI(nkAsgn, iter.info)
+  stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),
+                    c.state,iter.info))
+  stateAsgnStmt.add(newIntTypeNode(nkIntLit, -1, getSysType(tyInt)))
+  result.add(stateAsgnStmt)
 
 proc liftLambdas*(fn: PSym, body: PNode): PNode =
+  # XXX gCmd == cmdCompileToJS does not suffice! The compiletime stuff needs
+  # the transformation even when compiling to JS ...
   if body.kind == nkEmpty or gCmd == cmdCompileToJS:
     # ignore forward declaration:
     result = body
@@ -560,16 +746,19 @@ proc liftLambdas*(fn: PSym, body: PNode): PNode =
     let params = fn.typ.n
     for i in 1.. <params.len: 
       if params.sons[i].kind != nkSym:
-        InternalError(params.info, "liftLambdas: strange params")
+        internalError(params.info, "liftLambdas: strange params")
       let param = params.sons[i].sym
-      IdTablePut(o.localsToEnv, param, o.currentEnv)
+      idTablePut(o.localsToEnv, param, o.currentEnv)
     # put the 'result' into the environment so it can be captured:
     let ast = fn.ast
     if resultPos < sonsLen(ast) and ast.sons[resultPos].kind == nkSym:
-      IdTablePut(o.localsToEnv, ast.sons[resultPos].sym, o.currentEnv)
+      idTablePut(o.localsToEnv, ast.sons[resultPos].sym, o.currentEnv)
     searchForInnerProcs(o, body)
-    discard transformOuterProc(o, body)
-    result = ex
+    if o.isIter:
+      result = liftIterator(o, ex)
+    else:
+      discard transformOuterProc(o, body)
+      result = ex
 
 proc liftLambdasForTopLevel*(module: PSym, body: PNode): PNode =
   if body.kind == nkEmpty or gCmd == cmdCompileToJS:
@@ -584,140 +773,15 @@ proc liftLambdasForTopLevel*(module: PSym, body: PNode): PNode =
 
 # ------------------- iterator transformation --------------------------------
 
-discard """
-  iterator chain[S, T](a, b: *S->T, args: *S): T =
-    for x in a(args): yield x
-    for x in b(args): yield x
-
-  let c = chain(f, g)
-  for x in c: echo x
-  
-  # translated to:
-  let c = chain( (f, newClosure(f)), (g, newClosure(g)), newClosure(chain))
-"""
-
-type
-  TIterContext {.final, pure.} = object
-    iter, closureParam, state, resultSym: PSym
-    capturedVars: TIntSet
-    tup: PType
-
-proc newIterResult(iter: PSym): PSym =
-  result = iter.ast.sons[resultPos].sym
-  when false:
-    result = newSym(skResult, getIdent":result", iter, iter.info)
-    result.typ = iter.typ.sons[0]
-    incl(result.flags, sfUsed)
-
-proc interestingIterVar(s: PSym): bool {.inline.} =
-  result = s.kind in {skVar, skLet, skTemp, skForVar} and sfGlobal notin s.flags
-
-proc transfIterBody(c: var TIterContext, n: PNode): PNode =
-  # gather used vars for closure generation
-  if n == nil: return nil
-  case n.kind
-  of nkSym:
-    var s = n.sym
-    if interestingIterVar(s) and c.iter.id == s.owner.id:
-      if not containsOrIncl(c.capturedVars, s.id): addField(c.tup, s)
-      result = indirectAccess(newSymNode(c.closureParam), s, n.info)
-  of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit: nil
-  of nkYieldStmt:
-    inc c.state.typ.n.sons[1].intVal
-    let stateNo = c.state.typ.n.sons[1].intVal
-
-    var stateAsgnStmt = newNodeI(nkAsgn, n.info)
-    stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),c.state,n.info))
-    stateAsgnStmt.add(newIntTypeNode(nkIntLit, stateNo, getSysType(tyInt)))
-
-    var retStmt = newNodeI(nkReturnStmt, n.info)
-    if n.sons[0].kind != nkEmpty:
-      var a = newNodeI(nkAsgn, n.sons[0].info)
-      var retVal = transfIterBody(c, n.sons[0])
-      addSon(a, newSymNode(c.resultSym))
-      addSon(a, if retVal.isNil: n.sons[0] else: retVal)
-      retStmt.add(a)
-    else:
-      retStmt.add(emptyNode)
-    
-    var stateLabelStmt = newNodeI(nkState, n.info)
-    stateLabelStmt.add(newIntTypeNode(nkIntLit, stateNo, getSysType(tyInt)))
-    
-    result = newNodeI(nkStmtList, n.info)
-    result.add(stateAsgnStmt)
-    result.add(retStmt)
-    result.add(stateLabelStmt)
-  of nkReturnStmt:
-    result = newNodeI(nkStmtList, n.info)
-    var stateAsgnStmt = newNodeI(nkAsgn, n.info)
-    stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),c.state,n.info))
-    stateAsgnStmt.add(newIntTypeNode(nkIntLit, -1, getSysType(tyInt)))
-    result.add(stateAsgnStmt)
-    result.add(n)
-  else:
-    for i in countup(0, sonsLen(n)-1):
-      let x = transfIterBody(c, n.sons[i])
-      if x != nil: n.sons[i] = x
-
-proc getStateType(iter: PSym): PType =
-  var n = newNodeI(nkRange, iter.info)
-  addSon(n, newIntNode(nkIntLit, -1))
-  addSon(n, newIntNode(nkIntLit, 0))
-  result = newType(tyRange, iter)
-  result.n = n
-  rawAddSon(result, getSysType(tyInt))
-
-proc liftIterator*(iter: PSym, body: PNode): PNode =
-  var c: TIterContext
-  c.iter = iter
-  c.capturedVars = initIntSet()
-
-  c.tup = newType(tyTuple, iter)
-  c.tup.n = newNodeI(nkRecList, iter.info)
-
-  var cp = newSym(skParam, getIdent(paramname), iter, iter.info)
-  incl(cp.flags, sfFromGeneric)
-  cp.typ = newType(tyRef, iter)
-  rawAddSon(cp.typ, c.tup)
-  c.closureParam = cp
-  addHiddenParam(iter, cp)
-
-  c.state = newSym(skField, getIdent(":state"), iter, iter.info)
-  c.state.typ = getStateType(iter)
-  addField(c.tup, c.state)
-
-  if iter.typ.sons[0] != nil:
-    c.resultSym = newIterResult(iter)
-    iter.ast.add(newSymNode(c.resultSym))
-
-  result = newNodeI(nkStmtList, iter.info)
-  var gs = newNodeI(nkGotoState, iter.info)
-  gs.add(indirectAccess(newSymNode(c.closureParam), c.state, iter.info))
-  result.add(gs)
-  var state0 = newNodeI(nkState, iter.info)
-  state0.add(newIntNode(nkIntLit, 0))
-  result.add(state0)
-  
-  let newBody = transfIterBody(c, body)
-  if newBody != nil:
-    result.add(newBody)
-  else:
-    result.add(body)
-
-  var stateAsgnStmt = newNodeI(nkAsgn, iter.info)
-  stateAsgnStmt.add(indirectAccess(newSymNode(c.closureParam),
-                    c.state,iter.info))
-  stateAsgnStmt.add(newIntTypeNode(nkIntLit, -1, getSysType(tyInt)))
-  result.add(stateAsgnStmt)
-
 proc liftIterSym*(n: PNode): PNode =
   # transforms  (iter)  to  (let env = newClosure[iter](); (iter, env)) 
-  result = newNodeIT(nkStmtListExpr, n.info, n.typ)
   let iter = n.sym
   assert iter.kind == skIterator
+
+  result = newNodeIT(nkStmtListExpr, n.info, n.typ)
+  
   var env = copySym(getHiddenParam(iter))
   env.kind = skLet
-
   var v = newNodeI(nkVarSection, n.info)
   addVar(v, newSymNode(env))
   result.add(v)
@@ -754,7 +818,7 @@ proc liftForLoop*(body: PNode): PNode =
         ...
     """
   var L = body.len
-  InternalAssert body.kind == nkForStmt and body[L-2].kind in nkCallKinds
+  internalAssert body.kind == nkForStmt and body[L-2].kind in nkCallKinds
   var call = body[L-2]
 
   result = newNodeI(nkStmtList, body.info)
@@ -762,7 +826,7 @@ proc liftForLoop*(body: PNode): PNode =
   # static binding?
   var env: PSym
   if call[0].kind == nkSym and call[0].sym.kind == skIterator:
-    # createClose()
+    # createClosure()
     let iter = call[0].sym
     assert iter.kind == skIterator
     env = copySym(getHiddenParam(iter))
@@ -789,7 +853,7 @@ proc liftForLoop*(body: PNode): PNode =
     addSon(vpart, body[i])
 
   addSon(vpart, ast.emptyNode) # no explicit type
-  if not env.isnil:
+  if not env.isNil:
     call.sons[0] = makeClosure(call.sons[0].sym, env, body.info)
   addSon(vpart, call)
   addSon(v2, vpart)
diff --git a/compiler/lexer.nim b/compiler/lexer.nim
index 82bfa0ad4..0e7df13cd 100644
--- a/compiler/lexer.nim
+++ b/compiler/lexer.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -41,11 +41,12 @@ type
     tkGeneric, tkIf, tkImport, tkIn, tkInclude, tkInterface, 
     tkIs, tkIsnot, tkIterator,
     tkLambda, tkLet,
-    tkMacro, tkMethod, tkMixin, tkUsing, tkMod, tkNil, tkNot, tkNotin, 
+    tkMacro, tkMethod, tkMixin, tkMod, tkNil, tkNot, tkNotin, 
     tkObject, tkOf, tkOr, tkOut, 
     tkProc, tkPtr, tkRaise, tkRef, tkReturn, tkShared, tkShl, tkShr, tkStatic,
     tkTemplate, 
-    tkTry, tkTuple, tkType, tkVar, tkWhen, tkWhile, tkWith, tkWithout, tkXor,
+    tkTry, tkTuple, tkType, tkUsing, 
+    tkVar, tkWhen, tkWhile, tkWith, tkWithout, tkXor,
     tkYield, # end of keywords
     tkIntLit, tkInt8Lit, tkInt16Lit, tkInt32Lit, tkInt64Lit,
     tkUIntLit, tkUInt8Lit, tkUInt16Lit, tkUInt32Lit, tkUInt64Lit,
@@ -75,12 +76,13 @@ const
     "finally", "for", "from", "generic", "if", 
     "import", "in", "include", "interface", "is", "isnot", "iterator",
     "lambda", "let", 
-    "macro", "method", "mixin", "using", "mod", 
+    "macro", "method", "mixin", "mod", 
     "nil", "not", "notin", "object", "of", "or", 
     "out", "proc", "ptr", "raise", "ref", "return", 
     "shared", "shl", "shr", "static",
     "template", 
-    "try", "tuple", "type", "var", "when", "while", "with", "without", "xor",
+    "try", "tuple", "type", "using",
+    "var", "when", "while", "with", "without", "xor",
     "yield",
     "tkIntLit", "tkInt8Lit", "tkInt16Lit", "tkInt32Lit", "tkInt64Lit",
     "tkUIntLit", "tkUInt8Lit", "tkUInt16Lit", "tkUInt32Lit", "tkUInt64Lit",
@@ -130,11 +132,11 @@ proc getLineInfo*(L: TLexer, tok: TToken): TLineInfo {.inline.} =
   newLineInfo(L.fileIdx, tok.line, tok.col)
 
 proc closeLexer*(lex: var TLexer)
-proc PrintTok*(tok: TToken)
+proc printTok*(tok: TToken)
 proc tokToStr*(tok: TToken): string
 
 proc openLexer*(lex: var TLexer, filename: string, inputstream: PLLStream) =
-  OpenLexer(lex, filename.fileInfoIdx, inputStream)
+  openLexer(lex, filename.fileInfoIdx, inputstream)
 
 proc lexMessage*(L: TLexer, msg: TMsgKind, arg = "")
 
@@ -158,19 +160,19 @@ proc tokToStr*(tok: TToken): string =
   of tkFloatLit..tkFloat64Lit: result = $tok.fNumber
   of tkInvalid, tkStrLit..tkCharLit, tkComment: result = tok.literal
   of tkParLe..tkColon, tkEof, tkAccent: 
-    result = tokTypeToStr[tok.tokType]
+    result = TokTypeToStr[tok.tokType]
   else:
     if tok.ident != nil:
       result = tok.ident.s
     else: 
-      InternalError("tokToStr")
+      internalError("tokToStr")
       result = ""
   
 proc prettyTok*(tok: TToken): string =
-  if IsKeyword(tok.tokType): result = "keyword " & tok.ident.s
+  if isKeyword(tok.tokType): result = "keyword " & tok.ident.s
   else: result = tokToStr(tok)
   
-proc PrintTok*(tok: TToken) = 
+proc printTok*(tok: TToken) = 
   write(stdout, TokTypeToStr[tok.tokType])
   write(stdout, " ")
   writeln(stdout, tokToStr(tok))
@@ -178,18 +180,18 @@ proc PrintTok*(tok: TToken) =
 var dummyIdent: PIdent
 
 proc initToken*(L: var TToken) = 
-  L.TokType = tkInvalid
+  L.tokType = tkInvalid
   L.iNumber = 0
-  L.Indent = 0
+  L.indent = 0
   L.literal = ""
   L.fNumber = 0.0
   L.base = base10
   L.ident = dummyIdent
 
 proc fillToken(L: var TToken) = 
-  L.TokType = tkInvalid
+  L.tokType = tkInvalid
   L.iNumber = 0
-  L.Indent = 0
+  L.indent = 0
   setLen(L.literal, 0)
   L.fNumber = 0.0
   L.base = base10
@@ -197,26 +199,26 @@ proc fillToken(L: var TToken) =
   
 proc openLexer(lex: var TLexer, fileIdx: int32, inputstream: PLLStream) = 
   openBaseLexer(lex, inputstream)
-  lex.fileIdx = fileIdx
+  lex.fileIdx = fileidx
   lex.indentAhead = - 1
-  inc(lex.Linenumber, inputstream.lineOffset) 
+  inc(lex.lineNumber, inputstream.lineOffset) 
 
 proc closeLexer(lex: var TLexer) = 
-  inc(gLinesCompiled, lex.LineNumber)
+  inc(gLinesCompiled, lex.lineNumber)
   closeBaseLexer(lex)
 
 proc getColumn(L: TLexer): int = 
-  result = getColNumber(L, L.bufPos)
+  result = getColNumber(L, L.bufpos)
 
 proc getLineInfo(L: TLexer): TLineInfo = 
-  result = newLineInfo(L.fileIdx, L.linenumber, getColNumber(L, L.bufpos))
+  result = newLineInfo(L.fileIdx, L.lineNumber, getColNumber(L, L.bufpos))
 
 proc lexMessage(L: TLexer, msg: TMsgKind, arg = "") = 
-  msgs.Message(getLineInfo(L), msg, arg)
+  msgs.message(getLineInfo(L), msg, arg)
 
 proc lexMessagePos(L: var TLexer, msg: TMsgKind, pos: int, arg = "") = 
-  var info = newLineInfo(L.fileIdx, L.linenumber, pos - L.lineStart)
-  msgs.Message(info, msg, arg)
+  var info = newLineInfo(L.fileIdx, L.lineNumber, pos - L.lineStart)
+  msgs.message(info, msg, arg)
 
 proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) = 
   var pos = L.bufpos              # use registers for pos, buf
@@ -224,7 +226,7 @@ proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) =
   while true: 
     if buf[pos] in chars: 
       add(tok.literal, buf[pos])
-      Inc(pos)
+      inc(pos)
     else: 
       break 
     if buf[pos] == '_': 
@@ -232,11 +234,11 @@ proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) =
         lexMessage(L, errInvalidToken, "_")
         break
       add(tok.literal, '_')
-      Inc(pos)
-  L.bufPos = pos
+      inc(pos)
+  L.bufpos = pos
 
-proc matchTwoChars(L: TLexer, first: Char, second: TCharSet): bool = 
-  result = (L.buf[L.bufpos] == first) and (L.buf[L.bufpos + 1] in Second)
+proc matchTwoChars(L: TLexer, first: char, second: TCharSet): bool = 
+  result = (L.buf[L.bufpos] == first) and (L.buf[L.bufpos + 1] in second)
 
 proc isFloatLiteral(s: string): bool =
   for i in countup(0, len(s) - 1):
@@ -244,10 +246,10 @@ proc isFloatLiteral(s: string): bool =
       return true
   result = false
 
-proc GetNumber(L: var TLexer): TToken = 
+proc getNumber(L: var TLexer): TToken = 
   var 
     pos, endpos: int
-    xi: biggestInt
+    xi: BiggestInt
   # get the base:
   result.tokType = tkIntLit   # int literal until we know better
   result.literal = ""
@@ -388,25 +390,25 @@ proc GetNumber(L: var TLexer): TToken =
             xi = `shl`(xi, 4) or (ord(L.buf[pos]) - ord('A') + 10)
             inc(pos)
           else: break 
-      else: InternalError(getLineInfo(L), "getNumber")
+      else: internalError(getLineInfo(L), "getNumber")
       case result.tokType
       of tkIntLit, tkInt64Lit: result.iNumber = xi
-      of tkInt8Lit: result.iNumber = biggestInt(int8(toU8(int(xi))))
-      of tkInt16Lit: result.iNumber = biggestInt(toU16(int(xi)))
-      of tkInt32Lit: result.iNumber = biggestInt(toU32(xi))
+      of tkInt8Lit: result.iNumber = BiggestInt(int8(toU8(int(xi))))
+      of tkInt16Lit: result.iNumber = BiggestInt(toU16(int(xi)))
+      of tkInt32Lit: result.iNumber = BiggestInt(toU32(xi))
       of tkUIntLit, tkUInt64Lit: result.iNumber = xi
-      of tkUInt8Lit: result.iNumber = biggestInt(int8(toU8(int(xi))))
-      of tkUInt16Lit: result.iNumber = biggestInt(toU16(int(xi)))
-      of tkUInt32Lit: result.iNumber = biggestInt(toU32(xi))
+      of tkUInt8Lit: result.iNumber = BiggestInt(int8(toU8(int(xi))))
+      of tkUInt16Lit: result.iNumber = BiggestInt(toU16(int(xi)))
+      of tkUInt32Lit: result.iNumber = BiggestInt(toU32(xi))
       of tkFloat32Lit: 
         result.fNumber = (cast[PFloat32](addr(xi)))[] 
         # note: this code is endian neutral!
         # XXX: Test this on big endian machine!
       of tkFloat64Lit: result.fNumber = (cast[PFloat64](addr(xi)))[] 
-      else: InternalError(getLineInfo(L), "getNumber")
+      else: internalError(getLineInfo(L), "getNumber")
     elif isFloatLiteral(result.literal) or (result.tokType == tkFloat32Lit) or
         (result.tokType == tkFloat64Lit): 
-      result.fnumber = parseFloat(result.literal)
+      result.fNumber = parseFloat(result.literal)
       if result.tokType == tkIntLit: result.tokType = tkFloatLit
     else:
       result.iNumber = parseBiggestInt(result.literal)
@@ -432,7 +434,7 @@ proc handleHexChar(L: var TLexer, xi: var int) =
   of 'A'..'F': 
     xi = (xi shl 4) or (ord(L.buf[L.bufpos]) - ord('A') + 10)
     inc(L.bufpos)
-  else: nil
+  else: discard
 
 proc handleDecChars(L: var TLexer, xi: var int) = 
   while L.buf[L.bufpos] in {'0'..'9'}: 
@@ -443,51 +445,51 @@ proc getEscapedChar(L: var TLexer, tok: var TToken) =
   inc(L.bufpos)               # skip '\'
   case L.buf[L.bufpos]
   of 'n', 'N': 
-    if tok.toktype == tkCharLit: lexMessage(L, errNnotAllowedInCharacter)
+    if tok.tokType == tkCharLit: lexMessage(L, errNnotAllowedInCharacter)
     add(tok.literal, tnl)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'r', 'R', 'c', 'C': 
     add(tok.literal, CR)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'l', 'L': 
     add(tok.literal, LF)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'f', 'F': 
     add(tok.literal, FF)
     inc(L.bufpos)
   of 'e', 'E': 
     add(tok.literal, ESC)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'a', 'A': 
     add(tok.literal, BEL)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'b', 'B': 
     add(tok.literal, BACKSPACE)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'v', 'V': 
     add(tok.literal, VT)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 't', 'T': 
     add(tok.literal, Tabulator)
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of '\'', '\"': 
     add(tok.literal, L.buf[L.bufpos])
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of '\\': 
     add(tok.literal, '\\')
-    Inc(L.bufpos)
+    inc(L.bufpos)
   of 'x', 'X': 
     inc(L.bufpos)
     var xi = 0
     handleHexChar(L, xi)
     handleHexChar(L, xi)
-    add(tok.literal, Chr(xi))
+    add(tok.literal, chr(xi))
   of '0'..'9': 
     if matchTwoChars(L, '0', {'0'..'9'}): 
       lexMessage(L, warnOctalEscape)
     var xi = 0
     handleDecChars(L, xi)
-    if (xi <= 255): add(tok.literal, Chr(xi))
+    if (xi <= 255): add(tok.literal, chr(xi))
     else: lexMessage(L, errInvalidCharacterConstant)
   else: lexMessage(L, errInvalidCharacterConstant)
 
@@ -497,7 +499,7 @@ proc newString(s: cstring, len: int): string =
   for i in 0 .. <len:
     result[i] = s[i]
 
-proc HandleCRLF(L: var TLexer, pos: int): int =
+proc handleCRLF(L: var TLexer, pos: int): int =
   template registerLine =
     let col = L.getColNumber(pos)
     
@@ -512,21 +514,21 @@ proc HandleCRLF(L: var TLexer, pos: int): int =
   case L.buf[pos]
   of CR:
     registerLine()
-    result = nimlexbase.HandleCR(L, pos)
+    result = nimlexbase.handleCR(L, pos)
   of LF:
     registerLine()
-    result = nimlexbase.HandleLF(L, pos)
+    result = nimlexbase.handleLF(L, pos)
   else: result = pos
   
 proc getString(L: var TLexer, tok: var TToken, rawMode: bool) = 
-  var pos = L.bufPos + 1          # skip "
+  var pos = L.bufpos + 1          # skip "
   var buf = L.buf                 # put `buf` in a register
-  var line = L.linenumber         # save linenumber for better error message
+  var line = L.lineNumber         # save linenumber for better error message
   if buf[pos] == '\"' and buf[pos+1] == '\"': 
     tok.tokType = tkTripleStrLit # long string literal:
     inc(pos, 2)               # skip ""
     # skip leading newline:
-    pos = HandleCRLF(L, pos)
+    pos = handleCRLF(L, pos)
     buf = L.buf
     while true: 
       case buf[pos]
@@ -536,20 +538,20 @@ proc getString(L: var TLexer, tok: var TToken, rawMode: bool) =
           L.bufpos = pos + 3 # skip the three """
           break 
         add(tok.literal, '\"')
-        Inc(pos)
+        inc(pos)
       of CR, LF: 
-        pos = HandleCRLF(L, pos)
+        pos = handleCRLF(L, pos)
         buf = L.buf
         add(tok.literal, tnl)
       of nimlexbase.EndOfFile: 
-        var line2 = L.linenumber
-        L.LineNumber = line
+        var line2 = L.lineNumber
+        L.lineNumber = line
         lexMessagePos(L, errClosingTripleQuoteExpected, L.lineStart)
-        L.LineNumber = line2
+        L.lineNumber = line2
         break 
       else: 
         add(tok.literal, buf[pos])
-        Inc(pos)
+        inc(pos)
   else: 
     # ordinary string literal
     if rawMode: tok.tokType = tkRStrLit
@@ -567,23 +569,23 @@ proc getString(L: var TLexer, tok: var TToken, rawMode: bool) =
         lexMessage(L, errClosingQuoteExpected)
         break 
       elif (c == '\\') and not rawMode: 
-        L.bufPos = pos
+        L.bufpos = pos
         getEscapedChar(L, tok)
-        pos = L.bufPos
+        pos = L.bufpos
       else: 
         add(tok.literal, c)
-        Inc(pos)
+        inc(pos)
     L.bufpos = pos
 
 proc getCharacter(L: var TLexer, tok: var TToken) = 
-  Inc(L.bufpos)               # skip '
+  inc(L.bufpos)               # skip '
   var c = L.buf[L.bufpos]
   case c
-  of '\0'..Pred(' '), '\'': lexMessage(L, errInvalidCharacterConstant)
+  of '\0'..pred(' '), '\'': lexMessage(L, errInvalidCharacterConstant)
   of '\\': getEscapedChar(L, tok)
   else: 
     tok.literal = $c
-    Inc(L.bufpos)
+    inc(L.bufpos)
   if L.buf[L.bufpos] != '\'': lexMessage(L, errMissingFinalQuote)
   inc(L.bufpos)               # skip '
   
@@ -604,7 +606,7 @@ proc getSymbol(L: var TLexer, tok: var TToken) =
         lexMessage(L, errInvalidToken, "_")
         break
     else: break 
-    Inc(pos)
+    inc(pos)
   h = !$h
   tok.ident = getIdent(addr(L.buf[L.bufpos]), pos - L.bufpos, h)
   L.bufpos = pos
@@ -629,8 +631,8 @@ proc getOperator(L: var TLexer, tok: var TToken) =
   while true: 
     var c = buf[pos]
     if c notin OpChars: break
-    h = h !& Ord(c)
-    Inc(pos)
+    h = h !& ord(c)
+    inc(pos)
   endOperator(L, tok, pos, h)
 
 proc scanComment(L: var TLexer, tok: var TToken) = 
@@ -678,17 +680,17 @@ proc skip(L: var TLexer, tok: var TToken) =
   while true:
     case buf[pos]
     of ' ':
-      Inc(pos)
+      inc(pos)
     of Tabulator:
       lexMessagePos(L, errTabulatorsAreNotAllowed, pos)
       inc(pos)
     of CR, LF:
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
       var indent = 0
       while buf[pos] == ' ':
-        Inc(pos)
-        Inc(indent)
+        inc(pos)
+        inc(indent)
       if buf[pos] > ' ':
         tok.indent = indent
         break
@@ -705,7 +707,7 @@ proc rawGetTok(L: var TLexer, tok: var TToken) =
     tok.indent = -1
   skip(L, tok)
   var c = L.buf[L.bufpos]
-  tok.line = L.linenumber
+  tok.line = L.lineNumber
   tok.col = getColNumber(L, L.bufpos)
   if c in SymStartChars - {'r', 'R', 'l'}:
     getSymbol(L, tok)
@@ -722,8 +724,8 @@ proc rawGetTok(L: var TLexer, tok: var TToken) =
       else:
         getOperator(L, tok)
     of ',':
-      tok.toktype = tkComma
-      Inc(L.bufpos)
+      tok.tokType = tkComma
+      inc(L.bufpos)
     of 'l': 
       # if we parsed exactly one character and its a small L (l), this
       # is treated as a warning because it may be confused with the number 1
@@ -731,59 +733,59 @@ proc rawGetTok(L: var TLexer, tok: var TToken) =
         lexMessage(L, warnSmallLshouldNotBeUsed)
       getSymbol(L, tok)
     of 'r', 'R':
-      if L.buf[L.bufPos + 1] == '\"': 
-        Inc(L.bufPos)
+      if L.buf[L.bufpos + 1] == '\"': 
+        inc(L.bufpos)
         getString(L, tok, true)
       else: 
         getSymbol(L, tok)
     of '(': 
-      Inc(L.bufpos)
-      if L.buf[L.bufPos] == '.' and L.buf[L.bufPos+1] != '.': 
-        tok.toktype = tkParDotLe
-        Inc(L.bufpos)
+      inc(L.bufpos)
+      if L.buf[L.bufpos] == '.' and L.buf[L.bufpos+1] != '.': 
+        tok.tokType = tkParDotLe
+        inc(L.bufpos)
       else: 
-        tok.toktype = tkParLe
+        tok.tokType = tkParLe
     of ')': 
-      tok.toktype = tkParRi
-      Inc(L.bufpos)
+      tok.tokType = tkParRi
+      inc(L.bufpos)
     of '[': 
-      Inc(L.bufpos)
-      if L.buf[L.bufPos] == '.' and L.buf[L.bufPos+1] != '.':
-        tok.toktype = tkBracketDotLe
-        Inc(L.bufpos)
+      inc(L.bufpos)
+      if L.buf[L.bufpos] == '.' and L.buf[L.bufpos+1] != '.':
+        tok.tokType = tkBracketDotLe
+        inc(L.bufpos)
       else:
-        tok.toktype = tkBracketLe
+        tok.tokType = tkBracketLe
     of ']':
-      tok.toktype = tkBracketRi
-      Inc(L.bufpos)
+      tok.tokType = tkBracketRi
+      inc(L.bufpos)
     of '.':
-      if L.buf[L.bufPos+1] == ']': 
+      if L.buf[L.bufpos+1] == ']': 
         tok.tokType = tkBracketDotRi
-        Inc(L.bufpos, 2)
-      elif L.buf[L.bufPos+1] == '}': 
+        inc(L.bufpos, 2)
+      elif L.buf[L.bufpos+1] == '}': 
         tok.tokType = tkCurlyDotRi
-        Inc(L.bufpos, 2)
-      elif L.buf[L.bufPos+1] == ')': 
+        inc(L.bufpos, 2)
+      elif L.buf[L.bufpos+1] == ')': 
         tok.tokType = tkParDotRi
-        Inc(L.bufpos, 2)
+        inc(L.bufpos, 2)
       else: 
         getOperator(L, tok)
     of '{': 
-      Inc(L.bufpos)
-      if L.buf[L.bufPos] == '.' and L.buf[L.bufPos+1] != '.':
-        tok.toktype = tkCurlyDotLe
-        Inc(L.bufpos)
+      inc(L.bufpos)
+      if L.buf[L.bufpos] == '.' and L.buf[L.bufpos+1] != '.':
+        tok.tokType = tkCurlyDotLe
+        inc(L.bufpos)
       else: 
-        tok.toktype = tkCurlyLe
+        tok.tokType = tkCurlyLe
     of '}': 
-      tok.toktype = tkCurlyRi
-      Inc(L.bufpos)
+      tok.tokType = tkCurlyRi
+      inc(L.bufpos)
     of ';': 
-      tok.toktype = tkSemiColon
-      Inc(L.bufpos)
+      tok.tokType = tkSemiColon
+      inc(L.bufpos)
     of '`': 
       tok.tokType = tkAccent
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '\"': 
       # check for extended raw string literal:
       var rawMode = L.bufpos > 0 and L.buf[L.bufpos-1] in SymChars
@@ -802,12 +804,12 @@ proc rawGetTok(L: var TLexer, tok: var TToken) =
       if c in OpChars: 
         getOperator(L, tok)
       elif c == nimlexbase.EndOfFile:
-        tok.toktype = tkEof
+        tok.tokType = tkEof
         tok.indent = 0
       else:
         tok.literal = $c
         tok.tokType = tkInvalid
         lexMessage(L, errInvalidToken, c & " (\\" & $(ord(c)) & ')')
-        Inc(L.bufpos)
+        inc(L.bufpos)
   
 dummyIdent = getIdent("")
diff --git a/compiler/lists.nim b/compiler/lists.nim
index 22b1a183a..dd4f5d6be 100644
--- a/compiler/lists.nim
+++ b/compiler/lists.nim
@@ -20,17 +20,17 @@ type
   PStrEntry* = ref TStrEntry
   TLinkedList* = object       # for the "find" operation:
     head*, tail*: PListEntry
-    Counter*: int
+    counter*: int
 
-  TCompareProc* = proc (entry: PListEntry, closure: Pointer): bool {.nimcall.}
+  TCompareProc* = proc (entry: PListEntry, closure: pointer): bool {.nimcall.}
 
-proc InitLinkedList*(list: var TLinkedList) = 
-  list.Counter = 0
+proc initLinkedList*(list: var TLinkedList) = 
+  list.counter = 0
   list.head = nil
   list.tail = nil
 
-proc Append*(list: var TLinkedList, entry: PListEntry) = 
-  Inc(list.counter)
+proc append*(list: var TLinkedList, entry: PListEntry) = 
+  inc(list.counter)
   entry.next = nil
   entry.prev = list.tail
   if list.tail != nil: 
@@ -39,7 +39,7 @@ proc Append*(list: var TLinkedList, entry: PListEntry) =
   list.tail = entry
   if list.head == nil: list.head = entry
   
-proc Contains*(list: TLinkedList, data: string): bool = 
+proc contains*(list: TLinkedList, data: string): bool = 
   var it = list.head
   while it != nil: 
     if PStrEntry(it).data == data: 
@@ -50,15 +50,15 @@ proc newStrEntry(data: string): PStrEntry =
   new(result)
   result.data = data
 
-proc AppendStr*(list: var TLinkedList, data: string) = 
+proc appendStr*(list: var TLinkedList, data: string) = 
   append(list, newStrEntry(data))
 
-proc IncludeStr*(list: var TLinkedList, data: string): bool = 
-  if Contains(list, data): return true
-  AppendStr(list, data)       # else: add to list
+proc includeStr*(list: var TLinkedList, data: string): bool = 
+  if contains(list, data): return true
+  appendStr(list, data)       # else: add to list
 
-proc Prepend*(list: var TLinkedList, entry: PListEntry) = 
-  Inc(list.counter)
+proc prepend*(list: var TLinkedList, entry: PListEntry) = 
+  inc(list.counter)
   entry.prev = nil
   entry.next = list.head
   if list.head != nil: 
@@ -67,22 +67,22 @@ proc Prepend*(list: var TLinkedList, entry: PListEntry) =
   list.head = entry
   if list.tail == nil: list.tail = entry
 
-proc PrependStr*(list: var TLinkedList, data: string) = 
+proc prependStr*(list: var TLinkedList, data: string) = 
   prepend(list, newStrEntry(data))
 
-proc InsertBefore*(list: var TLinkedList, pos, entry: PListEntry) = 
+proc insertBefore*(list: var TLinkedList, pos, entry: PListEntry) = 
   assert(pos != nil)
   if pos == list.head: 
     prepend(list, entry)
   else: 
-    Inc(list.counter)
+    inc(list.counter)
     entry.next = pos
     entry.prev = pos.prev
     if pos.prev != nil: pos.prev.next = entry
     pos.prev = entry
  
-proc Remove*(list: var TLinkedList, entry: PListEntry) = 
-  Dec(list.counter)
+proc remove*(list: var TLinkedList, entry: PListEntry) = 
+  dec(list.counter)
   if entry == list.tail: 
     list.tail = entry.prev
   if entry == list.head: 
@@ -103,14 +103,14 @@ proc bringToFront*(list: var TLinkedList, entry: PListEntry) =
     entry.next = list.head
     list.head = entry
 
-proc ExcludeStr*(list: var TLinkedList, data: string) =
+proc excludeStr*(list: var TLinkedList, data: string) =
   var it = list.head
   while it != nil:
     let nxt = it.next
     if PStrEntry(it).data == data: remove(list, it)
     it = nxt
 
-proc Find*(list: TLinkedList, fn: TCompareProc, closure: Pointer): PListEntry = 
+proc find*(list: TLinkedList, fn: TCompareProc, closure: pointer): PListEntry = 
   result = list.head
   while result != nil:
     if fn(result, closure): return 
diff --git a/compiler/llstream.nim b/compiler/llstream.nim
index 8ccf24b99..510880ffd 100644
--- a/compiler/llstream.nim
+++ b/compiler/llstream.nim
@@ -23,63 +23,63 @@ type
     llsStdIn                  # stream encapsulates stdin
   TLLStream* = object of TObject
     kind*: TLLStreamKind # accessible for low-level access (lexbase uses this)
-    f*: tfile
+    f*: TFile
     s*: string
     rd*, wr*: int             # for string streams
     lineOffset*: int          # for fake stdin line numbers
   
   PLLStream* = ref TLLStream
 
-proc LLStreamOpen*(data: string): PLLStream
-proc LLStreamOpen*(f: var tfile): PLLStream
-proc LLStreamOpen*(filename: string, mode: TFileMode): PLLStream
-proc LLStreamOpen*(): PLLStream
-proc LLStreamOpenStdIn*(): PLLStream
-proc LLStreamClose*(s: PLLStream)
-proc LLStreamRead*(s: PLLStream, buf: pointer, bufLen: int): int
-proc LLStreamReadLine*(s: PLLStream, line: var string): bool
-proc LLStreamReadAll*(s: PLLStream): string
-proc LLStreamWrite*(s: PLLStream, data: string)
-proc LLStreamWrite*(s: PLLStream, data: Char)
-proc LLStreamWrite*(s: PLLStream, buf: pointer, buflen: int)
-proc LLStreamWriteln*(s: PLLStream, data: string)
+proc llStreamOpen*(data: string): PLLStream
+proc llStreamOpen*(f: var TFile): PLLStream
+proc llStreamOpen*(filename: string, mode: TFileMode): PLLStream
+proc llStreamOpen*(): PLLStream
+proc llStreamOpenStdIn*(): PLLStream
+proc llStreamClose*(s: PLLStream)
+proc llStreamRead*(s: PLLStream, buf: pointer, bufLen: int): int
+proc llStreamReadLine*(s: PLLStream, line: var string): bool
+proc llStreamReadAll*(s: PLLStream): string
+proc llStreamWrite*(s: PLLStream, data: string)
+proc llStreamWrite*(s: PLLStream, data: char)
+proc llStreamWrite*(s: PLLStream, buf: pointer, buflen: int)
+proc llStreamWriteln*(s: PLLStream, data: string)
 # implementation
 
-proc LLStreamOpen(data: string): PLLStream = 
+proc llStreamOpen(data: string): PLLStream = 
   new(result)
   result.s = data
   result.kind = llsString
 
-proc LLStreamOpen(f: var tfile): PLLStream = 
+proc llStreamOpen(f: var TFile): PLLStream = 
   new(result)
   result.f = f
   result.kind = llsFile
 
-proc LLStreamOpen(filename: string, mode: TFileMode): PLLStream = 
+proc llStreamOpen(filename: string, mode: TFileMode): PLLStream = 
   new(result)
   result.kind = llsFile
   if not open(result.f, filename, mode): result = nil
   
-proc LLStreamOpen(): PLLStream = 
+proc llStreamOpen(): PLLStream = 
   new(result)
   result.kind = llsNone
 
-proc LLStreamOpenStdIn(): PLLStream = 
+proc llStreamOpenStdIn(): PLLStream = 
   new(result)
   result.kind = llsStdIn
   result.s = ""
   result.lineOffset = -1
 
-proc LLStreamClose(s: PLLStream) = 
+proc llStreamClose(s: PLLStream) = 
   case s.kind
   of llsNone, llsString, llsStdIn: 
-    nil
+    discard
   of llsFile: 
     close(s.f)
 
-when not defined(ReadLineFromStdin): 
+when not defined(readLineFromStdin): 
   # fallback implementation:
-  proc ReadLineFromStdin(prompt: string, line: var string): bool =
+  proc readLineFromStdin(prompt: string, line: var string): bool =
     stdout.write(prompt)
     result = readLine(stdin, line)
 
@@ -99,7 +99,7 @@ proc endsWithOpr*(x: string): bool =
   result = x.endsWith(LineContinuationOprs)
 
 proc continueLine(line: string, inTripleString: bool): bool {.inline.} =
-  result = inTriplestring or
+  result = inTripleString or
       line[0] == ' ' or
       line.endsWith(LineContinuationOprs+AdditionalLineContinuationOprs)
 
@@ -111,12 +111,12 @@ proc countTriples(s: string): int =
       inc i, 2
     inc i
 
-proc LLreadFromStdin(s: PLLStream, buf: pointer, bufLen: int): int =
+proc llReadFromStdin(s: PLLStream, buf: pointer, bufLen: int): int =
   s.s = ""
   s.rd = 0
   var line = newStringOfCap(120)
   var triples = 0
-  while ReadLineFromStdin(if s.s.len == 0: ">>> " else: "... ", line): 
+  while readLineFromStdin(if s.s.len == 0: ">>> " else: "... ", line): 
     add(s.s, line)
     add(s.s, "\n")
     inc triples, countTriples(line)
@@ -127,7 +127,7 @@ proc LLreadFromStdin(s: PLLStream, buf: pointer, bufLen: int): int =
     copyMem(buf, addr(s.s[s.rd]), result)
     inc(s.rd, result)
 
-proc LLStreamRead(s: PLLStream, buf: pointer, bufLen: int): int = 
+proc llStreamRead(s: PLLStream, buf: pointer, bufLen: int): int = 
   case s.kind
   of llsNone: 
     result = 0
@@ -139,9 +139,9 @@ proc LLStreamRead(s: PLLStream, buf: pointer, bufLen: int): int =
   of llsFile: 
     result = readBuffer(s.f, buf, bufLen)
   of llsStdIn: 
-    result = LLreadFromStdin(s, buf, bufLen)
+    result = llReadFromStdin(s, buf, bufLen)
   
-proc LLStreamReadLine(s: PLLStream, line: var string): bool =
+proc llStreamReadLine(s: PLLStream, line: var string): bool =
   setLen(line, 0)
   case s.kind
   of llsNone:
@@ -165,25 +165,25 @@ proc LLStreamReadLine(s: PLLStream, line: var string): bool =
   of llsStdIn:
     result = readLine(stdin, line)
     
-proc LLStreamWrite(s: PLLStream, data: string) = 
+proc llStreamWrite(s: PLLStream, data: string) = 
   case s.kind
   of llsNone, llsStdIn: 
-    nil
+    discard
   of llsString: 
     add(s.s, data)
     inc(s.wr, len(data))
   of llsFile: 
     write(s.f, data)
   
-proc LLStreamWriteln(s: PLLStream, data: string) = 
-  LLStreamWrite(s, data)
-  LLStreamWrite(s, "\n")
+proc llStreamWriteln(s: PLLStream, data: string) = 
+  llStreamWrite(s, data)
+  llStreamWrite(s, "\n")
 
-proc LLStreamWrite(s: PLLStream, data: Char) = 
+proc llStreamWrite(s: PLLStream, data: char) = 
   var c: char
   case s.kind
   of llsNone, llsStdIn: 
-    nil
+    discard
   of llsString: 
     add(s.s, data)
     inc(s.wr)
@@ -191,22 +191,21 @@ proc LLStreamWrite(s: PLLStream, data: Char) =
     c = data
     discard writeBuffer(s.f, addr(c), sizeof(c))
 
-proc LLStreamWrite(s: PLLStream, buf: pointer, buflen: int) = 
+proc llStreamWrite(s: PLLStream, buf: pointer, buflen: int) = 
   case s.kind
   of llsNone, llsStdIn: 
-    nil
+    discard
   of llsString: 
-    if bufLen > 0: 
-      setlen(s.s, len(s.s) + bufLen)
-      copyMem(addr(s.s[0 + s.wr]), buf, bufLen)
-      inc(s.wr, bufLen)
+    if buflen > 0: 
+      setLen(s.s, len(s.s) + buflen)
+      copyMem(addr(s.s[0 + s.wr]), buf, buflen)
+      inc(s.wr, buflen)
   of llsFile: 
-    discard writeBuffer(s.f, buf, bufLen)
+    discard writeBuffer(s.f, buf, buflen)
   
-proc LLStreamReadAll(s: PLLStream): string = 
+proc llStreamReadAll(s: PLLStream): string = 
   const 
     bufSize = 2048
-  var bytes, i: int
   case s.kind
   of llsNone, llsStdIn: 
     result = ""
@@ -216,10 +215,10 @@ proc LLStreamReadAll(s: PLLStream): string =
     s.rd = len(s.s)
   of llsFile: 
     result = newString(bufSize)
-    bytes = readBuffer(s.f, addr(result[0]), bufSize)
-    i = bytes
+    var bytes = readBuffer(s.f, addr(result[0]), bufSize)
+    var i = bytes
     while bytes == bufSize: 
-      setlen(result, i + bufSize)
+      setLen(result, i + bufSize)
       bytes = readBuffer(s.f, addr(result[i + 0]), bufSize)
       inc(i, bytes)
-    setlen(result, i)
+    setLen(result, i)
diff --git a/compiler/lookups.nim b/compiler/lookups.nim
index e1ec9e14b..6dfd25968 100644
--- a/compiler/lookups.nim
+++ b/compiler/lookups.nim
@@ -21,7 +21,7 @@ proc considerAcc*(n: PNode): PIdent =
   of nkSym: result = n.sym.name
   of nkAccQuoted:
     case n.len
-    of 0: GlobalError(n.info, errIdentifierExpected, renderTree(n))
+    of 0: globalError(n.info, errIdentifierExpected, renderTree(n))
     of 1: result = considerAcc(n.sons[0])
     else:
       var id = ""
@@ -30,16 +30,16 @@ proc considerAcc*(n: PNode): PIdent =
         case x.kind
         of nkIdent: id.add(x.ident.s)
         of nkSym: id.add(x.sym.name.s)
-        else: GlobalError(n.info, errIdentifierExpected, renderTree(n))
+        else: globalError(n.info, errIdentifierExpected, renderTree(n))
       result = getIdent(id)
   else:
-    GlobalError(n.info, errIdentifierExpected, renderTree(n))
+    globalError(n.info, errIdentifierExpected, renderTree(n))
  
 template addSym*(scope: PScope, s: PSym) =
-  StrTableAdd(scope.symbols, s)
+  strTableAdd(scope.symbols, s)
 
 proc addUniqueSym*(scope: PScope, s: PSym): TResult =
-  if StrTableIncl(scope.symbols, s):
+  if strTableIncl(scope.symbols, s):
     result = Failure
   else:
     result = Success
@@ -64,17 +64,17 @@ iterator walkScopes*(scope: PScope): PScope =
     current = current.parent
 
 proc localSearchInScope*(c: PContext, s: PIdent): PSym =
-  result = StrTableGet(c.currentScope.symbols, s)
+  result = strTableGet(c.currentScope.symbols, s)
 
 proc searchInScopes*(c: PContext, s: PIdent): PSym =
   for scope in walkScopes(c.currentScope):
-    result = StrTableGet(scope.symbols, s)
+    result = strTableGet(scope.symbols, s)
     if result != nil: return
   result = nil
 
 proc searchInScopes*(c: PContext, s: PIdent, filter: TSymKinds): PSym =
   for scope in walkScopes(c.currentScope):
-    result = StrTableGet(scope.symbols, s)
+    result = strTableGet(scope.symbols, s)
     if result != nil and result.kind in filter: return
   result = nil
 
@@ -114,65 +114,65 @@ proc getSymRepr*(s: PSym): string =
 proc ensureNoMissingOrUnusedSymbols(scope: PScope) =
   # check if all symbols have been used and defined:
   var it: TTabIter
-  var s = InitTabIter(it, scope.symbols)
+  var s = initTabIter(it, scope.symbols)
   var missingImpls = 0
   while s != nil:
     if sfForward in s.flags:
       # too many 'implementation of X' errors are annoying
       # and slow 'suggest' down:
       if missingImpls == 0:
-        LocalError(s.info, errImplOfXexpected, getSymRepr(s))
+        localError(s.info, errImplOfXexpected, getSymRepr(s))
       inc missingImpls
     elif {sfUsed, sfExported} * s.flags == {} and optHints in s.options: 
       # BUGFIX: check options in s!
       if s.kind notin {skForVar, skParam, skMethod, skUnknown, skGenericParam}:
-        Message(s.info, hintXDeclaredButNotUsed, getSymRepr(s))
-    s = NextIter(it, scope.symbols)
+        message(s.info, hintXDeclaredButNotUsed, getSymRepr(s))
+    s = nextIter(it, scope.symbols)
   
-proc WrongRedefinition*(info: TLineInfo, s: string) =
+proc wrongRedefinition*(info: TLineInfo, s: string) =
   if gCmd != cmdInteractive:
     localError(info, errAttemptToRedefine, s)
   
 proc addDecl*(c: PContext, sym: PSym) =
   if c.currentScope.addUniqueSym(sym) == Failure:
-    WrongRedefinition(sym.info, sym.Name.s)
+    wrongRedefinition(sym.info, sym.name.s)
 
 proc addPrelimDecl*(c: PContext, sym: PSym) =
   discard c.currentScope.addUniqueSym(sym)
 
 proc addDeclAt*(scope: PScope, sym: PSym) =
   if scope.addUniqueSym(sym) == Failure:
-    WrongRedefinition(sym.info, sym.Name.s)
+    wrongRedefinition(sym.info, sym.name.s)
 
-proc AddInterfaceDeclAux(c: PContext, sym: PSym) = 
+proc addInterfaceDeclAux(c: PContext, sym: PSym) = 
   if sfExported in sym.flags:
     # add to interface:
-    if c.module != nil: StrTableAdd(c.module.tab, sym)
-    else: InternalError(sym.info, "AddInterfaceDeclAux")
+    if c.module != nil: strTableAdd(c.module.tab, sym)
+    else: internalError(sym.info, "AddInterfaceDeclAux")
 
 proc addInterfaceDeclAt*(c: PContext, scope: PScope, sym: PSym) =
   addDeclAt(scope, sym)
-  AddInterfaceDeclAux(c, sym)
+  addInterfaceDeclAux(c, sym)
 
 proc addOverloadableSymAt*(scope: PScope, fn: PSym) =
   if fn.kind notin OverloadableSyms: 
-    InternalError(fn.info, "addOverloadableSymAt")
+    internalError(fn.info, "addOverloadableSymAt")
     return
-  var check = StrTableGet(scope.symbols, fn.name)
-  if check != nil and check.Kind notin OverloadableSyms: 
-    WrongRedefinition(fn.info, fn.Name.s)
+  var check = strTableGet(scope.symbols, fn.name)
+  if check != nil and check.kind notin OverloadableSyms: 
+    wrongRedefinition(fn.info, fn.name.s)
   else:
     scope.addSym(fn)
   
 proc addInterfaceDecl*(c: PContext, sym: PSym) = 
   # it adds the symbol to the interface if appropriate
   addDecl(c, sym)
-  AddInterfaceDeclAux(c, sym)
+  addInterfaceDeclAux(c, sym)
 
 proc addInterfaceOverloadableSymAt*(c: PContext, scope: PScope, sym: PSym) =
   # it adds the symbol to the interface if appropriate
   addOverloadableSymAt(scope, sym)
-  AddInterfaceDeclAux(c, sym)
+  addInterfaceDeclAux(c, sym)
 
 proc lookUp*(c: PContext, n: PNode): PSym = 
   # Looks up a symbol. Generates an error in case of nil.
@@ -180,7 +180,7 @@ proc lookUp*(c: PContext, n: PNode): PSym =
   of nkIdent:
     result = searchInScopes(c, n.ident)
     if result == nil: 
-      LocalError(n.info, errUndeclaredIdentifier, n.ident.s)
+      localError(n.info, errUndeclaredIdentifier, n.ident.s)
       result = errorSym(c, n)
   of nkSym:
     result = n.sym
@@ -188,34 +188,34 @@ proc lookUp*(c: PContext, n: PNode): PSym =
     var ident = considerAcc(n)
     result = searchInScopes(c, ident)
     if result == nil:
-      LocalError(n.info, errUndeclaredIdentifier, ident.s)
+      localError(n.info, errUndeclaredIdentifier, ident.s)
       result = errorSym(c, n)
   else:
-    InternalError(n.info, "lookUp")
+    internalError(n.info, "lookUp")
     return
-  if Contains(c.AmbiguousSymbols, result.id): 
-    LocalError(n.info, errUseQualifier, result.name.s)
+  if contains(c.ambiguousSymbols, result.id): 
+    localError(n.info, errUseQualifier, result.name.s)
   if result.kind == skStub: loadStub(result)
   
 type 
   TLookupFlag* = enum 
     checkAmbiguity, checkUndeclared
 
-proc QualifiedLookUp*(c: PContext, n: PNode, flags = {checkUndeclared}): PSym = 
+proc qualifiedLookUp*(c: PContext, n: PNode, flags = {checkUndeclared}): PSym = 
   case n.kind
   of nkIdent, nkAccQuoted:
     var ident = considerAcc(n)
     result = searchInScopes(c, ident)
     if result == nil and checkUndeclared in flags: 
-      LocalError(n.info, errUndeclaredIdentifier, ident.s)
+      localError(n.info, errUndeclaredIdentifier, ident.s)
       result = errorSym(c, n)
     elif checkAmbiguity in flags and result != nil and 
-        Contains(c.AmbiguousSymbols, result.id): 
-      LocalError(n.info, errUseQualifier, ident.s)
+        contains(c.ambiguousSymbols, result.id): 
+      localError(n.info, errUseQualifier, ident.s)
   of nkSym:
     result = n.sym
-    if checkAmbiguity in flags and Contains(c.AmbiguousSymbols, result.id): 
-      LocalError(n.info, errUseQualifier, n.sym.name.s)
+    if checkAmbiguity in flags and contains(c.ambiguousSymbols, result.id): 
+      localError(n.info, errUseQualifier, n.sym.name.s)
   of nkDotExpr: 
     result = nil
     var m = qualifiedLookUp(c, n.sons[0], flags*{checkUndeclared})
@@ -227,28 +227,31 @@ proc QualifiedLookUp*(c: PContext, n: PNode, flags = {checkUndeclared}): PSym =
         ident = considerAcc(n.sons[1])
       if ident != nil: 
         if m == c.module: 
-          result = StrTableGet(c.topLevelScope.symbols, ident)
+          result = strTableGet(c.topLevelScope.symbols, ident)
         else: 
-          result = StrTableGet(m.tab, ident)
+          result = strTableGet(m.tab, ident)
         if result == nil and checkUndeclared in flags: 
-          LocalError(n.sons[1].info, errUndeclaredIdentifier, ident.s)
+          localError(n.sons[1].info, errUndeclaredIdentifier, ident.s)
           result = errorSym(c, n.sons[1])
-      elif checkUndeclared in flags:
-        LocalError(n.sons[1].info, errIdentifierExpected, 
+      elif n.sons[1].kind == nkSym:
+        result = n.sons[1].sym
+      elif checkUndeclared in flags and
+           n.sons[1].kind notin {nkOpenSymChoice, nkClosedSymChoice}:
+        localError(n.sons[1].info, errIdentifierExpected,
                    renderTree(n.sons[1]))
         result = errorSym(c, n.sons[1])
   else:
     result = nil
   if result != nil and result.kind == skStub: loadStub(result)
   
-proc InitOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
+proc initOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
   case n.kind
   of nkIdent, nkAccQuoted:
     var ident = considerAcc(n)
     o.scope = c.currentScope
     o.mode = oimNoQualifier
     while true:
-      result = InitIdentIter(o.it, o.scope.symbols, ident)
+      result = initIdentIter(o.it, o.scope.symbols, ident)
       if result != nil:
         break
       else:
@@ -269,12 +272,12 @@ proc InitOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
       if ident != nil: 
         if o.m == c.module: 
           # a module may access its private members:
-          result = InitIdentIter(o.it, c.topLevelScope.symbols, ident)
+          result = initIdentIter(o.it, c.topLevelScope.symbols, ident)
           o.mode = oimSelfModule
         else: 
-          result = InitIdentIter(o.it, o.m.tab, ident)
+          result = initIdentIter(o.it, o.m.tab, ident)
       else: 
-        LocalError(n.sons[1].info, errIdentifierExpected, 
+        localError(n.sons[1].info, errIdentifierExpected, 
                    renderTree(n.sons[1]))
         result = errorSym(c, n.sons[1])
   of nkClosedSymChoice, nkOpenSymChoice:
@@ -282,8 +285,8 @@ proc InitOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
     result = n.sons[0].sym
     o.symChoiceIndex = 1
     o.inSymChoice = initIntSet()
-    Incl(o.inSymChoice, result.id)
-  else: nil
+    incl(o.inSymChoice, result.id)
+  else: discard
   if result != nil and result.kind == skStub: loadStub(result)
 
 proc lastOverloadScope*(o: TOverloadIter): int =
@@ -303,7 +306,7 @@ proc nextOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
       while result == nil:
         o.scope = o.scope.parent
         if o.scope == nil: break
-        result = InitIdentIter(o.it, o.scope.symbols, o.it.name)
+        result = initIdentIter(o.it, o.scope.symbols, o.it.name)
         # BUGFIX: o.it.name <-> n.ident
     else: 
       result = nil
@@ -314,25 +317,25 @@ proc nextOverloadIter*(o: var TOverloadIter, c: PContext, n: PNode): PSym =
   of oimSymChoice: 
     if o.symChoiceIndex < sonsLen(n):
       result = n.sons[o.symChoiceIndex].sym
-      Incl(o.inSymChoice, result.id)
+      incl(o.inSymChoice, result.id)
       inc o.symChoiceIndex
     elif n.kind == nkOpenSymChoice:
       # try 'local' symbols too for Koenig's lookup:
       o.mode = oimSymChoiceLocalLookup
       o.scope = c.currentScope
-      result = FirstIdentExcluding(o.it, o.scope.symbols,
+      result = firstIdentExcluding(o.it, o.scope.symbols,
                                    n.sons[0].sym.name, o.inSymChoice)
       while result == nil:
         o.scope = o.scope.parent
         if o.scope == nil: break
-        result = FirstIdentExcluding(o.it, o.scope.symbols,
+        result = firstIdentExcluding(o.it, o.scope.symbols,
                                      n.sons[0].sym.name, o.inSymChoice)
   of oimSymChoiceLocalLookup:
     result = nextIdentExcluding(o.it, o.scope.symbols, o.inSymChoice)
     while result == nil:
       o.scope = o.scope.parent
       if o.scope == nil: break
-      result = FirstIdentExcluding(o.it, o.scope.symbols,
+      result = firstIdentExcluding(o.it, o.scope.symbols,
                                    n.sons[0].sym.name, o.inSymChoice)
   
   if result != nil and result.kind == skStub: loadStub(result)
diff --git a/compiler/magicsys.nim b/compiler/magicsys.nim
index 0c0b87222..b4f6e043d 100644
--- a/compiler/magicsys.nim
+++ b/compiler/magicsys.nim
@@ -12,14 +12,14 @@
 import 
   ast, astalgo, hashes, msgs, platform, nversion, times, idents, rodread
 
-var SystemModule*: PSym
+var systemModule*: PSym
 
 proc registerSysType*(t: PType)
   # magic symbols in the system module:
 proc getSysType*(kind: TTypeKind): PType
 proc getCompilerProc*(name: string): PSym
 proc registerCompilerProc*(s: PSym)
-proc FinishSystem*(tab: TStrTable)
+proc finishSystem*(tab: TStrTable)
 proc getSysSym*(name: string): PSym
 # implementation
 
@@ -36,7 +36,7 @@ proc newSysType(kind: TTypeKind, size: int): PType =
   result.align = size
 
 proc getSysSym(name: string): PSym = 
-  result = StrTableGet(systemModule.tab, getIdent(name))
+  result = strTableGet(systemModule.tab, getIdent(name))
   if result == nil: 
     rawMessage(errSystemNeeds, name)
     result = newSym(skError, getIdent(name), systemModule, systemModule.info)
@@ -46,11 +46,11 @@ proc getSysSym(name: string): PSym =
 proc getSysMagic*(name: string, m: TMagic): PSym =
   var ti: TIdentIter
   let id = getIdent(name)
-  result = InitIdentIter(ti, systemModule.tab, id)
+  result = initIdentIter(ti, systemModule.tab, id)
   while result != nil:
     if result.kind == skStub: loadStub(result)
     if result.magic == m: return result
-    result = NextIdentIter(ti, systemModule.tab)
+    result = nextIdentIter(ti, systemModule.tab)
   rawMessage(errSystemNeeds, name)
   result = newSym(skError, id, systemModule, systemModule.info)
   result.typ = newType(tyError, systemModule)
@@ -79,14 +79,14 @@ proc getSysType(kind: TTypeKind): PType =
     of tyBool: result = sysTypeFromName("bool")
     of tyChar: result = sysTypeFromName("char")
     of tyString: result = sysTypeFromName("string")
-    of tyCstring: result = sysTypeFromName("cstring")
+    of tyCString: result = sysTypeFromName("cstring")
     of tyPointer: result = sysTypeFromName("pointer")
     of tyNil: result = newSysType(tyNil, ptrSize)
-    else: InternalError("request for typekind: " & $kind)
+    else: internalError("request for typekind: " & $kind)
     gSysTypes[kind] = result
   if result.kind != kind: 
-    InternalError("wanted: " & $kind & " got: " & $result.kind)
-  if result == nil: InternalError("type not found: " & $kind)
+    internalError("wanted: " & $kind & " got: " & $result.kind)
+  if result == nil: internalError("type not found: " & $kind)
 
 var
   intTypeCache: array[-5..64, PType]
@@ -126,7 +126,7 @@ proc skipIntLit*(t: PType): PType {.inline.} =
       return getSysType(t.kind)
   result = t
 
-proc AddSonSkipIntLit*(father, son: PType) =
+proc addSonSkipIntLit*(father, son: PType) =
   if isNil(father.sons): father.sons = @[]
   let s = son.skipIntLit
   add(father.sons, s)
@@ -134,7 +134,7 @@ proc AddSonSkipIntLit*(father, son: PType) =
 
 proc setIntLitType*(result: PNode) =
   let i = result.intVal
-  case platform.IntSize
+  case platform.intSize
   of 8: result.typ = getIntLitType(result)
   of 4:
     if i >= low(int32) and i <= high(int32):
@@ -158,13 +158,13 @@ proc setIntLitType*(result: PNode) =
       result.typ = getSysType(tyInt32)
     else:
       result.typ = getSysType(tyInt64)
-  else: InternalError(result.info, "invalid int size")
+  else: internalError(result.info, "invalid int size")
 
 proc getCompilerProc(name: string): PSym = 
   var ident = getIdent(name, hashIgnoreStyle(name))
-  result = StrTableGet(compilerprocs, ident)
+  result = strTableGet(compilerprocs, ident)
   if result == nil: 
-    result = StrTableGet(rodCompilerProcs, ident)
+    result = strTableGet(rodCompilerprocs, ident)
     if result != nil: 
       strTableAdd(compilerprocs, result)
       if result.kind == skStub: loadStub(result)
@@ -172,7 +172,6 @@ proc getCompilerProc(name: string): PSym =
 proc registerCompilerProc(s: PSym) = 
   strTableAdd(compilerprocs, s)
 
-proc FinishSystem(tab: TStrTable) = nil
-  
-initStrTable(compilerprocs)
+proc finishSystem(tab: TStrTable) = discard
 
+initStrTable(compilerprocs)
diff --git a/compiler/main.nim b/compiler/main.nim
index 9ffe99454..cdea7b5ca 100644
--- a/compiler/main.nim
+++ b/compiler/main.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -14,16 +14,16 @@ import
   os, condsyms, rodread, rodwrite, times,
   wordrecg, sem, semdata, idents, passes, docgen, extccomp,
   cgen, jsgen, json, nversion,
-  platform, nimconf, importer, passaux, depends, evals, types, idgen,
+  platform, nimconf, importer, passaux, depends, vm, vmdef, types, idgen,
   tables, docgen2, service, parser, modules, ccgutils, sigmatch, ropes, lists,
   pretty
 
-from magicsys import SystemModule, resetSysTypes
+from magicsys import systemModule, resetSysTypes
 
 const
-  has_LLVM_Backend = false
+  hasLLVM_Backend = false
 
-when has_LLVM_Backend:
+when hasLLVM_Backend:
   import llvmgen
 
 proc rodPass =
@@ -37,22 +37,22 @@ proc semanticPasses =
   registerPass verbosePass
   registerPass semPass
 
-proc CommandGenDepend =
+proc commandGenDepend =
   semanticPasses()
-  registerPass(genDependPass)
+  registerPass(gendependPass)
   registerPass(cleanupPass)
   compileProject()
   generateDot(gProjectFull)
   execExternalProgram("dot -Tpng -o" & changeFileExt(gProjectFull, "png") &
       ' ' & changeFileExt(gProjectFull, "dot"))
 
-proc CommandCheck =
+proc commandCheck =
   msgs.gErrorMax = high(int)  # do not stop after first error
   semanticPasses()            # use an empty backend for semantic checking only
   rodPass()
   compileProject()
 
-proc CommandDoc2 =
+proc commandDoc2 =
   msgs.gErrorMax = high(int)  # do not stop after first error
   semanticPasses()
   registerPass(docgen2Pass)
@@ -60,7 +60,7 @@ proc CommandDoc2 =
   compileProject()
   finishDoc2Pass(gProjectName)
 
-proc CommandCompileToC =
+proc commandCompileToC =
   semanticPasses()
   registerPass(cgenPass)
   rodPass()
@@ -73,7 +73,7 @@ proc CommandCompileToC =
   compileProject()
   cgenWriteModules()
   if gCmd != cmdRun:
-    extccomp.CallCCompiler(changeFileExt(gProjectFull, ""))
+    extccomp.callCCompiler(changeFileExt(gProjectFull, ""))
 
   if isServing:
     # caas will keep track only of the compilation commands
@@ -111,45 +111,45 @@ proc CommandCompileToC =
     ccgutils.resetCaches()
     GC_fullCollect()
 
-when has_LLVM_Backend:
-  proc CommandCompileToLLVM =
+when hasLLVM_Backend:
+  proc commandCompileToLLVM =
     semanticPasses()
     registerPass(llvmgen.llvmgenPass())
     rodPass()
     #registerPass(cleanupPass())
     compileProject()
 
-proc CommandCompileToJS =
+proc commandCompileToJS =
   #incl(gGlobalOptions, optSafeCode)
   setTarget(osJS, cpuJS)
   #initDefines()
-  DefineSymbol("nimrod") # 'nimrod' is always defined
-  DefineSymbol("ecmascript") # For backward compatibility
-  DefineSymbol("js")
+  defineSymbol("nimrod") # 'nimrod' is always defined
+  defineSymbol("ecmascript") # For backward compatibility
+  defineSymbol("js")
   semanticPasses()
-  registerPass(jsgenPass)
+  registerPass(JSgenPass)
   compileProject()
 
-proc InteractivePasses =
+proc interactivePasses =
   #incl(gGlobalOptions, optSafeCode)
   #setTarget(osNimrodVM, cpuNimrodVM)
   initDefines()
-  DefineSymbol("nimrodvm")
+  defineSymbol("nimrodvm")
   when hasFFI: DefineSymbol("nimffi")
   registerPass(verbosePass)
   registerPass(semPass)
   registerPass(evalPass)
 
-proc CommandInteractive =
+proc commandInteractive =
   msgs.gErrorMax = high(int)  # do not stop after first error
-  InteractivePasses()
+  interactivePasses()
   compileSystemModule()
   if commandArgs.len > 0:
-    discard CompileModule(fileInfoIdx(gProjectFull), {})
+    discard compileModule(fileInfoIdx(gProjectFull), {})
   else:
     var m = makeStdinModule()
     incl(m.flags, sfMainModule)
-    processModule(m, LLStreamOpenStdIn(), nil)
+    processModule(m, llStreamOpenStdIn(), nil)
 
 const evalPasses = [verbosePass, semPass, evalPass]
 
@@ -157,28 +157,28 @@ proc evalNim(nodes: PNode, module: PSym) =
   carryPasses(nodes, module, evalPasses)
 
 proc commandEval(exp: string) =
-  if SystemModule == nil:
-    InteractivePasses()
+  if systemModule == nil:
+    interactivePasses()
     compileSystemModule()
   var echoExp = "echo \"eval\\t\", " & "repr(" & exp & ")"
   evalNim(echoExp.parseString, makeStdinModule())
 
-proc CommandPrettyOld =
+proc commandPrettyOld =
   var projectFile = addFileExt(mainCommandArg(), NimExt)
   var module = parseFile(projectFile.fileInfoIdx)
   if module != nil:
     renderModule(module, getOutFile(mainCommandArg(), "pretty." & NimExt))
 
-proc CommandPretty =
+proc commandPretty =
   msgs.gErrorMax = high(int)  # do not stop after first error
   semanticPasses()
   registerPass(prettyPass)
   compileProject()
   pretty.overwriteFiles()
 
-proc CommandScan =
-  var f = addFileExt(mainCommandArg(), nimExt)
-  var stream = LLStreamOpen(f, fmRead)
+proc commandScan =
+  var f = addFileExt(mainCommandArg(), NimExt)
+  var stream = llStreamOpen(f, fmRead)
   if stream != nil:
     var
       L: TLexer
@@ -187,20 +187,20 @@ proc CommandScan =
     openLexer(L, f, stream)
     while true:
       rawGetTok(L, tok)
-      PrintTok(tok)
+      printTok(tok)
       if tok.tokType == tkEof: break
-    CloseLexer(L)
+    closeLexer(L)
   else:
     rawMessage(errCannotOpenFile, f)
 
-proc CommandSuggest =
+proc commandSuggest =
   if isServing:
     # XXX: hacky work-around ahead
     # Currently, it's possible to issue a idetools command, before
     # issuing the first compile command. This will leave the compiler
     # cache in a state where "no recompilation is necessary", but the
     # cgen pass was never executed at all.
-    CommandCompileToC()
+    commandCompileToC()
     if gDirtyBufferIdx != 0:
       discard compileModule(gDirtyBufferIdx, {sfDirty})
       resetModule(gDirtyBufferIdx)
@@ -219,21 +219,21 @@ proc CommandSuggest =
 proc wantMainModule =
   if gProjectFull.len == 0:
     if optMainModule.len == 0:
-      Fatal(gCmdLineInfo, errCommandExpectsFilename)
+      fatal(gCmdLineInfo, errCommandExpectsFilename)
     else:
       gProjectName = optMainModule
       gProjectFull = gProjectPath / gProjectName
 
-  gProjectMainIdx = addFileExt(gProjectFull, nimExt).fileInfoIdx
+  gProjectMainIdx = addFileExt(gProjectFull, NimExt).fileInfoIdx
 
 proc requireMainModuleOption =
   if optMainModule.len == 0:
-    Fatal(gCmdLineInfo, errMainModuleMustBeSpecified)
+    fatal(gCmdLineInfo, errMainModuleMustBeSpecified)
   else:
     gProjectName = optMainModule
     gProjectFull = gProjectPath / gProjectName
 
-  gProjectMainIdx = addFileExt(gProjectFull, nimExt).fileInfoIdx
+  gProjectMainIdx = addFileExt(gProjectFull, NimExt).fileInfoIdx
 
 proc resetMemory =
   resetCompilationLists()
@@ -286,7 +286,7 @@ const
   SimiluateCaasMemReset = false
   PrintRopeCacheStats = false
 
-proc MainCommand* =
+proc mainCommand* =
   when SimiluateCaasMemReset:
     gGlobalOptions.incl(optCaasEnabled)
 
@@ -297,7 +297,7 @@ proc MainCommand* =
   if gProjectFull.len != 0:
     # current path is always looked first for modules
     prependStr(searchPaths, gProjectPath)
-  setID(100)
+  setId(100)
   passes.gIncludeFile = includeModule
   passes.gImportModule = importModule
   case command.normalize
@@ -305,20 +305,20 @@ proc MainCommand* =
     # compile means compileToC currently
     gCmd = cmdCompileToC
     wantMainModule()
-    CommandCompileToC()
+    commandCompileToC()
   of "cpp", "compiletocpp":
     extccomp.cExt = ".cpp"
     gCmd = cmdCompileToCpp
     if cCompiler == ccGcc: setCC("gpp")
     wantMainModule()
-    DefineSymbol("cpp")
-    CommandCompileToC()
+    defineSymbol("cpp")
+    commandCompileToC()
   of "objc", "compiletooc":
     extccomp.cExt = ".m"
     gCmd = cmdCompileToOC
     wantMainModule()
-    DefineSymbol("objc")
-    CommandCompileToC()
+    defineSymbol("objc")
+    commandCompileToC()
   of "run":
     gCmd = cmdRun
     wantMainModule()
@@ -330,63 +330,63 @@ proc MainCommand* =
   of "js", "compiletojs":
     gCmd = cmdCompileToJS
     wantMainModule()
-    CommandCompileToJS()
+    commandCompileToJS()
   of "compiletollvm":
     gCmd = cmdCompileToLLVM
     wantMainModule()
-    when has_LLVM_Backend:
+    when hasLLVM_Backend:
       CommandCompileToLLVM()
     else:
       rawMessage(errInvalidCommandX, command)
   of "pretty":
     gCmd = cmdPretty
     wantMainModule()
-    CommandPretty()
+    commandPretty()
   of "doc":
     gCmd = cmdDoc
-    LoadConfigs(DocConfig)
+    loadConfigs(DocConfig)
     wantMainModule()
-    CommandDoc()
+    commandDoc()
   of "doc2":
     gCmd = cmdDoc
-    LoadConfigs(DocConfig)
+    loadConfigs(DocConfig)
     wantMainModule()
-    DefineSymbol("nimdoc")
-    CommandDoc2()
+    defineSymbol("nimdoc")
+    commandDoc2()
   of "rst2html":
     gCmd = cmdRst2html
-    LoadConfigs(DocConfig)
+    loadConfigs(DocConfig)
     wantMainModule()
-    CommandRst2Html()
+    commandRst2Html()
   of "rst2tex":
     gCmd = cmdRst2tex
-    LoadConfigs(DocTexConfig)
+    loadConfigs(DocTexConfig)
     wantMainModule()
-    CommandRst2TeX()
+    commandRst2TeX()
   of "jsondoc":
     gCmd = cmdDoc
-    LoadConfigs(DocConfig)
+    loadConfigs(DocConfig)
     wantMainModule()
-    DefineSymbol("nimdoc")
-    CommandJSON()
+    defineSymbol("nimdoc")
+    commandJSON()
   of "buildindex":
     gCmd = cmdDoc
-    LoadConfigs(DocConfig)
-    CommandBuildIndex()
+    loadConfigs(DocConfig)
+    commandBuildIndex()
   of "gendepend":
     gCmd = cmdGenDepend
     wantMainModule()
-    CommandGenDepend()
+    commandGenDepend()
   of "dump":
-    gcmd = cmdDump
-    if getconfigvar("dump.format") == "json":
+    gCmd = cmdDump
+    if getConfigVar("dump.format") == "json":
       requireMainModuleOption()
 
       var definedSymbols = newJArray()
       for s in definedSymbolNames(): definedSymbols.elems.add(%s)
 
       var libpaths = newJArray()
-      for dir in itersearchpath(searchpaths): libpaths.elems.add(%dir)
+      for dir in iterSearchPath(searchPaths): libpaths.elems.add(%dir)
 
       var dumpdata = % [
         (key: "version", val: %VersionAsString),
@@ -395,17 +395,17 @@ proc MainCommand* =
         (key: "lib_paths", val: libpaths)
       ]
 
-      outWriteLn($dumpdata)
+      outWriteln($dumpdata)
     else:
-      outWriteLn("-- list of currently defined symbols --")
-      for s in definedSymbolNames(): outWriteLn(s)
-      outWriteLn("-- end of list --")
+      outWriteln("-- list of currently defined symbols --")
+      for s in definedSymbolNames(): outWriteln(s)
+      outWriteln("-- end of list --")
 
-      for it in iterSearchPath(searchpaths): msgWriteLn(it)
+      for it in iterSearchPath(searchPaths): msgWriteln(it)
   of "check":
     gCmd = cmdCheck
     wantMainModule()
-    CommandCheck()
+    commandCheck()
   of "parse":
     gCmd = cmdParse
     wantMainModule()
@@ -413,11 +413,11 @@ proc MainCommand* =
   of "scan":
     gCmd = cmdScan
     wantMainModule()
-    CommandScan()
-    MsgWriteln("Beware: Indentation tokens depend on the parser\'s state!")
+    commandScan()
+    msgWriteln("Beware: Indentation tokens depend on the parser\'s state!")
   of "i":
     gCmd = cmdInteractive
-    CommandInteractive()
+    commandInteractive()
   of "e":
     # XXX: temporary command for easier testing
     commandEval(mainCommandArg())
@@ -429,12 +429,12 @@ proc MainCommand* =
       commandEval(gEvalExpr)
     else:
       wantMainModule()
-      CommandSuggest()
+      commandSuggest()
   of "serve":
     isServing = true
     gGlobalOptions.incl(optCaasEnabled)
     msgs.gErrorMax = high(int)  # do not stop after first error
-    serve(MainCommand)
+    serve(mainCommand)
   else:
     rawMessage(errInvalidCommandX, command)
 
diff --git a/compiler/modules.nim b/compiler/modules.nim
index ef6af3d69..6a1491682 100644
--- a/compiler/modules.nim
+++ b/compiler/modules.nim
@@ -41,7 +41,7 @@ template crc(x: PSym): expr =
   gMemCacheData[x.position].crc
 
 proc crcChanged(fileIdx: int32): bool =
-  InternalAssert fileIdx >= 0 and fileIdx < gMemCacheData.len
+  internalAssert fileIdx >= 0 and fileIdx < gMemCacheData.len
   
   template updateStatus =
     gMemCacheData[fileIdx].crcStatus = if result: crcHasChanged
@@ -68,7 +68,7 @@ proc doCRC(fileIdx: int32) =
     # echo "FIRST CRC: ", fileIdx.ToFilename
     gMemCacheData[fileIdx].crc = crcFromFile(fileIdx.toFilename)
 
-proc addDep(x: Psym, dep: int32) =
+proc addDep(x: PSym, dep: int32) =
   growCache gMemCacheData, dep
   gMemCacheData[x.position].deps.safeAdd(dep)
 
@@ -130,7 +130,7 @@ proc newModule(fileIdx: int32): PSym =
   
   incl(result.flags, sfUsed)
   initStrTable(result.tab)
-  StrTableAdd(result.tab, result) # a module knows itself
+  strTableAdd(result.tab, result) # a module knows itself
 
 proc compileModule*(fileIdx: int32, flags: TSymFlags): PSym =
   result = getModule(fileIdx)
@@ -144,7 +144,7 @@ proc compileModule*(fileIdx: int32, flags: TSymFlags): PSym =
     if gCmd in {cmdCompileToC, cmdCompileToCpp, cmdCheck, cmdIdeTools}:
       rd = handleSymbolFile(result)
       if result.id < 0: 
-        InternalError("handleSymbolFile should have set the module\'s ID")
+        internalError("handleSymbolFile should have set the module\'s ID")
         return
     else:
       result.id = getID()
@@ -155,7 +155,7 @@ proc compileModule*(fileIdx: int32, flags: TSymFlags): PSym =
       doCRC fileIdx
   else:
     if checkDepMem(fileIdx) == Yes:
-      result = CompileModule(fileIdx, flags)
+      result = compileModule(fileIdx, flags)
     else:
       result = gCompiledModules[fileIdx]
 
@@ -164,14 +164,14 @@ proc importModule*(s: PSym, fileIdx: int32): PSym {.procvar.} =
   result = compileModule(fileIdx, {})
   if optCaasEnabled in gGlobalOptions: addDep(s, fileIdx)
   if sfSystemModule in result.flags:
-    LocalError(result.info, errAttemptToRedefine, result.Name.s)
+    localError(result.info, errAttemptToRedefine, result.name.s)
 
 proc includeModule*(s: PSym, fileIdx: int32): PNode {.procvar.} =
   result = syntaxes.parseFile(fileIdx)
   if optCaasEnabled in gGlobalOptions:
     growCache gMemCacheData, fileIdx
     addDep(s, fileIdx)
-    doCrc(fileIdx)
+    doCRC(fileIdx)
 
 proc `==^`(a, b: string): bool =
   try:
@@ -180,17 +180,17 @@ proc `==^`(a, b: string): bool =
     result = false
 
 proc compileSystemModule* =
-  if magicsys.SystemModule == nil:
-    SystemFileIdx = fileInfoIdx(options.libpath/"system.nim")
-    discard CompileModule(SystemFileIdx, {sfSystemModule})
+  if magicsys.systemModule == nil:
+    systemFileIdx = fileInfoIdx(options.libpath/"system.nim")
+    discard compileModule(systemFileIdx, {sfSystemModule})
 
-proc CompileProject*(projectFile = gProjectMainIdx) =
+proc compileProject*(projectFile = gProjectMainIdx) =
   let systemFileIdx = fileInfoIdx(options.libpath / "system.nim")
-  if projectFile == SystemFileIdx:
-    discard CompileModule(projectFile, {sfMainModule, sfSystemModule})
+  if projectFile == systemFileIdx:
+    discard compileModule(projectFile, {sfMainModule, sfSystemModule})
   else:
     compileSystemModule()
-    discard CompileModule(projectFile, {sfMainModule})
+    discard compileModule(projectFile, {sfMainModule})
 
 var stdinModule: PSym
 proc makeStdinModule*(): PSym =
diff --git a/compiler/msgs.nim b/compiler/msgs.nim
index 895ba71f3..61336aa87 100644
--- a/compiler/msgs.nim
+++ b/compiler/msgs.nim
@@ -93,6 +93,7 @@ type
     errNewSectionExpected, errWhitespaceExpected, errXisNoValidIndexFile, 
     errCannotRenderX, errVarVarTypeNotAllowed, errInstantiateXExplicitely,
     errOnlyACallOpCanBeDelegator, errUsingNoSymbol,
+    errDestructorNotGenericEnough,
     
     errXExpectsTwoArguments, 
     errXExpectsObjectTypes, errXcanNeverBeOfThisSubtype, errTooManyIterations, 
@@ -112,7 +113,7 @@ type
     warnDifferentHeaps, warnWriteToForeignHeap, warnImplicitClosure,
     warnEachIdentIsTuple, warnShadowIdent, 
     warnProveInit, warnProveField, warnProveIndex,
-    warnUninit, warnUser,
+    warnUninit, warnGcMem, warnUser,
     hintSuccess, hintSuccessX,
     hintLineTooLong, hintXDeclaredButNotUsed, hintConvToBaseNotNeeded,
     hintConvFromXtoItselfNotNeeded, hintExprAlwaysX, hintQuitCalled,
@@ -322,6 +323,8 @@ const
     errInstantiateXExplicitely: "instantiate '$1' explicitely",
     errOnlyACallOpCanBeDelegator: "only a call operator can be a delegator",
     errUsingNoSymbol: "'$1' is not a variable, constant or a proc name",
+    errDestructorNotGenericEnough: "Destructor signarue is too specific. " &
+                                   "A destructor must be associated will all instantiations of a generic type",
     errXExpectsTwoArguments: "\'$1\' expects two arguments", 
     errXExpectsObjectTypes: "\'$1\' expects object types",
     errXcanNeverBeOfThisSubtype: "\'$1\' can never be of this subtype", 
@@ -367,6 +370,7 @@ const
     warnProveField: "cannot prove that field '$1' is accessible [ProveField]",
     warnProveIndex: "cannot prove index '$1' is valid [ProveIndex]",
     warnUninit: "'$1' might not have been initialized [Uninit]",
+    warnGcMem: "'$1' uses GC'ed memory [GcMem]",
     warnUser: "$1 [User]", 
     hintSuccess: "operation successful [Success]", 
     hintSuccessX: "operation successful ($# lines compiled; $# sec total; $#) [SuccessX]", 
@@ -386,7 +390,7 @@ const
     hintUser: "$1 [User]"]
 
 const
-  WarningsToStr*: array[0..23, string] = ["CannotOpenFile", "OctalEscape", 
+  WarningsToStr*: array[0..24, string] = ["CannotOpenFile", "OctalEscape", 
     "XIsNeverRead", "XmightNotBeenInit",
     "Deprecated", "ConfigDeprecated",
     "SmallLshouldNotBeUsed", "UnknownMagic", 
@@ -394,7 +398,7 @@ const
     "CommentXIgnored", "NilStmt",
     "AnalysisLoophole", "DifferentHeaps", "WriteToForeignHeap",
     "ImplicitClosure", "EachIdentIsTuple", "ShadowIdent", 
-    "ProveInit", "ProveField", "ProveIndex", "Uninit", "User"]
+    "ProveInit", "ProveField", "ProveIndex", "Uninit", "GcMem", "User"]
 
   HintsToStr*: array[0..15, string] = ["Success", "SuccessX", "LineTooLong", 
     "XDeclaredButNotUsed", "ConvToBaseNotNeeded", "ConvFromXtoItselfNotNeeded", 
@@ -445,7 +449,7 @@ type
   TErrorOutputs* = set[TErrorOutput]
 
   ERecoverableError* = object of EInvalidValue
-  ESuggestDone* = object of EBase
+  ESuggestDone* = object of E_Base
 
 const
   InvalidFileIDX* = int32(-1)
@@ -453,9 +457,9 @@ const
 var
   filenameToIndexTbl = initTable[string, int32]()
   fileInfos*: seq[TFileInfo] = @[]
-  SystemFileIdx*: int32
+  systemFileIdx*: int32
 
-proc toCChar*(c: Char): string = 
+proc toCChar*(c: char): string = 
   case c
   of '\0'..'\x1F', '\x80'..'\xFF': result = '\\' & toOctal(c)
   of '\'', '\"', '\\': result = '\\' & c
@@ -474,7 +478,7 @@ proc makeCString*(s: string): PRope =
       add(res, '\"')
       add(res, tnl)
       app(result, toRope(res)) # reset:
-      setlen(res, 1)
+      setLen(res, 1)
       res[0] = '\"'
     add(res, toCChar(s[i]))
   add(res, '\"')
@@ -545,14 +549,14 @@ var
 when useCaas:
   var stdoutSocket*: TSocket
 
-proc UnknownLineInfo*(): TLineInfo =
+proc unknownLineInfo*(): TLineInfo =
   result.line = int16(-1)
   result.col = int16(-1)
   result.fileIndex = -1
 
 var 
   msgContext: seq[TLineInfo] = @[]
-  lastError = UnknownLineInfo()
+  lastError = unknownLineInfo()
   bufferedMsgs*: seq[string]
 
   errorOutputs* = {eStdOut, eStdErr}
@@ -560,20 +564,20 @@ var
 proc clearBufferedMsgs* =
   bufferedMsgs = nil
 
-proc SuggestWriteln*(s: string) =
+proc suggestWriteln*(s: string) =
   if eStdOut in errorOutputs:
     when useCaas:
-      if isNil(stdoutSocket): Writeln(stdout, s)
+      if isNil(stdoutSocket): writeln(stdout, s)
       else:
-        Writeln(stdout, s)
+        writeln(stdout, s)
         stdoutSocket.send(s & "\c\L")
     else:
-      Writeln(stdout, s)
+      writeln(stdout, s)
   
   if eInMemory in errorOutputs:
     bufferedMsgs.safeAdd(s)
 
-proc SuggestQuit*() =
+proc suggestQuit*() =
   if not isServing:
     quit(0)
   elif isWorkingWithDirtyBuffer:
@@ -601,12 +605,12 @@ proc pushInfoContext*(info: TLineInfo) =
   msgContext.add(info)
   
 proc popInfoContext*() = 
-  setlen(msgContext, len(msgContext) - 1)
+  setLen(msgContext, len(msgContext) - 1)
 
 proc getInfoContext*(index: int): TLineInfo =
   let L = msgContext.len
   let i = if index < 0: L + index else: index
-  if i >=% L: result = UnknownLineInfo()
+  if i >=% L: result = unknownLineInfo()
   else: result = msgContext[i]
 
 proc toFilename*(fileIdx: int32): string =
@@ -643,6 +647,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
@@ -656,18 +662,18 @@ proc addCheckpoint*(info: TLineInfo) =
 proc addCheckpoint*(filename: string, line: int) = 
   addCheckpoint(newLineInfo(filename, line, - 1))
 
-proc OutWriteln*(s: string) = 
+proc outWriteln*(s: string) = 
   ## Writes to stdout. Always.
-  if eStdOut in errorOutputs: Writeln(stdout, s)
+  if eStdOut in errorOutputs: writeln(stdout, s)
  
-proc MsgWriteln*(s: string) = 
+proc msgWriteln*(s: string) = 
   ## Writes to stdout. If --stdout option is given, writes to stderr instead.
   if gCmd == cmdIdeTools and optCDebug notin gGlobalOptions: return
 
   if optStdout in gGlobalOptions:
-    if eStdErr in errorOutputs: Writeln(stderr, s)
+    if eStdErr in errorOutputs: writeln(stderr, s)
   else:
-    if eStdOut in errorOutputs: Writeln(stdout, s)
+    if eStdOut in errorOutputs: writeln(stdout, s)
   
   if eInMemory in errorOutputs: bufferedMsgs.safeAdd(s)
 
@@ -675,9 +681,9 @@ proc coordToStr(coord: int): string =
   if coord == -1: result = "???"
   else: result = $coord
   
-proc MsgKindToString*(kind: TMsgKind): string = 
+proc msgKindToString*(kind: TMsgKind): string = 
   # later versions may provide translated error messages
-  result = msgKindToStr[kind]
+  result = MsgKindToStr[kind]
 
 proc getMessageStr(msg: TMsgKind, arg: string): string = 
   result = msgKindToString(msg) % [arg]
@@ -699,23 +705,20 @@ type
   TErrorHandling = enum doNothing, doAbort, doRaise
 
 proc handleError(msg: TMsgKind, eh: TErrorHandling, s: string) =
-  template maybeTrace =
-    if defined(debug) or gVerbosity >= 3:
+  template quit =
+    if defined(debug) or gVerbosity >= 3 or msg == errInternal:
       writeStackTrace()
+    quit 1
 
-  if msg == errInternal:
-    writeStackTrace() # we always want a stack trace here
   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)
 
@@ -723,34 +726,34 @@ proc `==`*(a, b: TLineInfo): bool =
   result = a.line == b.line and a.fileIndex == b.fileIndex
 
 proc writeContext(lastinfo: TLineInfo) = 
-  var info = lastInfo
+  var info = lastinfo
   for i in countup(0, len(msgContext) - 1): 
-    if msgContext[i] != lastInfo and msgContext[i] != info: 
-      MsgWriteln(posContextFormat % [toMsgFilename(msgContext[i]), 
+    if msgContext[i] != lastinfo and msgContext[i] != info: 
+      msgWriteln(PosContextFormat % [toMsgFilename(msgContext[i]), 
                                      coordToStr(msgContext[i].line), 
                                      coordToStr(msgContext[i].col), 
                                      getMessageStr(errInstantiationFrom, "")])
     info = msgContext[i]
 
-proc rawMessage*(msg: TMsgKind, args: openarray[string]) = 
+proc rawMessage*(msg: TMsgKind, args: openArray[string]) = 
   var frmt: string
   case msg
   of errMin..errMax: 
     writeContext(unknownLineInfo())
-    frmt = rawErrorFormat
+    frmt = RawErrorFormat
   of warnMin..warnMax: 
     if optWarns notin gOptions: return 
     if msg notin gNotes: return 
     writeContext(unknownLineInfo())
-    frmt = rawWarningFormat
+    frmt = RawWarningFormat
     inc(gWarnCounter)
   of hintMin..hintMax: 
     if optHints notin gOptions: return 
     if msg notin gNotes: return 
-    frmt = rawHintFormat
+    frmt = RawHintFormat
     inc(gHintCounter)
   let s = `%`(frmt, `%`(msgKindToString(msg), args))
-  MsgWriteln(s)
+  msgWriteln(s)
   handleError(msg, doAbort, s)
 
 proc rawMessage*(msg: TMsgKind, arg: string) = 
@@ -758,8 +761,8 @@ proc rawMessage*(msg: TMsgKind, arg: string) =
 
 proc writeSurroundingSrc(info: TLineInfo) =
   const indent = "  "
-  MsgWriteln(indent & info.sourceLine.ropeToStr)
-  MsgWriteln(indent & repeatChar(info.col, ' ') & '^')
+  msgWriteln(indent & info.sourceLine.ropeToStr)
+  msgWriteln(indent & repeatChar(info.col, ' ') & '^')
 
 proc liMessage(info: TLineInfo, msg: TMsgKind, arg: string, 
                eh: TErrorHandling) =
@@ -768,7 +771,7 @@ proc liMessage(info: TLineInfo, msg: TMsgKind, arg: string,
   case msg
   of errMin..errMax:
     writeContext(info)
-    frmt = posErrorFormat
+    frmt = PosErrorFormat
     # we try to filter error messages so that not two error message
     # in the same file and line are produced:
     #ignoreMsg = lastError == info and eh != doAbort
@@ -776,54 +779,54 @@ proc liMessage(info: TLineInfo, msg: TMsgKind, arg: string,
   of warnMin..warnMax:
     ignoreMsg = optWarns notin gOptions or msg notin gNotes
     if not ignoreMsg: writeContext(info)
-    frmt = posWarningFormat
+    frmt = PosWarningFormat
     inc(gWarnCounter)
   of hintMin..hintMax: 
     ignoreMsg = optHints notin gOptions or msg notin gNotes
-    frmt = posHintFormat
+    frmt = PosHintFormat
     inc(gHintCounter)
   let s = frmt % [toMsgFilename(info), coordToStr(info.line),
                   coordToStr(info.col), getMessageStr(msg, arg)]
   if not ignoreMsg:
-    MsgWriteln(s)
+    msgWriteln(s)
     if optPrintSurroundingSrc and msg in errMin..errMax:
       info.writeSurroundingSrc
   handleError(msg, eh, s)
   
-proc Fatal*(info: TLineInfo, msg: TMsgKind, arg = "") = 
+proc fatal*(info: TLineInfo, msg: TMsgKind, arg = "") = 
   liMessage(info, msg, arg, doAbort)
 
-proc GlobalError*(info: TLineInfo, msg: TMsgKind, arg = "") = 
+proc globalError*(info: TLineInfo, msg: TMsgKind, arg = "") = 
   liMessage(info, msg, arg, doRaise)
 
-proc GlobalError*(info: TLineInfo, arg: string) =
+proc globalError*(info: TLineInfo, arg: string) =
   liMessage(info, errGenerated, arg, doRaise)
 
-proc LocalError*(info: TLineInfo, msg: TMsgKind, arg = "") =
+proc localError*(info: TLineInfo, msg: TMsgKind, arg = "") =
   liMessage(info, msg, arg, doNothing)
 
-proc LocalError*(info: TLineInfo, arg: string) =
+proc localError*(info: TLineInfo, arg: string) =
   liMessage(info, errGenerated, arg, doNothing)
 
-proc Message*(info: TLineInfo, msg: TMsgKind, arg = "") =
+proc message*(info: TLineInfo, msg: TMsgKind, arg = "") =
   liMessage(info, msg, arg, doNothing)
 
-proc InternalError*(info: TLineInfo, errMsg: string) = 
+proc internalError*(info: TLineInfo, errMsg: string) = 
   if gCmd == cmdIdeTools: return
   writeContext(info)
   liMessage(info, errInternal, errMsg, doAbort)
 
-proc InternalError*(errMsg: string) = 
+proc internalError*(errMsg: string) = 
   if gCmd == cmdIdeTools: return
-  writeContext(UnknownLineInfo())
+  writeContext(unknownLineInfo())
   rawMessage(errInternal, errMsg)
 
-template AssertNotNil*(e: expr): expr =
-  if e == nil: InternalError($InstantiationInfo())
+template assertNotNil*(e: expr): expr =
+  if e == nil: internalError($instantiationInfo())
   e
 
-template InternalAssert*(e: bool): stmt =
-  if not e: InternalError($InstantiationInfo())
+template internalAssert*(e: bool): stmt =
+  if not e: internalError($instantiationInfo())
 
 proc addSourceLine*(fileIdx: int32, line: string) =
   fileInfos[fileIdx].lines.add line.toRope
@@ -837,23 +840,22 @@ proc sourceLine*(i: TLineInfo): PRope =
         addSourceLine i.fileIndex, line.string
     except EIO:
       discard
-  InternalAssert i.fileIndex < fileInfos.len
+  internalAssert i.fileIndex < fileInfos.len
   # can happen if the error points to EOF:
   if i.line > fileInfos[i.fileIndex].lines.len: return nil
 
   result = fileInfos[i.fileIndex].lines[i.line-1]
 
 proc quotedFilename*(i: TLineInfo): PRope =
-  InternalAssert i.fileIndex >= 0
+  internalAssert i.fileIndex >= 0
   result = fileInfos[i.fileIndex].quotedName
 
-ropes.ErrorHandler = proc (err: TRopesError, msg: string, useWarning: bool) =
+ropes.errorHandler = proc (err: TRopesError, msg: string, useWarning: bool) =
   case err
   of rInvalidFormatStr:
     internalError("ropes: invalid format string: " & msg)
   of rTokenTooLong:
     internalError("ropes: token too long: " & msg)
   of rCannotOpenFile:
-    rawMessage(if useWarning: warnCannotOpenFile else: errCannotOpenFile,
-               msg)
- 
+    rawMessage(if useWarning: warnCannotOpenFile else: errCannotOpenFile, msg)
+
diff --git a/compiler/nimconf.nim b/compiler/nimconf.nim
index 7ec566a01..136a0d454 100644
--- a/compiler/nimconf.nim
+++ b/compiler/nimconf.nim
@@ -49,7 +49,7 @@ proc parseExpr(L: var TLexer, tok: var TToken): bool =
     var b = parseAndExpr(L, tok)
     result = result or b
 
-proc EvalppIf(L: var TLexer, tok: var TToken): bool = 
+proc evalppIf(L: var TLexer, tok: var TToken): bool = 
   ppGetTok(L, tok)            # skip 'if' or 'elif'
   result = parseExpr(L, tok)
   if tok.tokType == tkColon: ppGetTok(L, tok)
@@ -60,7 +60,7 @@ var condStack: seq[bool] = @[]
 proc doEnd(L: var TLexer, tok: var TToken) = 
   if high(condStack) < 0: lexMessage(L, errTokenExpected, "@if")
   ppGetTok(L, tok)            # skip 'end'
-  setlen(condStack, high(condStack))
+  setLen(condStack, high(condStack))
 
 type 
   TJumpDest = enum 
@@ -75,18 +75,18 @@ proc doElse(L: var TLexer, tok: var TToken) =
   
 proc doElif(L: var TLexer, tok: var TToken) = 
   if high(condStack) < 0: lexMessage(L, errTokenExpected, "@if")
-  var res = EvalppIf(L, tok)
+  var res = evalppIf(L, tok)
   if condStack[high(condStack)] or not res: jumpToDirective(L, tok, jdElseEndif)
   else: condStack[high(condStack)] = true
   
 proc jumpToDirective(L: var TLexer, tok: var TToken, dest: TJumpDest) = 
   var nestedIfs = 0
-  while True: 
+  while true: 
     if (tok.ident != nil) and (tok.ident.s == "@"): 
       ppGetTok(L, tok)
       case whichKeyword(tok.ident)
       of wIf: 
-        Inc(nestedIfs)
+        inc(nestedIfs)
       of wElse: 
         if (dest == jdElseEndif) and (nestedIfs == 0): 
           doElse(L, tok)
@@ -99,21 +99,21 @@ proc jumpToDirective(L: var TLexer, tok: var TToken, dest: TJumpDest) =
         if nestedIfs == 0: 
           doEnd(L, tok)
           break 
-        if nestedIfs > 0: Dec(nestedIfs)
+        if nestedIfs > 0: dec(nestedIfs)
       else: 
-        nil
+        discard
       ppGetTok(L, tok)
-    elif tok.tokType == tkEof: 
+    elif tok.tokType == tkEof:
       lexMessage(L, errTokenExpected, "@end")
-    else: 
+    else:
       ppGetTok(L, tok)
   
 proc parseDirective(L: var TLexer, tok: var TToken) = 
   ppGetTok(L, tok)            # skip @
   case whichKeyword(tok.ident)
   of wIf:
-    setlen(condStack, len(condStack) + 1)
-    var res = EvalppIf(L, tok)
+    setLen(condStack, len(condStack) + 1)
+    var res = evalppIf(L, tok)
     condStack[high(condStack)] = res
     if not res: jumpToDirective(L, tok, jdElseEndif)
   of wElif: doElif(L, tok)
@@ -121,7 +121,7 @@ proc parseDirective(L: var TLexer, tok: var TToken) =
   of wEnd: doEnd(L, tok)
   of wWrite: 
     ppGetTok(L, tok)
-    msgs.MsgWriteln(tokToStr(tok))
+    msgs.msgWriteln(tokToStr(tok))
     ppGetTok(L, tok)
   else:
     case tok.ident.s.normalize
@@ -135,13 +135,13 @@ proc parseDirective(L: var TLexer, tok: var TToken) =
       ppGetTok(L, tok)
       var key = tokToStr(tok)
       ppGetTok(L, tok)
-      os.putEnv(key, tokToStr(tok) & os.getenv(key))
+      os.putEnv(key, tokToStr(tok) & os.getEnv(key))
       ppGetTok(L, tok)
     of "appendenv":
       ppGetTok(L, tok)
       var key = tokToStr(tok)
       ppGetTok(L, tok)
-      os.putEnv(key, os.getenv(key) & tokToStr(tok))
+      os.putEnv(key, os.getEnv(key) & tokToStr(tok))
       ppGetTok(L, tok)
     else: lexMessage(L, errInvalidDirectiveX, tokToStr(tok))
   
@@ -196,7 +196,7 @@ proc readConfigFile(filename: string) =
     L: TLexer
     tok: TToken
     stream: PLLStream
-  stream = LLStreamOpen(filename, fmRead)
+  stream = llStreamOpen(filename, fmRead)
   if stream != nil:
     initToken(tok)
     openLexer(L, filename, stream)
@@ -219,7 +219,7 @@ proc getSystemConfigPath(filename: string): string =
     if not existsFile(result): result = joinPath([p, "etc", filename])
     if not existsFile(result): result = "/etc/" & filename
 
-proc LoadConfigs*(cfg: string) =
+proc loadConfigs*(cfg: string) =
   # set default value (can be overwritten):
   if libpath == "": 
     # choose default libpath:
diff --git a/compiler/nimlexbase.nim b/compiler/nimlexbase.nim
index 6d45a825a..038573c35 100644
--- a/compiler/nimlexbase.nim
+++ b/compiler/nimlexbase.nim
@@ -42,7 +42,7 @@ type
     buf*: cstring
     bufLen*: int              # length of buffer in characters
     stream*: PLLStream        # we read from this stream
-    LineNumber*: int          # the current line number
+    lineNumber*: int          # the current line number
                               # private data:
     sentinel*: int
     lineStart*: int           # index of last line start in buffer
@@ -54,11 +54,11 @@ proc openBaseLexer*(L: var TBaseLexer, inputstream: PLLStream,
 proc closeBaseLexer*(L: var TBaseLexer)
 proc getCurrentLine*(L: TBaseLexer, marker: bool = true): string
 proc getColNumber*(L: TBaseLexer, pos: int): int
-proc HandleCR*(L: var TBaseLexer, pos: int): int
+proc handleCR*(L: var TBaseLexer, pos: int): int
   # Call this if you scanned over CR in the buffer; it returns the
   # position to continue the scanning from. `pos` must be the position
   # of the CR.
-proc HandleLF*(L: var TBaseLexer, pos: int): int
+proc handleLF*(L: var TBaseLexer, pos: int): int
   # Call this if you scanned over LF in the buffer; it returns the the
   # position to continue the scanning from. `pos` must be the position
   # of the LF.
@@ -69,9 +69,9 @@ const
 
 proc closeBaseLexer(L: var TBaseLexer) = 
   dealloc(L.buf)
-  LLStreamClose(L.stream)
+  llStreamClose(L.stream)
 
-proc FillBuffer(L: var TBaseLexer) = 
+proc fillBuffer(L: var TBaseLexer) = 
   var 
     charsRead, toCopy, s: int # all are in characters,
                               # not bytes (in case this
@@ -80,12 +80,12 @@ proc FillBuffer(L: var TBaseLexer) =
   # we know here that pos == L.sentinel, but not if this proc
   # is called the first time by initBaseLexer()
   assert(L.sentinel < L.bufLen)
-  toCopy = L.BufLen - L.sentinel - 1
+  toCopy = L.bufLen - L.sentinel - 1
   assert(toCopy >= 0)
   if toCopy > 0: 
-    MoveMem(L.buf, addr(L.buf[L.sentinel + 1]), toCopy * chrSize) 
+    moveMem(L.buf, addr(L.buf[L.sentinel + 1]), toCopy * chrSize) 
     # "moveMem" handles overlapping regions
-  charsRead = LLStreamRead(L.stream, addr(L.buf[toCopy]), 
+  charsRead = llStreamRead(L.stream, addr(L.buf[toCopy]), 
                            (L.sentinel + 1) * chrSize) div chrSize
   s = toCopy + charsRead
   if charsRead < L.sentinel + 1: 
@@ -96,7 +96,7 @@ proc FillBuffer(L: var TBaseLexer) =
     dec(s)                    # BUGFIX (valgrind)
     while true: 
       assert(s < L.bufLen)
-      while (s >= 0) and not (L.buf[s] in NewLines): Dec(s)
+      while (s >= 0) and not (L.buf[s] in NewLines): dec(s)
       if s >= 0: 
         # we found an appropriate character for a sentinel:
         L.sentinel = s
@@ -104,11 +104,11 @@ proc FillBuffer(L: var TBaseLexer) =
       else: 
         # rather than to give up here because the line is too long,
         # double the buffer's size and try again:
-        oldBufLen = L.BufLen
-        L.bufLen = L.BufLen * 2
+        oldBufLen = L.bufLen
+        L.bufLen = L.bufLen * 2
         L.buf = cast[cstring](realloc(L.buf, L.bufLen * chrSize))
-        assert(L.bufLen - oldBuflen == oldBufLen)
-        charsRead = LLStreamRead(L.stream, addr(L.buf[oldBufLen]), 
+        assert(L.bufLen - oldBufLen == oldBufLen)
+        charsRead = llStreamRead(L.stream, addr(L.buf[oldBufLen]), 
                                  oldBufLen * chrSize) div chrSize
         if charsRead < oldBufLen: 
           L.buf[oldBufLen + charsRead] = EndOfFile
@@ -126,20 +126,20 @@ proc fillBaseLexer(L: var TBaseLexer, pos: int): int =
     result = 0
   L.lineStart = result
 
-proc HandleCR(L: var TBaseLexer, pos: int): int = 
+proc handleCR(L: var TBaseLexer, pos: int): int = 
   assert(L.buf[pos] == CR)
-  inc(L.linenumber)
+  inc(L.lineNumber)
   result = fillBaseLexer(L, pos)
   if L.buf[result] == LF: 
     result = fillBaseLexer(L, result)
 
-proc HandleLF(L: var TBaseLexer, pos: int): int = 
+proc handleLF(L: var TBaseLexer, pos: int): int = 
   assert(L.buf[pos] == LF)
-  inc(L.linenumber)
+  inc(L.lineNumber)
   result = fillBaseLexer(L, pos) #L.lastNL := result-1; // BUGFIX: was: result;
   
-proc skip_UTF_8_BOM(L: var TBaseLexer) = 
-  if (L.buf[0] == '\xEF') and (L.buf[1] == '\xBB') and (L.buf[2] == '\xBF'): 
+proc skipUTF8BOM(L: var TBaseLexer) = 
+  if L.buf[0] == '\xEF' and L.buf[1] == '\xBB' and L.buf[2] == '\xBF':
     inc(L.bufpos, 3)
     inc(L.lineStart, 3)
 
@@ -150,10 +150,10 @@ proc openBaseLexer(L: var TBaseLexer, inputstream: PLLStream, bufLen = 8192) =
   L.buf = cast[cstring](alloc(bufLen * chrSize))
   L.sentinel = bufLen - 1
   L.lineStart = 0
-  L.linenumber = 1            # lines start at 1
+  L.lineNumber = 1            # lines start at 1
   L.stream = inputstream
   fillBuffer(L)
-  skip_UTF_8_BOM(L)
+  skipUTF8BOM(L)
 
 proc getColNumber(L: TBaseLexer, pos: int): int = 
   result = abs(pos - L.lineStart)
@@ -166,5 +166,4 @@ proc getCurrentLine(L: TBaseLexer, marker: bool = true): string =
     inc(i)
   result.add("\n")
   if marker: 
-    result.add(RepeatChar(getColNumber(L, L.bufpos)) & '^' & "\n")
-  
+    result.add(repeatChar(getColNumber(L, L.bufpos)) & '^' & "\n")
diff --git a/compiler/nimrod.dot b/compiler/nimrod.dot
deleted file mode 100644
index e9663d7c5..000000000
--- a/compiler/nimrod.dot
+++ /dev/null
@@ -1,591 +0,0 @@
-digraph nimrod {
-times -> strutils;
-os -> strutils;
-os -> times;
-posix -> times;
-os -> posix;
-nhashes -> strutils;
-nstrtabs -> os;
-nstrtabs -> nhashes;
-nstrtabs -> strutils;
-options -> os;
-options -> lists;
-options -> strutils;
-options -> nstrtabs;
-msgs -> options;
-msgs -> strutils;
-msgs -> os;
-crc -> strutils;
-platform -> strutils;
-ropes -> msgs;
-ropes -> strutils;
-ropes -> platform;
-ropes -> nhashes;
-ropes -> crc;
-idents -> nhashes;
-idents -> strutils;
-ast -> msgs;
-ast -> nhashes;
-ast -> nversion;
-ast -> options;
-ast -> strutils;
-ast -> crc;
-ast -> ropes;
-ast -> idents;
-ast -> lists;
-astalgo -> ast;
-astalgo -> nhashes;
-astalgo -> strutils;
-astalgo -> options;
-astalgo -> msgs;
-astalgo -> ropes;
-astalgo -> idents;
-condsyms -> ast;
-condsyms -> astalgo;
-condsyms -> msgs;
-condsyms -> nhashes;
-condsyms -> platform;
-condsyms -> strutils;
-condsyms -> idents;
-hashes -> strutils;
-strtabs -> os;
-strtabs -> hashes;
-strtabs -> strutils;
-osproc -> strutils;
-osproc -> os;
-osproc -> strtabs;
-osproc -> streams;
-osproc -> posix;
-extccomp -> lists;
-extccomp -> ropes;
-extccomp -> os;
-extccomp -> strutils;
-extccomp -> osproc;
-extccomp -> platform;
-extccomp -> condsyms;
-extccomp -> options;
-extccomp -> msgs;
-wordrecg -> nhashes;
-wordrecg -> strutils;
-wordrecg -> idents;
-commands -> os;
-commands -> msgs;
-commands -> options;
-commands -> nversion;
-commands -> condsyms;
-commands -> strutils;
-commands -> extccomp;
-commands -> platform;
-commands -> lists;
-commands -> wordrecg;
-llstream -> strutils;
-lexbase -> llstream;
-lexbase -> strutils;
-scanner -> nhashes;
-scanner -> options;
-scanner -> msgs;
-scanner -> strutils;
-scanner -> platform;
-scanner -> idents;
-scanner -> lexbase;
-scanner -> llstream;
-scanner -> wordrecg;
-nimconf -> llstream;
-nimconf -> nversion;
-nimconf -> commands;
-nimconf -> os;
-nimconf -> strutils;
-nimconf -> msgs;
-nimconf -> platform;
-nimconf -> condsyms;
-nimconf -> scanner;
-nimconf -> options;
-nimconf -> idents;
-nimconf -> wordrecg;
-pnimsyn -> llstream;
-pnimsyn -> scanner;
-pnimsyn -> idents;
-pnimsyn -> strutils;
-pnimsyn -> ast;
-pnimsyn -> msgs;
-pbraces -> llstream;
-pbraces -> scanner;
-pbraces -> idents;
-pbraces -> strutils;
-pbraces -> ast;
-pbraces -> msgs;
-pbraces -> pnimsyn;
-rnimsyn -> scanner;
-rnimsyn -> options;
-rnimsyn -> idents;
-rnimsyn -> strutils;
-rnimsyn -> ast;
-rnimsyn -> msgs;
-rnimsyn -> lists;
-filters -> llstream;
-filters -> os;
-filters -> wordrecg;
-filters -> idents;
-filters -> strutils;
-filters -> ast;
-filters -> astalgo;
-filters -> msgs;
-filters -> options;
-filters -> rnimsyn;
-ptmplsyn -> llstream;
-ptmplsyn -> os;
-ptmplsyn -> wordrecg;
-ptmplsyn -> idents;
-ptmplsyn -> strutils;
-ptmplsyn -> ast;
-ptmplsyn -> astalgo;
-ptmplsyn -> msgs;
-ptmplsyn -> options;
-ptmplsyn -> rnimsyn;
-ptmplsyn -> filters;
-syntaxes -> strutils;
-syntaxes -> llstream;
-syntaxes -> ast;
-syntaxes -> astalgo;
-syntaxes -> idents;
-syntaxes -> scanner;
-syntaxes -> options;
-syntaxes -> msgs;
-syntaxes -> pnimsyn;
-syntaxes -> pbraces;
-syntaxes -> ptmplsyn;
-syntaxes -> filters;
-syntaxes -> rnimsyn;
-paslex -> nhashes;
-paslex -> options;
-paslex -> msgs;
-paslex -> strutils;
-paslex -> platform;
-paslex -> idents;
-paslex -> lexbase;
-paslex -> wordrecg;
-paslex -> scanner;
-pasparse -> os;
-pasparse -> llstream;
-pasparse -> scanner;
-pasparse -> paslex;
-pasparse -> idents;
-pasparse -> wordrecg;
-pasparse -> strutils;
-pasparse -> ast;
-pasparse -> astalgo;
-pasparse -> msgs;
-pasparse -> options;
-rodread -> os;
-rodread -> options;
-rodread -> strutils;
-rodread -> nversion;
-rodread -> ast;
-rodread -> astalgo;
-rodread -> msgs;
-rodread -> platform;
-rodread -> condsyms;
-rodread -> ropes;
-rodread -> idents;
-rodread -> crc;
-trees -> ast;
-trees -> astalgo;
-trees -> scanner;
-trees -> msgs;
-trees -> strutils;
-types -> ast;
-types -> astalgo;
-types -> trees;
-types -> msgs;
-types -> strutils;
-types -> platform;
-magicsys -> ast;
-magicsys -> astalgo;
-magicsys -> nhashes;
-magicsys -> msgs;
-magicsys -> platform;
-magicsys -> nversion;
-magicsys -> times;
-magicsys -> idents;
-magicsys -> rodread;
-nimsets -> ast;
-nimsets -> astalgo;
-nimsets -> trees;
-nimsets -> nversion;
-nimsets -> msgs;
-nimsets -> platform;
-nimsets -> bitsets;
-nimsets -> types;
-nimsets -> rnimsyn;
-passes -> strutils;
-passes -> lists;
-passes -> options;
-passes -> ast;
-passes -> astalgo;
-passes -> llstream;
-passes -> msgs;
-passes -> platform;
-passes -> os;
-passes -> condsyms;
-passes -> idents;
-passes -> rnimsyn;
-passes -> types;
-passes -> extccomp;
-passes -> math;
-passes -> magicsys;
-passes -> nversion;
-passes -> nimsets;
-passes -> syntaxes;
-passes -> times;
-passes -> rodread;
-treetab -> nhashes;
-treetab -> ast;
-treetab -> astalgo;
-treetab -> types;
-semdata -> strutils;
-semdata -> lists;
-semdata -> options;
-semdata -> scanner;
-semdata -> ast;
-semdata -> astalgo;
-semdata -> trees;
-semdata -> treetab;
-semdata -> wordrecg;
-semdata -> ropes;
-semdata -> msgs;
-semdata -> platform;
-semdata -> os;
-semdata -> condsyms;
-semdata -> idents;
-semdata -> rnimsyn;
-semdata -> types;
-semdata -> extccomp;
-semdata -> math;
-semdata -> magicsys;
-semdata -> nversion;
-semdata -> nimsets;
-semdata -> pnimsyn;
-semdata -> times;
-semdata -> passes;
-semdata -> rodread;
-lookups -> ast;
-lookups -> astalgo;
-lookups -> idents;
-lookups -> semdata;
-lookups -> types;
-lookups -> msgs;
-lookups -> options;
-lookups -> rodread;
-lookups -> rnimsyn;
-importer -> strutils;
-importer -> os;
-importer -> ast;
-importer -> astalgo;
-importer -> msgs;
-importer -> options;
-importer -> idents;
-importer -> rodread;
-importer -> lookups;
-importer -> semdata;
-importer -> passes;
-rodwrite -> os;
-rodwrite -> options;
-rodwrite -> strutils;
-rodwrite -> nversion;
-rodwrite -> ast;
-rodwrite -> astalgo;
-rodwrite -> msgs;
-rodwrite -> platform;
-rodwrite -> condsyms;
-rodwrite -> ropes;
-rodwrite -> idents;
-rodwrite -> crc;
-rodwrite -> rodread;
-rodwrite -> passes;
-rodwrite -> importer;
-semfold -> strutils;
-semfold -> lists;
-semfold -> options;
-semfold -> ast;
-semfold -> astalgo;
-semfold -> trees;
-semfold -> treetab;
-semfold -> nimsets;
-semfold -> times;
-semfold -> nversion;
-semfold -> platform;
-semfold -> math;
-semfold -> msgs;
-semfold -> os;
-semfold -> condsyms;
-semfold -> idents;
-semfold -> rnimsyn;
-semfold -> types;
-evals -> strutils;
-evals -> magicsys;
-evals -> lists;
-evals -> options;
-evals -> ast;
-evals -> astalgo;
-evals -> trees;
-evals -> treetab;
-evals -> nimsets;
-evals -> msgs;
-evals -> os;
-evals -> condsyms;
-evals -> idents;
-evals -> rnimsyn;
-evals -> types;
-evals -> passes;
-evals -> semfold;
-procfind -> ast;
-procfind -> astalgo;
-procfind -> msgs;
-procfind -> semdata;
-procfind -> types;
-procfind -> trees;
-pragmas -> os;
-pragmas -> platform;
-pragmas -> condsyms;
-pragmas -> ast;
-pragmas -> astalgo;
-pragmas -> idents;
-pragmas -> semdata;
-pragmas -> msgs;
-pragmas -> rnimsyn;
-pragmas -> wordrecg;
-pragmas -> ropes;
-pragmas -> options;
-pragmas -> strutils;
-pragmas -> lists;
-pragmas -> extccomp;
-pragmas -> math;
-pragmas -> magicsys;
-pragmas -> trees;
-sem -> strutils;
-sem -> nhashes;
-sem -> lists;
-sem -> options;
-sem -> scanner;
-sem -> ast;
-sem -> astalgo;
-sem -> trees;
-sem -> treetab;
-sem -> wordrecg;
-sem -> ropes;
-sem -> msgs;
-sem -> os;
-sem -> condsyms;
-sem -> idents;
-sem -> rnimsyn;
-sem -> types;
-sem -> platform;
-sem -> math;
-sem -> magicsys;
-sem -> pnimsyn;
-sem -> nversion;
-sem -> nimsets;
-sem -> semdata;
-sem -> evals;
-sem -> semfold;
-sem -> importer;
-sem -> procfind;
-sem -> lookups;
-sem -> rodread;
-sem -> pragmas;
-sem -> passes;
-rst -> os;
-rst -> msgs;
-rst -> strutils;
-rst -> platform;
-rst -> nhashes;
-rst -> ropes;
-rst -> options;
-highlite -> nhashes;
-highlite -> options;
-highlite -> msgs;
-highlite -> strutils;
-highlite -> platform;
-highlite -> idents;
-highlite -> lexbase;
-highlite -> wordrecg;
-highlite -> scanner;
-docgen -> ast;
-docgen -> astalgo;
-docgen -> strutils;
-docgen -> nhashes;
-docgen -> options;
-docgen -> nversion;
-docgen -> msgs;
-docgen -> os;
-docgen -> ropes;
-docgen -> idents;
-docgen -> wordrecg;
-docgen -> math;
-docgen -> syntaxes;
-docgen -> rnimsyn;
-docgen -> scanner;
-docgen -> rst;
-docgen -> times;
-docgen -> highlite;
-ccgutils -> ast;
-ccgutils -> astalgo;
-ccgutils -> ropes;
-ccgutils -> lists;
-ccgutils -> nhashes;
-ccgutils -> strutils;
-ccgutils -> types;
-ccgutils -> msgs;
-cgmeth -> options;
-cgmeth -> ast;
-cgmeth -> astalgo;
-cgmeth -> msgs;
-cgmeth -> idents;
-cgmeth -> rnimsyn;
-cgmeth -> types;
-cgmeth -> magicsys;
-cgen -> ast;
-cgen -> astalgo;
-cgen -> strutils;
-cgen -> nhashes;
-cgen -> trees;
-cgen -> platform;
-cgen -> magicsys;
-cgen -> extccomp;
-cgen -> options;
-cgen -> nversion;
-cgen -> nimsets;
-cgen -> msgs;
-cgen -> crc;
-cgen -> bitsets;
-cgen -> idents;
-cgen -> lists;
-cgen -> types;
-cgen -> ccgutils;
-cgen -> os;
-cgen -> times;
-cgen -> ropes;
-cgen -> math;
-cgen -> passes;
-cgen -> rodread;
-cgen -> wordrecg;
-cgen -> rnimsyn;
-cgen -> treetab;
-cgen -> cgmeth;
-jsgen -> ast;
-jsgen -> astalgo;
-jsgen -> strutils;
-jsgen -> nhashes;
-jsgen -> trees;
-jsgen -> platform;
-jsgen -> magicsys;
-jsgen -> extccomp;
-jsgen -> options;
-jsgen -> nversion;
-jsgen -> nimsets;
-jsgen -> msgs;
-jsgen -> crc;
-jsgen -> bitsets;
-jsgen -> idents;
-jsgen -> lists;
-jsgen -> types;
-jsgen -> os;
-jsgen -> times;
-jsgen -> ropes;
-jsgen -> math;
-jsgen -> passes;
-jsgen -> ccgutils;
-jsgen -> wordrecg;
-jsgen -> rnimsyn;
-jsgen -> rodread;
-interact -> llstream;
-interact -> strutils;
-interact -> ropes;
-interact -> nstrtabs;
-interact -> msgs;
-passaux -> strutils;
-passaux -> ast;
-passaux -> astalgo;
-passaux -> passes;
-passaux -> msgs;
-passaux -> options;
-depends -> os;
-depends -> options;
-depends -> ast;
-depends -> astalgo;
-depends -> msgs;
-depends -> ropes;
-depends -> idents;
-depends -> passes;
-depends -> importer;
-transf -> strutils;
-transf -> lists;
-transf -> options;
-transf -> ast;
-transf -> astalgo;
-transf -> trees;
-transf -> treetab;
-transf -> evals;
-transf -> msgs;
-transf -> os;
-transf -> idents;
-transf -> rnimsyn;
-transf -> types;
-transf -> passes;
-transf -> semfold;
-transf -> magicsys;
-transf -> cgmeth;
-main -> llstream;
-main -> strutils;
-main -> ast;
-main -> astalgo;
-main -> scanner;
-main -> syntaxes;
-main -> rnimsyn;
-main -> options;
-main -> msgs;
-main -> os;
-main -> lists;
-main -> condsyms;
-main -> paslex;
-main -> pasparse;
-main -> rodread;
-main -> rodwrite;
-main -> ropes;
-main -> trees;
-main -> wordrecg;
-main -> sem;
-main -> semdata;
-main -> idents;
-main -> passes;
-main -> docgen;
-main -> extccomp;
-main -> cgen;
-main -> jsgen;
-main -> platform;
-main -> interact;
-main -> nimconf;
-main -> importer;
-main -> passaux;
-main -> depends;
-main -> transf;
-main -> evals;
-main -> types;
-parseopt -> os;
-parseopt -> strutils;
-nimrod -> times;
-nimrod -> commands;
-nimrod -> scanner;
-nimrod -> condsyms;
-nimrod -> options;
-nimrod -> msgs;
-nimrod -> nversion;
-nimrod -> nimconf;
-nimrod -> ropes;
-nimrod -> extccomp;
-nimrod -> strutils;
-nimrod -> os;
-nimrod -> platform;
-nimrod -> main;
-nimrod -> parseopt;
-}
diff --git a/compiler/nimrod.nim b/compiler/nimrod.nim
index 2bc94e3f8..38d440ade 100644
--- a/compiler/nimrod.nim
+++ b/compiler/nimrod.nim
@@ -31,12 +31,12 @@ proc prependCurDir(f: string): string =
   else:
     result = f
 
-proc HandleCmdLine() =
+proc handleCmdLine() =
   if paramCount() == 0:
     writeCommandLineUsage()
   else:
     # Process command line arguments:
-    ProcessCmdLine(passCmd1, "")
+    processCmdLine(passCmd1, "")
     if gProjectName != "":
       try:
         gProjectFull = canonicalizePath(gProjectName)
@@ -47,12 +47,12 @@ proc HandleCmdLine() =
       gProjectName = p.name
     else:
       gProjectPath = getCurrentDir()
-    LoadConfigs(DefaultConfig) # load all config files
+    loadConfigs(DefaultConfig) # load all config files
     # now process command line arguments again, because some options in the
     # command line can overwite the config file's settings
     extccomp.initVars()
-    ProcessCmdLine(passCmd2, "")
-    MainCommand()
+    processCmdLine(passCmd2, "")
+    mainCommand()
     if gVerbosity >= 2: echo(GC_getStatistics())
     #echo(GC_getStatistics())
     if msgs.gErrorCounter == 0:
@@ -71,7 +71,7 @@ proc HandleCmdLine() =
             binPath = options.outFile.prependCurDir
           else:
             # Figure out ourselves a valid binary name.
-            binPath = changeFileExt(gProjectFull, exeExt).prependCurDir
+            binPath = changeFileExt(gProjectFull, ExeExt).prependCurDir
           var ex = quoteShell(binPath)
           execExternalProgram(ex & ' ' & service.arguments)
 
@@ -81,8 +81,8 @@ when defined(GC_setMaxPause):
 when compileOption("gc", "v2") or compileOption("gc", "refc"):
   # the new correct mark&sweet collector is too slow :-/
   GC_disableMarkAndSweep()
-condsyms.InitDefines()
+condsyms.initDefines()
 
 when not defined(selftest):
-  HandleCmdLine()
+  handleCmdLine()
   quit(int8(msgs.gErrorCounter > 0))
diff --git a/compiler/nimrod.nimrod.cfg b/compiler/nimrod.nimrod.cfg
index 9fa1b8cba..657c47b28 100644
--- a/compiler/nimrod.nimrod.cfg
+++ b/compiler/nimrod.nimrod.cfg
@@ -13,3 +13,8 @@ path:"$lib/packages/docutils"
 define:booting
 import:testability
 
+@if windows:
+  cincludes: "$lib/wrappers/libffi/common"
+@end
+
+cs:partial
diff --git a/compiler/nimsets.nim b/compiler/nimsets.nim
index 34f79e14b..d65618e0a 100644
--- a/compiler/nimsets.nim
+++ b/compiler/nimsets.nim
@@ -18,7 +18,7 @@ proc overlap*(a, b: PNode): bool
 proc inSet*(s: PNode, elem: PNode): bool
 proc someInSet*(s: PNode, a, b: PNode): bool
 proc emptyRange*(a, b: PNode): bool
-proc SetHasRange*(s: PNode): bool
+proc setHasRange*(s: PNode): bool
   # returns true if set contains a range (needed by the code generator)
   # these are used for constant folding:
 proc unionSets*(a, b: PNode): PNode
@@ -32,7 +32,7 @@ proc cardSet*(s: PNode): BiggestInt
 
 proc inSet(s: PNode, elem: PNode): bool = 
   if s.kind != nkCurly: 
-    InternalError(s.info, "inSet")
+    internalError(s.info, "inSet")
     return false
   for i in countup(0, sonsLen(s) - 1): 
     if s.sons[i].kind == nkRange: 
@@ -58,10 +58,10 @@ proc overlap(a, b: PNode): bool =
     else:
       result = sameValue(a, b)
 
-proc SomeInSet(s: PNode, a, b: PNode): bool = 
+proc someInSet(s: PNode, a, b: PNode): bool = 
   # checks if some element of a..b is in the set s
   if s.kind != nkCurly:
-    InternalError(s.info, "SomeInSet")
+    internalError(s.info, "SomeInSet")
     return false
   for i in countup(0, sonsLen(s) - 1): 
     if s.sons[i].kind == nkRange: 
@@ -82,12 +82,12 @@ proc toBitSet(s: PNode, b: var TBitSet) =
     if s.sons[i].kind == nkRange: 
       j = getOrdValue(s.sons[i].sons[0])
       while j <= getOrdValue(s.sons[i].sons[1]): 
-        BitSetIncl(b, j - first)
+        bitSetIncl(b, j - first)
         inc(j)
     else: 
-      BitSetIncl(b, getOrdValue(s.sons[i]) - first)
+      bitSetIncl(b, getOrdValue(s.sons[i]) - first)
   
-proc ToTreeSet(s: TBitSet, settype: PType, info: TLineInfo): PNode = 
+proc toTreeSet(s: TBitSet, settype: PType, info: TLineInfo): PNode = 
   var 
     a, b, e, first: BiggestInt # a, b are interval borders
     elemType: PType
@@ -98,14 +98,14 @@ proc ToTreeSet(s: TBitSet, settype: PType, info: TLineInfo): PNode =
   result.typ = settype
   result.info = info
   e = 0
-  while e < len(s) * elemSize: 
+  while e < len(s) * ElemSize: 
     if bitSetIn(s, e): 
       a = e
       b = e
       while true: 
-        Inc(b)
-        if (b >= len(s) * elemSize) or not bitSetIn(s, b): break 
-      Dec(b)
+        inc(b)
+        if (b >= len(s) * ElemSize) or not bitSetIn(s, b): break 
+      dec(b)
       if a == b: 
         addSon(result, newIntTypeNode(nkIntLit, a + first, elemType))
       else: 
@@ -115,7 +115,7 @@ proc ToTreeSet(s: TBitSet, settype: PType, info: TLineInfo): PNode =
         addSon(n, newIntTypeNode(nkIntLit, b + first, elemType))
         addSon(result, n)
       e = b
-    Inc(e)
+    inc(e)
 
 template nodeSetOp(a, b: PNode, op: expr) {.dirty.} = 
   var x, y: TBitSet
@@ -124,10 +124,10 @@ template nodeSetOp(a, b: PNode, op: expr) {.dirty.} =
   op(x, y)
   result = toTreeSet(x, a.typ, a.info)
 
-proc unionSets(a, b: PNode): PNode = nodeSetOp(a, b, BitSetUnion)
-proc diffSets(a, b: PNode): PNode = nodeSetOp(a, b, BitSetDiff)
-proc intersectSets(a, b: PNode): PNode = nodeSetOp(a, b, BitSetIntersect)
-proc symdiffSets(a, b: PNode): PNode = nodeSetOp(a, b, BitSetSymDiff)
+proc unionSets(a, b: PNode): PNode = nodeSetOp(a, b, bitSetUnion)
+proc diffSets(a, b: PNode): PNode = nodeSetOp(a, b, bitSetDiff)
+proc intersectSets(a, b: PNode): PNode = nodeSetOp(a, b, bitSetIntersect)
+proc symdiffSets(a, b: PNode): PNode = nodeSetOp(a, b, bitSetSymDiff)
 
 proc containsSets(a, b: PNode): bool = 
   var x, y: TBitSet
@@ -156,11 +156,11 @@ proc cardSet(s: PNode): BiggestInt =
       result = result + getOrdValue(s.sons[i].sons[1]) -
           getOrdValue(s.sons[i].sons[0]) + 1
     else: 
-      Inc(result)
+      inc(result)
   
-proc SetHasRange(s: PNode): bool = 
+proc setHasRange(s: PNode): bool = 
   if s.kind != nkCurly:
-    InternalError(s.info, "SetHasRange")
+    internalError(s.info, "SetHasRange")
     return false
   for i in countup(0, sonsLen(s) - 1): 
     if s.sons[i].kind == nkRange: 
diff --git a/compiler/options.nim b/compiler/options.nim
index d4122c7b2..4f642e626 100644
--- a/compiler/options.nim
+++ b/compiler/options.nim
@@ -111,6 +111,7 @@ var
   gDirtyBufferIdx* = 0'i32    # indicates the fileIdx of the dirty version of
                               # the tracked source X, saved by the CAAS client.
   gDirtyOriginalIdx* = 0'i32  # the original source file of the dirtified buffer.
+  gNoBabelPath* = false
 
 proc importantComments*(): bool {.inline.} = gCmd in {cmdDoc, cmdIdeTools}
 proc usesNativeGC*(): bool {.inline.} = gSelectedGC >= gcRefc
@@ -142,7 +143,7 @@ const
 # additional configuration variables:
 var
   gConfigVars* = newStringTable(modeStyleInsensitive)
-  gDllOverrides = newStringtable(modeCaseInsensitive)
+  gDllOverrides = newStringTable(modeCaseInsensitive)
   libpath* = ""
   gProjectName* = "" # holds a name like 'nimrod'
   gProjectPath* = "" # holds a path like /home/alice/projects/nimrod/compiler/
@@ -158,8 +159,6 @@ var
 
 const oKeepVariableNames* = true
 
-const oUseLateInstantiation* = false
-
 proc mainCommandArg*: string =
   ## This is intended for commands like check or parse
   ## which will work on the main project file unless
@@ -184,7 +183,7 @@ proc getOutFile*(filename, ext: string): string =
   
 proc getPrefixDir*(): string = 
   ## gets the application directory
-  result = SplitPath(getAppDir()).head
+  result = splitPath(getAppDir()).head
 
 proc canonicalizePath*(path: string): string =
   result = path.expandFilename
@@ -192,16 +191,16 @@ proc canonicalizePath*(path: string): string =
 
 proc shortenDir*(dir: string): string = 
   ## returns the interesting part of a dir
-  var prefix = getPrefixDir() & dirSep
+  var prefix = getPrefixDir() & DirSep
   if startsWith(dir, prefix): 
     return substr(dir, len(prefix))
-  prefix = gProjectPath & dirSep
+  prefix = gProjectPath & DirSep
   if startsWith(dir, prefix):
     return substr(dir, len(prefix))
   result = dir
 
 proc removeTrailingDirSep*(path: string): string = 
-  if (len(path) > 0) and (path[len(path) - 1] == dirSep): 
+  if (len(path) > 0) and (path[len(path) - 1] == DirSep): 
     result = substr(path, 0, len(path) - 2)
   else: 
     result = path
@@ -213,9 +212,9 @@ proc getGeneratedPath: string =
 proc getPackageName*(path: string): string =
   var q = 1
   var b = 0
-  if path[len(path)-1] in {dirsep, altsep}: q = 2
+  if path[len(path)-1] in {DirSep, AltSep}: q = 2
   for i in countdown(len(path)-q, 0):
-    if path[i] in {dirsep, altsep}:
+    if path[i] in {DirSep, AltSep}:
       if b == 0: b = i
       else:
         let x = path.substr(i+1, b-1)
@@ -254,15 +253,15 @@ proc completeGeneratedFilePath*(f: string, createSubDir: bool = true): string =
   result = joinPath(subdir, tail)
   #echo "completeGeneratedFilePath(", f, ") = ", result
 
-iterator iterSearchPath*(SearchPaths: TLinkedList): string = 
-  var it = PStrEntry(SearchPaths.head)
+iterator iterSearchPath*(searchPaths: TLinkedList): string = 
+  var it = PStrEntry(searchPaths.head)
   while it != nil:
     yield it.data
-    it = PStrEntry(it.Next)
+    it = PStrEntry(it.next)
 
 proc rawFindFile(f: string): string =
-  for it in iterSearchPath(SearchPaths):
-    result = JoinPath(it, f)
+  for it in iterSearchPath(searchPaths):
+    result = joinPath(it, f)
     if existsFile(result):
       return result.canonicalizePath
   result = ""
@@ -270,14 +269,14 @@ proc rawFindFile(f: string): string =
 proc rawFindFile2(f: string): string =
   var it = PStrEntry(lazyPaths.head)
   while it != nil:
-    result = JoinPath(it.data, f)
+    result = joinPath(it.data, f)
     if existsFile(result):
       bringToFront(lazyPaths, it)
       return result.canonicalizePath
-    it = PStrEntry(it.Next)
+    it = PStrEntry(it.next)
   result = ""
 
-proc FindFile*(f: string): string {.procvar.} = 
+proc findFile*(f: string): string {.procvar.} = 
   result = f.rawFindFile
   if result.len == 0:
     result = f.toLower.rawFindFile
@@ -288,11 +287,11 @@ proc FindFile*(f: string): string {.procvar.} =
 
 proc findModule*(modulename, currentModule: string): string =
   # returns path to module
-  let m = addFileExt(modulename, nimExt)
+  let m = addFileExt(modulename, NimExt)
   let currentPath = currentModule.splitFile.dir
   result = currentPath / m
   if not existsFile(result):
-    result = FindFile(m)
+    result = findFile(m)
 
 proc libCandidates*(s: string, dest: var seq[string]) = 
   var le = strutils.find(s, '(')
@@ -319,7 +318,7 @@ proc inclDynlibOverride*(lib: string) =
 proc isDynlibOverride*(lib: string): bool =
   result = gDllOverrides.hasKey(lib.canonDynlibName)
 
-proc binaryStrSearch*(x: openarray[string], y: string): int = 
+proc binaryStrSearch*(x: openArray[string], y: string): int = 
   var a = 0
   var b = len(x) - 1
   while a <= b: 
diff --git a/compiler/parampatterns.nim b/compiler/parampatterns.nim
index 283f83906..e94068776 100644
--- a/compiler/parampatterns.nim
+++ b/compiler/parampatterns.nim
@@ -42,7 +42,7 @@ const
   MaxStackSize* = 64 ## max required stack size by the VM
 
 proc patternError(n: PNode) = 
-  LocalError(n.info, errIllFormedAstX, renderTree(n, {renderNoComments}))
+  localError(n.info, errIllFormedAstX, renderTree(n, {renderNoComments}))
 
 proc add(code: var TPatternCode, op: TOpcode) {.inline.} =
   add(code, chr(ord(op)))
@@ -97,14 +97,14 @@ proc compileConstraints(p: PNode, result: var TPatternCode) =
     of "nosideeffect": result.add(ppNoSideEffect)
     else:
       # check all symkinds:
-      InternalAssert int(high(TSymKind)) < 255
+      internalAssert int(high(TSymKind)) < 255
       for i in low(TSymKind)..high(TSymKind):
         if cmpIgnoreStyle(($i).substr(2), spec) == 0:
           result.add(ppSymKind)
           result.add(chr(i.ord))
           return
       # check all nodekinds:
-      InternalAssert int(high(TNodeKind)) < 255
+      internalAssert int(high(TNodeKind)) < 255
       for i in low(TNodeKind)..high(TNodeKind):
         if cmpIgnoreStyle($i, spec) == 0:
           result.add(ppNodeKind)
@@ -124,8 +124,8 @@ proc semNodeKindConstraints*(p: PNode): PNode =
   if p.len >= 2:
     for i in 1.. <p.len:
       compileConstraints(p.sons[i], result.strVal)
-    if result.strVal.len > maxStackSize-1:
-      InternalError(p.info, "parameter pattern too complex")
+    if result.strVal.len > MaxStackSize-1:
+      internalError(p.info, "parameter pattern too complex")
   else:
     patternError(p)
   result.strVal.add(ppEof)
@@ -216,12 +216,12 @@ proc isAssignable*(owner: PSym, n: PNode): TAssignableResult =
   of nkObjUpConv, nkObjDownConv, nkCheckedFieldExpr: 
     result = isAssignable(owner, n.sons[0])
   else:
-    nil
+    discard
 
 proc matchNodeKinds*(p, n: PNode): bool =
   # matches the parameter constraint 'p' against the concrete AST 'n'. 
   # Efficiency matters here.
-  var stack {.noinit.}: array[0..maxStackSize, bool]
+  var stack {.noinit.}: array[0..MaxStackSize, bool]
   # empty patterns are true:
   stack[0] = true
   var sp = 1
diff --git a/compiler/parser.nim b/compiler/parser.nim
index fd51b04ec..3765557b9 100644
--- a/compiler/parser.nim
+++ b/compiler/parser.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -18,10 +18,10 @@
 # In fact the grammar is generated from this file:
 when isMainModule:
   import pegs
-  var outp = open("compiler/grammar.txt", fmWrite)
+  var outp = open("doc/grammar.txt", fmWrite)
   for line in lines("compiler/parser.nim"):
     if line =~ peg" \s* '#| ' {.*}":
-      outp.writeln matches[0]
+      outp.write matches[0], "\L"
   outp.close
 
 import
@@ -31,11 +31,12 @@ type
   TParser*{.final.} = object  # a TParser object represents a module that
                               # is being parsed
     currInd: int              # current indentation
-    firstTok: bool
+    firstTok, strongSpaces: bool
     lex*: TLexer              # the lexer that is used for parsing
     tok*: TToken              # the current token
+    inPragma: int
 
-proc ParseAll*(p: var TParser): PNode
+proc parseAll*(p: var TParser): PNode
 proc openParser*(p: var TParser, filename: string, inputstream: PLLStream)
 proc closeParser*(p: var TParser)
 proc parseTopLevelStmt*(p: var TParser): PNode
@@ -59,9 +60,9 @@ proc newFloatNodeP*(kind: TNodeKind, floatVal: BiggestFloat, p: TParser): PNode
 proc newStrNodeP*(kind: TNodeKind, strVal: string, p: TParser): PNode
 proc newIdentNodeP*(ident: PIdent, p: TParser): PNode
 proc expectIdentOrKeyw*(p: TParser)
-proc ExpectIdent*(p: TParser)
+proc expectIdent*(p: TParser)
 proc parLineInfo*(p: TParser): TLineInfo
-proc Eat*(p: var TParser, TokType: TTokType)
+proc eat*(p: var TParser, tokType: TTokType)
 proc skipInd*(p: var TParser)
 proc optPar*(p: var TParser)
 proc optInd*(p: var TParser, n: PNode)
@@ -75,17 +76,17 @@ proc parseCase(p: var TParser): PNode
 proc getTok(p: var TParser) = 
   rawGetTok(p.lex, p.tok)
 
-proc OpenParser*(p: var TParser, fileIdx: int32, inputStream: PLLStream) =
+proc openParser*(p: var TParser, fileIdx: int32, inputStream: PLLStream) =
   initToken(p.tok)
-  OpenLexer(p.lex, fileIdx, inputstream)
+  openLexer(p.lex, fileIdx, inputStream)
   getTok(p)                   # read the first token
   p.firstTok = true
 
-proc OpenParser*(p: var TParser, filename: string, inputStream: PLLStream) =
-  openParser(p, filename.fileInfoIdx, inputStream)
+proc openParser*(p: var TParser, filename: string, inputStream: PLLStream) =
+  openParser(p, filename.fileInfoIdx, inputstream)
 
-proc CloseParser(p: var TParser) = 
-  CloseLexer(p.lex)
+proc closeParser(p: var TParser) = 
+  closeLexer(p.lex)
 
 proc parMessage(p: TParser, msg: TMsgKind, arg: string = "") = 
   lexMessage(p.lex, msg, arg)
@@ -135,12 +136,12 @@ proc expectIdentOrKeyw(p: TParser) =
   if p.tok.tokType != tkSymbol and not isKeyword(p.tok.tokType):
     lexMessage(p.lex, errIdentifierExpected, prettyTok(p.tok))
   
-proc ExpectIdent(p: TParser) =
+proc expectIdent(p: TParser) =
   if p.tok.tokType != tkSymbol:
     lexMessage(p.lex, errIdentifierExpected, prettyTok(p.tok))
   
-proc Eat(p: var TParser, TokType: TTokType) =
-  if p.tok.TokType == TokType: getTok(p)
+proc eat(p: var TParser, tokType: TTokType) =
+  if p.tok.tokType == tokType: getTok(p)
   else: lexMessage(p.lex, errTokenExpected, TokTypeToStr[tokType])
   
 proc parLineInfo(p: TParser): TLineInfo =
@@ -185,10 +186,10 @@ proc relevantOprChar(ident: PIdent): char {.inline.} =
   if result == '\\' and L > 1:
     result = ident.s[1]
 
-proc IsSigilLike(tok: TToken): bool {.inline.} =
+proc isSigilLike(tok: TToken): bool {.inline.} =
   result = tok.tokType == tkOpr and relevantOprChar(tok.ident) == '@'
 
-proc IsLeftAssociative(tok: TToken): bool {.inline.} =
+proc isLeftAssociative(tok: TToken): bool {.inline.} =
   result = tok.tokType != tkOpr or relevantOprChar(tok.ident) != '^'
 
 proc getPrecedence(tok: TToken): int = 
@@ -211,7 +212,7 @@ proc getPrecedence(tok: TToken): int =
     of '?': result = 2
     else: considerAsgn(2)
   of tkDiv, tkMod, tkShl, tkShr: result = 9
-  of tkIn, tkNotIn, tkIs, tkIsNot, tkNot, tkOf, tkAs: result = 5
+  of tkIn, tkNotin, tkIs, tkIsnot, tkNot, tkOf, tkAs: result = 5
   of tkDotDot: result = 6
   of tkAnd: result = 4
   of tkOr, tkXor: result = 3
@@ -427,7 +428,7 @@ proc parseCast(p: var TParser): PNode =
 
 proc setBaseFlags(n: PNode, base: TNumericalBase) = 
   case base
-  of base10: nil
+  of base10: discard
   of base2: incl(n.flags, nfBase2)
   of base8: incl(n.flags, nfBase8)
   of base16: incl(n.flags, nfBase16)
@@ -455,7 +456,7 @@ proc simpleExpr(p: var TParser, mode = pmNormal): PNode
 
 proc semiStmtList(p: var TParser, result: PNode) =
   result.add(complexOrSimpleStmt(p))
-  while p.tok.tokType == tkSemicolon:
+  while p.tok.tokType == tkSemiColon:
     getTok(p)
     optInd(p, result)
     result.add(complexOrSimpleStmt(p))
@@ -482,7 +483,7 @@ proc parsePar(p: var TParser): PNode =
     # XXX 'bind' used to be an expression, so we exclude it here;
     # tests/reject/tbind2 fails otherwise.
     semiStmtList(p, result)
-  elif p.tok.tokType == tkSemicolon:
+  elif p.tok.tokType == tkSemiColon:
     # '(;' enforces 'stmt' context:
     getTok(p)
     optInd(p, result)
@@ -498,7 +499,7 @@ proc parsePar(p: var TParser): PNode =
       asgn.sons[0] = a
       asgn.sons[1] = b
       result.add(asgn)
-    elif p.tok.tokType == tkSemicolon:
+    elif p.tok.tokType == tkSemiColon:
       # stmt context:
       result.add(a)
       semiStmtList(p, result)
@@ -518,14 +519,14 @@ proc parsePar(p: var TParser): PNode =
   eat(p, tkParRi)
 
 proc identOrLiteral(p: var TParser, mode: TPrimaryMode): PNode = 
+  #| literal = | INT_LIT | INT8_LIT | INT16_LIT | INT32_LIT | INT64_LIT
+  #|           | UINT_LIT | UINT8_LIT | UINT16_LIT | UINT32_LIT | UINT64_LIT
+  #|           | FLOAT_LIT | FLOAT32_LIT | FLOAT64_LIT
+  #|           | STR_LIT | RSTR_LIT | TRIPLESTR_LIT
+  #|           | CHAR_LIT
+  #|           | NIL
   #| generalizedLit = GENERALIZED_STR_LIT | GENERALIZED_TRIPLESTR_LIT
-  #| identOrLiteral = generalizedLit | symbol 
-  #|                | INT_LIT | INT8_LIT | INT16_LIT | INT32_LIT | INT64_LIT
-  #|                | UINT_LIT | UINT8_LIT | UINT16_LIT | UINT32_LIT | UINT64_LIT
-  #|                | FLOAT_LIT | FLOAT32_LIT | FLOAT64_LIT
-  #|                | STR_LIT | RSTR_LIT | TRIPLESTR_LIT
-  #|                | CHAR_LIT
-  #|                | NIL
+  #| identOrLiteral = generalizedLit | symbol | literal
   #|                | par | arrayConstr | setOrTableConstr
   #|                | castExpr
   #| tupleConstr = '(' optInd (exprColonEqExpr comma?)* optPar ')'
@@ -634,12 +635,15 @@ proc namedParams(p: var TParser, callee: PNode,
   addSon(result, a)
   exprColonEqExprListAux(p, endTok, result)
 
+proc parseMacroColon(p: var TParser, x: PNode): PNode
 proc primarySuffix(p: var TParser, r: PNode): PNode =
   #| primarySuffix = '(' (exprColonEqExpr comma?)* ')' doBlocks?
   #|               | doBlocks
   #|               | '.' optInd ('type' | 'addr' | symbol) generalizedLit?
   #|               | '[' optInd indexExprList optPar ']'
   #|               | '{' optInd indexExprList optPar '}'
+  #|               | &( '`'|IDENT|literal|'cast') expr ^+ ',' # command syntax
+  #|                      (doBlock | macroColon)?
   result = r
   while p.tok.indent < 0:
     case p.tok.tokType
@@ -661,8 +665,27 @@ proc primarySuffix(p: var TParser, r: PNode): PNode =
       result = namedParams(p, result, nkBracketExpr, tkBracketRi)
     of tkCurlyLe:
       result = namedParams(p, result, nkCurlyExpr, tkCurlyRi)
-    else: break
-
+    of tkSymbol, tkAccent, tkIntLit..tkCharLit, tkNil, tkCast:
+      if p.inPragma == 0:
+        # actually parsing {.push hints:off.} as {.push(hints:off).} is a sweet
+        # solution, but pragmas.nim can't handle that
+        let a = result
+        result = newNodeP(nkCommand, p)
+        addSon(result, a)
+        while p.tok.tokType != tkEof:
+          let a = parseExpr(p)
+          addSon(result, a)
+          if p.tok.tokType != tkComma: break
+          getTok(p)
+          optInd(p, a)
+        if p.tok.tokType == tkDo:
+          parseDoBlocks(p, result)
+        else:
+          result = parseMacroColon(p, result)
+      break
+    else:
+      break
+    
 proc primary(p: var TParser, mode: TPrimaryMode): PNode
 
 proc simpleExprAux(p: var TParser, limit: int, mode: TPrimaryMode): PNode =
@@ -672,7 +695,7 @@ proc simpleExprAux(p: var TParser, limit: int, mode: TPrimaryMode): PNode =
   let modeB = if mode == pmTypeDef: pmTypeDesc else: mode
   # the operator itself must not start on a new line:
   while opPrec >= limit and p.tok.indent < 0:
-    var leftAssoc = ord(IsLeftAssociative(p.tok))
+    var leftAssoc = ord(isLeftAssociative(p.tok))
     var a = newNodeP(nkInfix, p)
     var opNode = newIdentNodeP(p.tok.ident, p) # skip operator:
     getTok(p)
@@ -713,6 +736,7 @@ proc parseIfExpr(p: var TParser, kind: TNodeKind): PNode =
 proc parsePragma(p: var TParser): PNode =
   #| pragma = '{.' optInd (exprColonExpr comma?)* optPar ('.}' | '}')
   result = newNodeP(nkPragma, p)
+  inc p.inPragma
   getTok(p)
   optInd(p, result)
   while p.tok.tokType notin {tkCurlyDotRi, tkCurlyRi, tkEof}:
@@ -724,6 +748,7 @@ proc parsePragma(p: var TParser): PNode =
   optPar(p)
   if p.tok.tokType in {tkCurlyDotRi, tkCurlyRi}: getTok(p)
   else: parMessage(p, errTokenExpected, ".}")
+  dec p.inPragma
   
 proc identVis(p: var TParser): PNode = 
   #| identVis = symbol opr?  # postfix position
@@ -798,7 +823,7 @@ proc parseTuple(p: var TParser, indentAllowed = false): PNode =
     while p.tok.tokType in {tkSymbol, tkAccent}:
       var a = parseIdentColonEquals(p, {})
       addSon(result, a)
-      if p.tok.tokType notin {tkComma, tkSemicolon}: break
+      if p.tok.tokType notin {tkComma, tkSemiColon}: break
       getTok(p)
       skipComment(p, a)
     optPar(p)
@@ -840,13 +865,13 @@ proc parseParamList(p: var TParser, retColon = true): PNode =
         parMessage(p, errTokenExpected, ")")
         break 
       addSon(result, a)
-      if p.tok.tokType notin {tkComma, tkSemicolon}: break 
+      if p.tok.tokType notin {tkComma, tkSemiColon}: break 
       getTok(p)
       skipComment(p, a)
     optPar(p)
     eat(p, tkParRi)
   let hasRet = if retColon: p.tok.tokType == tkColon
-               else: p.tok.tokType == tkOpr and IdentEq(p.tok.ident, "->")
+               else: p.tok.tokType == tkOpr and identEq(p.tok.ident, "->")
   if hasRet and p.tok.indent < 0:
     getTok(p)
     optInd(p, result)
@@ -941,7 +966,7 @@ proc primary(p: var TParser, mode: TPrimaryMode): PNode =
   #|         / 'static' primary
   #|         / 'bind' primary
   if isOperator(p.tok):
-    let isSigil = IsSigilLike(p.tok)
+    let isSigil = isSigilLike(p.tok)
     result = newNodeP(nkPrefix, p)
     var a = newIdentNodeP(p.tok.ident, p)
     addSon(result, a)
@@ -965,14 +990,19 @@ 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 false:
+      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})
+      if result.kind == nkLambda: result.kind = nkIteratorDef
+      else: result.kind = nkIteratorTy
   of tkEnum:
     if mode == pmTypeDef:
       result = parseEnum(p)
@@ -995,9 +1025,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)
@@ -1014,6 +1048,7 @@ proc parseTypeDesc(p: var TParser): PNode =
 
 proc parseTypeDefAux(p: var TParser): PNode = 
   #| typeDefAux = simpleExpr
+  #|            | 'generic' typeClass
   result = simpleExpr(p, pmTypeDef)
 
 proc makeCall(n: PNode): PNode =
@@ -1023,15 +1058,50 @@ proc makeCall(n: PNode): PNode =
     result = newNodeI(nkCall, n.info)
     result.add n
 
+proc parseMacroColon(p: var TParser, x: PNode): PNode =
+  #| macroColon = ':' stmt? ( IND{=} 'of' exprList ':' stmt 
+  #|                        | IND{=} 'elif' expr ':' stmt
+  #|                        | IND{=} 'except' exprList ':' stmt
+  #|                        | IND{=} 'else' ':' stmt )*
+  result = x
+  if p.tok.tokType == tkColon and p.tok.indent < 0:
+    result = makeCall(result)
+    getTok(p)
+    skipComment(p, result)
+    if p.tok.tokType notin {tkOf, tkElif, tkElse, tkExcept}:
+      let body = parseStmt(p)
+      addSon(result, newProcNode(nkDo, body.info, body))
+    while sameInd(p):
+      var b: PNode
+      case p.tok.tokType
+      of tkOf:
+        b = newNodeP(nkOfBranch, p)
+        exprList(p, tkColon, b)
+      of tkElif: 
+        b = newNodeP(nkElifBranch, p)
+        getTok(p)
+        optInd(p, b)
+        addSon(b, parseExpr(p))
+        eat(p, tkColon)
+      of tkExcept: 
+        b = newNodeP(nkExceptBranch, p)
+        exprList(p, tkColon, b)
+        skipComment(p, b)
+      of tkElse: 
+        b = newNodeP(nkElse, p)
+        getTok(p)
+        eat(p, tkColon)
+      else: break 
+      addSon(b, parseStmt(p))
+      addSon(result, b)
+      if b.kind == nkElse: break
+
 proc parseExprStmt(p: var TParser): PNode = 
   #| exprStmt = simpleExpr
   #|          (( '=' optInd expr )
   #|          / ( expr ^+ comma
   #|              doBlocks
-  #|               / ':' stmt? ( IND{=} 'of' exprList ':' stmt 
-  #|                           | IND{=} 'elif' expr ':' stmt
-  #|                           | IND{=} 'except' exprList ':' stmt
-  #|                           | IND{=} 'else' ':' stmt )*
+  #|               / macroColon
   #|            ))?
   var a = simpleExpr(p)
   if p.tok.tokType == tkEquals: 
@@ -1056,37 +1126,7 @@ proc parseExprStmt(p: var TParser): PNode =
       result = makeCall(result)
       parseDoBlocks(p, result)
       return result
-    if p.tok.tokType == tkColon and p.tok.indent < 0:
-      result = makeCall(result)
-      getTok(p)
-      skipComment(p, result)
-      if p.tok.TokType notin {tkOf, tkElif, tkElse, tkExcept}:
-        let body = parseStmt(p)
-        addSon(result, newProcNode(nkDo, body.info, body))
-      while sameInd(p):
-        var b: PNode
-        case p.tok.tokType
-        of tkOf:
-          b = newNodeP(nkOfBranch, p)
-          exprList(p, tkColon, b)
-        of tkElif: 
-          b = newNodeP(nkElifBranch, p)
-          getTok(p)
-          optInd(p, b)
-          addSon(b, parseExpr(p))
-          eat(p, tkColon)
-        of tkExcept: 
-          b = newNodeP(nkExceptBranch, p)
-          exprList(p, tkColon, b)
-          skipComment(p, b)
-        of tkElse: 
-          b = newNodeP(nkElse, p)
-          getTok(p)
-          eat(p, tkColon)
-        else: break 
-        addSon(b, parseStmt(p))
-        addSon(result, b)
-        if b.kind == nkElse: break
+    result = parseMacroColon(p, result)
 
 proc parseModuleName(p: var TParser, kind: TNodeKind): PNode =
   result = parseExpr(p)
@@ -1169,8 +1209,7 @@ proc parseReturnOrRaise(p: var TParser, kind: TNodeKind): PNode =
   if p.tok.tokType == tkComment:
     skipComment(p, result)
     addSon(result, ast.emptyNode)
-  elif p.tok.indent >= 0 and p.tok.indent <= p.currInd or
-      p.tok.tokType == tkEof:
+  elif p.tok.indent >= 0 and p.tok.indent <= p.currInd or not isExprStart(p):
     # NL terminates:
     addSon(result, ast.emptyNode)
   else:
@@ -1378,7 +1417,7 @@ proc parseGenericParamList(p: var TParser): PNode =
   while p.tok.tokType in {tkSymbol, tkAccent}: 
     var a = parseGenericParam(p)
     addSon(result, a)
-    if p.tok.tokType notin {tkComma, tkSemicolon}: break 
+    if p.tok.tokType notin {tkComma, tkSemiColon}: break 
     getTok(p)
     skipComment(p, a)
   optPar(p)
@@ -1633,12 +1672,15 @@ proc parseTypeClassParam(p: var TParser): PNode =
     result = p.parseSymbol
 
 proc parseTypeClass(p: var TParser): PNode =
+  #| typeClassParam = ('var')? symbol
+  #| typeClass = typeClassParam ^* ',' (pragma)? ('of' typeDesc ^* ',')?
+  #|               &IND{>} stmt
   result = newNodeP(nkTypeClassTy, p)
   getTok(p)
   var args = newNode(nkArgList)
   addSon(result, args)
   addSon(args, p.parseTypeClassParam)
-  while p.tok.TokType == tkComma:
+  while p.tok.tokType == tkComma:
     getTok(p)
     addSon(args, p.parseTypeClassParam)
   if p.tok.tokType == tkCurlyDotLe and p.validInd:
@@ -1809,8 +1851,8 @@ proc parseStmt(p: var TParser): PNode =
     withInd(p):
       while true:
         if p.tok.indent == p.currInd:
-          nil
-        elif p.tok.tokType == tkSemicolon:
+          discard
+        elif p.tok.tokType == tkSemiColon:
           getTok(p)
           if p.tok.indent < 0 or p.tok.indent == p.currInd: discard
           else: break
@@ -1818,7 +1860,7 @@ proc parseStmt(p: var TParser): PNode =
           if p.tok.indent > p.currInd:
             parMessage(p, errInvalidIndentation)
           break
-        if p.tok.toktype in {tkCurlyRi, tkParRi, tkCurlyDotRi, tkBracketRi}:
+        if p.tok.tokType in {tkCurlyRi, tkParRi, tkCurlyDotRi, tkBracketRi}:
           # XXX this ensures tnamedparamanonproc still compiles;
           # deprecate this syntax later
           break
@@ -1842,7 +1884,7 @@ proc parseStmt(p: var TParser): PNode =
         let a = simpleStmt(p)
         if a.kind == nkEmpty: parMessage(p, errExprExpected, p.tok)
         result.add(a)
-        if p.tok.tokType != tkSemicolon: break
+        if p.tok.tokType != tkSemiColon: break
         getTok(p)
   
 proc parseAll(p: var TParser): PNode = 
@@ -1862,11 +1904,11 @@ proc parseTopLevelStmt(p: var TParser): PNode =
   result = ast.emptyNode
   while true:
     if p.tok.indent != 0: 
-      if p.firstTok and p.tok.indent < 0: nil
+      if p.firstTok and p.tok.indent < 0: discard
       else: parMessage(p, errInvalidIndentation)
     p.firstTok = false
     case p.tok.tokType
-    of tkSemicolon:
+    of tkSemiColon:
       getTok(p)
       if p.tok.indent <= 0: discard
       else: parMessage(p, errInvalidIndentation)
@@ -1877,11 +1919,11 @@ proc parseTopLevelStmt(p: var TParser): PNode =
       break
 
 proc parseString(s: string, filename: string = "", line: int = 0): PNode =
-  var stream = LLStreamOpen(s)
+  var stream = llStreamOpen(s)
   stream.lineOffset = line
 
   var parser: TParser
-  OpenParser(parser, filename, stream)
+  openParser(parser, filename, stream)
 
   result = parser.parseAll
-  CloseParser(parser)
+  closeParser(parser)
diff --git a/compiler/pas2nim/pas2nim.nim b/compiler/pas2nim/pas2nim.nim
index ce5eb5c1a..d10028167 100644
--- a/compiler/pas2nim/pas2nim.nim
+++ b/compiler/pas2nim/pas2nim.nim
@@ -26,7 +26,7 @@ Options:
 """
 
 proc main(infile, outfile: string, flags: set[TParserFlag]) =
-  var stream = LLStreamOpen(infile, fmRead)
+  var stream = llStreamOpen(infile, fmRead)
   if stream == nil: rawMessage(errCannotOpenFile, infile)
   var p: TParser
   openParser(p, infile, stream, flags)
diff --git a/compiler/pas2nim/paslex.nim b/compiler/pas2nim/paslex.nim
index 94e664832..67473e71f 100644
--- a/compiler/pas2nim/paslex.nim
+++ b/compiler/pas2nim/paslex.nim
@@ -78,7 +78,7 @@ type
 
 
 proc getTok*(L: var TLexer, tok: var TToken)
-proc PrintTok*(tok: TToken)
+proc printTok*(tok: TToken)
 proc `$`*(tok: TToken): string
 # implementation
 
@@ -109,17 +109,17 @@ proc getLineInfo*(L: TLexer): TLineInfo =
   result = newLineInfo(L.filename, L.linenumber, getColNumber(L, L.bufpos))
 
 proc lexMessage*(L: TLexer, msg: TMsgKind, arg = "") =
-  msgs.GlobalError(getLineInfo(L), msg, arg)
+  msgs.globalError(getLineInfo(L), msg, arg)
 
 proc lexMessagePos(L: var TLexer, msg: TMsgKind, pos: int, arg = "") =
   var info = newLineInfo(L.filename, L.linenumber, pos - L.lineStart)
-  msgs.GlobalError(info, msg, arg)
+  msgs.globalError(info, msg, arg)
 
-proc TokKindToStr*(k: TTokKind): string =
+proc tokKindToStr*(k: TTokKind): string =
   case k
   of pxEof: result = "[EOF]"
   of firstKeyword..lastKeyword:
-    result = keywords[ord(k)-ord(firstKeyword)]
+    result = Keywords[ord(k)-ord(firstKeyword)]
   of pxInvalid, pxComment, pxStrLit: result = "string literal"
   of pxCommand: result = "{@"
   of pxAmp: result = "{&"
@@ -160,9 +160,9 @@ proc `$`(tok: TToken): string =
   of pxSymbol: result = tok.ident.s
   of pxIntLit, pxInt64Lit: result = $tok.iNumber
   of pxFloatLit: result = $tok.fNumber
-  else: result = TokKindToStr(tok.xkind)
+  else: result = tokKindToStr(tok.xkind)
 
-proc PrintTok(tok: TToken) =
+proc printTok(tok: TToken) =
   writeln(stdout, $tok)
 
 proc setKeyword(L: var TLexer, tok: var TToken) =
@@ -177,12 +177,12 @@ proc matchUnderscoreChars(L: var TLexer, tok: var TToken, chars: TCharSet) =
   while true:
     if buf[pos] in chars:
       add(tok.literal, buf[pos])
-      Inc(pos)
+      inc(pos)
     else:
       break
     if buf[pos] == '_':
       add(tok.literal, '_')
-      Inc(pos)
+      inc(pos)
   L.bufPos = pos
 
 proc isFloatLiteral(s: string): bool =
@@ -199,7 +199,7 @@ proc getNumber2(L: var TLexer, tok: var TToken) =
     inc(L.bufpos)
     return
   tok.base = base2
-  var xi: biggestInt = 0
+  var xi: BiggestInt = 0
   var bits = 0
   while true:
     case L.buf[pos]
@@ -221,7 +221,7 @@ proc getNumber2(L: var TLexer, tok: var TToken) =
 proc getNumber16(L: var TLexer, tok: var TToken) =
   var pos = L.bufpos + 1          # skip $
   tok.base = base16
-  var xi: biggestInt = 0
+  var xi: BiggestInt = 0
   var bits = 0
   while true:
     case L.buf[pos]
@@ -261,7 +261,7 @@ proc getNumber10(L: var TLexer, tok: var TToken) =
       tok.fnumber = parseFloat(tok.literal)
       tok.xkind = pxFloatLit
     else:
-      tok.iNumber = ParseInt(tok.literal)
+      tok.iNumber = parseInt(tok.literal)
       if (tok.iNumber < low(int32)) or (tok.iNumber > high(int32)):
         tok.xkind = pxInt64Lit
       else:
@@ -271,10 +271,10 @@ proc getNumber10(L: var TLexer, tok: var TToken) =
   except EOverflow:
     lexMessage(L, errNumberOutOfRange, tok.literal)
 
-proc HandleCRLF(L: var TLexer, pos: int): int =
+proc handleCRLF(L: var TLexer, pos: int): int =
   case L.buf[pos]
-  of CR: result = nimlexbase.HandleCR(L, pos)
-  of LF: result = nimlexbase.HandleLF(L, pos)
+  of CR: result = nimlexbase.handleCR(L, pos)
+  of LF: result = nimlexbase.handleLF(L, pos)
   else: result = pos
 
 proc getString(L: var TLexer, tok: var TToken) =
@@ -319,7 +319,7 @@ proc getString(L: var TLexer, tok: var TToken) =
           xi = (xi * 10) + (ord(buf[pos]) - ord('0'))
           inc(pos)
       else: lexMessage(L, errInvalidCharacterConstant)
-      if (xi <= 255): add(tok.literal, Chr(xi))
+      if (xi <= 255): add(tok.literal, chr(xi))
       else: lexMessage(L, errInvalidCharacterConstant)
     else:
       break
@@ -334,17 +334,17 @@ proc getSymbol(L: var TLexer, tok: var TToken) =
     var c = buf[pos]
     case c
     of 'a'..'z', '0'..'9', '\x80'..'\xFF':
-      h = h +% Ord(c)
+      h = h +% ord(c)
       h = h +% h shl 10
       h = h xor (h shr 6)
     of 'A'..'Z':
       c = chr(ord(c) + (ord('a') - ord('A'))) # toLower()
-      h = h +% Ord(c)
+      h = h +% ord(c)
       h = h +% h shl 10
       h = h xor (h shr 6)
     of '_': nil
     else: break
-    Inc(pos)
+    inc(pos)
   h = h +% h shl 3
   h = h xor (h shr 11)
   h = h +% h shl 15
@@ -385,7 +385,7 @@ proc scanCurlyComment(L: var TLexer, tok: var TToken) =
   while true:
     case buf[pos]
     of CR, LF:
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
       add(tok.literal, "\n#")
     of '}':
@@ -405,7 +405,7 @@ proc scanStarComment(L: var TLexer, tok: var TToken) =
   while true:
     case buf[pos]
     of CR, LF:
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
       add(tok.literal, "\n#")
     of '*':
@@ -428,9 +428,9 @@ proc skip(L: var TLexer, tok: var TToken) =
   while true:
     case buf[pos]
     of ' ', Tabulator:
-      Inc(pos)                # newline is special:
+      inc(pos)                # newline is special:
     of CR, LF:
-      pos = HandleCRLF(L, pos)
+      pos = handleCRLF(L, pos)
       buf = L.buf
     else:
       break                   # EndOfFile also leaves the loop
@@ -449,7 +449,7 @@ proc getTok(L: var TLexer, tok: var TToken) =
     case c
     of ';':
       tok.xkind = pxSemicolon
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '/':
       if L.buf[L.bufpos + 1] == '/':
         scanLineComment(L, tok)
@@ -458,12 +458,12 @@ proc getTok(L: var TLexer, tok: var TToken) =
         inc(L.bufpos)
     of ',':
       tok.xkind = pxComma
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '(':
-      Inc(L.bufpos)
+      inc(L.bufpos)
       if (L.buf[L.bufPos] == '*'):
         if (L.buf[L.bufPos + 1] == '$'):
-          Inc(L.bufpos, 2)
+          inc(L.bufpos, 2)
           skip(L, tok)
           getSymbol(L, tok)
           tok.xkind = pxStarDirLe
@@ -481,12 +481,12 @@ proc getTok(L: var TLexer, tok: var TToken) =
         tok.xkind = pxStar
     of ')':
       tok.xkind = pxParRi
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '[':
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxBracketLe
     of ']':
-      Inc(L.bufpos)
+      inc(L.bufpos)
       tok.xkind = pxBracketRi
     of '.':
       inc(L.bufpos)
@@ -496,21 +496,21 @@ proc getTok(L: var TLexer, tok: var TToken) =
       else:
         tok.xkind = pxDot
     of '{':
-      Inc(L.bufpos)
+      inc(L.bufpos)
       case L.buf[L.bufpos]
       of '$':
-        Inc(L.bufpos)
+        inc(L.bufpos)
         skip(L, tok)
         getSymbol(L, tok)
         tok.xkind = pxCurlyDirLe
       of '&':
-        Inc(L.bufpos)
+        inc(L.bufpos)
         tok.xkind = pxAmp
       of '%':
-        Inc(L.bufpos)
+        inc(L.bufpos)
         tok.xkind = pxPer
       of '@':
-        Inc(L.bufpos)
+        inc(L.bufpos)
         tok.xkind = pxCommand
       else: scanCurlyComment(L, tok)
     of '+':
@@ -554,7 +554,7 @@ proc getTok(L: var TLexer, tok: var TToken) =
       inc(L.bufpos)
     of '}':
       tok.xkind = pxCurlyDirRi
-      Inc(L.bufpos)
+      inc(L.bufpos)
     of '\'', '#':
       getString(L, tok)
     of '$':
@@ -567,4 +567,4 @@ proc getTok(L: var TLexer, tok: var TToken) =
       tok.literal = c & ""
       tok.xkind = pxInvalid
       lexMessage(L, errInvalidToken, c & " (\\" & $(ord(c)) & ')')
-      Inc(L.bufpos)
+      inc(L.bufpos)
diff --git a/compiler/pas2nim/pasparse.nim b/compiler/pas2nim/pasparse.nim
index 61d57dec3..928896338 100644
--- a/compiler/pas2nim/pasparse.nim
+++ b/compiler/pas2nim/pasparse.nim
@@ -57,7 +57,7 @@ const
     ["tbinaryfile", "tfile"], ["strstart", "0"], ["nl", "\"\\n\""],
     ["tostring", "$"]]
 
-proc ParseUnit*(p: var TParser): PNode
+proc parseUnit*(p: var TParser): PNode
 proc openParser*(p: var TParser, filename: string, inputStream: PLLStream,
                  flags: set[TParserFlag] = {})
 proc closeParser*(p: var TParser)
@@ -67,20 +67,20 @@ proc fixRecordDef*(n: var PNode)
 
 # implementation
 
-proc OpenParser(p: var TParser, filename: string, 
+proc openParser(p: var TParser, filename: string, 
                 inputStream: PLLStream, flags: set[TParserFlag] = {}) = 
-  OpenLexer(p.lex, filename, inputStream)
+  openLexer(p.lex, filename, inputStream)
   initIdTable(p.repl)
   for i in countup(low(stdReplacements), high(stdReplacements)): 
-    IdTablePut(p.repl, getIdent(stdReplacements[i][0]), 
+    idTablePut(p.repl, getIdent(stdReplacements[i][0]), 
                getIdent(stdReplacements[i][1]))
   if pfMoreReplacements in flags: 
     for i in countup(low(nimReplacements), high(nimReplacements)): 
-      IdTablePut(p.repl, getIdent(nimReplacements[i][0]), 
+      idTablePut(p.repl, getIdent(nimReplacements[i][0]), 
                  getIdent(nimReplacements[i][1]))
   p.flags = flags
   
-proc CloseParser(p: var TParser) = CloseLexer(p.lex)
+proc closeParser(p: var TParser) = closeLexer(p.lex)
 proc getTok(p: var TParser) = getTok(p.lex, p.tok)
 
 proc parMessage(p: TParser, msg: TMsgKind, arg = "") = 
@@ -98,15 +98,15 @@ proc skipCom(p: var TParser, n: PNode) =
       parMessage(p, warnCommentXIgnored, p.tok.literal)
     getTok(p)
 
-proc ExpectIdent(p: TParser) = 
+proc expectIdent(p: TParser) = 
   if p.tok.xkind != pxSymbol: 
     lexMessage(p.lex, errIdentifierExpected, $(p.tok))
   
-proc Eat(p: var TParser, xkind: TTokKind) = 
+proc eat(p: var TParser, xkind: TTokKind) = 
   if p.tok.xkind == xkind: getTok(p)
-  else: lexMessage(p.lex, errTokenExpected, TokKindToStr(xkind))
+  else: lexMessage(p.lex, errTokenExpected, tokKindToStr(xkind))
   
-proc Opt(p: var TParser, xkind: TTokKind) = 
+proc opt(p: var TParser, xkind: TTokKind) = 
   if p.tok.xkind == xkind: getTok(p)
   
 proc newNodeP(kind: TNodeKind, p: TParser): PNode = 
@@ -131,7 +131,7 @@ proc newIdentNodeP(ident: PIdent, p: TParser): PNode =
 
 proc createIdentNodeP(ident: PIdent, p: TParser): PNode = 
   result = newNodeP(nkIdent, p)
-  var x = PIdent(IdTableGet(p.repl, ident))
+  var x = PIdent(idTableGet(p.repl, ident))
   if x != nil: result.ident = x
   else: result.ident = ident
   
@@ -170,7 +170,7 @@ proc parseCommand(p: var TParser, definition: PNode = nil): PNode =
     getTok(p)
     eat(p, pxCurlyDirRi)
     result = parseExpr(p)
-    if result.kind == nkEmpty: InternalError("emptyNode modified")
+    if result.kind == nkEmpty: internalError("emptyNode modified")
     result.kind = nkCurly
   elif p.tok.ident.id == getIdent("cast").id: 
     getTok(p)
@@ -251,7 +251,7 @@ proc bracketExprList(p: var TParser, first: PNode): PNode =
       getTok(p)
       break 
     if p.tok.xkind == pxEof: 
-      parMessage(p, errTokenExpected, TokKindToStr(pxBracketRi))
+      parMessage(p, errTokenExpected, tokKindToStr(pxBracketRi))
       break 
     var a = rangeExpr(p)
     skipCom(p, a)
@@ -281,7 +281,7 @@ proc exprListAux(p: var TParser, elemKind: TNodeKind,
       getTok(p)
       break 
     if p.tok.xkind == pxEof: 
-      parMessage(p, errTokenExpected, TokKindToStr(endtok))
+      parMessage(p, errTokenExpected, tokKindToStr(endTok))
       break 
     var a = exprColonEqExpr(p, elemKind, sepTok)
     skipCom(p, a)
@@ -319,7 +319,7 @@ proc qualifiedIdentListAux(p: var TParser, endTok: TTokKind,
       getTok(p)
       break 
     if p.tok.xkind == pxEof: 
-      parMessage(p, errTokenExpected, TokKindToStr(endtok))
+      parMessage(p, errTokenExpected, tokKindToStr(endTok))
       break 
     var a = qualifiedIdent(p)
     skipCom(p, a)
@@ -584,7 +584,7 @@ proc parseIncludeDir(p: var TParser): PNode =
 proc definedExprAux(p: var TParser): PNode = 
   result = newNodeP(nkCall, p)
   addSon(result, newIdentNodeP(getIdent("defined"), p))
-  ExpectIdent(p)
+  expectIdent(p)
   addSon(result, createIdentNodeP(p.tok.ident, p))
   getTok(p)
 
@@ -753,7 +753,7 @@ proc parseCase(p: var TParser): PNode =
       while (p.tok.xkind != pxEof) and (p.tok.xkind != pxColon): 
         addSon(b, rangeExpr(p))
         opt(p, pxComma)
-        skipcom(p, b)
+        skipCom(p, b)
       eat(p, pxColon)
     skipCom(p, b)
     addSon(b, parseStmt(p))
@@ -818,7 +818,7 @@ proc parseFor(p: var TParser): PNode =
     getTok(p)
     b = parseExpr(p)
   else: 
-    parMessage(p, errTokenExpected, TokKindToStr(pxTo))
+    parMessage(p, errTokenExpected, tokKindToStr(pxTo))
   addSon(c, a)
   addSon(c, b)
   eat(p, pxDo)
@@ -915,7 +915,7 @@ proc parseCallingConvention(p: var TParser): PNode =
       getTok(p)
       opt(p, pxSemicolon)
     else: 
-      nil
+      discard
 
 proc parseRoutineSpecifiers(p: var TParser, noBody: var bool): PNode = 
   var e: PNode
@@ -1096,7 +1096,7 @@ proc parseRecordCase(p: var TParser): PNode =
       while (p.tok.xkind != pxEof) and (p.tok.xkind != pxColon): 
         addSon(b, rangeExpr(p))
         opt(p, pxComma)
-        skipcom(p, b)
+        skipCom(p, b)
       eat(p, pxColon)
     skipCom(p, b)
     c = newNodeP(nkRecList, p)
@@ -1168,7 +1168,7 @@ proc addPragmaToIdent(ident: var PNode, pragma: PNode) =
   else: 
     pragmasNode = ident.sons[1]
     if pragmasNode.kind != nkPragma: 
-      InternalError(ident.info, "addPragmaToIdent")
+      internalError(ident.info, "addPragmaToIdent")
   addSon(pragmasNode, pragma)
 
 proc parseRecordBody(p: var TParser, result, definition: PNode) = 
@@ -1183,13 +1183,13 @@ proc parseRecordBody(p: var TParser, result, definition: PNode) =
       if definition != nil: 
         addPragmaToIdent(definition.sons[0], newIdentNodeP(p.tok.ident, p))
       else: 
-        InternalError(result.info, "anonymous record is not supported")
+        internalError(result.info, "anonymous record is not supported")
       getTok(p)
     else: 
-      InternalError(result.info, "parseRecordBody")
+      internalError(result.info, "parseRecordBody")
   of pxCommand: 
     if definition != nil: addPragmaToIdent(definition.sons[0], parseCommand(p))
-    else: InternalError(result.info, "anonymous record is not supported")
+    else: internalError(result.info, "anonymous record is not supported")
   else: 
     nil
   opt(p, pxSemicolon)
@@ -1223,7 +1223,7 @@ proc parseTypeDesc(p: var TParser, definition: PNode = nil): PNode =
     getTok(p)
     if p.tok.xkind == pxCommand: 
       result = parseCommand(p)
-      if result.kind != nkTupleTy: InternalError(result.info, "parseTypeDesc")
+      if result.kind != nkTupleTy: internalError(result.info, "parseTypeDesc")
       parseRecordBody(p, result, definition)
       var a = lastSon(result)     # embed nkRecList directly into nkTupleTy
       for i in countup(0, sonsLen(a) - 1): 
@@ -1237,7 +1237,7 @@ proc parseTypeDesc(p: var TParser, definition: PNode = nil): PNode =
       if definition != nil: 
         addPragmaToIdent(definition.sons[0], newIdentNodeP(getIdent("final"), p))
       else: 
-        InternalError(result.info, "anonymous record is not supported")
+        internalError(result.info, "anonymous record is not supported")
   of pxObject: result = parseRecordOrObject(p, nkObjectTy, definition)
   of pxParLe: result = parseEnum(p)
   of pxArray: 
diff --git a/compiler/passaux.nim b/compiler/passaux.nim
index 4a85c994c..0ba9f22d0 100644
--- a/compiler/passaux.nim
+++ b/compiler/passaux.nim
@@ -19,12 +19,12 @@ proc verboseOpen(s: PSym): PPassContext =
   
 proc verboseProcess(context: PPassContext, n: PNode): PNode = 
   result = n
-  if context != nil: InternalError("logpass: context is not nil")
+  if context != nil: internalError("logpass: context is not nil")
   if gVerbosity == 3: 
     # system.nim deactivates all hints, for verbosity:3 we want the processing
     # messages nonetheless, so we activate them again unconditionally:
     incl(msgs.gNotes, hintProcessing)
-    Message(n.info, hintProcessing, $idgen.gBackendId)
+    message(n.info, hintProcessing, $idgen.gBackendId)
   
 const verbosePass* = makePass(open = verboseOpen, process = verboseProcess)
 
@@ -34,14 +34,14 @@ proc cleanUp(c: PPassContext, n: PNode): PNode =
   if optDeadCodeElim in gGlobalOptions or n == nil: return 
   case n.kind
   of nkStmtList: 
-    for i in countup(0, sonsLen(n) - 1): discard cleanup(c, n.sons[i])
+    for i in countup(0, sonsLen(n) - 1): discard cleanUp(c, n.sons[i])
   of nkProcDef, nkMethodDef: 
     if n.sons[namePos].kind == nkSym: 
       var s = n.sons[namePos].sym
       if sfDeadCodeElim notin getModule(s).flags and not astNeeded(s): 
         s.ast.sons[bodyPos] = ast.emptyNode # free the memory
   else: 
-    nil
+    discard
 
 const cleanupPass* = makePass(process = cleanUp, close = cleanUp)
 
diff --git a/compiler/passes.nim b/compiler/passes.nim
index 8d228fe9a..3dc31e7ac 100644
--- a/compiler/passes.nim
+++ b/compiler/passes.nim
@@ -30,8 +30,8 @@ type
   TPass* = tuple[open: TPassOpen, openCached: TPassOpenCached,
                  process: TPassProcess, close: TPassClose]
 
-  TPassData* = tuple[input: PNode, closeOutput: Pnode]
-  TPasses* = openarray[TPass]
+  TPassData* = tuple[input: PNode, closeOutput: PNode]
+  TPasses* = openArray[TPass]
 
 # a pass is a tuple of procedure vars ``TPass.close`` may produce additional 
 # nodes. These are passed to the other close procedures. 
@@ -169,7 +169,7 @@ proc processModule(module: PSym, stream: PLLStream, rd: PRodReader) =
     openPasses(a, module)
     if stream == nil: 
       let filename = fileIdx.toFullPath
-      s = LLStreamOpen(filename, fmRead)
+      s = llStreamOpen(filename, fmRead)
       if s == nil: 
         rawMessage(errCannotOpenFile, filename)
         return
@@ -195,7 +195,7 @@ proc processModule(module: PSym, stream: PLLStream, rd: PRodReader) =
       if s.kind != llsStdIn: break 
     closePasses(a)
     # id synchronization point for more consistent code generation:
-    IDsynchronizationPoint(1000)
+    idSynchronizationPoint(1000)
   else:
     openPassesCached(a, module, rd)
     var n = loadInitSection(rd)
diff --git a/compiler/patterns.nim b/compiler/patterns.nim
index b7792100f..d262790ab 100644
--- a/compiler/patterns.nim
+++ b/compiler/patterns.nim
@@ -40,7 +40,7 @@ proc canonKind(n: PNode): TNodeKind =
   of nkCallKinds: result = nkCall
   of nkStrLit..nkTripleStrLit: result = nkStrLit
   of nkFastAsgn: result = nkAsgn
-  else: nil
+  else: discard
 
 proc sameKinds(a, b: PNode): bool {.inline.} =
   result = a.kind == b.kind or a.canonKind == b.canonKind
@@ -87,22 +87,22 @@ proc matchChoice(c: PPatternContext, p, n: PNode): bool =
     if matches(c, p.sons[i], n): return true
 
 proc bindOrCheck(c: PPatternContext, param: PSym, n: PNode): bool =
-  var pp = GetLazy(c, param)
+  var pp = getLazy(c, param)
   if pp != nil:
     # check if we got the same pattern (already unified):
     result = sameTrees(pp, n) #matches(c, pp, n)
   elif n.kind == nkArgList or checkTypes(c, param, n):
-    PutLazy(c, param, n)
+    putLazy(c, param, n)
     result = true
 
 proc gather(c: PPatternContext, param: PSym, n: PNode) =
-  var pp = GetLazy(c, param)
+  var pp = getLazy(c, param)
   if pp != nil and pp.kind == nkArgList:
     pp.add(n)
   else:
     pp = newNodeI(nkArgList, n.info, 1)
     pp.sons[0] = n
-    PutLazy(c, param, pp)
+    putLazy(c, param, pp)
 
 proc matchNested(c: PPatternContext, p, n: PNode, rpn: bool): bool =
   # match ``op * param`` or ``op *| param``
@@ -148,7 +148,7 @@ proc matches(c: PPatternContext, p, n: PNode): bool =
     of "*": result = matchNested(c, p, n, rpn=false)
     of "**": result = matchNested(c, p, n, rpn=true)
     of "~": result = not matches(c, p.sons[1], n)
-    else: InternalError(p.info, "invalid pattern")
+    else: internalError(p.info, "invalid pattern")
     # template {add(a, `&` * b)}(a: string{noalias}, b: varargs[string]) = 
     #   add(a, b)
   elif p.kind == nkCurlyExpr:
@@ -256,7 +256,7 @@ proc applyRule*(c: PContext, s: PSym, n: PNode): PNode =
     args = newNodeI(nkArgList, n.info)
   for i in 1 .. < params.len:
     let param = params.sons[i].sym
-    let x = GetLazy(ctx, param)
+    let x = getLazy(ctx, param)
     # couldn't bind parameter:
     if isNil(x): return nil
     result.add(x)
@@ -267,7 +267,7 @@ proc applyRule*(c: PContext, s: PSym, n: PNode): PNode =
       var rs = result.sons[i]
       let param = params.sons[i].sym
       case whichAlias(param)
-      of aqNone: nil
+      of aqNone: discard
       of aqShouldAlias:
         # it suffices that it aliases for sure with *some* other param:
         var ok = false
diff --git a/compiler/pbraces.nim b/compiler/pbraces.nim
index a944fe0ab..ce6e0d9a9 100644
--- a/compiler/pbraces.nim
+++ b/compiler/pbraces.nim
@@ -10,7 +10,7 @@
 import 
   llstream, lexer, parser, idents, strutils, ast, msgs
 
-proc ParseAll*(p: var TParser): PNode = 
+proc parseAll*(p: var TParser): PNode = 
   result = nil
 
 proc parseTopLevelStmt*(p: var TParser): PNode = 
diff --git a/compiler/platform.nim b/compiler/platform.nim
index 59091b690..2e78d4fc5 100644
--- a/compiler/platform.nim
+++ b/compiler/platform.nim
@@ -185,13 +185,13 @@ var
   targetCPU*, hostCPU*: TSystemCPU
   targetOS*, hostOS*: TSystemOS
 
-proc NameToOS*(name: string): TSystemOS
-proc NameToCPU*(name: string): TSystemCPU
+proc nameToOS*(name: string): TSystemOS
+proc nameToCPU*(name: string): TSystemCPU
 
 var 
-  IntSize*: int
+  intSize*: int
   floatSize*: int
-  PtrSize*: int
+  ptrSize*: int
   tnl*: string                # target newline
 
 proc setTarget*(o: TSystemOS, c: TSystemCPU) = 
@@ -200,18 +200,18 @@ proc setTarget*(o: TSystemOS, c: TSystemCPU) =
   #echo "new Target: OS: ", o, " CPU: ", c
   targetCPU = c
   targetOS = o
-  intSize = cpu[c].intSize div 8
-  floatSize = cpu[c].floatSize div 8
-  ptrSize = cpu[c].bit div 8
-  tnl = os[o].newLine
+  intSize = CPU[c].intSize div 8
+  floatSize = CPU[c].floatSize div 8
+  ptrSize = CPU[c].bit div 8
+  tnl = OS[o].newLine
 
-proc NameToOS(name: string): TSystemOS = 
+proc nameToOS(name: string): TSystemOS = 
   for i in countup(succ(osNone), high(TSystemOS)): 
     if cmpIgnoreStyle(name, OS[i].name) == 0: 
       return i
   result = osNone
 
-proc NameToCPU(name: string): TSystemCPU = 
+proc nameToCPU(name: string): TSystemCPU = 
   for i in countup(succ(cpuNone), high(TSystemCPU)): 
     if cmpIgnoreStyle(name, CPU[i].name) == 0: 
       return i
diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim
index 6f1e7af25..d9ed50cfe 100644
--- a/compiler/pragmas.nim
+++ b/compiler/pragmas.nim
@@ -20,49 +20,49 @@ const
 
 const
   procPragmas* = {FirstCallConv..LastCallConv, wImportc, wExportc, wNodecl, 
-    wMagic, wNosideEffect, wSideEffect, wNoreturn, wDynLib, wHeader, 
-    wCompilerProc, wProcVar, wDeprecated, wVarargs, wCompileTime, wMerge, 
+    wMagic, wNosideeffect, wSideeffect, wNoreturn, wDynlib, wHeader, 
+    wCompilerproc, wProcVar, wDeprecated, wVarargs, wCompileTime, wMerge, 
     wBorrow, wExtern, wImportCompilerProc, wThread, wImportCpp, wImportObjC,
     wNoStackFrame, wError, wDiscardable, wNoInit, wDestructor, wCodegenDecl,
-    wGenSym, wInject, wRaises, wTags, wOperator, wDelegator}
+    wGensym, wInject, wRaises, wTags, wOperator, wDelegator}
   converterPragmas* = procPragmas
   methodPragmas* = procPragmas
-  templatePragmas* = {wImmediate, wDeprecated, wError, wGenSym, wInject, wDirty,
+  templatePragmas* = {wImmediate, wDeprecated, wError, wGensym, wInject, wDirty,
     wDelegator}
   macroPragmas* = {FirstCallConv..LastCallConv, wImmediate, wImportc, wExportc,
-    wNodecl, wMagic, wNosideEffect, wCompilerProc, wDeprecated, wExtern,
-    wImportcpp, wImportobjc, wError, wDiscardable, wGenSym, wInject, wDelegator}
-  iteratorPragmas* = {FirstCallConv..LastCallConv, wNosideEffect, wSideEffect, 
+    wNodecl, wMagic, wNosideeffect, wCompilerproc, wDeprecated, wExtern,
+    wImportCpp, wImportObjC, wError, wDiscardable, wGensym, wInject, wDelegator}
+  iteratorPragmas* = {FirstCallConv..LastCallConv, wNosideeffect, wSideeffect, 
     wImportc, wExportc, wNodecl, wMagic, wDeprecated, wBorrow, wExtern,
-    wImportcpp, wImportobjc, wError, wDiscardable, wGenSym, wInject, wRaises,
+    wImportCpp, wImportObjC, wError, wDiscardable, wGensym, wInject, wRaises,
     wTags, wOperator}
   exprPragmas* = {wLine}
   stmtPragmas* = {wChecks, wObjChecks, wFieldChecks, wRangechecks,
     wBoundchecks, wOverflowchecks, wNilchecks, wAssertions, wWarnings, wHints,
     wLinedir, wStacktrace, wLinetrace, wOptimization, wHint, wWarning, wError,
-    wFatal, wDefine, wUndef, wCompile, wLink, wLinkSys, wPure, wPush, wPop,
-    wBreakpoint, wWatchpoint, wPassL, wPassC, wDeadCodeElim, wDeprecated,
-    wFloatChecks, wInfChecks, wNanChecks, wPragma, wEmit, wUnroll,
+    wFatal, wDefine, wUndef, wCompile, wLink, wLinksys, wPure, wPush, wPop,
+    wBreakpoint, wWatchPoint, wPassl, wPassc, wDeadCodeElim, wDeprecated,
+    wFloatchecks, wInfChecks, wNanChecks, wPragma, wEmit, wUnroll,
     wLinearScanEnd, wPatterns, wEffects, wNoForward, wComputedGoto,
     wInjectStmt}
   lambdaPragmas* = {FirstCallConv..LastCallConv, wImportc, wExportc, wNodecl, 
-    wNosideEffect, wSideEffect, wNoreturn, wDynLib, wHeader, 
-    wDeprecated, wExtern, wThread, wImportcpp, wImportobjc, wNoStackFrame,
+    wNosideeffect, wSideeffect, wNoreturn, wDynlib, wHeader, 
+    wDeprecated, wExtern, wThread, wImportCpp, wImportObjC, wNoStackFrame,
     wRaises, wTags}
   typePragmas* = {wImportc, wExportc, wDeprecated, wMagic, wAcyclic, wNodecl, 
-    wPure, wHeader, wCompilerProc, wFinal, wSize, wExtern, wShallow, 
-    wImportcpp, wImportobjc, wError, wIncompleteStruct, wByCopy, wByRef,
-    wInheritable, wGenSym, wInject, wRequiresInit}
+    wPure, wHeader, wCompilerproc, wFinal, wSize, wExtern, wShallow, 
+    wImportCpp, wImportObjC, wError, wIncompleteStruct, wByCopy, wByRef,
+    wInheritable, wGensym, wInject, wRequiresInit}
   fieldPragmas* = {wImportc, wExportc, wDeprecated, wExtern, 
-    wImportcpp, wImportobjc, wError}
+    wImportCpp, wImportObjC, wError}
   varPragmas* = {wImportc, wExportc, wVolatile, wRegister, wThreadVar, wNodecl, 
-    wMagic, wHeader, wDeprecated, wCompilerProc, wDynLib, wExtern,
-    wImportcpp, wImportobjc, wError, wNoInit, wCompileTime, wGlobal,
-    wGenSym, wInject, wCodegenDecl}
+    wMagic, wHeader, wDeprecated, wCompilerproc, wDynlib, wExtern,
+    wImportCpp, wImportObjC, wError, wNoInit, wCompileTime, wGlobal,
+    wGensym, wInject, wCodegenDecl}
   constPragmas* = {wImportc, wExportc, wHeader, wDeprecated, wMagic, wNodecl,
-    wExtern, wImportcpp, wImportobjc, wError, wGenSym, wInject}
+    wExtern, wImportCpp, wImportObjC, wError, wGensym, wInject}
   letPragmas* = varPragmas
-  procTypePragmas* = {FirstCallConv..LastCallConv, wVarargs, wNosideEffect,
+  procTypePragmas* = {FirstCallConv..LastCallConv, wVarargs, wNosideeffect,
                       wThread, wRaises, wTags}
   allRoutinePragmas* = procPragmas + iteratorPragmas + lambdaPragmas
 
@@ -70,7 +70,7 @@ proc pragma*(c: PContext, sym: PSym, n: PNode, validPragmas: TSpecialWords)
 # implementation
 
 proc invalidPragma(n: PNode) = 
-  LocalError(n.info, errInvalidPragmaX, renderTree(n, {renderNoComments}))
+  localError(n.info, errInvalidPragmaX, renderTree(n, {renderNoComments}))
 
 proc pragmaAsm*(c: PContext, n: PNode): char = 
   result = '\0'
@@ -92,12 +92,12 @@ proc setExternName(s: PSym, extname: string) =
     # note that '{.importc.}' is transformed into '{.importc: "$1".}'
     s.loc.flags.incl(lfFullExternalName)
 
-proc MakeExternImport(s: PSym, extname: string) = 
+proc makeExternImport(s: PSym, extname: string) = 
   setExternName(s, extname)
   incl(s.flags, sfImportc)
   excl(s.flags, sfForward)
 
-proc MakeExternExport(s: PSym, extname: string) = 
+proc makeExternExport(s: PSym, extname: string) = 
   setExternName(s, extname)
   incl(s.flags, sfExportc)
 
@@ -125,7 +125,7 @@ proc newEmptyStrNode(n: PNode): PNode {.noinline.} =
 
 proc getStrLitNode(c: PContext, n: PNode): PNode =
   if n.kind != nkExprColonExpr: 
-    LocalError(n.info, errStringLiteralExpected)
+    localError(n.info, errStringLiteralExpected)
     # error correction:
     result = newEmptyStrNode(n)
   else:
@@ -133,7 +133,7 @@ proc getStrLitNode(c: PContext, n: PNode): PNode =
     case n.sons[1].kind
     of nkStrLit, nkRStrLit, nkTripleStrLit: result = n.sons[1]
     else: 
-      LocalError(n.info, errStringLiteralExpected)
+      localError(n.info, errStringLiteralExpected)
       # error correction:
       result = newEmptyStrNode(n)
 
@@ -142,12 +142,12 @@ proc expectStrLit(c: PContext, n: PNode): string =
 
 proc expectIntLit(c: PContext, n: PNode): int = 
   if n.kind != nkExprColonExpr: 
-    LocalError(n.info, errIntLiteralExpected)
+    localError(n.info, errIntLiteralExpected)
   else: 
     n.sons[1] = c.semConstExpr(c, n.sons[1])
     case n.sons[1].kind
     of nkIntLit..nkInt64Lit: result = int(n.sons[1].intVal)
-    else: LocalError(n.info, errIntLiteralExpected)
+    else: localError(n.info, errIntLiteralExpected)
 
 proc getOptionalStr(c: PContext, n: PNode, defaultStr: string): string = 
   if n.kind == nkExprColonExpr: result = expectStrLit(c, n)
@@ -160,7 +160,7 @@ proc processMagic(c: PContext, n: PNode, s: PSym) =
   #if sfSystemModule notin c.module.flags:
   #  liMessage(n.info, errMagicOnlyInSystem)
   if n.kind != nkExprColonExpr: 
-    LocalError(n.info, errStringLiteralExpected)
+    localError(n.info, errStringLiteralExpected)
     return
   var v: string
   if n.sons[1].kind == nkIdent: v = n.sons[1].ident.s
@@ -169,57 +169,57 @@ proc processMagic(c: PContext, n: PNode, s: PSym) =
     if substr($m, 1) == v: 
       s.magic = m
       break
-  if s.magic == mNone: Message(n.info, warnUnknownMagic, v)
+  if s.magic == mNone: message(n.info, warnUnknownMagic, v)
 
 proc wordToCallConv(sw: TSpecialWord): TCallingConvention = 
   # this assumes that the order of special words and calling conventions is
   # the same
   result = TCallingConvention(ord(ccDefault) + ord(sw) - ord(wNimcall))
 
-proc IsTurnedOn(c: PContext, n: PNode): bool = 
+proc isTurnedOn(c: PContext, n: PNode): bool = 
   if n.kind == nkExprColonExpr:
     let x = c.semConstBoolExpr(c, n.sons[1])
     n.sons[1] = x
     if x.kind == nkIntLit: return x.intVal != 0
-  LocalError(n.info, errOnOrOffExpected)
+  localError(n.info, errOnOrOffExpected)
 
 proc onOff(c: PContext, n: PNode, op: TOptions) = 
-  if IsTurnedOn(c, n): gOptions = gOptions + op
+  if isTurnedOn(c, n): gOptions = gOptions + op
   else: gOptions = gOptions - op
   
 proc pragmaDeadCodeElim(c: PContext, n: PNode) = 
-  if IsTurnedOn(c, n): incl(c.module.flags, sfDeadCodeElim)
+  if isTurnedOn(c, n): incl(c.module.flags, sfDeadCodeElim)
   else: excl(c.module.flags, sfDeadCodeElim)
 
 proc pragmaNoForward(c: PContext, n: PNode) =
-  if IsTurnedOn(c, n): incl(c.module.flags, sfNoForward)
+  if isTurnedOn(c, n): incl(c.module.flags, sfNoForward)
   else: excl(c.module.flags, sfNoForward)
 
 proc processCallConv(c: PContext, n: PNode) = 
   if (n.kind == nkExprColonExpr) and (n.sons[1].kind == nkIdent): 
     var sw = whichKeyword(n.sons[1].ident)
     case sw
-    of firstCallConv..lastCallConv: 
+    of FirstCallConv..LastCallConv: 
       POptionEntry(c.optionStack.tail).defaultCC = wordToCallConv(sw)
-    else: LocalError(n.info, errCallConvExpected)
+    else: localError(n.info, errCallConvExpected)
   else: 
-    LocalError(n.info, errCallConvExpected)
+    localError(n.info, errCallConvExpected)
   
 proc getLib(c: PContext, kind: TLibKind, path: PNode): PLib = 
   var it = PLib(c.libs.head)
   while it != nil: 
     if it.kind == kind: 
-      if trees.ExprStructuralEquivalent(it.path, path): return it
+      if trees.exprStructuralEquivalent(it.path, path): return it
     it = PLib(it.next)
   result = newLib(kind)
   result.path = path
-  Append(c.libs, result)
+  append(c.libs, result)
   if path.kind in {nkStrLit..nkTripleStrLit}:
-    result.isOverriden = options.isDynLibOverride(path.strVal)
+    result.isOverriden = options.isDynlibOverride(path.strVal)
 
 proc expectDynlibNode(c: PContext, n: PNode): PNode =
   if n.kind != nkExprColonExpr:
-    LocalError(n.info, errStringLiteralExpected)
+    localError(n.info, errStringLiteralExpected)
     # error correction:
     result = newEmptyStrNode(n)
   else:
@@ -229,7 +229,7 @@ proc expectDynlibNode(c: PContext, n: PNode): PNode =
     if result.kind == nkSym and result.sym.kind == skConst:
       result = result.sym.ast # look it up
     if result.typ == nil or result.typ.kind notin {tyPointer, tyString, tyProc}:
-      LocalError(n.info, errStringLiteralExpected)
+      localError(n.info, errStringLiteralExpected)
       result = newEmptyStrNode(n)
     
 proc processDynLib(c: PContext, n: PNode, sym: PSym) = 
@@ -247,7 +247,7 @@ proc processDynLib(c: PContext, n: PNode, sym: PSym) =
     # since we'll be loading the dynlib symbols dynamically, we must use
     # a calling convention that doesn't introduce custom name mangling
     # cdecl is the default - the user can override this explicitly
-    if sym.kind in RoutineKinds and sym.typ != nil and 
+    if sym.kind in routineKinds and sym.typ != nil and 
         sym.typ.callConv == ccDefault:
       sym.typ.callConv = ccCDecl
 
@@ -265,7 +265,7 @@ proc processNote(c: PContext, n: PNode) =
     of wWarning:
       var x = findStr(msgs.WarningsToStr, n.sons[0].sons[1].ident.s)
       if x >= 0: nk = TNoteKind(x + ord(warnMin))
-      else: InvalidPragma(n); return
+      else: invalidPragma(n); return
     else:
       invalidPragma(n)
       return
@@ -284,27 +284,27 @@ proc processOption(c: PContext, n: PNode): bool =
   else:
     var sw = whichKeyword(n.sons[0].ident)
     case sw
-    of wChecks: OnOff(c, n, checksOptions)
-    of wObjChecks: OnOff(c, n, {optObjCheck})
-    of wFieldchecks: OnOff(c, n, {optFieldCheck})
-    of wRangechecks: OnOff(c, n, {optRangeCheck})
-    of wBoundchecks: OnOff(c, n, {optBoundsCheck})
-    of wOverflowchecks: OnOff(c, n, {optOverflowCheck})
-    of wNilchecks: OnOff(c, n, {optNilCheck})
-    of wFloatChecks: OnOff(c, n, {optNanCheck, optInfCheck})
-    of wNaNchecks: OnOff(c, n, {optNanCheck})
-    of wInfChecks: OnOff(c, n, {optInfCheck})
-    of wAssertions: OnOff(c, n, {optAssert})
-    of wWarnings: OnOff(c, n, {optWarns})
-    of wHints: OnOff(c, n, {optHints})
-    of wCallConv: processCallConv(c, n)   
-    of wLinedir: OnOff(c, n, {optLineDir})
-    of wStacktrace: OnOff(c, n, {optStackTrace})
-    of wLinetrace: OnOff(c, n, {optLineTrace})
-    of wDebugger: OnOff(c, n, {optEndb})
-    of wProfiler: OnOff(c, n, {optProfiler})
-    of wByRef: OnOff(c, n, {optByRef})
-    of wDynLib: processDynLib(c, n, nil) 
+    of wChecks: onOff(c, n, ChecksOptions)
+    of wObjChecks: onOff(c, n, {optObjCheck})
+    of wFieldChecks: onOff(c, n, {optFieldCheck})
+    of wRangechecks: onOff(c, n, {optRangeCheck})
+    of wBoundchecks: onOff(c, n, {optBoundsCheck})
+    of wOverflowchecks: onOff(c, n, {optOverflowCheck})
+    of wNilchecks: onOff(c, n, {optNilCheck})
+    of wFloatchecks: onOff(c, n, {optNaNCheck, optInfCheck})
+    of wNanChecks: onOff(c, n, {optNaNCheck})
+    of wInfChecks: onOff(c, n, {optInfCheck})
+    of wAssertions: onOff(c, n, {optAssert})
+    of wWarnings: onOff(c, n, {optWarns})
+    of wHints: onOff(c, n, {optHints})
+    of wCallconv: processCallConv(c, n)   
+    of wLinedir: onOff(c, n, {optLineDir})
+    of wStacktrace: onOff(c, n, {optStackTrace})
+    of wLinetrace: onOff(c, n, {optLineTrace})
+    of wDebugger: onOff(c, n, {optEndb})
+    of wProfiler: onOff(c, n, {optProfiler})
+    of wByRef: onOff(c, n, {optByRef})
+    of wDynlib: processDynLib(c, n, nil) 
     of wOptimization: 
       if n.sons[1].kind != nkIdent: 
         invalidPragma(n)
@@ -319,14 +319,14 @@ proc processOption(c: PContext, n: PNode): bool =
         of "none": 
           excl(gOptions, optOptimizeSpeed)
           excl(gOptions, optOptimizeSize)
-        else: LocalError(n.info, errNoneSpeedOrSizeExpected)
-    of wImplicitStatic: OnOff(c, n, {optImplicitStatic})
-    of wPatterns: OnOff(c, n, {optPatterns})
+        else: localError(n.info, errNoneSpeedOrSizeExpected)
+    of wImplicitStatic: onOff(c, n, {optImplicitStatic})
+    of wPatterns: onOff(c, n, {optPatterns})
     else: result = true
   
 proc processPush(c: PContext, n: PNode, start: int) = 
   if n.sons[start-1].kind == nkExprColonExpr:
-    LocalError(n.info, errGenerated, "':' after 'push' not supported")
+    localError(n.info, errGenerated, "':' after 'push' not supported")
   var x = newOptionEntry()
   var y = POptionEntry(c.optionStack.tail)
   x.options = gOptions
@@ -344,7 +344,7 @@ proc processPush(c: PContext, n: PNode, start: int) =
   
 proc processPop(c: PContext, n: PNode) = 
   if c.optionStack.counter <= 1: 
-    LocalError(n.info, errAtPopWithoutPush)
+    localError(n.info, errAtPopWithoutPush)
   else: 
     gOptions = POptionEntry(c.optionStack.tail).options 
     gNotes = POptionEntry(c.optionStack.tail).notes
@@ -352,15 +352,15 @@ proc processPop(c: PContext, n: PNode) =
 
 proc processDefine(c: PContext, n: PNode) = 
   if (n.kind == nkExprColonExpr) and (n.sons[1].kind == nkIdent): 
-    DefineSymbol(n.sons[1].ident.s)
-    Message(n.info, warnDeprecated, "define")
+    defineSymbol(n.sons[1].ident.s)
+    message(n.info, warnDeprecated, "define")
   else: 
     invalidPragma(n)
   
 proc processUndef(c: PContext, n: PNode) = 
   if (n.kind == nkExprColonExpr) and (n.sons[1].kind == nkIdent): 
-    UndefSymbol(n.sons[1].ident.s)
-    Message(n.info, warnDeprecated, "undef")
+    undefSymbol(n.sons[1].ident.s)
+    message(n.info, warnDeprecated, "undef")
   else: 
     invalidPragma(n)
   
@@ -372,13 +372,13 @@ proc processCompile(c: PContext, n: PNode) =
   var s = expectStrLit(c, n)
   var found = findFile(s)
   if found == "": found = s
-  var trunc = ChangeFileExt(found, "")
+  var trunc = changeFileExt(found, "")
   extccomp.addExternalFileToCompile(found)
   extccomp.addFileToLink(completeCFilePath(trunc, false))
 
 proc processCommonLink(c: PContext, n: PNode, feature: TLinkFeature) = 
   var f = expectStrLit(c, n)
-  if splitFile(f).ext == "": f = addFileExt(f, cc[ccompiler].objExt)
+  if splitFile(f).ext == "": f = addFileExt(f, CC[cCompiler].objExt)
   var found = findFile(f)
   if found == "": found = f # use the default
   case feature
@@ -387,16 +387,16 @@ proc processCommonLink(c: PContext, n: PNode, feature: TLinkFeature) =
     extccomp.addFileToLink(libpath / completeCFilePath(found, false))
   else: internalError(n.info, "processCommonLink")
   
-proc PragmaBreakpoint(c: PContext, n: PNode) = 
+proc pragmaBreakpoint(c: PContext, n: PNode) = 
   discard getOptionalStr(c, n, "")
 
-proc PragmaCheckpoint(c: PContext, n: PNode) = 
+proc pragmaCheckpoint(c: PContext, n: PNode) = 
   # checkpoints can be used to debug the compiler; they are not documented
   var info = n.info
   inc(info.line)              # next line is affected!
   msgs.addCheckpoint(info)
 
-proc PragmaWatchpoint(c: PContext, n: PNode) =
+proc pragmaWatchpoint(c: PContext, n: PNode) =
   if n.kind == nkExprColonExpr:
     n.sons[1] = c.semExpr(c, n.sons[1])
   else:
@@ -408,7 +408,7 @@ proc semAsmOrEmit*(con: PContext, n: PNode, marker: char): PNode =
     result = newNode(if n.kind == nkAsmStmt: nkAsmStmt else: nkArgList, n.info)
     var str = n.sons[1].strVal
     if str == "":
-      LocalError(n.info, errEmptyAsm)
+      localError(n.info, errEmptyAsm)
       return
     # now parse the string literal and substitute symbols:
     var a = 0
@@ -431,14 +431,14 @@ proc semAsmOrEmit*(con: PContext, n: PNode, marker: char): PNode =
       a = c + 1
   else: illFormedAst(n)
   
-proc PragmaEmit(c: PContext, n: PNode) = 
+proc pragmaEmit(c: PContext, n: PNode) = 
   discard getStrLitNode(c, n)
   n.sons[1] = semAsmOrEmit(c, n, '`')
 
 proc noVal(n: PNode) = 
   if n.kind == nkExprColonExpr: invalidPragma(n)
 
-proc PragmaUnroll(c: PContext, n: PNode) = 
+proc pragmaUnroll(c: PContext, n: PNode) = 
   if c.p.nestedLoopCounter <= 0: 
     invalidPragma(n)
   elif n.kind == nkExprColonExpr:
@@ -448,7 +448,7 @@ proc PragmaUnroll(c: PContext, n: PNode) =
     else: 
       invalidPragma(n)
 
-proc PragmaLine(c: PContext, n: PNode) =
+proc pragmaLine(c: PContext, n: PNode) =
   if n.kind == nkExprColonExpr:
     n.sons[1] = c.semConstExpr(c, n.sons[1])
     let a = n.sons[1]
@@ -458,14 +458,14 @@ proc PragmaLine(c: PContext, n: PNode) =
       if x.kind == nkExprColonExpr: x = x.sons[1]
       if y.kind == nkExprColonExpr: y = y.sons[1]
       if x.kind != nkStrLit: 
-        LocalError(n.info, errStringLiteralExpected)
+        localError(n.info, errStringLiteralExpected)
       elif y.kind != nkIntLit: 
-        LocalError(n.info, errIntLiteralExpected)
+        localError(n.info, errIntLiteralExpected)
       else:
         n.info.fileIndex = msgs.fileInfoIdx(x.strVal)
         n.info.line = int16(y.intVal)
     else:
-      LocalError(n.info, errXExpected, "tuple")
+      localError(n.info, errXExpected, "tuple")
   else:
     # sensible default:
     n.info = getInfoContext(-1)
@@ -476,11 +476,11 @@ proc processPragma(c: PContext, n: PNode, i: int) =
   elif it.sons[0].kind != nkIdent: invalidPragma(n)
   elif it.sons[1].kind != nkIdent: invalidPragma(n)
   
-  var userPragma = NewSym(skTemplate, it.sons[1].ident, nil, it.info)
+  var userPragma = newSym(skTemplate, it.sons[1].ident, nil, it.info)
   var body = newNodeI(nkPragma, n.info)
   for j in i+1 .. sonsLen(n)-1: addSon(body, n.sons[j])
   userPragma.ast = body
-  StrTableAdd(c.userPragmas, userPragma)
+  strTableAdd(c.userPragmas, userPragma)
 
 proc pragmaRaisesOrTags(c: PContext, n: PNode) =
   proc processExc(c: PContext, x: PNode) =
@@ -503,13 +503,13 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
   var it = n.sons[i]
   var key = if it.kind == nkExprColonExpr: it.sons[0] else: it
   if key.kind == nkIdent: 
-    var userPragma = StrTableGet(c.userPragmas, key.ident)
+    var userPragma = strTableGet(c.userPragmas, key.ident)
     if userPragma != nil: 
-      inc c.InstCounter
-      if c.InstCounter > 100: 
-        GlobalError(it.info, errRecursiveDependencyX, userPragma.name.s)
+      inc c.instCounter
+      if c.instCounter > 100: 
+        globalError(it.info, errRecursiveDependencyX, userPragma.name.s)
       pragma(c, sym, userPragma.ast, validPragmas)
-      dec c.InstCounter
+      dec c.instCounter
     else:
       var k = whichKeyword(key.ident)
       if k in validPragmas: 
@@ -534,20 +534,20 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
         of wAlign:
           if sym.typ == nil: invalidPragma(it)
           var align = expectIntLit(c, it)
-          if not IsPowerOfTwo(align) and align != 0: 
-            LocalError(it.info, errPowerOfTwoExpected)
+          if not isPowerOfTwo(align) and align != 0: 
+            localError(it.info, errPowerOfTwoExpected)
           else: 
             sym.typ.align = align              
         of wSize: 
           if sym.typ == nil: invalidPragma(it)
           var size = expectIntLit(c, it)
-          if not IsPowerOfTwo(size) or size <= 0 or size > 8: 
-            LocalError(it.info, errPowerOfTwoExpected)
+          if not isPowerOfTwo(size) or size <= 0 or size > 8: 
+            localError(it.info, errPowerOfTwoExpected)
           else:
             sym.typ.size = size
         of wNodecl: 
           noVal(it)
-          incl(sym.loc.Flags, lfNoDecl)
+          incl(sym.loc.flags, lfNoDecl)
         of wPure, wNoStackFrame:
           noVal(it)
           if sym != nil: incl(sym.flags, sfPure)
@@ -566,20 +566,20 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
         of wCompileTime: 
           noVal(it)
           incl(sym.flags, sfCompileTime)
-          incl(sym.loc.Flags, lfNoDecl)
+          incl(sym.loc.flags, lfNoDecl)
         of wGlobal:
           noVal(it)
           incl(sym.flags, sfGlobal)
           incl(sym.flags, sfPure)
         of wMerge: 
-          noval(it)
+          noVal(it)
           incl(sym.flags, sfMerge)
         of wHeader: 
           var lib = getLib(c, libHeader, getStrLitNode(c, it))
           addToLib(lib, sym)
           incl(sym.flags, sfImportc)
           incl(sym.loc.flags, lfHeader)
-          incl(sym.loc.Flags, lfNoDecl) 
+          incl(sym.loc.flags, lfNoDecl) 
           # implies nodecl, because otherwise header would not make sense
           if sym.loc.r == nil: sym.loc.r = toRope(sym.name.s)
         of wDestructor:
@@ -591,23 +591,23 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
           noVal(it)
           incl(sym.flags, sfNoSideEffect)
           if sym.typ != nil: incl(sym.typ.flags, tfNoSideEffect)
-        of wSideEffect: 
+        of wSideeffect: 
           noVal(it)
           incl(sym.flags, sfSideEffect)
-        of wNoReturn: 
+        of wNoreturn: 
           noVal(it)
           incl(sym.flags, sfNoReturn)
-        of wDynLib: 
+        of wDynlib: 
           processDynLib(c, it, sym)
-        of wCompilerProc: 
+        of wCompilerproc: 
           noVal(it)           # compilerproc may not get a string!
           makeExternExport(sym, "$1")
           incl(sym.flags, sfCompilerProc)
           incl(sym.flags, sfUsed) # suppress all those stupid warnings
           registerCompilerProc(sym)
-        of wProcvar: 
+        of wProcVar: 
           noVal(it)
-          incl(sym.flags, sfProcVar)
+          incl(sym.flags, sfProcvar)
         of wDeprecated: 
           noVal(it)
           if sym != nil: incl(sym.flags, sfDeprecated)
@@ -638,10 +638,10 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
         of wThread:
           noVal(it)
           incl(sym.flags, sfThread)
-          incl(sym.flags, sfProcVar)
+          incl(sym.flags, sfProcvar)
           if sym.typ != nil: incl(sym.typ.flags, tfThread)
-        of wHint: Message(it.info, hintUser, expectStrLit(c, it))
-        of wWarning: Message(it.info, warnUser, expectStrLit(c, it))
+        of wHint: message(it.info, hintUser, expectStrLit(c, it))
+        of wWarning: message(it.info, warnUser, expectStrLit(c, it))
         of wError: 
           if sym != nil and sym.isRoutine:
             # This is subtle but correct: the error *statement* is only
@@ -651,17 +651,17 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
             noVal(it)
             incl(sym.flags, sfError)
           else:
-            LocalError(it.info, errUser, expectStrLit(c, it))
-        of wFatal: Fatal(it.info, errUser, expectStrLit(c, it))
+            localError(it.info, errUser, expectStrLit(c, it))
+        of wFatal: fatal(it.info, errUser, expectStrLit(c, it))
         of wDefine: processDefine(c, it)
         of wUndef: processUndef(c, it)
         of wCompile: processCompile(c, it)
         of wLink: processCommonLink(c, it, linkNormal)
-        of wLinkSys: processCommonLink(c, it, linkSys)
-        of wPassL: extccomp.addLinkOption(expectStrLit(c, it))
-        of wPassC: extccomp.addCompileOption(expectStrLit(c, it))
-        of wBreakpoint: PragmaBreakpoint(c, it)
-        of wWatchpoint: PragmaWatchpoint(c, it)
+        of wLinksys: processCommonLink(c, it, linkSys)
+        of wPassl: extccomp.addLinkOption(expectStrLit(c, it))
+        of wPassc: extccomp.addCompileOption(expectStrLit(c, it))
+        of wBreakpoint: pragmaBreakpoint(c, it)
+        of wWatchPoint: pragmaWatchpoint(c, it)
         of wPush: 
           processPush(c, n, i + 1)
           result = true 
@@ -679,18 +679,18 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
         of wChecks, wObjChecks, wFieldChecks, wRangechecks, wBoundchecks, 
            wOverflowchecks, wNilchecks, wAssertions, wWarnings, wHints, 
            wLinedir, wStacktrace, wLinetrace, wOptimization,
-           wCallConv, 
-           wDebugger, wProfiler, wFloatChecks, wNanChecks, wInfChecks,
+           wCallconv, 
+           wDebugger, wProfiler, wFloatchecks, wNanChecks, wInfChecks,
            wPatterns:
           if processOption(c, it):
             # calling conventions (boring...):
-            LocalError(it.info, errOptionExpected)
-        of firstCallConv..lastCallConv: 
+            localError(it.info, errOptionExpected)
+        of FirstCallConv..LastCallConv: 
           assert(sym != nil)
           if sym.typ == nil: invalidPragma(it)
           else: sym.typ.callConv = wordToCallConv(k)
-        of wEmit: PragmaEmit(c, it)
-        of wUnroll: PragmaUnroll(c, it)
+        of wEmit: pragmaEmit(c, it)
+        of wUnroll: pragmaUnroll(c, it)
         of wLinearScanEnd, wComputedGoto: noVal(it)
         of wEffects:
           # is later processed in effect analysis:
@@ -706,19 +706,19 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
         of wByRef:
           noVal(it)
           if sym == nil or sym.typ == nil:
-            if processOption(c, it): LocalError(it.info, errOptionExpected)
+            if processOption(c, it): localError(it.info, errOptionExpected)
           else:
             incl(sym.typ.flags, tfByRef)
         of wByCopy:
           noVal(it)
           if sym.kind != skType or sym.typ == nil: invalidPragma(it)
           else: incl(sym.typ.flags, tfByCopy)
-        of wInject, wGenSym:
+        of wInject, wGensym:
           # We check for errors, but do nothing with these pragmas otherwise
           # as they are handled directly in 'evalTemplate'.
           noVal(it)
           if sym == nil: invalidPragma(it)
-        of wLine: PragmaLine(c, it)
+        of wLine: pragmaLine(c, it)
         of wRaises, wTags: pragmaRaisesOrTags(c, it)
         of wOperator:
           if sym == nil: invalidPragma(it)
@@ -735,18 +735,18 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int,
 proc implictPragmas*(c: PContext, sym: PSym, n: PNode,
                      validPragmas: TSpecialWords) =
   if sym != nil and sym.kind != skModule:
-    var it = POptionEntry(c.optionstack.head)
+    var it = POptionEntry(c.optionStack.head)
     while it != nil:
       let o = it.otherPragmas
       if not o.isNil:
         for i in countup(0, sonsLen(o) - 1):
           if singlePragma(c, sym, o, i, validPragmas):
-            InternalError(n.info, "implicitPragmas")
+            internalError(n.info, "implicitPragmas")
       it = it.next.POptionEntry
 
     if lfExportLib in sym.loc.flags and sfExportc notin sym.flags: 
-      LocalError(n.info, errDynlibRequiresExportc)
-    var lib = POptionEntry(c.optionstack.tail).dynlib
+      localError(n.info, errDynlibRequiresExportc)
+    var lib = POptionEntry(c.optionStack.tail).dynlib
     if {lfDynamicLib, lfHeader} * sym.loc.flags == {} and
         sfImportc in sym.flags and lib != nil:
       incl(sym.loc.flags, lfDynamicLib)
diff --git a/compiler/pretty.nim b/compiler/pretty.nim
index 5036a16a3..3a5bfe197 100644
--- a/compiler/pretty.nim
+++ b/compiler/pretty.nim
@@ -12,12 +12,12 @@
 
 import 
   strutils, os, options, ast, astalgo, msgs, ropes, idents, passes,
-  intsets, strtabs
+  intsets, strtabs, semdata
   
 const
   removeTP = false # when true, "nimrod pretty" converts TTyp to Typ.
 
-type 
+type
   TGen = object of TPassContext
     module*: PSym
   PGen = ref TGen
@@ -29,6 +29,7 @@ type
 
 var
   gSourceFiles: seq[TSourceFile] = @[]
+  gCheckExtern: bool
   rules: PStringTable
 
 proc loadFile(info: TLineInfo) =
@@ -44,13 +45,20 @@ proc loadFile(info: TLineInfo) =
       gSourceFiles[i].lines.add(line)
 
 proc overwriteFiles*() =
+  let overWrite = options.getConfigVar("pretty.overwrite").normalize == "on"
+  let doStrip = options.getConfigVar("pretty.strip").normalize == "on"
   for i in 0 .. high(gSourceFiles):
     if not gSourceFiles[i].dirty: continue
-    let newFile = gSourceFiles[i].fullpath.changeFileExt(".pretty.nim")
+    let newFile = if overWrite: gSourceFiles[i].fullpath
+                  else: gSourceFiles[i].fullpath.changeFileExt(".pretty.nim")
     try:
       var f = open(newFile, fmWrite)
       for line in gSourceFiles[i].lines:
-        f.writeln(line)
+        if doStrip:
+          f.write line.strip(leading = false, trailing = true)
+        else:
+          f.write line
+        f.write("\L")
       f.close
     except EIO:
       rawMessage(errCannotOpenFile, newFile)
@@ -60,18 +68,25 @@ proc `=~`(s: string, a: openArray[string]): bool =
     if s.startsWith(x): return true
 
 proc beautifyName(s: string, k: TSymKind): string =
+  # minimal set of rules here for transition:
+  # GC_ is allowed
+
+  let allUpper = allCharsInSet(s, {'A'..'Z', '0'..'9', '_'})
+  if allUpper and k in {skConst, skEnumField, skType}: return s
   result = newStringOfCap(s.len)
   var i = 0
   case k
   of skType, skGenericParam:
-    # skip leading 'T'
+    # Types should start with a capital unless builtins like 'int' etc.:
     when removeTP:
       if s[0] == 'T' and s[1] in {'A'..'Z'}:
         i = 1
     if s =~ ["int", "uint", "cint", "cuint", "clong", "cstring", "string",
              "char", "byte", "bool", "openArray", "seq", "array", "void",
              "pointer", "float", "csize", "cdouble", "cchar", "cschar",
-             "cshort", "cu"]:
+             "cshort", "cu", "nil", "expr", "stmt", "typedesc", "auto", "any",
+             "range", "openarray", "varargs", "set", "cfloat"
+             ]:
       result.add s[i]
     else:
       result.add toUpper(s[i])
@@ -81,13 +96,19 @@ proc beautifyName(s: string, k: TSymKind): string =
   else:
     # as a special rule, don't transform 'L' to 'l'
     if s.len == 1 and s[0] == 'L': result.add 'L'
+    elif '_' in s: result.add(s[i])
     else: result.add toLower(s[0])
   inc i
-  let allUpper = allCharsInSet(s, {'A'..'Z', '0'..'9', '_'})
   while i < s.len:
     if s[i] == '_':
-      inc i
-      result.add toUpper(s[i])
+      if i > 0 and s[i-1] in {'A'..'Z'}:
+        # don't skip '_' as it's essential for e.g. 'GC_disable'
+        result.add('_')
+        inc i
+        result.add s[i]
+      else:
+        inc i
+        result.add toUpper(s[i])
     elif allUpper:
       result.add toLower(s[i])
     else:
@@ -97,8 +118,7 @@ proc beautifyName(s: string, k: TSymKind): string =
 proc checkStyle*(info: TLineInfo, s: string, k: TSymKind) =
   let beau = beautifyName(s, k)
   if s != beau:
-    Message(info, errGenerated, 
-      "name does not adhere to naming convention; should be: " & beau)
+    message(info, errGenerated, "name should be: " & beau)
 
 const
   Letters = {'a'..'z', 'A'..'Z', '0'..'9', '\x80'..'\xFF', '_'}
@@ -117,13 +137,90 @@ proc differ(line: string, a, b: int, x: string): bool =
       inc j
     return false
 
-var cannotRename = initIntSet()
+proc checkDef*(n: PNode; s: PSym) =
+  # operators stay as they are:
+  if s.kind in {skResult, skTemp} or s.name.s[0] notin Letters: return
+  if s.kind in {skType, skGenericParam} and sfAnon in s.flags: return
 
-proc processSym(c: PPassContext, n: PNode): PNode = 
-  result = n
-  var g = PGen(c)
-  case n.kind
-  of nkSym:
+  if {sfImportc, sfExportc} * s.flags == {} or gCheckExtern:
+    checkStyle(n.info, s.name.s, s.kind)
+
+proc checkDef(c: PGen; n: PNode) =
+  if n.kind != nkSym: return
+  checkDef(n, n.sym)
+
+proc checkUse*(n: PNode, s: PSym) =
+  if n.info.fileIndex < 0: return
+  # we simply convert it to what it looks like in the definition
+  # for consistency
+  
+  # operators stay as they are:
+  if s.kind in {skResult, skTemp} or s.name.s[0] notin Letters: return
+  if s.kind in {skType, skGenericParam} and sfAnon in s.flags: return
+  let newName = s.name.s
+  
+  loadFile(n.info)
+  
+  let line = gSourceFiles[n.info.fileIndex].lines[n.info.line-1]
+  var first = min(n.info.col.int, line.len)
+  if first < 0: return
+  #inc first, skipIgnoreCase(line, "proc ", first)
+  while first > 0 and line[first-1] in Letters: dec first
+  if first < 0: return
+  if line[first] == '`': inc first
+  
+  let last = first+identLen(line, first)-1
+  if differ(line, first, last, newName):
+    # last-first+1 != newName.len or 
+    var x = line.substr(0, first-1) & newName & line.substr(last+1)
+    when removeTP:
+      # the WinAPI module is full of 'TX = X' which after the substitution
+      # becomes 'X = X'. We remove those lines:
+      if x.match(peg"\s* {\ident} \s* '=' \s* y$1 ('#' .*)?"):
+        x = ""
+    
+    system.shallowCopy(gSourceFiles[n.info.fileIndex].lines[n.info.line-1], x)
+    gSourceFiles[n.info.fileIndex].dirty = true
+
+when false:
+  var cannotRename = initIntSet()
+
+  proc beautifyName(s: string, k: TSymKind): string =
+    let allUpper = allCharsInSet(s, {'A'..'Z', '0'..'9', '_'})
+    result = newStringOfCap(s.len)
+    var i = 0
+    case k
+    of skType, skGenericParam:
+      # skip leading 'T'
+      when removeTP:
+        if s[0] == 'T' and s[1] in {'A'..'Z'}:
+          i = 1
+      if s =~ ["int", "uint", "cint", "cuint", "clong", "cstring", "string",
+               "char", "byte", "bool", "openArray", "seq", "array", "void",
+               "pointer", "float", "csize", "cdouble", "cchar", "cschar",
+               "cshort", "cu"]:
+        result.add s[i]
+      else:
+        result.add toUpper(s[i])
+    of skConst, skEnumField:
+      # for 'const' we keep how it's spelt; either upper case or lower case:
+      result.add s[0]
+    else:
+      # as a special rule, don't transform 'L' to 'l'
+      if s.len == 1 and s[0] == 'L': result.add 'L'
+      else: result.add toLower(s[0])
+    inc i
+    while i < s.len:
+      if s[i] == '_':
+        inc i
+        result.add toUpper(s[i])
+      elif allUpper:
+        result.add toLower(s[i])
+      else:
+        result.add s[i]
+      inc i
+
+  proc checkUse(c: PGen; n: PNode) =
     if n.info.fileIndex < 0: return
     let s = n.sym
     # operators stay as they are:
@@ -138,10 +235,11 @@ proc processSym(c: PPassContext, n: PNode): PNode =
     loadFile(n.info)
     
     let line = gSourceFiles[n.info.fileIndex].lines[n.info.line-1]
-    var first = n.info.col.int
+    var first = min(n.info.col.int, line.len)
     if first < 0: return
     #inc first, skipIgnoreCase(line, "proc ", first)
     while first > 0 and line[first-1] in Letters: dec first
+    if first < 0: return
     if line[first] == '`': inc first
     
     if {sfImportc, sfExportc} * s.flags != {}:
@@ -149,8 +247,8 @@ proc processSym(c: PPassContext, n: PNode): PNode =
       # name:
       if newName != s.name.s and newName != s.loc.r.ropeToStr and
           lfFullExternalName notin s.loc.flags:
-        Message(n.info, errGenerated, 
-          "cannot rename $# to $# due to external name" % [s.name.s, newName])
+        #Message(n.info, errGenerated, 
+        #  "cannot rename $# to $# due to external name" % [s.name.s, newName])
         cannotRename.incl(s.id)
         return
     let last = first+identLen(line, first)-1
@@ -165,14 +263,50 @@ proc processSym(c: PPassContext, n: PNode): PNode =
       
       system.shallowCopy(gSourceFiles[n.info.fileIndex].lines[n.info.line-1], x)
       gSourceFiles[n.info.fileIndex].dirty = true
+
+proc check(c: PGen, n: PNode) =
+  case n.kind
+  of nkSym: checkUse(n, n.sym)
+  of nkBlockStmt, nkBlockExpr, nkBlockType:
+    checkDef(c, n[0])
+    check(c, n.sons[1])
+  of nkForStmt, nkParForStmt:
+    let L = n.len
+    for i in countup(0, L-3):
+      checkDef(c, n[i])
+    check(c, n[L-2])
+    check(c, n[L-1])
+  of nkProcDef, nkLambdaKinds, nkMethodDef, nkIteratorDef, nkTemplateDef,
+      nkMacroDef, nkConverterDef:
+    checkDef(c, n[namePos])
+    for i in namePos+1 .. <n.len: check(c, n.sons[i])
+  of nkIdentDefs, nkVarTuple:
+    let a = n
+    checkMinSonsLen(a, 3)
+    let L = len(a)
+    for j in countup(0, L-3): checkDef(c, a.sons[j])
+    check(c, a.sons[L-2])
+    check(c, a.sons[L-1])
+  of nkTypeSection, nkConstSection:
+    for i in countup(0, sonsLen(n) - 1): 
+      let a = n.sons[i]
+      if a.kind == nkCommentStmt: continue 
+      checkSonsLen(a, 3)
+      checkDef(c, a.sons[0])
+      check(c, a.sons[1])
+      check(c, a.sons[2])
   else:
-    for i in 0 .. <n.safeLen:
-      discard processSym(c, n.sons[i])
+    for i in 0 .. <n.safeLen: check(c, n.sons[i])
+
+proc processSym(c: PPassContext, n: PNode): PNode = 
+  result = n
+  check(PGen(c), n)
 
 proc myOpen(module: PSym): PPassContext =
   var g: PGen
   new(g)
   g.module = module
+  gCheckExtern = options.getConfigVar("pretty.checkextern").normalize == "on"
   result = g
   if rules.isNil:
     rules = newStringTable(modeStyleInsensitive)
diff --git a/compiler/procfind.nim b/compiler/procfind.nim
index aefccd140..0354d585d 100644
--- a/compiler/procfind.nim
+++ b/compiler/procfind.nim
@@ -17,52 +17,76 @@ proc equalGenericParams(procA, procB: PNode): bool =
   if sonsLen(procA) != sonsLen(procB): return
   for i in countup(0, sonsLen(procA) - 1):
     if procA.sons[i].kind != nkSym:
-      InternalError(procA.info, "equalGenericParams")
+      internalError(procA.info, "equalGenericParams")
       return
     if procB.sons[i].kind != nkSym:
-      InternalError(procB.info, "equalGenericParams")
+      internalError(procB.info, "equalGenericParams")
       return
     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
+      if not exprStructuralEquivalent(a.ast, b.ast): return
   result = true
 
-proc SearchForProc*(c: PContext, scope: PScope, fn: PSym): PSym =
+proc searchForProcOld*(c: PContext, scope: PScope, fn: PSym): PSym =
   # Searchs for a forward declaration or a "twin" symbol of fn
   # in the symbol table. If the parameter lists are exactly
   # the same the sym in the symbol table is returned, else nil.
   var it: TIdentIter
-  result = initIdentIter(it, scope.symbols, fn.Name)
+  result = initIdentIter(it, scope.symbols, fn.name)
   if isGenericRoutine(fn):
     # we simply check the AST; this is imprecise but nearly the best what
     # can be done; this doesn't work either though as type constraints are
     # not kept in the AST ..
     while result != nil:
-      if result.Kind == fn.kind and isGenericRoutine(result):
+      if result.kind == fn.kind and isGenericRoutine(result):
         let genR = result.ast.sons[genericParamsPos]
         let genF = fn.ast.sons[genericParamsPos]
-        if ExprStructuralEquivalent(genR, genF) and
-           ExprStructuralEquivalent(result.ast.sons[paramsPos],
+        if exprStructuralEquivalent(genR, genF) and
+           exprStructuralEquivalent(result.ast.sons[paramsPos],
                                     fn.ast.sons[paramsPos]) and
            equalGenericParams(genR, genF):
             return
-      result = NextIdentIter(it, scope.symbols)
+      result = nextIdentIter(it, scope.symbols)
   else:
     while result != nil:
-      if result.Kind == fn.kind and not isGenericRoutine(result):
+      if result.kind == fn.kind and not isGenericRoutine(result):
         case equalParams(result.typ.n, fn.typ.n)
         of paramsEqual:
           return
         of paramsIncompatible:
-          LocalError(fn.info, errNotOverloadable, fn.name.s)
+          localError(fn.info, errNotOverloadable, fn.name.s)
           return
         of paramsNotEqual:
-          nil
-      result = NextIdentIter(it, scope.symbols)
+          discard
+      result = nextIdentIter(it, scope.symbols)
 
+proc searchForProcNew(c: PContext, scope: PScope, fn: PSym): PSym =
+  const flags = {ExactGenericParams, ExactTypeDescValues,
+                 ExactConstraints, IgnoreCC}
+
+  var it: TIdentIter
+  result = initIdentIter(it, scope.symbols, fn.name)
+  while result != nil:
+    if result.kind in skProcKinds and
+       sameType(result.typ, fn.typ, flags): return
+
+    result = nextIdentIter(it, scope.symbols)
+  
+  return nil
+
+proc searchForProc*(c: PContext, scope: PScope, fn: PSym): PSym =
+  result = searchForProcNew(c, scope, fn)
+  when false:
+    let old = searchForProcOld(c, scope, fn)
+    if old != result:
+      echo "Mismatch in searchForProc: ", fn.info
+      debug fn.typ
+      debug if result != nil: result.typ else: nil
+      debug if old != nil: old.typ else: nil
+ 
 when false:
   proc paramsFitBorrow(child, parent: PNode): bool = 
     var length = sonsLen(child)
@@ -77,7 +101,7 @@ when false:
                           dcEqOrDistinctOf): return
       result = true
 
-  proc SearchForBorrowProc*(c: PContext, startScope: PScope, fn: PSym): PSym =
+  proc searchForBorrowProc*(c: PContext, startScope: PScope, fn: PSym): PSym =
     # Searchs for the fn in the symbol table. If the parameter lists are suitable
     # for borrowing the sym in the symbol table is returned, else nil.
     var it: TIdentIter
diff --git a/compiler/renderer.nim b/compiler/renderer.nim
index f6fb0f8c0..1afb5961e 100644
--- a/compiler/renderer.nim
+++ b/compiler/renderer.nim
@@ -62,7 +62,7 @@ const
   MaxLineLen = 80
   LineCommentColumn = 30
 
-proc InitSrcGen(g: var TSrcGen, renderFlags: TRenderFlags) = 
+proc initSrcGen(g: var TSrcGen, renderFlags: TRenderFlags) = 
   g.comStack = @[]
   g.tokens = @[]
   g.indent = 0
@@ -76,7 +76,7 @@ proc InitSrcGen(g: var TSrcGen, renderFlags: TRenderFlags) =
 
 proc addTok(g: var TSrcGen, kind: TTokType, s: string) = 
   var length = len(g.tokens)
-  setlen(g.tokens, length + 1)
+  setLen(g.tokens, length + 1)
   g.tokens[length].kind = kind
   g.tokens[length].length = int16(len(s))
   add(g.buf, s)
@@ -104,16 +104,16 @@ proc optNL(g: var TSrcGen) =
   optNL(g, g.indent)
 
 proc indentNL(g: var TSrcGen) = 
-  inc(g.indent, indentWidth)
+  inc(g.indent, IndentWidth)
   g.pendingNL = g.indent
   g.lineLen = g.indent
 
-proc Dedent(g: var TSrcGen) = 
-  dec(g.indent, indentWidth)
+proc dedent(g: var TSrcGen) = 
+  dec(g.indent, IndentWidth)
   assert(g.indent >= 0)
-  if g.pendingNL > indentWidth: 
-    Dec(g.pendingNL, indentWidth)
-    Dec(g.lineLen, indentWidth)
+  if g.pendingNL > IndentWidth: 
+    dec(g.pendingNL, IndentWidth)
+    dec(g.lineLen, IndentWidth)
 
 proc put(g: var TSrcGen, kind: TTokType, s: string) = 
   addPendingNL(g)
@@ -127,7 +127,7 @@ proc putLong(g: var TSrcGen, kind: TTokType, s: string, lineLen: int) =
   addTok(g, kind, s)
   g.lineLen = lineLen
 
-proc toNimChar(c: Char): string = 
+proc toNimChar(c: char): string = 
   case c
   of '\0': result = "\\0"
   of '\x01'..'\x1F', '\x80'..'\xFF': result = "\\x" & strutils.toHex(ord(c), 2)
@@ -236,19 +236,19 @@ proc containsNL(s: string): bool =
     of '\x0D', '\x0A': 
       return true
     else: 
-      nil
+      discard
   result = false
 
 proc pushCom(g: var TSrcGen, n: PNode) = 
   var length = len(g.comStack)
-  setlen(g.comStack, length + 1)
+  setLen(g.comStack, length + 1)
   g.comStack[length] = n
 
 proc popAllComs(g: var TSrcGen) = 
-  setlen(g.comStack, 0)
+  setLen(g.comStack, 0)
 
 proc popCom(g: var TSrcGen) = 
-  setlen(g.comStack, len(g.comStack) - 1)
+  setLen(g.comStack, len(g.comStack) - 1)
 
 const 
   Space = " "
@@ -269,7 +269,7 @@ proc gcom(g: var TSrcGen, n: PNode) =
     if (g.pendingNL < 0) and (len(g.buf) > 0) and
         (g.lineLen < LineCommentColumn): 
       var ml = maxLineLength(n.comment)
-      if ml + LineCommentColumn <= maxLineLen: 
+      if ml + LineCommentColumn <= MaxLineLen: 
         put(g, tkSpaces, repeatChar(LineCommentColumn - g.lineLen))
     putComment(g, n.comment)  #assert(g.comStack[high(g.comStack)] = n);
   
@@ -278,7 +278,7 @@ proc gcoms(g: var TSrcGen) =
   popAllComs(g)
 
 proc lsub(n: PNode): int
-proc litAux(n: PNode, x: biggestInt, size: int): string =
+proc litAux(n: PNode, x: BiggestInt, size: int): string =
   proc skip(t: PType): PType = 
     result = t
     while result.kind in {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
@@ -295,7 +295,7 @@ proc litAux(n: PNode, x: biggestInt, size: int): string =
   elif nfBase16 in n.flags: result = "0x" & toHex(x, size * 2)
   else: result = $x
 
-proc ulitAux(n: PNode, x: biggestInt, size: int): string = 
+proc ulitAux(n: PNode, x: BiggestInt, size: int): string = 
   if nfBase2 in n.flags: result = "0b" & toBin(x, size * 8)
   elif nfBase8 in n.flags: result = "0o" & toOct(x, size * 3)
   elif nfBase16 in n.flags: result = "0x" & toHex(x, size * 2)
@@ -341,7 +341,7 @@ proc atom(n: PNode): string =
     if (n.typ != nil) and (n.typ.sym != nil): result = n.typ.sym.name.s
     else: result = "[type node]"
   else: 
-    InternalError("rnimsyn.atom " & $n.kind)
+    internalError("rnimsyn.atom " & $n.kind)
     result = ""
   
 proc lcomma(n: PNode, start: int = 0, theEnd: int = - 1): int = 
@@ -361,11 +361,11 @@ proc lsons(n: PNode, start: int = 0, theEnd: int = - 1): int =
 proc lsub(n: PNode): int = 
   # computes the length of a tree
   if isNil(n): return 0
-  if n.comment != nil: return maxLineLen + 1
+  if n.comment != nil: return MaxLineLen + 1
   case n.kind
   of nkEmpty: result = 0
   of nkTripleStrLit: 
-    if containsNL(n.strVal): result = maxLineLen + 1
+    if containsNL(n.strVal): result = MaxLineLen + 1
     else: result = len(atom(n))
   of succ(nkEmpty)..pred(nkTripleStrLit), succ(nkTripleStrLit)..nkNilLit: 
     result = len(atom(n))
@@ -421,10 +421,13 @@ proc lsub(n: PNode): int =
   of nkElifExpr: result = lsons(n) + len("_elif_:_")
   of nkElseExpr: result = lsub(n.sons[0]) + len("_else:_") # type descriptions
   of nkTypeOfExpr: result = lsub(n.sons[0]) + len("type_")
-  of nkRefTy: result = lsub(n.sons[0]) + len("ref_")
-  of nkPtrTy: result = lsub(n.sons[0]) + len("ptr_")
-  of nkVarTy: result = lsub(n.sons[0]) + len("var_")
-  of nkDistinctTy: result = lsub(n.sons[0]) + len("Distinct_")
+  of nkRefTy: result = (if n.len > 0: lsub(n.sons[0])+1 else: 0) + len("ref")
+  of nkPtrTy: result = (if n.len > 0: lsub(n.sons[0])+1 else: 0) + len("ptr")
+  of nkVarTy: result = (if n.len > 0: lsub(n.sons[0])+1 else: 0) + len("var")
+  of nkDistinctTy: result = (if n.len > 0: lsub(n.sons[0])+1 else: 0) +
+                                                         len("Distinct")
+  of nkStaticTy: result = (if n.len > 0: lsub(n.sons[0]) else: 0) +
+                                                         len("static[]")
   of nkTypeDef: result = lsons(n) + 3
   of nkOfInherit: result = lsub(n.sons[0]) + len("of_")
   of nkProcTy: result = lsons(n) + len("proc_")
@@ -437,7 +440,7 @@ proc lsub(n: PNode): int =
       result = len("enum")
   of nkEnumFieldDef: result = lsons(n) + 3
   of nkVarSection, nkLetSection: 
-    if sonsLen(n) > 1: result = maxLineLen + 1
+    if sonsLen(n) > 1: result = MaxLineLen + 1
     else: result = lsons(n) + len("var_")
   of nkReturnStmt: result = lsub(n.sons[0]) + len("return_")
   of nkRaiseStmt: result = lsub(n.sons[0]) + len("raise_")
@@ -458,10 +461,10 @@ proc lsub(n: PNode): int =
     if n.sons[0].kind != nkEmpty: result = result + lsub(n.sons[0]) + 2
   of nkExceptBranch: 
     result = lcomma(n, 0, -2) + lsub(lastSon(n)) + len("except_:_")
-  else: result = maxLineLen + 1
+  else: result = MaxLineLen + 1
   
 proc fits(g: TSrcGen, x: int): bool = 
-  result = x + g.lineLen <= maxLineLen
+  result = x + g.lineLen <= MaxLineLen
 
 type 
   TSubFlag = enum 
@@ -486,7 +489,7 @@ proc hasCom(n: PNode): bool =
   result = false
   if n.comment != nil: return true
   case n.kind
-  of nkEmpty..nkNilLit: nil
+  of nkEmpty..nkNilLit: discard
   else: 
     for i in countup(0, sonsLen(n) - 1): 
       if hasCom(n.sons[i]): return true
@@ -500,7 +503,7 @@ proc gcommaAux(g: var TSrcGen, n: PNode, ind: int, start: int = 0,
   for i in countup(start, sonsLen(n) + theEnd):
     var c = i < sonsLen(n) + theEnd
     var sublen = lsub(n.sons[i]) + ord(c)
-    if not fits(g, sublen) and (ind + sublen < maxLineLen): optNL(g, ind)
+    if not fits(g, sublen) and (ind + sublen < MaxLineLen): optNL(g, ind)
     let oldLen = g.tokens.len
     gsub(g, n.sons[i])
     if c:
@@ -514,21 +517,21 @@ proc gcomma(g: var TSrcGen, n: PNode, c: TContext, start: int = 0,
             theEnd: int = - 1) = 
   var ind: int
   if rfInConstExpr in c.flags: 
-    ind = g.indent + indentWidth
+    ind = g.indent + IndentWidth
   else: 
     ind = g.lineLen
-    if ind > maxLineLen div 2: ind = g.indent + longIndentWid
+    if ind > MaxLineLen div 2: ind = g.indent + longIndentWid
   gcommaAux(g, n, ind, start, theEnd)
 
 proc gcomma(g: var TSrcGen, n: PNode, start: int = 0, theEnd: int = - 1) = 
   var ind = g.lineLen
-  if ind > maxLineLen div 2: ind = g.indent + longIndentWid
+  if ind > MaxLineLen div 2: ind = g.indent + longIndentWid
   gcommaAux(g, n, ind, start, theEnd)
 
 proc gsemicolon(g: var TSrcGen, n: PNode, start: int = 0, theEnd: int = - 1) = 
   var ind = g.lineLen
-  if ind > maxLineLen div 2: ind = g.indent + longIndentWid
-  gcommaAux(g, n, ind, start, theEnd, tkSemicolon)
+  if ind > MaxLineLen div 2: ind = g.indent + longIndentWid
+  gcommaAux(g, n, ind, start, theEnd, tkSemiColon)
 
 proc gsons(g: var TSrcGen, n: PNode, c: TContext, start: int = 0, 
            theEnd: int = - 1) = 
@@ -551,13 +554,13 @@ proc longMode(n: PNode, start: int = 0, theEnd: int = - 1): bool =
   if not result: 
     # check further
     for i in countup(start, sonsLen(n) + theEnd): 
-      if (lsub(n.sons[i]) > maxLineLen): 
+      if (lsub(n.sons[i]) > MaxLineLen): 
         result = true
         break 
 
 proc gstmts(g: var TSrcGen, n: PNode, c: TContext) = 
   if n.kind == nkEmpty: return 
-  if (n.kind == nkStmtList) or (n.kind == nkStmtListExpr): 
+  if n.kind in {nkStmtList, nkStmtListExpr, nkStmtListType}:
     indentNL(g)
     for i in countup(0, sonsLen(n) - 1): 
       optNL(g)
@@ -576,7 +579,7 @@ proc gif(g: var TSrcGen, n: PNode) =
   gsub(g, n.sons[0].sons[0])
   initContext(c)
   putWithSpace(g, tkColon, ":")
-  if longMode(n) or (lsub(n.sons[0].sons[1]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[0].sons[1]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[0].sons[1], c)
@@ -591,7 +594,7 @@ proc gwhile(g: var TSrcGen, n: PNode) =
   gsub(g, n.sons[0])
   putWithSpace(g, tkColon, ":")
   initContext(c)
-  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[1], c)
@@ -600,7 +603,7 @@ proc gpattern(g: var TSrcGen, n: PNode) =
   var c: TContext
   put(g, tkCurlyLe, "{")
   initContext(c)
-  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > maxLineLen):
+  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > MaxLineLen):
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[0], c)
@@ -611,7 +614,7 @@ proc gpragmaBlock(g: var TSrcGen, n: PNode) =
   gsub(g, n.sons[0])
   putWithSpace(g, tkColon, ":")
   initContext(c)
-  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > maxLineLen):
+  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > MaxLineLen):
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[1], c)
@@ -621,7 +624,7 @@ proc gtry(g: var TSrcGen, n: PNode) =
   put(g, tkTry, "try")
   putWithSpace(g, tkColon, ":")
   initContext(c)
-  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[0], c)
@@ -634,7 +637,7 @@ proc gfor(g: var TSrcGen, n: PNode) =
   initContext(c)
   if longMode(n) or
       (lsub(n.sons[length - 1]) + lsub(n.sons[length - 2]) + 6 + g.lineLen >
-      maxLineLen): 
+      MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcomma(g, n, c, 0, - 3)
   put(g, tkSpaces, Space)
@@ -649,7 +652,7 @@ proc gmacro(g: var TSrcGen, n: PNode) =
   initContext(c)
   gsub(g, n.sons[0])
   putWithSpace(g, tkColon, ":")
-  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)
   gsons(g, n, c, 1)
@@ -700,6 +703,19 @@ proc gproc(g: var TSrcGen, n: PNode) =
       gcoms(g)
       dedent(g)
 
+proc gTypeClassTy(g: var TSrcGen, n: PNode) =
+  var c: TContext
+  initContext(c)
+  putWithSpace(g, tkGeneric, "generic")
+  gsons(g, n[0], c) # arglist
+  gsub(g, n[1]) # pragmas
+  gsub(g, n[2]) # of
+  gcoms(g)
+  indentNL(g)
+  gcoms(g)
+  gstmts(g, n[3], c)
+  dedent(g)
+
 proc gblock(g: var TSrcGen, n: PNode) = 
   var c: TContext
   initContext(c)
@@ -709,7 +725,7 @@ proc gblock(g: var TSrcGen, n: PNode) =
   else:
     put(g, tkBlock, "block")
   putWithSpace(g, tkColon, ":")
-  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[1]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)
   # XXX I don't get why this is needed here! gstmts should already handle this!
@@ -722,7 +738,7 @@ proc gstaticStmt(g: var TSrcGen, n: PNode) =
   putWithSpace(g, tkStatic, "static")
   putWithSpace(g, tkColon, ":")
   initContext(c)
-  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > maxLineLen): 
+  if longMode(n) or (lsub(n.sons[0]) + g.lineLen > MaxLineLen): 
     incl(c.flags, rfLongMode)
   gcoms(g)                    # a good place for comments
   gstmts(g, n.sons[0], c)
@@ -768,7 +784,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
   if n.comment != nil: pushCom(g, n)
   case n.kind                 # atoms:
   of nkTripleStrLit: putRawStr(g, tkTripleStrLit, n.strVal)
-  of nkEmpty: nil
+  of nkEmpty: discard
   of nkType: put(g, tkInvalid, atom(n))
   of nkSym, nkIdent: gident(g, n)
   of nkIntLit: put(g, tkIntLit, atom(n))
@@ -816,7 +832,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
     put(g, tkParRi, ")")
   of nkStaticExpr:
     put(g, tkStatic, "static")
-    put(g, tkSpaces, space)
+    put(g, tkSpaces, Space)
     gsub(g, n.sons[0])
   of nkBracketExpr: 
     gsub(g, n.sons[0])
@@ -833,7 +849,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
     gcomma(g, n, 1)
   of nkCommand: 
     gsub(g, n.sons[0])
-    put(g, tkSpaces, space)
+    put(g, tkSpaces, Space)
     gcomma(g, n, 1)
   of nkExprEqExpr, nkAsgn, nkFastAsgn: 
     gsub(g, n.sons[0])
@@ -940,7 +956,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
   of nkPrefix: 
     gsub(g, n.sons[0])
     if n.len > 1:
-      put(g, tkSpaces, space)
+      put(g, tkSpaces, Space)
       if n.sons[1].kind == nkInfix:
         put(g, tkParLe, "(")
         gsub(g, n.sons[1])
@@ -1053,6 +1069,12 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
       gsub(g, n.sons[0])
     else:
       put(g, tkShared, "shared")
+  of nkStaticTy:
+    put(g, tkStatic, "static")
+    put(g, tkBracketLe, "[")
+    if n.len > 0:
+      gsub(g, n.sons[0])
+    put(g, tkBracketRi, "]")    
   of nkEnumTy:
     if sonsLen(n) > 0:
       putWithSpace(g, tkEnum, "enum")
@@ -1069,7 +1091,7 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
     put(g, tkSpaces, Space)
     putWithSpace(g, tkEquals, "=")
     gsub(g, n.sons[1])
-  of nkStmtList, nkStmtListExpr: gstmts(g, n, emptyContext)
+  of nkStmtList, nkStmtListExpr, nkStmtListType: gstmts(g, n, emptyContext)
   of nkIfStmt: 
     putWithSpace(g, tkIf, "if")
     gif(g, n)
@@ -1246,9 +1268,20 @@ proc gsub(g: var TSrcGen, n: PNode, c: TContext) =
       put(g, tkBracketLe, "[")
       gcomma(g, n)
       put(g, tkBracketRi, "]")
+  of nkMetaNode:
+    put(g, tkParLe, "(META|")
+    gsub(g, n.sons[0])
+    put(g, tkParRi, ")")
+  of nkGotoState, nkState:
+    var c: TContext
+    initContext c
+    putWithSpace g, tkSymbol, if n.kind == nkState: "state" else: "goto"
+    gsons(g, n, c)
+  of nkTypeClassTy:
+    gTypeClassTy(g, n)
   else: 
-    #nkNone, nkMetaNode, nkExplicitTypeListCall: 
-    InternalError(n.info, "rnimsyn.gsub(" & $n.kind & ')')
+    #nkNone, nkExplicitTypeListCall: 
+    internalError(n.info, "rnimsyn.gsub(" & $n.kind & ')')
 
 proc renderTree(n: PNode, renderFlags: TRenderFlags = {}): string = 
   var g: TSrcGen
@@ -1259,7 +1292,7 @@ proc renderTree(n: PNode, renderFlags: TRenderFlags = {}): string =
 proc renderModule(n: PNode, filename: string, 
                   renderFlags: TRenderFlags = {}) =
   var
-    f: tfile
+    f: TFile
     g: TSrcGen
   initSrcGen(g, renderFlags)
   for i in countup(0, sonsLen(n) - 1):
@@ -1268,7 +1301,7 @@ proc renderModule(n: PNode, filename: string,
     case n.sons[i].kind
     of nkTypeSection, nkConstSection, nkVarSection, nkLetSection,
        nkCommentStmt: putNL(g)
-    else: nil
+    else: discard
   gcoms(g)
   if optStdout in gGlobalOptions:
     write(stdout, g.buf)
diff --git a/compiler/rodread.nim b/compiler/rodread.nim
index 6e6b83260..b53135a95 100644
--- a/compiler/rodread.nim
+++ b/compiler/rodread.nim
@@ -184,7 +184,7 @@ proc skipNode(r: PRodReader) =
       if par == 0: break
       dec par
     of '(': inc par
-    else: nil
+    else: discard
     inc pos
   r.pos = pos+1 # skip ')'
 
@@ -248,7 +248,7 @@ proc decodeNodeLazyBody(r: PRodReader, fInfo: TLineInfo,
     if r.s[r.pos] == ')': inc(r.pos)
     else: internalError(result.info, "decodeNode: ')' missing")
   else:
-    InternalError(fInfo, "decodeNode: '(' missing " & $r.pos)
+    internalError(fInfo, "decodeNode: '(' missing " & $r.pos)
 
 proc decodeNode(r: PRodReader, fInfo: TLineInfo): PNode =
   result = decodeNodeLazyBody(r, fInfo, nil)
@@ -286,7 +286,7 @@ proc decodeLoc(r: PRodReader, loc: var TLoc, info: TLineInfo) =
     else: 
       loc.a = 0
     if r.s[r.pos] == '>': inc(r.pos)
-    else: InternalError(info, "decodeLoc " & r.s[r.pos])
+    else: internalError(info, "decodeLoc " & r.s[r.pos])
   
 proc decodeType(r: PRodReader, info: TLineInfo): PType = 
   result = nil
@@ -303,10 +303,10 @@ proc decodeType(r: PRodReader, info: TLineInfo): PType =
     setId(result.id)
     if debugIds: registerID(result)
   else: 
-    InternalError(info, "decodeType: no id")
+    internalError(info, "decodeType: no id")
   # here this also avoids endless recursion for recursive type
-  IdTablePut(gTypeTable, result, result) 
-  if r.s[r.pos] == '(': result.n = decodeNode(r, UnknownLineInfo())
+  idTablePut(gTypeTable, result, result) 
+  if r.s[r.pos] == '(': result.n = decodeNode(r, unknownLineInfo())
   if r.s[r.pos] == '$': 
     inc(r.pos)
     result.flags = cast[TTypeFlags](int32(decodeVInt(r.s, r.pos)))
@@ -335,7 +335,7 @@ proc decodeType(r: PRodReader, info: TLineInfo): PType =
     if r.s[r.pos] == '(': 
       inc(r.pos)
       if r.s[r.pos] == ')': inc(r.pos)
-      else: InternalError(info, "decodeType ^(" & r.s[r.pos])
+      else: internalError(info, "decodeType ^(" & r.s[r.pos])
       rawAddSon(result, nil)
     else: 
       var d = decodeVInt(r.s, r.pos)
@@ -347,10 +347,10 @@ proc decodeLib(r: PRodReader, info: TLineInfo): PLib =
     new(result)
     inc(r.pos)
     result.kind = TLibKind(decodeVInt(r.s, r.pos))
-    if r.s[r.pos] != '|': InternalError("decodeLib: 1")
+    if r.s[r.pos] != '|': internalError("decodeLib: 1")
     inc(r.pos)
     result.name = toRope(decodeStr(r.s, r.pos))
-    if r.s[r.pos] != '|': InternalError("decodeLib: 2")
+    if r.s[r.pos] != '|': internalError("decodeLib: 2")
     inc(r.pos)
     result.path = decodeNode(r, info)
 
@@ -370,21 +370,21 @@ proc decodeSym(r: PRodReader, info: TLineInfo): PSym =
     id = decodeVInt(r.s, r.pos)
     setId(id)
   else:
-    InternalError(info, "decodeSym: no id")
+    internalError(info, "decodeSym: no id")
   if r.s[r.pos] == '&': 
     inc(r.pos)
     ident = getIdent(decodeStr(r.s, r.pos))
   else:
-    InternalError(info, "decodeSym: no ident")
+    internalError(info, "decodeSym: no ident")
   #echo "decoding: {", ident.s
-  result = PSym(IdTableGet(r.syms, id))
+  result = PSym(idTableGet(r.syms, id))
   if result == nil: 
     new(result)
     result.id = id
-    IdTablePut(r.syms, result, result)
+    idTablePut(r.syms, result, result)
     if debugIds: registerID(result)
   elif result.id != id:
-    InternalError(info, "decodeSym: wrong id")
+    internalError(info, "decodeSym: wrong id")
   elif result.kind != skStub and not r.inViewMode:
     # we already loaded the symbol
     return
@@ -427,7 +427,7 @@ proc decodeSym(r: PRodReader, info: TLineInfo): PSym =
   result.annex = decodeLib(r, info)
   if r.s[r.pos] == '#':
     inc(r.pos)
-    result.constraint = decodeNode(r, UnknownLineInfo())
+    result.constraint = decodeNode(r, unknownLineInfo())
   if r.s[r.pos] == '(':
     if result.kind in routineKinds:
       result.ast = decodeNodeLazyBody(r, result.info, result)
@@ -455,10 +455,10 @@ proc skipSection(r: PRodReader) =
         elif c > 0: 
           dec(c)
       of '\0': break          # end of file
-      else: nil
+      else: discard
       inc(r.pos)
   else: 
-    InternalError("skipSection " & $r.line)
+    internalError("skipSection " & $r.line)
   
 proc rdWord(r: PRodReader): string = 
   result = ""
@@ -472,11 +472,11 @@ proc newStub(r: PRodReader, name: string, id: int): PSym =
   result.id = id
   result.name = getIdent(name)
   result.position = r.readerIndex
-  setID(id)                   #MessageOut(result.name.s);
+  setId(id)                   #MessageOut(result.name.s);
   if debugIds: registerID(result)
   
 proc processInterf(r: PRodReader, module: PSym) = 
-  if r.interfIdx == 0: InternalError("processInterf")
+  if r.interfIdx == 0: internalError("processInterf")
   r.pos = r.interfIdx
   while (r.s[r.pos] > '\x0A') and (r.s[r.pos] != ')'): 
     var w = decodeStr(r.s, r.pos)
@@ -485,23 +485,23 @@ proc processInterf(r: PRodReader, module: PSym) =
     inc(r.pos)                # #10
     var s = newStub(r, w, key)
     s.owner = module
-    StrTableAdd(module.tab, s)
-    IdTablePut(r.syms, s, s)
+    strTableAdd(module.tab, s)
+    idTablePut(r.syms, s, s)
 
 proc processCompilerProcs(r: PRodReader, module: PSym) = 
-  if r.compilerProcsIdx == 0: InternalError("processCompilerProcs")
+  if r.compilerProcsIdx == 0: internalError("processCompilerProcs")
   r.pos = r.compilerProcsIdx
   while (r.s[r.pos] > '\x0A') and (r.s[r.pos] != ')'): 
     var w = decodeStr(r.s, r.pos)
     inc(r.pos)
     var key = decodeVInt(r.s, r.pos)
     inc(r.pos)                # #10
-    var s = PSym(IdTableGet(r.syms, key))
+    var s = PSym(idTableGet(r.syms, key))
     if s == nil: 
       s = newStub(r, w, key)
       s.owner = module
-      IdTablePut(r.syms, s, s)
-    StrTableAdd(rodCompilerProcs, s)
+      idTablePut(r.syms, s, s)
+    strTableAdd(rodCompilerprocs, s)
 
 proc processIndex(r: PRodReader; idx: var TIndex; outf: TFile = nil) = 
   var key, val, tmp: int
@@ -516,11 +516,11 @@ proc processIndex(r: PRodReader; idx: var TIndex; outf: TFile = nil) =
     else:
       key = idx.lastIdxKey + 1
       val = tmp + idx.lastIdxVal
-    IITablePut(idx.tab, key, val)
+    iiTablePut(idx.tab, key, val)
     if not outf.isNil: outf.write(key, " ", val, "\n")
     idx.lastIdxKey = key
     idx.lastIdxVal = val
-    setID(key)                # ensure that this id will not be used
+    setId(key)                # ensure that this id will not be used
     if r.s[r.pos] == '\x0A': 
       inc(r.pos)
       inc(r.line)
@@ -539,7 +539,7 @@ proc cmdChangeTriggersRecompilation(old, new: TCommands): bool =
   of cmdNone, cmdDoc, cmdInterpret, cmdPretty, cmdGenDepend, cmdDump,
       cmdCheck, cmdParse, cmdScan, cmdIdeTools, cmdDef, 
       cmdRst2html, cmdRst2tex, cmdInteractive, cmdRun:
-    nil
+    discard
   # else: trigger recompilation:
   result = true
   
@@ -558,7 +558,7 @@ proc processRodFile(r: PRodReader, crc: TCrc32) =
     of "ID": 
       inc(r.pos)              # skip ':'
       r.moduleID = decodeVInt(r.s, r.pos)
-      setID(r.moduleID)
+      setId(r.moduleID)
     of "ORIGFILE":
       inc(r.pos)
       r.origFile = decodeStr(r.s, r.pos)
@@ -603,7 +603,7 @@ proc processRodFile(r: PRodReader, crc: TCrc32) =
         inc(r.pos)            # skip ' '
         inclCrc = decodeVInt(r.s, r.pos)
         if r.reason == rrNone: 
-          if not ExistsFile(w) or (inclCrc != int(crcFromFile(w))): 
+          if not existsFile(w) or (inclCrc != int(crcFromFile(w))): 
             r.reason = rrInclDeps
         if r.s[r.pos] == '\x0A': 
           inc(r.pos)
@@ -639,7 +639,7 @@ proc processRodFile(r: PRodReader, crc: TCrc32) =
       r.initIdx = r.pos + 2   # "(\10"
       skipSection(r)
     else:
-      InternalError("invalid section: '" & section &
+      internalError("invalid section: '" & section &
                     "' at " & $r.line & " in " & r.filename)
       #MsgWriteln("skipping section: " & section &
       #           " at " & $r.line & " in " & r.filename)
@@ -658,7 +658,7 @@ proc newRodReader(modfilename: string, crc: TCrc32,
                   readerIndex: int): PRodReader = 
   new(result)
   try:
-    result.memFile = memfiles.open(modfilename)
+    result.memfile = memfiles.open(modfilename)
   except EOS:
     return nil
   result.files = @[]
@@ -670,13 +670,13 @@ proc newRodReader(modfilename: string, crc: TCrc32,
   r.line = 1
   r.readerIndex = readerIndex
   r.filename = modfilename
-  InitIdTable(r.syms)
+  initIdTable(r.syms)
   # we terminate the file explicitely with ``\0``, so the cast to `cstring`
   # is safe:
-  r.s = cast[cstring](r.memFile.mem)
+  r.s = cast[cstring](r.memfile.mem)
   if startsWith(r.s, "NIM:"): 
-    initIITable(r.index.tab)
-    initIITable(r.imports.tab) # looks like a ROD file
+    initIiTable(r.index.tab)
+    initIiTable(r.imports.tab) # looks like a ROD file
     inc(r.pos, 4)
     var version = ""
     while r.s[r.pos] notin {'\0', '\x0A'}:
@@ -691,12 +691,12 @@ proc newRodReader(modfilename: string, crc: TCrc32,
     result = nil
   
 proc rrGetType(r: PRodReader, id: int, info: TLineInfo): PType = 
-  result = PType(IdTableGet(gTypeTable, id))
+  result = PType(idTableGet(gTypeTable, id))
   if result == nil: 
     # load the type:
     var oldPos = r.pos
-    var d = IITableGet(r.index.tab, id)
-    if d == invalidKey: InternalError(info, "rrGetType")
+    var d = iiTableGet(r.index.tab, id)
+    if d == InvalidKey: internalError(info, "rrGetType")
     r.pos = d + r.dataIdx
     result = decodeType(r, info)
     r.pos = oldPos
@@ -715,7 +715,7 @@ var gMods*: TFileModuleMap = @[]
 
 proc decodeSymSafePos(rd: PRodReader, offset: int, info: TLineInfo): PSym = 
   # all compiled modules
-  if rd.dataIdx == 0: InternalError(info, "dataIdx == 0")
+  if rd.dataIdx == 0: internalError(info, "dataIdx == 0")
   var oldPos = rd.pos
   rd.pos = offset + rd.dataIdx
   result = decodeSym(rd, info)
@@ -725,8 +725,8 @@ proc findSomeWhere(id: int) =
   for i in countup(0, high(gMods)): 
     var rd = gMods[i].rd
     if rd != nil: 
-      var d = IITableGet(rd.index.tab, id)
-      if d != invalidKey:
+      var d = iiTableGet(rd.index.tab, id)
+      if d != InvalidKey:
         echo "found id ", id, " in ", gMods[i].filename
 
 proc getReader(moduleId: int): PRodReader =
@@ -736,37 +736,37 @@ proc getReader(moduleId: int): PRodReader =
   # problems:
   for i in 0 .. <gMods.len:
     result = gMods[i].rd
-    if result != nil and result.moduleId == moduleId: return result
+    if result != nil and result.moduleID == moduleId: return result
   return nil
 
 proc rrGetSym(r: PRodReader, id: int, info: TLineInfo): PSym = 
-  result = PSym(IdTableGet(r.syms, id))
+  result = PSym(idTableGet(r.syms, id))
   if result == nil: 
     # load the symbol:
-    var d = IITableGet(r.index.tab, id)
-    if d == invalidKey: 
+    var d = iiTableGet(r.index.tab, id)
+    if d == InvalidKey: 
       # import from other module:
-      var moduleID = IiTableGet(r.imports.tab, id)
+      var moduleID = iiTableGet(r.imports.tab, id)
       if moduleID < 0:
         var x = ""
         encodeVInt(id, x)
-        InternalError(info, "missing from both indexes: +" & x)
+        internalError(info, "missing from both indexes: +" & x)
       var rd = getReader(moduleID)
-      d = IITableGet(rd.index.tab, id)
-      if d != invalidKey: 
+      d = iiTableGet(rd.index.tab, id)
+      if d != InvalidKey: 
         result = decodeSymSafePos(rd, d, info)
       else:
         var x = ""
         encodeVInt(id, x)
         when false: findSomeWhere(id)
-        InternalError(info, "rrGetSym: no reader found: +" & x)
+        internalError(info, "rrGetSym: no reader found: +" & x)
     else: 
       # own symbol:
       result = decodeSymSafePos(r, d, info)
   if result != nil and result.kind == skStub: rawLoadStub(result)
   
 proc loadInitSection(r: PRodReader): PNode = 
-  if r.initIdx == 0 or r.dataIdx == 0: InternalError("loadInitSection")
+  if r.initIdx == 0 or r.dataIdx == 0: internalError("loadInitSection")
   var oldPos = r.pos
   r.pos = r.initIdx
   result = newNode(nkStmtList)
@@ -775,7 +775,7 @@ proc loadInitSection(r: PRodReader): PNode =
     inc(r.pos)                # #10
     var p = r.pos
     r.pos = d + r.dataIdx
-    addSon(result, decodeNode(r, UnknownLineInfo()))
+    addSon(result, decodeNode(r, unknownLineInfo()))
     r.pos = p
   r.pos = oldPos
 
@@ -783,24 +783,24 @@ proc loadConverters(r: PRodReader) =
   # We have to ensure that no exported converter is a stub anymore, and the
   # import mechanism takes care of the rest.
   if r.convertersIdx == 0 or r.dataIdx == 0: 
-    InternalError("importConverters")
+    internalError("importConverters")
   r.pos = r.convertersIdx
   while r.s[r.pos] > '\x0A': 
     var d = decodeVInt(r.s, r.pos)
-    discard rrGetSym(r, d, UnknownLineInfo())
+    discard rrGetSym(r, d, unknownLineInfo())
     if r.s[r.pos] == ' ': inc(r.pos)
 
 proc loadMethods(r: PRodReader) =
   if r.methodsIdx == 0 or r.dataIdx == 0:
-    InternalError("loadMethods")
+    internalError("loadMethods")
   r.pos = r.methodsIdx
   while r.s[r.pos] > '\x0A':
     var d = decodeVInt(r.s, r.pos)
-    r.methods.add(rrGetSym(r, d, UnknownLineInfo()))
+    r.methods.add(rrGetSym(r, d, unknownLineInfo()))
     if r.s[r.pos] == ' ': inc(r.pos)
 
-proc GetCRC*(fileIdx: int32): TCrc32 =
-  InternalAssert fileIdx >= 0 and fileIdx < gMods.len
+proc getCRC*(fileIdx: int32): TCrc32 =
+  internalAssert fileIdx >= 0 and fileIdx < gMods.len
 
   if gMods[fileIdx].crcDone:
     return gMods[fileIdx].crc
@@ -818,14 +818,14 @@ proc checkDep(fileIdx: int32): TReasonForRecompile =
     # reason has already been computed for this module:
     return gMods[fileIdx].reason
   let filename = fileIdx.toFilename
-  var crc = GetCRC(fileIdx)
+  var crc = getCRC(fileIdx)
   gMods[fileIdx].reason = rrNone  # we need to set it here to avoid cycles
   result = rrNone
   var r: PRodReader = nil
   var rodfile = toGeneratedFile(filename.withPackageName, RodExt)
   r = newRodReader(rodfile, crc, fileIdx)
   if r == nil: 
-    result = (if ExistsFile(rodfile): rrRodInvalid else: rrRodDoesNotExist)
+    result = (if existsFile(rodfile): rrRodInvalid else: rrRodDoesNotExist)
   else:
     processRodFile(r, crc)
     result = r.reason
@@ -834,7 +834,7 @@ proc checkDep(fileIdx: int32): TReasonForRecompile =
       # NOTE: we need to process the entire module graph so that no ID will
       # be used twice! However, compilation speed does not suffer much from
       # this, since results are cached.
-      var res = checkDep(SystemFileIdx)
+      var res = checkDep(systemFileIdx)
       if res != rrNone: result = rrModDeps
       for i in countup(0, high(r.modDeps)):
         res = checkDep(r.modDeps[i])
@@ -845,7 +845,7 @@ proc checkDep(fileIdx: int32): TReasonForRecompile =
     rawMessage(hintProcessing, reasonToFrmt[result] % filename)
   if result != rrNone or optForceFullMake in gGlobalOptions:
     # recompilation is necessary:
-    if r != nil: memfiles.close(r.memFile)
+    if r != nil: memfiles.close(r.memfile)
     r = nil
   gMods[fileIdx].rd = r
   gMods[fileIdx].reason = result  # now we know better
@@ -858,11 +858,11 @@ proc handleSymbolFile(module: PSym): PRodReader =
   idgen.loadMaxIds(options.gProjectPath / options.gProjectName)
 
   discard checkDep(fileIdx)
-  if gMods[fileIdx].reason == rrEmpty: InternalError("handleSymbolFile")
+  if gMods[fileIdx].reason == rrEmpty: internalError("handleSymbolFile")
   result = gMods[fileIdx].rd
   if result != nil: 
     module.id = result.moduleID
-    IdTablePut(result.syms, module, module)
+    idTablePut(result.syms, module, module)
     processInterf(result, module)
     processCompilerProcs(result, module)
     loadConverters(result)
@@ -871,21 +871,21 @@ proc handleSymbolFile(module: PSym): PRodReader =
     module.id = getID()
 
 proc rawLoadStub(s: PSym) =
-  if s.kind != skStub: InternalError("loadStub")
+  if s.kind != skStub: internalError("loadStub")
   var rd = gMods[s.position].rd
   var theId = s.id                # used for later check
-  var d = IITableGet(rd.index.tab, s.id)
-  if d == invalidKey: InternalError("loadStub: invalid key")
-  var rs = decodeSymSafePos(rd, d, UnknownLineInfo())
+  var d = iiTableGet(rd.index.tab, s.id)
+  if d == InvalidKey: internalError("loadStub: invalid key")
+  var rs = decodeSymSafePos(rd, d, unknownLineInfo())
   if rs != s:
     #echo "rs: ", toHex(cast[int](rs.position), int.sizeof * 2),
     #     "\ns:  ", toHex(cast[int](s.position), int.sizeof * 2)
-    InternalError(rs.info, "loadStub: wrong symbol")
+    internalError(rs.info, "loadStub: wrong symbol")
   elif rs.id != theId: 
-    InternalError(rs.info, "loadStub: wrong ID") 
+    internalError(rs.info, "loadStub: wrong ID") 
   #MessageOut('loaded stub: ' + s.name.s);
   
-proc LoadStub*(s: PSym) =
+proc loadStub*(s: PSym) =
   ## loads the stub symbol `s`.
   
   # deactivate the GC here because we do a deep recursion and generate no
@@ -912,8 +912,8 @@ proc getBody*(s: PSym): PNode =
     s.ast.sons[bodyPos] = result
     s.offset = 0
   
-InitIdTable(gTypeTable)
-InitStrTable(rodCompilerProcs)
+initIdTable(gTypeTable)
+initStrTable(rodCompilerprocs)
 
 # viewer:
 proc writeNode(f: TFile; n: PNode) =
@@ -1038,7 +1038,7 @@ proc viewFile(rodfile: string) =
     of "ID": 
       inc(r.pos)              # skip ':'
       r.moduleID = decodeVInt(r.s, r.pos)
-      setID(r.moduleID)
+      setId(r.moduleID)
       outf.writeln("ID:", $r.moduleID)
     of "ORIGFILE":
       inc(r.pos)
@@ -1140,12 +1140,12 @@ proc viewFile(rodfile: string) =
       outf.write("DATA(\n")
       while r.s[r.pos] != ')':
         if r.s[r.pos] == '(':
-          outf.writeNode decodeNode(r, UnknownLineInfo())
+          outf.writeNode decodeNode(r, unknownLineInfo())
           outf.write("\n")
         elif r.s[r.pos] == '[':
-          outf.writeType decodeType(r, UnknownLineInfo())
+          outf.writeType decodeType(r, unknownLineInfo())
         else:
-          outf.writeSym decodeSym(r, UnknownLineInfo())
+          outf.writeSym decodeSym(r, unknownLineInfo())
         if r.s[r.pos] == '\x0A':
           inc(r.pos)
           inc(r.line)
@@ -1166,7 +1166,7 @@ proc viewFile(rodfile: string) =
       if r.s[r.pos] == ')': inc r.pos
       outf.write("<not supported by viewer>)\n")
     else:
-      InternalError("invalid section: '" & section &
+      internalError("invalid section: '" & section &
                     "' at " & $r.line & " in " & r.filename)
       skipSection(r)
     if r.s[r.pos] == '\x0A':
diff --git a/compiler/rodutils.nim b/compiler/rodutils.nim
index 0ee3b1ec4..4433ed4ab 100644
--- a/compiler/rodutils.nim
+++ b/compiler/rodutils.nim
@@ -12,7 +12,7 @@ import strutils
 
 proc c_sprintf(buf, frmt: cstring) {.importc: "sprintf", nodecl, varargs.}
 
-proc ToStrMaxPrecision*(f: BiggestFloat): string = 
+proc toStrMaxPrecision*(f: BiggestFloat): string = 
   if f != f:
     result = "NAN"
   elif f == 0.0:
@@ -36,7 +36,7 @@ proc hexChar(c: char, xi: var int) =
   of '0'..'9': xi = (xi shl 4) or (ord(c) - ord('0'))
   of 'a'..'f': xi = (xi shl 4) or (ord(c) - ord('a') + 10)
   of 'A'..'F': xi = (xi shl 4) or (ord(c) - ord('A') + 10)
-  else: nil
+  else: discard
 
 proc decodeStr*(s: cstring, pos: var int): string =
   var i = pos
@@ -119,7 +119,7 @@ template decodeIntImpl() =
 proc decodeVInt*(s: cstring, pos: var int): int = 
   decodeIntImpl()
 
-proc decodeVBiggestInt*(s: cstring, pos: var int): biggestInt =
+proc decodeVBiggestInt*(s: cstring, pos: var int): BiggestInt =
   decodeIntImpl()
 
 iterator decodeVIntArray*(s: cstring): int =
diff --git a/compiler/rodwrite.nim b/compiler/rodwrite.nim
index 2e52aeaa7..4231da2d0 100644
--- a/compiler/rodwrite.nim
+++ b/compiler/rodwrite.nim
@@ -56,7 +56,7 @@ proc fileIdx(w: PRodWriter, filename: string): int =
     if w.files[i] == filename: 
       return i
   result = len(w.files)
-  setlen(w.files, result + 1)
+  setLen(w.files, result + 1)
   w.files[result] = filename
 
 template filename*(w: PRodWriter): string =
@@ -66,8 +66,8 @@ proc newRodWriter(crc: TCrc32, module: PSym): PRodWriter =
   new(result)
   result.sstack = @[]
   result.tstack = @[]
-  InitIITable(result.index.tab)
-  InitIITable(result.imports.tab)
+  initIiTable(result.index.tab)
+  initIiTable(result.imports.tab)
   result.index.r = ""
   result.imports.r = ""
   result.crc = crc
@@ -101,12 +101,12 @@ proc addInclDep(w: PRodWriter, dep: string) =
 
 proc pushType(w: PRodWriter, t: PType) =
   # check so that the stack does not grow too large:
-  if IiTableGet(w.index.tab, t.id) == invalidKey:
+  if iiTableGet(w.index.tab, t.id) == InvalidKey:
     w.tstack.add(t)
 
 proc pushSym(w: PRodWriter, s: PSym) =
   # check so that the stack does not grow too large:
-  if IiTableGet(w.index.tab, s.id) == invalidKey:
+  if iiTableGet(w.index.tab, s.id) == InvalidKey:
     w.sstack.add(s)
 
 proc encodeNode(w: PRodWriter, fInfo: TLineInfo, n: PNode, 
@@ -120,19 +120,19 @@ proc encodeNode(w: PRodWriter, fInfo: TLineInfo, n: PNode,
   # we do not write comments for now
   # Line information takes easily 20% or more of the filesize! Therefore we
   # omit line information if it is the same as the father's line information:
-  if finfo.fileIndex != n.info.fileIndex: 
+  if fInfo.fileIndex != n.info.fileIndex: 
     result.add('?')
     encodeVInt(n.info.col, result)
     result.add(',')
     encodeVInt(n.info.line, result)
     result.add(',')
     encodeVInt(fileIdx(w, toFilename(n.info)), result)
-  elif finfo.line != n.info.line:
+  elif fInfo.line != n.info.line:
     result.add('?')
     encodeVInt(n.info.col, result)
     result.add(',')
     encodeVInt(n.info.line, result)
-  elif finfo.col != n.info.col:
+  elif fInfo.col != n.info.col:
     result.add('?')
     encodeVInt(n.info.col, result)
   # No need to output the file index, as this is the serialization of one
@@ -190,7 +190,7 @@ proc encodeLoc(w: PRodWriter, loc: TLoc, result: var string) =
   if loc.a != 0: 
     add(result, '?')
     encodeVInt(loc.a, result)
-  if oldlen + 1 == result.len:
+  if oldLen + 1 == result.len:
     # no data was necessary, so remove the '<' again:
     setLen(result, oldLen)
   else:
@@ -202,7 +202,7 @@ proc encodeType(w: PRodWriter, t: PType, result: var string) =
     result.add("[]")
     return
   # we need no surrounding [] here because the type is in a line of its own
-  if t.kind == tyForward: InternalError("encodeType: tyForward")
+  if t.kind == tyForward: internalError("encodeType: tyForward")
   # for the new rodfile viewer we use a preceeding [ so that the data section
   # can easily be disambiguated:
   add(result, '[')
@@ -210,7 +210,7 @@ proc encodeType(w: PRodWriter, t: PType, result: var string) =
   add(result, '+')
   encodeVInt(t.id, result)
   if t.n != nil: 
-    encodeNode(w, UnknownLineInfo(), t.n, result)
+    encodeNode(w, unknownLineInfo(), t.n, result)
   if t.flags != {}: 
     add(result, '$')
     encodeVInt(cast[int32](t.flags), result)
@@ -292,7 +292,7 @@ proc encodeSym(w: PRodWriter, s: PSym, result: var string) =
   if s.annex != nil: encodeLib(w, s.annex, s.info, result)
   if s.constraint != nil:
     add(result, '#')
-    encodeNode(w, UnknownLineInfo(), s.constraint, result)
+    encodeNode(w, unknownLineInfo(), s.constraint, result)
   # lazy loading will soon reload the ast lazily, so the ast needs to be
   # the last entry of a symbol:
   if s.ast != nil:
@@ -322,7 +322,7 @@ proc addToIndex(w: var TIndex, key, val: int) =
   add(w.r, rodNL)
   w.lastIdxKey = key
   w.lastIdxVal = val
-  IiTablePut(w.tab, key, val)
+  iiTablePut(w.tab, key, val)
 
 const debugWrittenIds = false
 
@@ -336,9 +336,9 @@ proc symStack(w: PRodWriter): int =
     if sfForward in s.flags:
       w.sstack[result] = s
       inc result
-    elif IiTableGet(w.index.tab, s.id) == invalidKey:
+    elif iiTableGet(w.index.tab, s.id) == InvalidKey:
       var m = getModule(s)
-      if m == nil: InternalError("symStack: module nil: " & s.name.s)
+      if m == nil: internalError("symStack: module nil: " & s.name.s)
       if (m.id == w.module.id) or (sfFromGeneric in s.flags): 
         # put definition in here
         var L = w.data.len
@@ -364,7 +364,7 @@ proc symStack(w: PRodWriter): int =
         if s.kind == skMethod and sfDispatcher notin s.flags:
           if w.methods.len != 0: add(w.methods, ' ')
           encodeVInt(s.id, w.methods)
-      elif IiTableGet(w.imports.tab, s.id) == invalidKey: 
+      elif iiTableGet(w.imports.tab, s.id) == InvalidKey: 
         addToIndex(w.imports, s.id, m.id)
         when debugWrittenIds:
           if not Contains(debugWritten, s.id):
@@ -374,7 +374,7 @@ proc symStack(w: PRodWriter): int =
             debug(m)
             InternalError("Symbol referred to but never written")
     inc(i)
-  setlen(w.sstack, result)
+  setLen(w.sstack, result)
 
 proc typeStack(w: PRodWriter): int = 
   var i = 0
@@ -383,13 +383,13 @@ proc typeStack(w: PRodWriter): int =
     if t.kind == tyForward:
       w.tstack[result] = t
       inc result
-    elif IiTableGet(w.index.tab, t.id) == invalidKey: 
+    elif iiTableGet(w.index.tab, t.id) == InvalidKey: 
       var L = w.data.len
       addToIndex(w.index, t.id, L)
       encodeType(w, t, w.data)
       add(w.data, rodNL)
     inc(i)
-  setlen(w.tstack, result)
+  setLen(w.tstack, result)
 
 proc processStacks(w: PRodWriter, finalPass: bool) =
   var oldS = 0
@@ -401,7 +401,7 @@ proc processStacks(w: PRodWriter, finalPass: bool) =
     oldS = slen
     oldT = tlen
   if finalPass and (oldS != 0 or oldT != 0):
-    InternalError("could not serialize some forwarded symbols/types")
+    internalError("could not serialize some forwarded symbols/types")
 
 proc rawAddInterfaceSym(w: PRodWriter, s: PSym) = 
   pushSym(w, s)
@@ -416,7 +416,7 @@ proc addInterfaceSym(w: PRodWriter, s: PSym) =
 proc addStmt(w: PRodWriter, n: PNode) = 
   encodeVInt(w.data.len, w.init)
   add(w.init, rodNL)
-  encodeNode(w, UnknownLineInfo(), n, w.data)
+  encodeNode(w, unknownLineInfo(), n, w.data)
   add(w.data, rodNL)
   processStacks(w, false)
 
@@ -534,9 +534,9 @@ proc process(c: PPassContext, n: PNode): PNode =
   of nkProcDef, nkMethodDef, nkIteratorDef, nkConverterDef, 
       nkTemplateDef, nkMacroDef: 
     var s = n.sons[namePos].sym
-    if s == nil: InternalError(n.info, "rodwrite.process")
+    if s == nil: internalError(n.info, "rodwrite.process")
     if n.sons[bodyPos] == nil:
-      InternalError(n.info, "rodwrite.process: body is nil")
+      internalError(n.info, "rodwrite.process: body is nil")
     if n.sons[bodyPos].kind != nkEmpty or s.magic != mNone or
         sfForward notin s.flags:
       addInterfaceSym(w, s)
@@ -549,7 +549,7 @@ proc process(c: PPassContext, n: PNode): PNode =
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if a.sons[0].kind != nkSym: InternalError(a.info, "rodwrite.process")
+      if a.sons[0].kind != nkSym: internalError(a.info, "rodwrite.process")
       var s = a.sons[0].sym
       addInterfaceSym(w, s) 
       # this takes care of enum fields too
@@ -573,11 +573,11 @@ proc process(c: PPassContext, n: PNode): PNode =
   of nkPragma: 
     addStmt(w, n)
   else: 
-    nil
+    discard
 
 proc myOpen(module: PSym): PPassContext =
-  if module.id < 0: InternalError("rodwrite: module ID not set")
-  var w = newRodWriter(module.fileIdx.GetCRC, module)
+  if module.id < 0: internalError("rodwrite: module ID not set")
+  var w = newRodWriter(module.fileIdx.getCRC, module)
   rawAddInterfaceSym(w, module)
   result = w
 
diff --git a/compiler/ropes.nim b/compiler/ropes.nim
index 707c29123..fcf5dd202 100644
--- a/compiler/ropes.nim
+++ b/compiler/ropes.nim
@@ -91,13 +91,13 @@ proc writeRopeIfNotEqual*(r: PRope, filename: string): bool
 proc ropeToStr*(p: PRope): string
 proc ropef*(frmt: TFormatStr, args: varargs[PRope]): PRope
 proc appf*(c: var PRope, frmt: TFormatStr, args: varargs[PRope])
-proc RopeEqualsFile*(r: PRope, f: string): bool
+proc ropeEqualsFile*(r: PRope, f: string): bool
   # returns true if the rope r is the same as the contents of file f
-proc RopeInvariant*(r: PRope): bool
+proc ropeInvariant*(r: PRope): bool
   # exported for debugging
 # implementation
 
-var ErrorHandler*: proc(err: TRopesError, msg: string, useWarning = false)
+var errorHandler*: proc(err: TRopesError, msg: string, useWarning = false)
   # avoid dependency on msgs.nim
   
 proc ropeLen(a: PRope): int = 
@@ -126,7 +126,7 @@ proc resetRopeCache* =
   for i in low(cache)..high(cache):
     cache[i] = nil
 
-proc RopeInvariant(r: PRope): bool = 
+proc ropeInvariant(r: PRope): bool = 
   if r == nil: 
     result = true
   else: 
@@ -157,14 +157,14 @@ proc toRope(s: string): PRope =
     result = nil
   else:
     result = insertInCache(s)
-  assert(RopeInvariant(result))
+  assert(ropeInvariant(result))
 
-proc RopeSeqInsert(rs: var TRopeSeq, r: PRope, at: Natural) = 
+proc ropeSeqInsert(rs: var TRopeSeq, r: PRope, at: Natural) = 
   var length = len(rs)
   if at > length: 
-    setlen(rs, at + 1)
+    setLen(rs, at + 1)
   else: 
-    setlen(rs, length + 1)    # move old rope elements:
+    setLen(rs, length + 1)    # move old rope elements:
   for i in countdown(length, at + 1): 
     rs[i] = rs[i - 1] # this is correct, I used pen and paper to validate it
   rs[at] = r
@@ -177,8 +177,8 @@ proc newRecRopeToStr(result: var string, resultLen: var int, r: PRope) =
       add(stack, it.right)
       it = it.left
     assert(it.data != nil)
-    CopyMem(addr(result[resultLen]), addr(it.data[0]), it.length)
-    Inc(resultLen, it.length)
+    copyMem(addr(result[resultLen]), addr(it.data[0]), it.length)
+    inc(resultLen, it.length)
     assert(resultLen <= len(result))
 
 proc ropeToStr(p: PRope): string = 
@@ -227,13 +227,13 @@ proc writeRope*(f: TFile, c: PRope) =
     assert(it.data != nil)
     write(f, it.data)
 
-proc WriteRope*(head: PRope, filename: string, useWarning = false) =
-  var f: tfile
+proc writeRope*(head: PRope, filename: string, useWarning = false) =
+  var f: TFile
   if open(f, filename, fmWrite):
-    if head != nil: WriteRope(f, head)
+    if head != nil: writeRope(f, head)
     close(f)
   else:
-    ErrorHandler(rCannotOpenFile, filename, useWarning)
+    errorHandler(rCannotOpenFile, filename, useWarning)
 
 var
   rnl* = tnl.newRope
@@ -258,12 +258,12 @@ proc ropef(frmt: TFormatStr, args: varargs[PRope]): PRope =
       of '0'..'9': 
         var j = 0
         while true: 
-          j = (j * 10) + Ord(frmt[i]) - ord('0')
+          j = (j * 10) + ord(frmt[i]) - ord('0')
           inc(i)
           if (i > length + 0 - 1) or not (frmt[i] in {'0'..'9'}): break 
         num = j
         if j > high(args) + 1:
-          ErrorHandler(rInvalidFormatStr, $(j))
+          errorHandler(rInvalidFormatStr, $(j))
         else:
           app(result, args[j - 1])
       of 'n':
@@ -273,22 +273,25 @@ proc ropef(frmt: TFormatStr, args: varargs[PRope]): PRope =
         app(result, rnl)
         inc(i)
       else:
-        ErrorHandler(rInvalidFormatStr, $(frmt[i]))
+        errorHandler(rInvalidFormatStr, $(frmt[i]))
     var start = i
     while i < length:
       if frmt[i] != '$': inc(i)
       else: break
     if i - 1 >= start: 
       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.}
+  assert(ropeInvariant(result))
+
+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))
@@ -296,10 +299,10 @@ proc appf(c: var PRope, frmt: TFormatStr, args: varargs[PRope]) =
 const 
   bufSize = 1024              # 1 KB is reasonable
 
-proc auxRopeEqualsFile(r: PRope, bin: var tfile, buf: Pointer): bool = 
+proc auxRopeEqualsFile(r: PRope, bin: var TFile, buf: pointer): bool = 
   if r.data != nil:
     if r.length > bufSize:
-      ErrorHandler(rTokenTooLong, r.data)
+      errorHandler(rTokenTooLong, r.data)
       return
     var readBytes = readBuffer(bin, buf, r.length)
     result = readBytes == r.length and
@@ -308,12 +311,12 @@ proc auxRopeEqualsFile(r: PRope, bin: var tfile, buf: Pointer): bool =
     result = auxRopeEqualsFile(r.left, bin, buf)
     if result: result = auxRopeEqualsFile(r.right, bin, buf)
   
-proc RopeEqualsFile(r: PRope, f: string): bool = 
-  var bin: tfile
+proc ropeEqualsFile(r: PRope, f: string): bool = 
+  var bin: TFile
   result = open(bin, f)
   if not result: 
     return                    # not equal if file does not exist
-  var buf = alloc(BufSize)
+  var buf = alloc(bufSize)
   result = auxRopeEqualsFile(r, bin, buf)
   if result: 
     result = readBuffer(bin, buf, bufSize) == 0 # really at the end of file?
@@ -346,7 +349,7 @@ proc newCrcFromRopeAux(r: PRope, startVal: TCrc32): TCrc32 =
       inc(i)
 
 proc crcFromRope(r: PRope): TCrc32 = 
-  result = newCrcFromRopeAux(r, initCrc32)
+  result = newCrcFromRopeAux(r, InitCrc32)
 
 proc writeRopeIfNotEqual(r: PRope, filename: string): bool = 
   # returns true if overwritten
diff --git a/compiler/saturate.nim b/compiler/saturate.nim
index e0968843b..ed197bdd1 100644
--- a/compiler/saturate.nim
+++ b/compiler/saturate.nim
@@ -9,7 +9,7 @@
 
 ## Saturated arithmetic routines. XXX Make part of the stdlib?
 
-proc `|+|`*(a, b: biggestInt): biggestInt =
+proc `|+|`*(a, b: BiggestInt): BiggestInt =
   ## saturated addition.
   result = a +% b
   if (result xor a) >= 0'i64 or (result xor b) >= 0'i64:
@@ -19,7 +19,7 @@ proc `|+|`*(a, b: biggestInt): biggestInt =
   else:
     result = high(result)
 
-proc `|-|`*(a, b: biggestInt): biggestInt =
+proc `|-|`*(a, b: BiggestInt): BiggestInt =
   result = a -% b
   if (result xor a) >= 0'i64 or (result xor not b) >= 0'i64:
     return result
@@ -28,14 +28,14 @@ proc `|-|`*(a, b: biggestInt): biggestInt =
   else:
     result = high(result)
 
-proc `|abs|`*(a: biggestInt): biggestInt =
+proc `|abs|`*(a: BiggestInt): BiggestInt =
   if a != low(a):
     if a >= 0: result = a
     else: result = -a
   else:
     result = low(a)
 
-proc `|div|`*(a, b: biggestInt): biggestInt =
+proc `|div|`*(a, b: BiggestInt): BiggestInt =
   # (0..5) div (0..4) == (0..5) div (1..4) == (0 div 4) .. (5 div 1)
   if b == 0'i64:
     # make the same as ``div 1``:
@@ -45,13 +45,13 @@ proc `|div|`*(a, b: biggestInt): biggestInt =
   else:
     result = a div b
 
-proc `|mod|`*(a, b: biggestInt): biggestInt =
+proc `|mod|`*(a, b: BiggestInt): BiggestInt =
   if b == 0'i64:
     result = a
   else:
     result = a mod b
 
-proc `|*|`*(a, b: biggestInt): biggestInt =
+proc `|*|`*(a, b: BiggestInt): BiggestInt =
   var
     resAsFloat, floatProd: float64
   result = a *% b
diff --git a/compiler/sem.nim b/compiler/sem.nim
index 3ace623bc..e89e32f4e 100644
--- a/compiler/sem.nim
+++ b/compiler/sem.nim
@@ -14,8 +14,8 @@ import
   wordrecg, ropes, msgs, os, condsyms, idents, renderer, types, platform, math,
   magicsys, parser, nversion, nimsets, semfold, importer,
   procfind, lookups, rodread, pragmas, passes, semdata, semtypinst, sigmatch,
-  semthreads, intsets, transf, evals, idgen, aliases, cgmeth, lambdalifting,
-  evaltempl, patterns, parampatterns, sempass2
+  semthreads, intsets, transf, vmdef, vm, idgen, aliases, cgmeth, lambdalifting,
+  evaltempl, patterns, parampatterns, sempass2, pretty, semmacrosanity
 
 # implementation
 
@@ -43,30 +43,30 @@ proc activate(c: PContext, n: PNode)
 proc semQuoteAst(c: PContext, n: PNode): PNode
 proc finishMethod(c: PContext, s: PSym)
 
-proc IndexTypesMatch(c: PContext, f, a: PType, arg: PNode): PNode
+proc indexTypesMatch(c: PContext, f, a: PType, arg: PNode): PNode
 
 proc typeMismatch(n: PNode, formal, actual: PType) = 
   if formal.kind != tyError and actual.kind != tyError: 
-    LocalError(n.Info, errGenerated, msgKindToString(errTypeMismatch) &
+    localError(n.info, errGenerated, msgKindToString(errTypeMismatch) &
         typeToString(actual) & ") " &
         `%`(msgKindToString(errButExpectedX), [typeToString(formal)]))
 
 proc fitNode(c: PContext, formal: PType, arg: PNode): PNode =
   if arg.typ.isNil:
-    LocalError(arg.info, errExprXHasNoType,
+    localError(arg.info, errExprXHasNoType,
                renderTree(arg, {renderNoComments}))
     # error correction:
     result = copyNode(arg)
     result.typ = formal
   else:
-    result = IndexTypesMatch(c, formal, arg.typ, arg)
+    result = indexTypesMatch(c, formal, arg.typ, arg)
     if result == nil:
       typeMismatch(arg, formal, arg.typ)
       # error correction:
-      result = copyNode(arg)
+      result = copyTree(arg)
       result.typ = formal
 
-var CommonTypeBegin = PType(kind: tyExpr)
+var commonTypeBegin = PType(kind: tyExpr)
 
 proc commonType*(x, y: PType): PType =
   # new type relation that is used for array constructors,
@@ -134,8 +134,8 @@ proc newSymG*(kind: TSymKind, n: PNode, c: PContext): PSym =
   # like newSymS, but considers gensym'ed symbols
   if n.kind == nkSym:
     result = n.sym
-    InternalAssert sfGenSym in result.flags
-    InternalAssert result.kind == kind
+    internalAssert sfGenSym in result.flags
+    internalAssert result.kind == kind
   else:
     result = newSym(kind, considerAcc(n), getCurrOwner(), n.info)
 
@@ -146,73 +146,108 @@ proc semIdentWithPragma(c: PContext, kind: TSymKind, n: PNode,
                         allowed: TSymFlags): PSym
 proc semStmtScope(c: PContext, n: PNode): PNode
 
-proc ParamsTypeCheck(c: PContext, typ: PType) {.inline.} =
+proc paramsTypeCheck(c: PContext, typ: PType) {.inline.} =
   if not typeAllowed(typ, skConst):
-    LocalError(typ.n.info, errXisNoType, typeToString(typ))
+    localError(typ.n.info, errXisNoType, typeToString(typ))
 
 proc expectMacroOrTemplateCall(c: PContext, n: PNode): PSym
 proc semTemplateExpr(c: PContext, n: PNode, s: PSym, semCheck = true): PNode
 proc semDirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode
 proc semWhen(c: PContext, n: PNode, semCheck: bool = true): PNode
-proc IsOpImpl(c: PContext, n: PNode): PNode
+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 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)
-
-proc createEvalContext(c: PContext, mode: TEvalMode): PEvalContext =
-  result = newEvalContext(c.module, mode)
-  result.getType = proc (n: PNode): PNode =
-    result = tryExpr(c, n)
-    if result == nil:
-      result = newSymNode(errorSym(c, n))
-    elif result.typ == nil:
-      result = newSymNode(getSysSym"void")
+  proc createEvalContext(c: PContext, mode: TEvalMode): PEvalContext =
+    result = newEvalContext(c.module, mode)
+    result.getType = proc (n: PNode): PNode =
+      result = tryExpr(c, n)
+      if result == nil:
+        result = newSymNode(errorSym(c, n))
+      elif result.typ == nil:
+        result = newSymNode(getSysSym"void")
+      else:
+        result.typ = makeTypeDesc(c, result.typ)
+    
+    result.handleIsOperator = proc (n: PNode): PNode =
+      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:
+  when true:
+    if eOrig.typ.kind in {tyExpr, tyStmt, tyTypeDesc}:
+      result = semExprWithType(c, evaluated)
     else:
-      result.typ = makeTypeDesc(c, result.typ)
+      result = evaluated
+      semmacrosanity.annotateType(result, eOrig.typ)
+  else:
+    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
 
-  result.handleIsOperator = proc (n: PNode): PNode =
-    result = IsOpImpl(c, n)
+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
 
-proc evalConstExpr(c: PContext, module: PSym, e: PNode): PNode = 
-  result = evalConstExprAux(c.createEvalContext(emConst), module, nil, e)
+  try:
+    result = evalConstExpr(c.module, e)
+    if result == nil or result.kind == nkEmpty:
+      return nil
 
-proc evalStaticExpr(c: PContext, module: PSym, e: PNode, prc: PSym): PNode = 
-  result = evalConstExprAux(c.createEvalContext(emStatic), module, prc, e)
+    result = fixupTypeAfterEval(c, result, e)
+  except:
+    return nil
 
 proc semConstExpr(c: PContext, n: PNode): PNode =
   var e = semExprWithType(c, n)
   if e == nil:
-    LocalError(n.info, errConstExprExpected)
+    localError(n.info, errConstExprExpected)
     return n
   result = getConstExpr(c.module, e)
   if result == nil:
-    result = evalConstExpr(c, c.module, e)
+    result = evalConstExpr(c.module, e)
     if result == nil or result.kind == nkEmpty:
       if e.info != n.info:
         pushInfoContext(n.info)
-        LocalError(e.info, errConstExprExpected)
+        localError(e.info, errConstExprExpected)
         popInfoContext()
       else:
-        LocalError(e.info, errConstExprExpected)
+        localError(e.info, errConstExprExpected)
       # error correction:
       result = e
+    else:
+      result = fixupTypeAfterEval(c, result, e)
 
 include hlo, seminst, semcall
 
 proc semAfterMacroCall(c: PContext, n: PNode, s: PSym): PNode = 
   inc(evalTemplateCounter)
   if evalTemplateCounter > 100:
-    GlobalError(s.info, errTemplateInstantiationTooNested)
+    globalError(s.info, errTemplateInstantiationTooNested)
+  let oldFriend = c.friendModule
+  c.friendModule = s.owner.getModule
 
   result = n
   if s.typ.sons[0] == nil:
@@ -236,17 +271,18 @@ proc semAfterMacroCall(c: PContext, n: PNode, s: PSym): PNode =
       result = fitNode(c, s.typ.sons[0], result)
       #GlobalError(s.info, errInvalidParamKindX, typeToString(s.typ.sons[0]))
   dec(evalTemplateCounter)
+  c.friendModule = oldFriend
 
 proc semMacroExpr(c: PContext, n, nOrig: PNode, sym: PSym, 
                   semCheck: bool = true): PNode = 
   markUsed(n, sym)
   if sym == c.p.owner:
-    GlobalError(n.info, errRecursiveDependencyX, sym.name.s)
+    globalError(n.info, errRecursiveDependencyX, sym.name.s)
 
-  if c.evalContext == nil:
-    c.evalContext = c.createEvalContext(emStatic)
+  #if c.evalContext == nil:
+  #  c.evalContext = c.createEvalContext(emStatic)
 
-  result = evalMacroCall(c.evalContext, n, nOrig, sym)
+  result = evalMacroCall(c.module, n, nOrig, sym)
   if semCheck: result = semAfterMacroCall(c, result, sym)
 
 proc forceBool(c: PContext, n: PNode): PNode = 
@@ -257,13 +293,21 @@ proc semConstBoolExpr(c: PContext, n: PNode): PNode =
   let nn = semExprWithType(c, n)
   result = fitNode(c, getSysType(tyBool), nn)
   if result == nil:
-    LocalError(n.info, errConstExprExpected)
+    localError(n.info, errConstExprExpected)
     return nn
   result = getConstExpr(c.module, result)
   if result == nil: 
-    LocalError(n.info, errConstExprExpected)
+    localError(n.info, errConstExprExpected)
     result = nn
 
+type
+  TSemGenericFlag = enum
+    withinBind, withinTypeDesc, withinMixin
+  TSemGenericFlags = set[TSemGenericFlag]
+
+proc semGenericStmt(c: PContext, n: PNode, flags: TSemGenericFlags,
+                    ctx: var TIntSet): PNode
+
 include semtypes, semtempl, semgnrc, semstmts, semexprs
 
 proc addCodeForGenerics(c: PContext, n: PNode) =
@@ -271,17 +315,18 @@ proc addCodeForGenerics(c: PContext, n: PNode) =
     var prc = c.generics[i].inst.sym
     if prc.kind in {skProc, skMethod, skConverter} and prc.magic == mNone:
       if prc.ast == nil or prc.ast.sons[bodyPos] == nil:
-        InternalError(prc.info, "no code for " & prc.name.s)
+        internalError(prc.info, "no code for " & prc.name.s)
       else:
         addSon(n, prc.ast)
   c.lastGenericIdx = c.generics.len
 
 proc myOpen(module: PSym): PPassContext =
   var c = newContext(module)
-  if c.p != nil: InternalError(module.info, "sem.myOpen")
+  if c.p != nil: internalError(module.info, "sem.myOpen")
   c.semConstExpr = semConstExpr
   c.semExpr = semExpr
   c.semTryExpr = tryExpr
+  c.semTryConstExpr = tryConstExpr
   c.semOperand = semOperand
   c.semConstBoolExpr = semConstBoolExpr
   c.semOverloadedCall = semOverloadedCall
@@ -291,10 +336,10 @@ proc myOpen(module: PSym): PPassContext =
   c.importTable = openScope(c)
   c.importTable.addSym(module) # a module knows itself
   if sfSystemModule in module.flags: 
-    magicsys.SystemModule = module # set global variable!
+    magicsys.systemModule = module # set global variable!
   else: 
-    c.importTable.addSym magicsys.SystemModule # import the "System" identifier
-    importAllSymbols(c, magicsys.SystemModule)
+    c.importTable.addSym magicsys.systemModule # import the "System" identifier
+    importAllSymbols(c, magicsys.systemModule)
   c.topLevelScope = openScope(c)
   result = c
 
@@ -302,7 +347,7 @@ proc myOpenCached(module: PSym, rd: PRodReader): PPassContext =
   result = myOpen(module)
   for m in items(rd.methods): methodDef(m, true)
 
-proc SemStmtAndGenerateGenerics(c: PContext, n: PNode): PNode = 
+proc semStmtAndGenerateGenerics(c: PContext, n: PNode): PNode = 
   result = semStmt(c, n)
   # BUGFIX: process newly generated generics here, not at the end!
   if c.lastGenericIdx < c.generics.len:
@@ -317,7 +362,7 @@ proc SemStmtAndGenerateGenerics(c: PContext, n: PNode): PNode =
     result = buildEchoStmt(c, result)
   result = transformStmt(c.module, result)
     
-proc RecoverContext(c: PContext) = 
+proc recoverContext(c: PContext) = 
   # clean up in case of a semantic error: We clean up the stacks, etc. This is
   # faster than wrapping every stack operation in a 'try finally' block and 
   # requires far less code.
@@ -329,15 +374,15 @@ proc myProcess(context: PPassContext, n: PNode): PNode =
   var c = PContext(context)    
   # no need for an expensive 'try' if we stop after the first error anyway:
   if msgs.gErrorMax <= 1:
-    result = SemStmtAndGenerateGenerics(c, n)
+    result = semStmtAndGenerateGenerics(c, n)
   else:
     let oldContextLen = msgs.getInfoContextLen()
-    let oldInGenericInst = c.InGenericInst
+    let oldInGenericInst = c.inGenericInst
     try:
-      result = SemStmtAndGenerateGenerics(c, n)
+      result = semStmtAndGenerateGenerics(c, n)
     except ERecoverableError, ESuggestDone:
-      RecoverContext(c)
-      c.InGenericInst = oldInGenericInst
+      recoverContext(c)
+      c.inGenericInst = oldInGenericInst
       msgs.setInfoContextLen(oldContextLen)
       if getCurrentException() of ESuggestDone: result = nil
       else: result = ast.emptyNode
@@ -346,7 +391,7 @@ proc myProcess(context: PPassContext, n: PNode): PNode =
 proc checkThreads(c: PContext) =
   if not needsGlobalAnalysis(): return
   for i in 0 .. c.threadEntries.len-1:
-    semthreads.AnalyseThreadProc(c.threadEntries[i])
+    semthreads.analyseThreadProc(c.threadEntries[i])
   
 proc myClose(context: PPassContext, n: PNode): PNode = 
   var c = PContext(context)
@@ -354,7 +399,7 @@ proc myClose(context: PPassContext, n: PNode): PNode =
   rawCloseScope(c)      # imported symbols; don't check for unused ones!
   result = newNode(nkStmtList)
   if n != nil:
-    InternalError(n.info, "n is not nil") #result := n;
+    internalError(n.info, "n is not nil") #result := n;
   addCodeForGenerics(c, result)
   if c.module.ast != nil:
     result.add(c.module.ast)
diff --git a/compiler/semcall.nim b/compiler/semcall.nim
index 9e9614796..6b19dc359 100644
--- a/compiler/semcall.nim
+++ b/compiler/semcall.nim
@@ -19,7 +19,7 @@ proc sameMethodDispatcher(a, b: PSym): bool =
       if aa.sym == bb.sym: 
         result = true
     else:
-      nil
+      discard
       # generics have no dispatcher yet, so we need to compare the method
       # names; however, the names are equal anyway because otherwise we
       # wouldn't even consider them to be overloaded. But even this does
@@ -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:
@@ -71,16 +71,16 @@ proc pickBestCandidate(c: PContext, headSymbol: PNode,
           var cmp = cmpCandidates(best, z)
           if cmp < 0: best = z   # x is better than the best so far
           elif cmp == 0: alt = z # x is as good as the best so far
-          else: nil
+          else: discard
     sym = nextOverloadIter(o, c, headSymbol)
 
-proc NotFoundError*(c: PContext, n: PNode, errors: seq[string]) =
+proc notFoundError*(c: PContext, n: PNode, errors: seq[string]) =
   # Gives a detailed error message; this is separated from semOverloadedCall,
   # as semOverlodedCall is already pretty slow (and we need this information
   # only in case of an error).
-  if c.InCompilesContext > 0: 
+  if c.inCompilesContext > 0: 
     # fail fast:
-    GlobalError(n.info, errTypeMismatch, "")
+    globalError(n.info, errTypeMismatch, "")
   var result = msgKindToString(errTypeMismatch)
   add(result, describeArgs(c, n, 1 + ord(nfDelegate in n.flags)))
   add(result, ')')
@@ -93,7 +93,7 @@ proc NotFoundError*(c: PContext, n: PNode, errors: seq[string]) =
   if candidates != "":
     add(result, "\n" & msgKindToString(errButExpected) & "\n" & candidates)
 
-  LocalError(n.Info, errGenerated, result)
+  localError(n.info, errGenerated, result)
 
 proc gatherUsedSyms(c: PContext, usedSyms: var seq[PNode]) =
   for scope in walkScopes(c.currentScope):
@@ -139,7 +139,7 @@ proc resolveOverloads(c: PContext, n, orig: PNode,
   let overloadsState = result.state
   if overloadsState != csMatch:
     if nfDelegate in n.flags:
-      InternalAssert f.kind == nkIdent
+      internalAssert f.kind == nkIdent
       let calleeName = newStrNode(nkStrLit, f.ident.s)
       calleeName.info = n.info
 
@@ -150,26 +150,26 @@ proc resolveOverloads(c: PContext, n, orig: PNode,
       pickBest(callOp)
 
     if overloadsState == csEmpty and result.state == csEmpty:
-      LocalError(n.info, errUndeclaredIdentifier, considerAcc(f).s)
+      localError(n.info, errUndeclaredIdentifier, considerAcc(f).s)
       return
     elif result.state != csMatch:
       if nfExprCall in n.flags:
-        LocalError(n.info, errExprXCannotBeCalled,
+        localError(n.info, errExprXCannotBeCalled,
                    renderTree(n, {renderNoComments}))
       else:
         errors = @[]
         pickBest(f)
-        NotFoundError(c, n, errors)
+        notFoundError(c, n, errors)
       return
 
   if alt.state == csMatch and cmpCandidates(result, alt) == 0 and
       not sameMethodDispatcher(result.calleeSym, alt.calleeSym):
-    InternalAssert result.state == csMatch
+    internalAssert result.state == csMatch
     #writeMatches(result)
     #writeMatches(alt)
     if c.inCompilesContext > 0: 
       # quick error message for performance of 'compiles' built-in:
-      GlobalError(n.Info, errGenerated, "ambiguous call")
+      globalError(n.info, errGenerated, "ambiguous call")
     elif gErrorCounter == 0:
       # don't cascade errors
       var args = "("
@@ -178,7 +178,7 @@ proc resolveOverloads(c: PContext, n, orig: PNode,
         add(args, typeToString(n.sons[i].typ))
       add(args, ")")
 
-      LocalError(n.Info, errGenerated, msgKindToString(errAmbiguousCallXYZ) % [
+      localError(n.info, errGenerated, msgKindToString(errAmbiguousCallXYZ) % [
         getProcHeader(result.calleeSym), getProcHeader(alt.calleeSym),
         args])
 
@@ -197,17 +197,17 @@ proc instGenericConvertersSons*(c: PContext, n: PNode, x: TCandidate) =
     for i in 1 .. <n.len:
       instGenericConvertersArg(c, n.sons[i], x)
 
-proc IndexTypesMatch(c: PContext, f, a: PType, arg: PNode): PNode = 
+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 = 
+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)
 
@@ -225,7 +225,7 @@ proc semResolvedCall(c: PContext, n: PNode, x: TCandidate): PNode =
       result = x.call
       result.sons[0] = newSymNode(finalCallee, result.sons[0].info)
       result.typ = finalCallee.typ.sons[0]
-      if ContainsGenericType(result.typ): result.typ = errorType(c)
+      if containsGenericType(result.typ): result.typ = errorType(c)
       return
   result = x.call
   instGenericConvertersSons(c, result, x)
@@ -239,13 +239,13 @@ proc semOverloadedCall(c: PContext, n, nOrig: PNode,
   # else: result = errorNode(c, n)
     
 proc explicitGenericInstError(n: PNode): PNode =
-  LocalError(n.info, errCannotInstantiateX, renderTree(n))
+  localError(n.info, errCannotInstantiateX, renderTree(n))
   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)
 
@@ -260,7 +260,7 @@ proc explicitGenericInstantiation(c: PContext, n: PNode, s: PSym): PNode =
     # number of generic type parameters:
     if safeLen(s.ast.sons[genericParamsPos]) != n.len-1:
       let expected = safeLen(s.ast.sons[genericParamsPos])
-      LocalError(n.info, errGenerated, "cannot instantiate: " & renderTree(n) &
+      localError(n.info, errGenerated, "cannot instantiate: " & renderTree(n) &
          "; got " & $(n.len-1) & " type(s) but expected " & $expected)
       return n
     result = explicitGenericSym(c, n, s)
@@ -283,7 +283,7 @@ proc explicitGenericInstantiation(c: PContext, n: PNode, s: PSym): PNode =
   else:
     result = explicitGenericInstError(n)
 
-proc SearchForBorrowProc(c: PContext, startScope: PScope, fn: PSym): PSym =
+proc searchForBorrowProc(c: PContext, startScope: PScope, fn: PSym): PSym =
   # Searchs for the fn in the symbol table. If the parameter lists are suitable
   # for borrowing the sym in the symbol table is returned, else nil.
   # New approach: generate fn(x, y, z) where x, y, z have the proper types
diff --git a/compiler/semdata.nim b/compiler/semdata.nim
index d02359d4c..980abb865 100644
--- a/compiler/semdata.nim
+++ b/compiler/semdata.nim
@@ -13,7 +13,7 @@ import
   strutils, lists, intsets, options, lexer, ast, astalgo, trees, treetab,
   wordrecg, 
   ropes, msgs, platform, os, condsyms, idents, renderer, types, extccomp, math, 
-  magicsys, nversion, nimsets, parser, times, passes, rodread, evals
+  magicsys, nversion, nimsets, parser, times, passes, rodread, vmdef
 
 type 
   TOptionEntry* = object of lists.TListEntry # entries to put on a
@@ -21,7 +21,7 @@ type
     options*: TOptions
     defaultCC*: TCallingConvention
     dynlib*: PLib
-    Notes*: TNoteKinds
+    notes*: TNoteKinds
     otherPragmas*: PNode      # every pragma can be pushed
 
   POptionEntry* = ref TOptionEntry
@@ -32,7 +32,7 @@ type
     resultSym*: PSym          # the result symbol (if we are in a proc)
     nestedLoopCounter*: int   # whether we are in a loop or not
     nestedBlockCounter*: int  # whether we are in a block or not
-    InTryStmt*: int           # whether we are in a try statement; works also
+    inTryStmt*: int           # whether we are in a try statement; works also
                               # in standalone ``except`` and ``finally``
     next*: PProcCon           # used for stacking procedure contexts
   
@@ -55,16 +55,16 @@ type
     friendModule*: PSym        # current friend module; may access private data;
                                # this is used so that generic instantiations
                                # can access private object fields
-    InstCounter*: int          # to prevent endless instantiations
+    instCounter*: int          # to prevent endless instantiations
    
     threadEntries*: TSymSeq    # list of thread entries to check
-    AmbiguousSymbols*: TIntSet # ids of all ambiguous symbols (cannot
+    ambiguousSymbols*: TIntSet # ids of all ambiguous symbols (cannot
                                # store this info in the syms themselves!)
-    InTypeClass*: int          # > 0 if we are in a user-defined type class
-    InGenericContext*: int     # > 0 if we are in a generic type
-    InUnrolledContext*: int    # > 0 if we are unrolling a loop
-    InCompilesContext*: int    # > 0 if we are in a ``compiles`` magic
-    InGenericInst*: int        # > 0 if we are instantiating a generic
+    inTypeClass*: int          # > 0 if we are in a user-defined type class
+    inGenericContext*: int     # > 0 if we are in a generic type
+    inUnrolledContext*: int    # > 0 if we are unrolling a loop
+    inCompilesContext*: int    # > 0 if we are in a ``compiles`` magic
+    inGenericInst*: int        # > 0 if we are instantiating a generic
     converters*: TSymSeq       # sequence of converters
     patterns*: TSymSeq         # sequence of pattern matchers
     optionStack*: TLinkedList
@@ -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,
@@ -83,7 +84,7 @@ type
     includedFiles*: TIntSet    # used to detect recursive include files
     userPragmas*: TStrTable
     evalContext*: PEvalContext
-    UnknownIdents*: TIntSet    # ids of all unknown identifiers to prevent
+    unknownIdents*: TIntSet    # ids of all unknown identifiers to prevent
                                # naming it multiple times
     generics*: seq[TInstantiationPair] # pending list of instantiated generics to compile
     lastGenericIdx*: int      # used for the generics stack
@@ -114,8 +115,8 @@ proc scopeDepth*(c: PContext): int {.inline.} =
 
 # owner handling:
 proc getCurrOwner*(): PSym
-proc PushOwner*(owner: PSym)
-proc PopOwner*()
+proc pushOwner*(owner: PSym)
+proc popOwner*()
 # implementation
 
 var gOwners*: seq[PSym] = @[]
@@ -128,20 +129,20 @@ proc getCurrOwner(): PSym =
   # BUGFIX: global array is needed!
   result = gOwners[high(gOwners)]
 
-proc PushOwner(owner: PSym) = 
+proc pushOwner(owner: PSym) = 
   add(gOwners, owner)
 
-proc PopOwner() = 
+proc popOwner() = 
   var length = len(gOwners)
-  if length > 0: setlen(gOwners, length - 1)
-  else: InternalError("popOwner")
+  if length > 0: setLen(gOwners, length - 1)
+  else: internalError("popOwner")
 
 proc lastOptionEntry(c: PContext): POptionEntry = 
   result = POptionEntry(c.optionStack.tail)
 
 proc pushProcCon*(c: PContext, owner: PSym) {.inline.} = 
   if owner == nil: 
-    InternalError("owner is nil")
+    internalError("owner is nil")
     return
   var x: PProcCon
   new(x)
@@ -160,7 +161,7 @@ proc newOptionEntry(): POptionEntry =
 
 proc newContext(module: PSym): PContext =
   new(result)
-  result.AmbiguousSymbols = initIntset()
+  result.ambiguousSymbols = initIntSet()
   initLinkedList(result.optionStack)
   initLinkedList(result.libs)
   append(result.optionStack, newOptionEntry())
@@ -172,13 +173,13 @@ proc newContext(module: PSym): PContext =
   result.includedFiles = initIntSet()
   initStrTable(result.userPragmas)
   result.generics = @[]
-  result.UnknownIdents = initIntSet()
+  result.unknownIdents = initIntSet()
 
 proc inclSym(sq: var TSymSeq, s: PSym) =
   var L = len(sq)
   for i in countup(0, L - 1): 
     if sq[i].id == s.id: return 
-  setlen(sq, L + 1)
+  setLen(sq, L + 1)
   sq[L] = s
 
 proc addConverter*(c: PContext, conv: PSym) =
@@ -198,29 +199,55 @@ proc addToLib(lib: PLib, sym: PSym) =
 
 proc makePtrType(c: PContext, baseType: PType): PType = 
   result = newTypeS(tyPtr, c)
-  addSonSkipIntLit(result, baseType.AssertNotNil)
+  addSonSkipIntLit(result, baseType.assertNotNil)
 
 proc makeVarType(c: PContext, baseType: PType): PType = 
   result = newTypeS(tyVar, c)
-  addSonSkipIntLit(result, baseType.AssertNotNil)
+  addSonSkipIntLit(result, baseType.assertNotNil)
 
 proc makeTypeDesc*(c: PContext, typ: PType): PType =
   result = newTypeS(tyTypeDesc, c)
-  result.addSonSkipIntLit(typ.AssertNotNil)
+  result.addSonSkipIntLit(typ.assertNotNil)
 
 proc makeTypeSymNode*(c: PContext, typ: PType, info: TLineInfo): PNode =
   let typedesc = makeTypeDesc(c, typ)
   let sym = newSym(skType, idAnon, getCurrOwner(), info).linkTo(typedesc)
   return newSymNode(sym, info)
 
-proc newTypeS(kind: TTypeKind, c: PContext): PType = 
-  result = newType(kind, getCurrOwner())
+proc makeTypeFromExpr*(c: PContext, n: PNode): PType =
+  result = newTypeS(tyFromExpr, c)
+  result.n = n
 
 proc newTypeWithSons*(c: PContext, kind: TTypeKind,
                       sons: seq[PType]): PType =
   result = newType(kind, getCurrOwner())
   result.sons = sons
 
+proc makeStaticExpr*(c: PContext, n: PNode): PNode =
+  result = newNodeI(nkStaticExpr, n.info)
+  result.sons = @[n]
+  result.typ = newTypeWithSons(c, tyStatic, @[n.typ])
+
+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 errorType*(c: PContext): PType =
   ## creates a type representing an error state
   result = newTypeS(tyError, c)
@@ -234,7 +261,7 @@ proc fillTypeS(dest: PType, kind: TTypeKind, c: PContext) =
   dest.owner = getCurrOwner()
   dest.size = - 1
 
-proc makeRangeType*(c: PContext; first, last: biggestInt;
+proc makeRangeType*(c: PContext; first, last: BiggestInt;
                     info: TLineInfo; intType = getSysType(tyInt)): PType =
   var n = newNodeI(nkRange, info)
   addSon(n, newIntTypeNode(nkIntLit, first, intType))
@@ -249,7 +276,7 @@ proc markIndirect*(c: PContext, s: PSym) {.inline.} =
     # XXX add to 'c' for global analysis
 
 proc illFormedAst*(n: PNode) =
-  GlobalError(n.info, errIllFormedAstX, renderTree(n, {renderNoComments}))
+  globalError(n.info, errIllFormedAstX, renderTree(n, {renderNoComments}))
 
 proc checkSonsLen*(n: PNode, length: int) = 
   if sonsLen(n) != length: illFormedAst(n)
diff --git a/compiler/semdestruct.nim b/compiler/semdestruct.nim
index 797d8895e..fb05826cb 100644
--- a/compiler/semdestruct.nim
+++ b/compiler/semdestruct.nim
@@ -9,26 +9,39 @@
 
 ## This module implements destructors.
 
+# included from sem.nim
 
 # special marker values that indicates that we are
 # 1) AnalyzingDestructor: currently analyzing the type for destructor 
 # generation (needed for recursive types)
 # 2) DestructorIsTrivial: completed the analysis before and determined
 # that the type has a trivial destructor
-var AnalyzingDestructor, DestructorIsTrivial: PSym
-new(AnalyzingDestructor)
-new(DestructorIsTrivial)
+var analyzingDestructor, destructorIsTrivial: PSym
+new(analyzingDestructor)
+new(destructorIsTrivial)
 
 var
   destructorName = getIdent"destroy_"
   destructorParam = getIdent"this_"
-  destructorPragma = newIdentNode(getIdent"destructor", UnknownLineInfo())
+  destructorPragma = newIdentNode(getIdent"destructor", unknownLineInfo())
   rangeDestructorProc*: PSym
 
-proc instantiateDestructor(c: PContext, typ: PType): bool
+proc instantiateDestructor(c: PContext, typ: PType): PType
 
 proc doDestructorStuff(c: PContext, s: PSym, n: PNode) =
-  let t = s.typ.sons[1].skipTypes({tyVar})
+  var t = s.typ.sons[1].skipTypes({tyVar})
+  if t.kind == tyGenericInvokation:
+    for i in 1 .. <t.sonsLen:
+      if t.sons[i].kind != tyGenericParam:
+        localError(n.info, errDestructorNotGenericEnough)
+        return
+    t = t.base
+  elif t.kind == tyCompositeTypeClass:
+    t = t.base
+    if t.kind != tyGenericBody:
+      localError(n.info, errDestructorNotGenericEnough)
+      return
+  
   t.destructor = s
   # automatically insert calls to base classes' destructors
   if n.sons[bodyPos].kind != nkEmpty:
@@ -36,15 +49,17 @@ proc doDestructorStuff(c: PContext, s: PSym, n: PNode) =
       # when inheriting directly from object
       # there will be a single nil son
       if t.sons[i] == nil: continue
-      if instantiateDestructor(c, t.sons[i]):
+      let destructableT = instantiateDestructor(c, t.sons[i])
+      if destructableT != nil:
         n.sons[bodyPos].addSon(newNode(nkCall, t.sym.info, @[
-            useSym(t.sons[i].destructor),
+            useSym(destructableT.destructor),
             n.sons[paramsPos][1][0]]))
 
 proc destroyField(c: PContext, field: PSym, holder: PNode): PNode =
-  if instantiateDestructor(c, field.typ):
+  let destructableT = instantiateDestructor(c, field.typ)
+  if destructableT != nil:
     result = newNode(nkCall, field.info, @[
-      useSym(field.typ.destructor),
+      useSym(destructableT.destructor),
       newNode(nkDotExpr, field.info, @[holder, useSym(field)])])
 
 proc destroyCase(c: PContext, n: PNode, holder: PNode): PNode =
@@ -90,7 +105,7 @@ proc generateDestructor(c: PContext, t: PType): PNode =
   # Tposix_spawnattr
   if t.n == nil or t.n.sons == nil: return
   internalAssert t.n.kind == nkRecList
-  let destructedObj = newIdentNode(destructorParam, UnknownLineInfo())
+  let destructedObj = newIdentNode(destructorParam, unknownLineInfo())
   # call the destructods of all fields
   for s in countup(0, t.n.sons.len - 1):
     case t.n.sons[s].kind
@@ -101,32 +116,44 @@ proc generateDestructor(c: PContext, t: PType): PNode =
       let stmt = destroyField(c, t.n.sons[s].sym, destructedObj)
       if stmt != nil: addLine(stmt)
     else:
-      internalAssert false
+      # XXX just skip it for now so that the compiler doesn't crash, but
+      # please zahary fix it! arbitrary nesting of nkRecList/nkRecCase is
+      # possible. Any thread example seems to trigger this. 
+      discard
   # base classes' destructors will be automatically called by
   # semProcAux for both auto-generated and user-defined destructors
 
-proc instantiateDestructor(c: PContext, typ: PType): bool =
-  # returns true if the type already had a user-defined
-  # destructor or if the compiler generated a default
-  # member-wise one
-  var t = skipTypes(typ, {tyConst, tyMutable})
+proc instantiateDestructor(c: PContext, typ: PType): PType =
+  # returns nil if a variable of type `typ` doesn't require a
+  # destructor. Otherwise, returns the type, which holds the 
+  # destructor that must be used for the varialbe.
+  # The destructor is either user-defined or automatically
+  # generated by the compiler in a member-wise fashion.
+  var t = skipTypes(typ, {tyConst, tyMutable}).skipGenericAlias
+  let typeHoldingUserDefinition = if t.kind == tyGenericInst: t.base
+                                  else: t
   
-  if t.destructor != nil:
+  if typeHoldingUserDefinition.destructor != nil:
     # XXX: This is not entirely correct for recursive types, but we need
     # it temporarily to hide the "destroy is already defined" problem
-    return t.destructor notin [AnalyzingDestructor, DestructorIsTrivial]
+    if typeHoldingUserDefinition.destructor notin
+        [analyzingDestructor, destructorIsTrivial]:
+      return typeHoldingUserDefinition
+    else:
+      return nil
   
+  t = t.skipTypes({tyGenericInst})
   case t.kind
   of tySequence, tyArray, tyArrayConstr, tyOpenArray, tyVarargs:
-    if instantiateDestructor(c, t.sons[0]):
+    if instantiateDestructor(c, t.sons[0]) != nil:
       if rangeDestructorProc == nil:
         rangeDestructorProc = searchInScopes(c, getIdent"nimDestroyRange")
       t.destructor = rangeDestructorProc
-      return true
+      return t
     else:
-      return false
+      return nil
   of tyTuple, tyObject:
-    t.destructor = AnalyzingDestructor
+    t.destructor = analyzingDestructor
     let generated = generateDestructor(c, t)
     if generated != nil:
       internalAssert t.sym != nil
@@ -139,21 +166,21 @@ proc instantiateDestructor(c: PContext, typ: PType): bool =
           emptyNode,
           newNode(nkIdentDefs, i, @[
             newIdentNode(destructorParam, i),
-            useSym(t.sym),
+            symNodeFromType(c, makeVarType(c, t), t.sym.info),
             emptyNode]),
           ]),
         newNode(nkPragma, i, @[destructorPragma]),
         emptyNode,
         generated
         ])
-      discard semProc(c, fullDef)
-      internalAssert t.destructor != nil
-      return true
+      let semantizedDef = semProc(c, fullDef)
+      t.destructor = semantizedDef[namePos].sym
+      return t
     else:
-      t.destructor = DestructorIsTrivial
-      return false
+      t.destructor = destructorIsTrivial
+      return nil
   else:
-    return false
+    return nil
 
 proc insertDestructors(c: PContext,
                        varSection: PNode): tuple[outer, inner: PNode] =
@@ -179,9 +206,11 @@ proc insertDestructors(c: PContext,
       varId = varSection[j][0]
       varTyp = varId.sym.typ
       info = varId.info
-
-    if varTyp != nil and instantiateDestructor(c, varTyp) and 
-        sfGlobal notin varId.sym.flags:
+    
+    if varTyp == nil or sfGlobal in varId.sym.flags: continue
+    let destructableT = instantiateDestructor(c, varTyp)
+    
+    if destructableT != nil:
       var tryStmt = newNodeI(nkTryStmt, info)
 
       if j < totalVars - 1:
@@ -198,11 +227,11 @@ proc insertDestructors(c: PContext,
       else:
         result.inner = newNodeI(nkStmtList, info)
         tryStmt.addSon(result.inner)
-
+    
       tryStmt.addSon(
         newNode(nkFinally, info, @[
           semStmt(c, newNode(nkCall, info, @[
-            useSym(varTyp.destructor),
+            useSym(destructableT.destructor),
             useSym(varId.sym)]))]))
 
       result.outer = newNodeI(nkStmtList, info)
diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim
index ccbb1e367..84303b6cd 100644
--- a/compiler/semexprs.nim
+++ b/compiler/semexprs.nim
@@ -30,7 +30,7 @@ proc semOperand(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
     # XXX tyGenericInst here?
     if result.typ.kind == tyVar: result = newDeref(result)
   else:
-    LocalError(n.info, errExprXHasNoType, 
+    localError(n.info, errExprXHasNoType, 
                renderTree(result, {renderNoComments}))
     result.typ = errorType(c)
 
@@ -40,9 +40,9 @@ proc semExprWithType(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
     # do not produce another redundant error message:
     #raiseRecoverableError("")
     result = errorNode(c, n)
-  if result.typ == nil or result.typ == EnforceVoidContext:
+  if result.typ == nil or result.typ == enforceVoidContext:
     # we cannot check for 'void' in macros ...
-    LocalError(n.info, errExprXHasNoType, 
+    localError(n.info, errExprXHasNoType, 
                renderTree(result, {renderNoComments}))
     result.typ = errorType(c)
   else:
@@ -57,7 +57,7 @@ proc semExprNoDeref(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
     # do not produce another redundant error message:
     result = errorNode(c, n)
   if result.typ == nil:
-    LocalError(n.info, errExprXHasNoType, 
+    localError(n.info, errExprXHasNoType, 
                renderTree(result, {renderNoComments}))
     result.typ = errorType(c)
   else:
@@ -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,13 +111,13 @@ 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:
       result = semExpr(c, s.ast)
     else:
-      InternalError(n.info, "no default for")
+      internalError(n.info, "no default for")
       result = emptyNode
   of skType:
     markUsed(n, s)
@@ -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:
@@ -151,31 +151,31 @@ proc checkConvertible(castDest, src: PType): TConvStatus =
     return
   var d = skipTypes(castDest, abstractVar)
   var s = skipTypes(src, abstractVar-{tyTypeDesc})
-  while (d != nil) and (d.Kind in {tyPtr, tyRef}) and (d.Kind == s.Kind):
+  while (d != nil) and (d.kind in {tyPtr, tyRef}) and (d.kind == s.kind):
     d = base(d)
     s = base(s)
   if d == nil:
     result = convNotLegal
-  elif d.Kind == tyObject and s.Kind == tyObject:
+  elif d.kind == tyObject and s.kind == tyObject:
     result = checkConversionBetweenObjects(d, s)
-  elif (skipTypes(castDest, abstractVarRange).Kind in IntegralTypes) and
-      (skipTypes(src, abstractVarRange-{tyTypeDesc}).Kind in IntegralTypes):
+  elif (skipTypes(castDest, abstractVarRange).kind in IntegralTypes) and
+      (skipTypes(src, abstractVarRange-{tyTypeDesc}).kind in IntegralTypes):
     # 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
     else:
-      nil
+      discard
 
 proc isCastable(dst, src: PType): bool = 
   #const
   #  castableTypeKinds = {tyInt, tyPtr, tyRef, tyCstring, tyString, 
   #                       tySequence, tyPointer, tyNil, tyOpenArray,
   #                       tyProc, tySet, tyEnum, tyBool, tyChar}
-  var ds, ss: biggestInt
+  var ds, ss: BiggestInt
   # this is very unrestrictive; cast is allowed if castDest.size >= src.size
   ds = computeSize(dst)
   ss = computeSize(src)
@@ -193,7 +193,7 @@ proc isSymChoice(n: PNode): bool {.inline.} =
 
 proc semConv(c: PContext, n: PNode): PNode =
   if sonsLen(n) != 2:
-    LocalError(n.info, errConvNeedsOneArg)
+    localError(n.info, errConvNeedsOneArg)
     return n
   result = newNodeI(nkConv, n.info)
   result.typ = semTypeNode(c, n.sons[0], nil).skipTypes({tyGenericInst})
@@ -202,18 +202,18 @@ 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 convOK: discard
     of convNotNeedeed:
-      Message(n.info, hintConvFromXtoItselfNotNeeded, result.typ.typeToString)
+      message(n.info, hintConvFromXtoItselfNotNeeded, result.typ.typeToString)
     of convNotLegal:
-      LocalError(n.info, errGenerated, MsgKindToString(errIllegalConvFromXtoY)%
+      localError(n.info, errGenerated, msgKindToString(errIllegalConvFromXtoY)%
         [op.typ.typeToString, result.typ.typeToString])
   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)
@@ -228,36 +228,39 @@ proc semCast(c: PContext, n: PNode): PNode =
   result.typ = semTypeNode(c, n.sons[0], nil)
   addSon(result, copyTree(n.sons[0]))
   addSon(result, semExprWithType(c, n.sons[1]))
-  if not isCastable(result.typ, result.sons[1].Typ): 
-    LocalError(result.info, errExprCannotBeCastedToX, 
-               typeToString(result.Typ))
-  
+  if not isCastable(result.typ, result.sons[1].typ): 
+    localError(result.info, errExprCannotBeCastedToX, 
+               typeToString(result.typ))
+
 proc semLowHigh(c: PContext, n: PNode, m: TMagic): PNode = 
   const 
     opToStr: array[mLow..mHigh, string] = ["low", "high"]
   if sonsLen(n) != 2: 
-    LocalError(n.info, errXExpectsTypeOrValue, opToStr[m])
+    localError(n.info, errXExpectsTypeOrValue, opToStr[m])
   else: 
     n.sons[1] = semExprWithType(c, n.sons[1], {efDetermineType})
-    var typ = skipTypes(n.sons[1].typ, abstractVarRange)
-    case typ.Kind
+    var typ = skipTypes(n.sons[1].typ, abstractVarRange +
+                                       {tyTypeDesc, tyFieldAccessor})
+    case typ.kind
     of tySequence, tyString, tyOpenArray, tyVarargs: 
       n.typ = getSysType(tyInt)
     of tyArrayConstr, tyArray: 
       n.typ = typ.sons[0] # indextype
     of tyInt..tyInt64, tyChar, tyBool, tyEnum, tyUInt8, tyUInt16, tyUInt32: 
       # do not skip the range!
-      n.typ = n.sons[1].typ.skipTypes(abstractVar)
+      n.typ = n.sons[1].typ.skipTypes(abstractVar + {tyFieldAccessor})
     of tyGenericParam:
-      # leave it for now, it will be resolved in semtypinst
-      n.typ = getSysType(tyInt)
+      # prepare this for resolving in semtypinst:
+      # we must use copyTree here in order to avoid creating a cycle
+      # that could easily turn into an infinite recursion in semtypinst
+      n.typ = makeTypeFromExpr(c, n.copyTree)
     else:
-      LocalError(n.info, errInvalidArgForX, opToStr[m])
+      localError(n.info, errInvalidArgForX, opToStr[m])
   result = n
 
 proc semSizeof(c: PContext, n: PNode): PNode =
   if sonsLen(n) != 2:
-    LocalError(n.info, errXExpectsTypeOrValue, "sizeof")
+    localError(n.info, errXExpectsTypeOrValue, "sizeof")
   else:
     n.sons[1] = semExprWithType(c, n.sons[1], {efDetermineType})
     #restoreOldStyleType(n.sons[1])
@@ -276,9 +279,9 @@ proc semOf(c: PContext, n: PNode): PNode =
     let y = skipTypes(n.sons[2].typ, abstractPtrs-{tyTypeDesc})
 
     if x.kind == tyTypeDesc or y.kind != tyTypeDesc:
-      LocalError(n.info, errXExpectsObjectTypes, "of")
+      localError(n.info, errXExpectsObjectTypes, "of")
     elif b.kind != tyObject or a.kind != tyObject:
-      LocalError(n.info, errXExpectsObjectTypes, "of")
+      localError(n.info, errXExpectsObjectTypes, "of")
     else:
       let diff = inheritanceDiff(a, b)
       # | returns: 0 iff `a` == `b`
@@ -287,24 +290,24 @@ proc semOf(c: PContext, n: PNode): PNode =
       # | returns: `maxint` iff `a` and `b` are not compatible at all
       if diff <= 0:
         # optimize to true:
-        Message(n.info, hintConditionAlwaysTrue, renderTree(n))
+        message(n.info, hintConditionAlwaysTrue, renderTree(n))
         result = newIntNode(nkIntLit, 1)
         result.info = n.info
         result.typ = getSysType(tyBool)
         return result
       elif diff == high(int):
-        LocalError(n.info, errXcanNeverBeOfThisSubtype, typeToString(a))
+        localError(n.info, errXcanNeverBeOfThisSubtype, typeToString(a))
   else:
-    LocalError(n.info, errXExpectsTwoArguments, "of")
+    localError(n.info, errXExpectsTwoArguments, "of")
   n.typ = getSysType(tyBool)
   result = n
 
 proc isOpImpl(c: PContext, n: PNode): PNode =
-  InternalAssert n.sonsLen == 3 and
-    n[1].kind == nkSym and n[1].sym.kind == skType and
+  internalAssert n.sonsLen == 3 and
+    n[1].typ != nil and n[1].typ.kind == tyTypeDesc and
     n[2].kind in {nkStrLit..nkTripleStrLit, nkType}
   
-  let t1 = n[1].sym.typ.skipTypes({tyTypeDesc})
+  let t1 = n[1].typ.skipTypes({tyTypeDesc, tyFieldAccessor})
 
   if n[2].kind in {nkStrLit..nkTripleStrLit}:
     case n[2].strVal.normalize
@@ -319,31 +322,20 @@ proc isOpImpl(c: PContext, n: PNode): PNode =
                                         t.callConv == ccClosure and 
                                         tfIterator in t.flags))
   else:
-    var match: bool
-    let t2 = n[2].typ
-    case t2.kind
-    of tyTypeClasses:
-      var m: TCandidate
-      InitCandidate(m, t2)
-      match = matchUserTypeClass(c, m, emptyNode, t2, t1) != nil
-    of tyOrdinal:
-      var m: TCandidate
-      InitCandidate(m, t2)
-      match = isOrdinalType(t1)
-    of tySequence, tyArray, tySet:
-      var m: TCandidate
-      InitCandidate(m, t2)
-      match = typeRel(m, t2, t1) != isNone
-    else:
-      match = sameType(t1, t2)
- 
+    var t2 = n[2].typ.skipTypes({tyTypeDesc})
+    let lifted = liftParamType(c, skType, newNodeI(nkArgList, n.info),
+                               t2, ":anon", n.info)
+    if lifted != nil: t2 = lifted
+    var m: TCandidate
+    initCandidate(c, m, t2)
+    let match = typeRel(m, t2, t1) != isNone
     result = newIntNode(nkIntLit, ord(match))
 
   result.typ = n.typ
 
 proc semIs(c: PContext, n: PNode): PNode =
   if sonsLen(n) != 3:
-    LocalError(n.info, errXExpectsTwoArguments, "is")
+    localError(n.info, errXExpectsTwoArguments, "is")
 
   result = n
   n.typ = getSysType(tyBool)
@@ -394,8 +386,8 @@ proc changeType(n: PNode, newType: PType, check: bool) =
       changeType(n.sons[i], elemType(newType), check)
   of nkPar: 
     if newType.kind != tyTuple: 
-      InternalError(n.info, "changeType: no tuple type for constructor")
-    elif newType.n == nil: nil
+      internalError(n.info, "changeType: no tuple type for constructor")
+    elif newType.n == nil: discard
     elif sonsLen(n) > 0 and n.sons[0].kind == nkExprColonExpr: 
       for i in countup(0, sonsLen(n) - 1): 
         var m = n.sons[i].sons[0]
@@ -419,9 +411,9 @@ proc changeType(n: PNode, newType: PType, check: bool) =
     if check:
       let value = n.intVal
       if value < firstOrd(newType) or value > lastOrd(newType):
-        LocalError(n.info, errGenerated, "cannot convert " & $value &
+        localError(n.info, errGenerated, "cannot convert " & $value &
                                          " to " & typeToString(newType))
-  else: nil
+  else: discard
   n.typ = newType
 
 proc arrayConstrType(c: PContext, n: PNode): PType = 
@@ -431,7 +423,7 @@ proc arrayConstrType(c: PContext, n: PNode): PType =
     rawAddSon(typ, newTypeS(tyEmpty, c)) # needs an empty basetype!
   else:
     var x = n.sons[0]
-    var lastIndex: biggestInt = sonsLen(n) - 1
+    var lastIndex: BiggestInt = sonsLen(n) - 1
     var t = skipTypes(n.sons[0].typ, {tyGenericInst, tyVar, tyOrdinal})
     addSonSkipIntLit(typ, t)
   typ.sons[0] = makeRangeType(c, 0, sonsLen(n) - 1, n.info)
@@ -445,7 +437,7 @@ proc semArrayConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
     rawAddSon(result.typ, newTypeS(tyEmpty, c)) # needs an empty basetype!
   else:
     var x = n.sons[0]
-    var lastIndex: biggestInt = 0
+    var lastIndex: BiggestInt = 0
     var indexType = getSysType(tyInt)
     if x.kind == nkExprColonExpr and sonsLen(x) == 2: 
       var idx = semConstExpr(c, x.sons[0])
@@ -508,10 +500,10 @@ proc fixAbstractType(c: PContext, n: PNode) =
         changeType(it.sons[1], s, check=true)
         n.sons[i] = it.sons[1]
     of nkBracket: 
-      # an implicitely constructed array (passed to an open array):
+      # an implicitly constructed array (passed to an open array):
       n.sons[i] = semArrayConstr(c, it, {})
     else: 
-      nil
+      discard
       #if (it.typ == nil): 
       #  InternalError(it.info, "fixAbstractType: " & renderTree(it))  
   
@@ -582,7 +574,7 @@ proc analyseIfAddressTakenInCall(c: PContext, n: PNode) =
           skipTypes(t.sons[i], abstractInst-{tyTypeDesc}).kind == tyVar: 
         if isAssignable(c, n.sons[i]) notin {arLValue, arLocalLValue}: 
           if n.sons[i].kind != nkHiddenAddr:
-            LocalError(n.sons[i].info, errVarForOutParamNeeded)
+            localError(n.sons[i].info, errVarForOutParamNeeded)
     return
   for i in countup(1, sonsLen(n) - 1):
     if n.sons[i].kind == nkHiddenCallConv:
@@ -640,25 +632,25 @@ proc evalAtCompileTime(c: PContext, n: PNode): PNode =
       call.add(a)
     #echo "NOW evaluating at compile time: ", call.renderTree
     if sfCompileTime in callee.flags:
-      result = evalStaticExpr(c, c.module, call, c.p.owner)
+      result = evalStaticExpr(c.module, call, c.p.owner)
       if result.isNil: 
-        LocalError(n.info, errCannotInterpretNodeX, renderTree(call))
+        localError(n.info, errCannotInterpretNodeX, renderTree(call))
     else:
-      result = evalConstExpr(c, c.module, call)
+      result = evalConstExpr(c.module, call)
       if result.isNil: result = n
     #if result != n:
     #  echo "SUCCESS evaluated at compile time: ", call.renderTree
 
 proc semStaticExpr(c: PContext, n: PNode): PNode =
   let a = semExpr(c, n.sons[0])
-  result = evalStaticExpr(c, c.module, a, c.p.owner)
+  result = evalStaticExpr(c.module, a, c.p.owner)
   if result.isNil:
-    LocalError(n.info, errCannotInterpretNodeX, renderTree(n))
+    localError(n.info, errCannotInterpretNodeX, renderTree(n))
     result = emptyNode
 
 proc semOverloadedCallAnalyseEffects(c: PContext, n: PNode, nOrig: PNode,
                                      flags: TExprFlags): PNode =
-  if flags*{efInTypeOf, efWantIterator} != {}:
+  if flags*{efInTypeof, efWantIterator} != {}:
     # consider: 'for x in pReturningArray()' --> we don't want the restriction
     # to 'skIterator' anymore; skIterator is preferred in sigmatch already for
     # typeof support.
@@ -668,16 +660,17 @@ 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")
+      internalError("semOverloadedCallAnalyseEffects")
       return
     let callee = result.sons[0].sym
     case callee.kind
-    of skMacro, skTemplate: nil
+    of skMacro, skTemplate: discard
     else:
       if (callee.kind == skIterator) and (callee.id == c.p.owner.id): 
-        LocalError(n.info, errRecursiveDependencyX, callee.name.s)
+        localError(n.info, errRecursiveDependencyX, callee.name.s)
       if sfNoSideEffect notin callee.flags: 
         if {sfImportc, sfSideEffect} * callee.flags != {}:
           incl(c.p.owner.flags, sfSideEffect)
@@ -702,16 +695,16 @@ proc semIndirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode =
   semOpAux(c, n)
   var t: PType = nil
   if n.sons[0].typ != nil:
-    t = skipTypes(n.sons[0].typ, abstractInst-{tyTypedesc})
+    t = skipTypes(n.sons[0].typ, abstractInst-{tyTypeDesc})
   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:
         # speed up error generation:
-        GlobalError(n.Info, errTypeMismatch, "")
+        globalError(n.info, errTypeMismatch, "")
         return emptyNode
       else:
         var hasErrorType = false
@@ -726,7 +719,7 @@ proc semIndirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode =
         if not hasErrorType:
           add(msg, ")\n" & msgKindToString(errButExpected) & "\n" &
               typeToString(n.sons[0].typ))
-          LocalError(n.Info, errGenerated, msg)
+          localError(n.info, errGenerated, msg)
         return errorNode(c, n)
       result = nil
     else:
@@ -771,7 +764,7 @@ proc afterCallActions(c: PContext; n, orig: PNode, flags: TExprFlags): PNode =
     analyseIfAddressTakenInCall(c, result)
     if callee.magic != mNone:
       result = magicsAfterOverloadResolution(c, result, flags)
-  if c.InTypeClass == 0:
+  if c.inTypeClass == 0:
     result = evalAtCompileTime(c, result)
 
 proc semDirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode = 
@@ -780,6 +773,7 @@ proc semDirectOp(c: PContext, n: PNode, flags: TExprFlags): PNode =
   #semLazyOpAux(c, n)
   result = semOverloadedCallAnalyseEffects(c, n, nOrig, flags)
   if result != nil: result = afterCallActions(c, result, nOrig, flags)
+  else: result = errorNode(c, n)
 
 proc buildStringify(c: PContext, arg: PNode): PNode = 
   if arg.typ != nil and 
@@ -800,7 +794,7 @@ proc semEcho(c: PContext, n: PNode): PNode =
     let t = arg.typ
     if (t == nil or t.skipTypes(abstractInst).kind != tyString) and 
         arg.kind != nkEmpty:
-      LocalError(n.info, errGenerated,
+      localError(n.info, errGenerated,
                  "implicitly invoked '$' does not return string")
   let t = n.sons[0].typ
   if tfNoSideEffect notin t.flags: incl(c.p.owner.flags, sfSideEffect)
@@ -809,11 +803,11 @@ proc semEcho(c: PContext, n: PNode): PNode =
 proc buildEchoStmt(c: PContext, n: PNode): PNode = 
   # we MUST not check 'n' for semantics again here!
   result = newNodeI(nkCall, n.info)
-  var e = StrTableGet(magicsys.systemModule.Tab, getIdent"echo")
+  var e = strTableGet(magicsys.systemModule.tab, getIdent"echo")
   if e != nil:
     addSon(result, newSymNode(e))
   else:
-    LocalError(n.info, errSystemNeeds, "echo")
+    localError(n.info, errSystemNeeds, "echo")
     addSon(result, errorNode(c, n))
   var arg = buildStringify(c, n)
   # problem is: implicit '$' is not checked for semantics yet. So we give up
@@ -843,7 +837,7 @@ proc lookupInRecordAndBuildCheck(c: PContext, n, r: PNode, field: PIdent,
       if result != nil: return 
   of nkRecCase: 
     checkMinSonsLen(r, 2)
-    if (r.sons[0].kind != nkSym): IllFormedAst(r)
+    if (r.sons[0].kind != nkSym): illFormedAst(r)
     result = lookupInRecordAndBuildCheck(c, n, r.sons[0], field, check)
     if result != nil: return 
     var s = newNodeI(nkCurly, r.info)
@@ -905,8 +899,9 @@ proc builtinFieldAccess(c: PContext, n: PNode, flags: TExprFlags): PNode =
   # early exit for this; see tests/compile/tbindoverload.nim:
   if isSymChoice(n.sons[1]): return
 
-  var s = qualifiedLookup(c, n, {checkAmbiguity, checkUndeclared})
+  var s = qualifiedLookUp(c, n, {checkAmbiguity, checkUndeclared})
   if s != nil:
+    markUsed(n.sons[1], s)
     return semSym(c, n, s, flags)
 
   n.sons[0] = semExprWithType(c, n.sons[0], flags+{efDetermineType})
@@ -937,19 +932,26 @@ 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)
             return newSymNode(copySym(tParam.sym).linkTo(foundTyp), n.info)
       return
+    of tyObject, tyTuple:
+      if ty.n.kind == nkRecList:
+        for field in ty.n.sons:
+          if field.sym.name == i:
+            n.typ = newTypeWithSons(c, tyFieldAccessor, @[ty, field.sym.typ])
+            n.typ.n = copyTree(n)
+            return n
     else:
       # echo "TYPE FIELD ACCESS"
       # debug ty
       return
     # XXX: This is probably not relevant any more
     # reset to prevent 'nil' bug: see "tests/reject/tenumitems.nim":
-    ty = n.sons[0].Typ
+    ty = n.sons[0].typ
     
   ty = skipTypes(ty, {tyGenericInst, tyVar, tyPtr, tyRef})
   var check: PNode = nil
@@ -963,10 +965,10 @@ proc builtinFieldAccess(c: PContext, n: PNode, flags: TExprFlags): PNode =
     if f != nil:
       if fieldVisible(c, f):
         # is the access to a public field or in the same module or in a friend?
+        markUsed(n.sons[1], f)
         n.sons[0] = makeDeref(n.sons[0])
         n.sons[1] = newSymNode(f) # we now have the correct field
         n.typ = f.typ
-        markUsed(n, f)
         if check == nil: 
           result = n
         else: 
@@ -976,11 +978,11 @@ proc builtinFieldAccess(c: PContext, n: PNode, flags: TExprFlags): PNode =
   elif ty.kind == tyTuple and ty.n != nil: 
     f = getSymFromList(ty.n, i)
     if f != nil:
+      markUsed(n.sons[1], f)
       n.sons[0] = makeDeref(n.sons[0])
       n.sons[1] = newSymNode(f)
       n.typ = f.typ
       result = n
-      markUsed(n, f)
 
 proc dotTransformation(c: PContext, n: PNode): PNode =
   if isSymChoice(n.sons[1]):
@@ -1037,7 +1039,7 @@ proc semSubscript(c: PContext, n: PNode, flags: TExprFlags): PNode =
       n.sons[i] = semExprWithType(c, n.sons[i], 
                                   flags*{efInTypeof, efDetermineType})
     var indexType = if arr.kind == tyArray: arr.sons[0] else: getSysType(tyInt)
-    var arg = IndexTypesMatch(c, indexType, n.sons[1].typ, n.sons[1])
+    var arg = indexTypesMatch(c, indexType, n.sons[1].typ, n.sons[1])
     if arg != nil:
       n.sons[1] = arg
       result = n
@@ -1059,11 +1061,11 @@ proc semSubscript(c: PContext, n: PNode, flags: TExprFlags): PNode =
         {tyInt..tyInt64}: 
       var idx = getOrdValue(n.sons[1])
       if idx >= 0 and idx < sonsLen(arr): n.typ = arr.sons[int(idx)]
-      else: LocalError(n.info, errInvalidIndexValueForTuple)
+      else: localError(n.info, errInvalidIndexValueForTuple)
     else: 
-      LocalError(n.info, errIndexTypesDoNotMatch)
+      localError(n.info, errIndexTypesDoNotMatch)
     result = n
-  else: nil
+  else: discard
   
 proc semArrayAccess(c: PContext, n: PNode, flags: TExprFlags): PNode = 
   result = semSubscript(c, n, flags)
@@ -1093,13 +1095,13 @@ proc takeImplicitAddr(c: PContext, n: PNode): PNode =
   of nkHiddenDeref, nkDerefExpr: return n.sons[0]
   of nkBracketExpr:
     if len(n) == 1: return n.sons[0]
-  else: nil
+  else: discard
   var valid = isAssignable(c, n)
   if valid != arLValue:
     if valid == arLocalLValue:
-      LocalError(n.info, errXStackEscape, renderTree(n, {renderNoComments}))
+      localError(n.info, errXStackEscape, renderTree(n, {renderNoComments}))
     else:
-      LocalError(n.info, errExprHasNoAddress)
+      localError(n.info, errExprHasNoAddress)
   result = newNodeIT(nkHiddenAddr, n.info, makePtrType(c, n.typ))
   result.add(n)
   
@@ -1148,7 +1150,7 @@ proc semAsgn(c: PContext, n: PNode): PNode =
   # a = b # b no 'var T' means: a = addr(b)
   var le = a.typ
   if skipTypes(le, {tyGenericInst}).kind != tyVar and 
-      IsAssignable(c, a) == arNone:
+      isAssignable(c, a) == arNone:
     # Direct assignment to a discriminant is allowed!
     localError(a.info, errXCannotBeAssignedTo,
                renderTree(a, {renderNoComments}))
@@ -1160,10 +1162,10 @@ proc semAsgn(c: PContext, n: PNode): PNode =
       rhs = semExprWithType(c, n.sons[1], 
         if lhsIsResult: {efAllowDestructor} else: {})
     if lhsIsResult:
-      n.typ = EnforceVoidContext
-      if lhs.sym.typ.kind == tyGenericParam:
-        if matchTypeClass(lhs.typ, rhs.typ):
-          InternalAssert c.p.resultSym != nil
+      n.typ = enforceVoidContext
+      if lhs.sym.typ.isMetaType and lhs.sym.typ.kind != tyTypeDesc:
+        if cmpTypes(c, lhs.typ, rhs.typ) == isGeneric:
+          internalAssert c.p.resultSym != nil
           lhs.typ = rhs.typ
           c.p.resultSym.typ = rhs.typ
           c.p.owner.typ.sons[0] = rhs.typ
@@ -1175,7 +1177,7 @@ proc semAsgn(c: PContext, n: PNode): PNode =
     asgnToResultVar(c, n, n.sons[0], n.sons[1])
   result = n
 
-proc SemReturn(c: PContext, n: PNode): PNode =
+proc semReturn(c: PContext, n: PNode): PNode =
   result = n
   checkSonsLen(n, 1)
   if c.p.owner.kind in {skConverter, skMethod, skProc, skMacro} or
@@ -1191,9 +1193,9 @@ proc SemReturn(c: PContext, n: PNode): PNode =
         if n[0][1].kind == nkSym and n[0][1].sym == c.p.resultSym: 
           n.sons[0] = ast.emptyNode
       else:
-        LocalError(n.info, errNoReturnTypeDeclared)
+        localError(n.info, errNoReturnTypeDeclared)
   else:
-    LocalError(n.info, errXNotAllowedHere, "\'return\'")
+    localError(n.info, errXNotAllowedHere, "\'return\'")
 
 proc semProcBody(c: PContext, n: PNode): PNode =
   openScope(c)
@@ -1202,7 +1204,7 @@ proc semProcBody(c: PContext, n: PNode): PNode =
     # transform ``expr`` to ``result = expr``, but not if the expr is already
     # ``result``:
     if result.kind == nkSym and result.sym == c.p.resultSym:
-      nil
+      discard
     elif result.kind == nkNilLit:
       # or ImplicitlyDiscardable(result):
       # new semantic: 'result = x' triggers the void context
@@ -1222,7 +1224,7 @@ proc semProcBody(c: PContext, n: PNode): PNode =
     discardCheck(c, result)
   closeScope(c)
 
-proc SemYieldVarResult(c: PContext, n: PNode, restype: PType) =
+proc semYieldVarResult(c: PContext, n: PNode, restype: PType) =
   var t = skipTypes(restype, {tyGenericInst})
   case t.kind
   of tyVar:
@@ -1239,22 +1241,22 @@ proc SemYieldVarResult(c: PContext, n: PNode, restype: PType) =
           a.sons[i] = takeImplicitAddr(c, a.sons[i])
         else:
           localError(n.sons[0].info, errXExpected, "tuple constructor")
-  else: nil
+  else: discard
   
-proc SemYield(c: PContext, n: PNode): PNode =
+proc semYield(c: PContext, n: PNode): PNode =
   result = n
   checkSonsLen(n, 1)
   if c.p.owner == nil or c.p.owner.kind != skIterator:
-    LocalError(n.info, errYieldNotAllowedHere)
+    localError(n.info, errYieldNotAllowedHere)
   elif c.p.inTryStmt > 0 and c.p.owner.typ.callConv != ccInline:
-    LocalError(n.info, errYieldNotAllowedInTryStmt)
+    localError(n.info, errYieldNotAllowedInTryStmt)
   elif n.sons[0].kind != nkEmpty:
-    n.sons[0] = SemExprWithType(c, n.sons[0]) # check for type compatibility:
+    n.sons[0] = semExprWithType(c, n.sons[0]) # check for type compatibility:
     var restype = c.p.owner.typ.sons[0]
     if restype != nil:
       n.sons[0] = fitNode(c, restype, n.sons[0])
-      if n.sons[0].typ == nil: InternalError(n.info, "semYield")
-      SemYieldVarResult(c, n, restype)
+      if n.sons[0].typ == nil: internalError(n.info, "semYield")
+      semYieldVarResult(c, n, restype)
     else:
       localError(n.info, errCannotReturnExpr)
   elif c.p.owner.typ.sons[0] != nil:
@@ -1266,37 +1268,37 @@ proc lookUpForDefined(c: PContext, i: PIdent, onlyCurrentScope: bool): PSym =
   else: 
     result = searchInScopes(c, i) # no need for stub loading
 
-proc LookUpForDefined(c: PContext, n: PNode, onlyCurrentScope: bool): PSym = 
+proc lookUpForDefined(c: PContext, n: PNode, onlyCurrentScope: bool): PSym = 
   case n.kind
   of nkIdent: 
-    result = LookupForDefined(c, n.ident, onlyCurrentScope)
+    result = lookUpForDefined(c, n.ident, onlyCurrentScope)
   of nkDotExpr:
     result = nil
     if onlyCurrentScope: return 
     checkSonsLen(n, 2)
-    var m = LookupForDefined(c, n.sons[0], onlyCurrentScope)
+    var m = lookUpForDefined(c, n.sons[0], onlyCurrentScope)
     if (m != nil) and (m.kind == skModule): 
       if (n.sons[1].kind == nkIdent): 
         var ident = n.sons[1].ident
         if m == c.module: 
-          result = StrTableGet(c.topLevelScope.symbols, ident)
+          result = strTableGet(c.topLevelScope.symbols, ident)
         else: 
-          result = StrTableGet(m.tab, ident)
+          result = strTableGet(m.tab, ident)
       else: 
-        LocalError(n.sons[1].info, errIdentifierExpected, "")
+        localError(n.sons[1].info, errIdentifierExpected, "")
   of nkAccQuoted:
-    result = lookupForDefined(c, considerAcc(n), onlyCurrentScope)
+    result = lookUpForDefined(c, considerAcc(n), onlyCurrentScope)
   of nkSym:
     result = n.sym
   else: 
-    LocalError(n.info, errIdentifierExpected, renderTree(n))
+    localError(n.info, errIdentifierExpected, renderTree(n))
     result = nil
 
 proc semDefined(c: PContext, n: PNode, onlyCurrentScope: bool): PNode = 
   checkSonsLen(n, 2)
   # we replace this node by a 'true' or 'false' node:
   result = newIntNode(nkIntLit, 0)
-  if LookUpForDefined(c, n.sons[1], onlyCurrentScope) != nil: 
+  if lookUpForDefined(c, n.sons[1], onlyCurrentScope) != nil: 
     result.intVal = 1
   elif not onlyCurrentScope and (n.sons[1].kind == nkIdent) and
       condsyms.isDefined(n.sons[1].ident): 
@@ -1313,18 +1315,18 @@ proc expectMacroOrTemplateCall(c: PContext, n: PNode): PSym =
   ## The argument to the proc should be nkCall(...) or similar
   ## Returns the macro/template symbol
   if isCallExpr(n):
-    var expandedSym = qualifiedLookup(c, n[0], {checkUndeclared})
+    var expandedSym = qualifiedLookUp(c, n[0], {checkUndeclared})
     if expandedSym == nil:
-      LocalError(n.info, errUndeclaredIdentifier, n[0].renderTree)
+      localError(n.info, errUndeclaredIdentifier, n[0].renderTree)
       return errorSym(c, n[0])
 
     if expandedSym.kind notin {skMacro, skTemplate}:
-      LocalError(n.info, errXisNoMacroOrTemplate, expandedSym.name.s)
+      localError(n.info, errXisNoMacroOrTemplate, expandedSym.name.s)
       return errorSym(c, n[0])
 
     result = expandedSym
   else:
-    LocalError(n.info, errXisNoMacroOrTemplate, n.renderTree)
+    localError(n.info, errXisNoMacroOrTemplate, n.renderTree)
     result = errorSym(c, n)
 
 proc expectString(c: PContext, n: PNode): string =
@@ -1332,10 +1334,10 @@ proc expectString(c: PContext, n: PNode): string =
   if n.kind in nkStrKinds:
     return n.strVal
   else:
-    LocalError(n.info, errStringLiteralExpected)
+    localError(n.info, errStringLiteralExpected)
 
 proc getMagicSym(magic: TMagic): PSym =
-  result = newSym(skProc, getIdent($magic), GetCurrOwner(), gCodegenLineInfo)
+  result = newSym(skProc, getIdent($magic), getCurrOwner(), gCodegenLineInfo)
   result.magic = magic
 
 proc newAnonSym(kind: TSymKind, info: TLineInfo,
@@ -1355,9 +1357,9 @@ proc semUsing(c: PContext, n: PNode): PNode =
       of skProcKinds:
         addDeclAt(c.currentScope, usedSym.sym)
         continue
-      else: nil
+      else: discard
 
-    LocalError(e.info, errUsingNoSymbol, e.renderTree)
+    localError(e.info, errUsingNoSymbol, e.renderTree)
 
 proc semExpandToAst(c: PContext, n: PNode): PNode =
   var macroCall = n[1]
@@ -1371,7 +1373,7 @@ proc semExpandToAst(c: PContext, n: PNode): PNode =
     macroCall.sons[i] = semExprWithType(c, macroCall[i], {})
 
   # Preserve the magic symbol in order to be handled in evals.nim
-  InternalAssert n.sons[0].sym.magic == mExpandToAst
+  internalAssert n.sons[0].sym.magic == mExpandToAst
   n.typ = getSysSym("PNimrodNode").typ # expandedSym.getReturnType
   result = n
 
@@ -1408,7 +1410,7 @@ proc processQuotations(n: var PNode, op: string,
       processQuotations(n.sons[i], op, quotes, ids)
 
 proc semQuoteAst(c: PContext, n: PNode): PNode =
-  InternalAssert n.len == 2 or n.len == 3
+  internalAssert n.len == 2 or n.len == 3
   # We transform the do block into a template with a param for
   # each interpolation. We'll pass this template to getAst.
   var
@@ -1421,7 +1423,7 @@ proc semQuoteAst(c: PContext, n: PNode): PNode =
       # this will store the generated param names
 
   if doBlk.kind != nkDo:
-    LocalError(n.info, errXExpected, "block")
+    localError(n.info, errXExpected, "block")
 
   processQuotations(doBlk.sons[bodyPos], op, quotes, ids)
   
@@ -1445,7 +1447,7 @@ proc tryExpr(c: PContext, n: PNode,
   # watch out, hacks ahead:
   let oldErrorCount = msgs.gErrorCounter
   let oldErrorMax = msgs.gErrorMax
-  inc c.InCompilesContext
+  inc c.inCompilesContext
   # do not halt after first error:
   msgs.gErrorMax = high(int)
   
@@ -1458,26 +1460,26 @@ proc tryExpr(c: PContext, n: PNode,
   errorOutputs = if bufferErrors: {eInMemory} else: {}
   let oldContextLen = msgs.getInfoContextLen()
   
-  let oldInGenericContext = c.InGenericContext
-  let oldInUnrolledContext = c.InUnrolledContext
-  let oldInGenericInst = c.InGenericInst
+  let oldInGenericContext = c.inGenericContext
+  let oldInUnrolledContext = c.inUnrolledContext
+  let oldInGenericInst = c.inGenericInst
   let oldProcCon = c.p
   c.generics = @[]
   try:
     result = semExpr(c, n, flags)
     if msgs.gErrorCounter != oldErrorCount: result = nil
   except ERecoverableError:
-    nil
+    discard
   # undo symbol table changes (as far as it's possible):
   c.generics = oldGenerics
-  c.InGenericContext = oldInGenericContext
-  c.InUnrolledContext = oldInUnrolledContext
-  c.InGenericInst = oldInGenericInst
+  c.inGenericContext = oldInGenericContext
+  c.inUnrolledContext = oldInUnrolledContext
+  c.inGenericInst = oldInGenericInst
   c.p = oldProcCon
   msgs.setInfoContextLen(oldContextLen)
-  setlen(gOwners, oldOwnerLen)
+  setLen(gOwners, oldOwnerLen)
   c.currentScope = oldScope
-  dec c.InCompilesContext
+  dec c.inCompilesContext
   errorOutputs = oldErrorOutputs
   msgs.gErrorCounter = oldErrorCount
   msgs.gErrorMax = oldErrorMax
@@ -1555,7 +1557,7 @@ proc semWhen(c: PContext, n: PNode, semCheck = true): PNode =
   # The ``when`` statement implements the mechanism for platform dependent
   # code. Thus we try to ensure here consistent ID allocation after the
   # ``when`` statement.
-  IDsynchronizationPoint(200)
+  idSynchronizationPoint(200)
 
 proc semSetConstr(c: PContext, n: PNode): PNode = 
   result = newNodeI(nkCurly, n.info)
@@ -1584,10 +1586,10 @@ proc semSetConstr(c: PContext, n: PNode): PNode =
         if typ == nil: 
           typ = skipTypes(n.sons[i].typ, {tyGenericInst, tyVar, tyOrdinal})
     if not isOrdinalType(typ):
-      LocalError(n.info, errOrdinalTypeExpected)
-      typ = makeRangeType(c, 0, MaxSetElements - 1, n.info)
+      localError(n.info, errOrdinalTypeExpected)
+      typ = makeRangeType(c, 0, MaxSetElements-1, n.info)
     elif lengthOrd(typ) > MaxSetElements: 
-      typ = makeRangeType(c, 0, MaxSetElements - 1, n.info)
+      typ = makeRangeType(c, 0, MaxSetElements-1, n.info)
     addSonSkipIntLit(result.typ, typ)
     for i in countup(0, sonsLen(n) - 1): 
       var m: PNode
@@ -1624,28 +1626,28 @@ proc semTableConstr(c: PContext, n: PNode): PNode =
   if lastKey != n.len: illFormedAst(n)
   result = semExpr(c, result)
 
-type 
-  TParKind = enum 
+type
+  TParKind = enum
     paNone, paSingle, paTupleFields, paTuplePositions
 
-proc checkPar(n: PNode): TParKind = 
+proc checkPar(n: PNode): TParKind =
   var length = sonsLen(n)
   if length == 0: 
     result = paTuplePositions # ()
   elif length == 1: 
     result = paSingle         # (expr)
-  else: 
+  else:
     if n.sons[0].kind == nkExprColonExpr: result = paTupleFields
     else: result = paTuplePositions
-    for i in countup(0, length - 1): 
-      if result == paTupleFields: 
+    for i in countup(0, length - 1):
+      if result == paTupleFields:
         if (n.sons[i].kind != nkExprColonExpr) or
-            not (n.sons[i].sons[0].kind in {nkSym, nkIdent}): 
-          LocalError(n.sons[i].info, errNamedExprExpected)
+            not (n.sons[i].sons[0].kind in {nkSym, nkIdent}):
+          localError(n.sons[i].info, errNamedExprExpected)
           return paNone
-      else: 
-        if n.sons[i].kind == nkExprColonExpr: 
-          LocalError(n.sons[i].info, errNamedExprNotAllowed)
+      else:
+        if n.sons[i].kind == nkExprColonExpr:
+          localError(n.sons[i].info, errNamedExprNotAllowed)
           return paNone
 
 proc semTupleFieldsConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
@@ -1654,13 +1656,12 @@ proc semTupleFieldsConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
   typ.n = newNodeI(nkRecList, n.info) # nkIdentDefs
   var ids = initIntSet()
   for i in countup(0, sonsLen(n) - 1):
-    if (n.sons[i].kind != nkExprColonExpr) or
-        not (n.sons[i].sons[0].kind in {nkSym, nkIdent}):
+    if n[i].kind != nkExprColonExpr or n[i][0].kind notin {nkSym, nkIdent}:
       illFormedAst(n.sons[i])
     var id: PIdent
     if n.sons[i].sons[0].kind == nkIdent: id = n.sons[i].sons[0].ident
     else: id = n.sons[i].sons[0].sym.name
-    if ContainsOrIncl(ids, id.id): 
+    if containsOrIncl(ids, id.id): 
       localError(n.sons[i].info, errFieldInitTwice, id.s)
     n.sons[i].sons[1] = semExprWithType(c, n.sons[i].sons[1],
                                         flags*{efAllowDestructor})
@@ -1687,7 +1688,7 @@ proc checkInitialized(n: PNode, ids: TIntSet, info: TLineInfo) =
     for i in countup(0, sonsLen(n) - 1):
       checkInitialized(n.sons[i], ids, info)
   of nkRecCase:
-    if (n.sons[0].kind != nkSym): InternalError(info, "checkInitialized")
+    if (n.sons[0].kind != nkSym): internalError(info, "checkInitialized")
     checkInitialized(n.sons[0], ids, info)
     when false:
       # XXX we cannot check here, as we don't know the branch!
@@ -1697,7 +1698,7 @@ proc checkInitialized(n: PNode, ids: TIntSet, info: TLineInfo) =
         else: internalError(info, "checkInitialized")
   of nkSym:
     if tfNeedsInit in n.sym.typ.flags and n.sym.name.id notin ids:
-      Message(info, errGenerated, "field not initialized: " & n.sym.name.s)
+      message(info, errGenerated, "field not initialized: " & n.sym.name.s)
   else: internalError(info, "checkInitialized")
 
 proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
@@ -1720,7 +1721,7 @@ proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
     var id: PIdent
     if it.sons[0].kind == nkIdent: id = it.sons[0].ident
     else: id = it.sons[0].sym.name
-    if ContainsOrIncl(ids, id.id):
+    if containsOrIncl(ids, id.id):
       localError(it.info, errFieldInitTwice, id.s)
     var e = semExprWithType(c, it.sons[1], flags*{efAllowDestructor})
     var
@@ -1753,7 +1754,7 @@ proc semObjConstr(c: PContext, n: PNode, flags: TExprFlags): PNode =
 
 proc semBlock(c: PContext, n: PNode): PNode =
   result = n
-  Inc(c.p.nestedBlockCounter)
+  inc(c.p.nestedBlockCounter)
   checkSonsLen(n, 2)
   openScope(c) # BUGFIX: label is in the scope of block!
   if n.sons[0].kind != nkEmpty:
@@ -1767,7 +1768,7 @@ proc semBlock(c: PContext, n: PNode): PNode =
   if isEmptyType(n.typ): n.kind = nkBlockStmt
   else: n.kind = nkBlockExpr
   closeScope(c)
-  Dec(c.p.nestedBlockCounter)
+  dec(c.p.nestedBlockCounter)
 
 proc buildCall(n: PNode): PNode =
   if n.kind == nkDotExpr and n.len == 2:
@@ -1833,13 +1834,13 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
       if result.kind == nkSym:
         markIndirect(c, result.sym)
         if isGenericRoutine(result.sym):
-          LocalError(n.info, errInstantiateXExplicitely, s.name.s)
+          localError(n.info, errInstantiateXExplicitely, s.name.s)
   of nkSym:
     # because of the changed symbol binding, this does not mean that we
     # don't have to check the symbol for semantics here again!
     result = semSym(c, n, n.sym, flags)
   of nkEmpty, nkNone, nkCommentStmt: 
-    nil
+    discard
   of nkNilLit: 
     result.typ = getSysType(tyNil)
   of nkIntLit:
@@ -1880,9 +1881,9 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
       result.kind = nkCall
       result = semExpr(c, result, flags)
   of nkBind:
-    Message(n.info, warnDeprecated, "bind")
+    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)
@@ -1890,8 +1891,10 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
     # check if it is an expression macro:
     checkMinSonsLen(n, 1)
     let mode = if nfDelegate in n.flags: {} else: {checkUndeclared}
-    var s = qualifiedLookup(c, n.sons[0], mode)
+    var s = qualifiedLookUp(c, n.sons[0], mode)
     if s != nil: 
+      if gCmd == cmdPretty and n.sons[0].kind == nkDotExpr:
+        pretty.checkUse(n.sons[0].sons[1], s)
       case s.kind
       of skMacro:
         if sfImmediate notin s.flags:
@@ -1911,8 +1914,8 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
           result = semConv(c, n)
         elif n.len == 1:
           result = semObjConstr(c, n, flags)
-        elif Contains(c.AmbiguousSymbols, s.id): 
-          LocalError(n.info, errUseQualifier, s.name.s)
+        elif contains(c.ambiguousSymbols, s.id): 
+          localError(n.info, errUseQualifier, s.name.s)
         elif s.magic == mNone: result = semDirectOp(c, n, flags)
         else: result = semMagic(c, n, s, flags)
       of skProc, skMethod, skConverter, skIterator: 
@@ -1936,12 +1939,14 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
       result = semExpr(c, result, flags)
   of nkBracketExpr:
     checkMinSonsLen(n, 1)
-    var s = qualifiedLookup(c, n.sons[0], {checkUndeclared})
+    var s = qualifiedLookUp(c, n.sons[0], {checkUndeclared})
     if s != nil and s.kind in {skProc, skMethod, skConverter, skIterator}: 
       # 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)
@@ -1964,7 +1969,7 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
     checkSonsLen(n, 1)
     n.sons[0] = semExprWithType(c, n.sons[0])
     if isAssignable(c, n.sons[0]) notin {arLValue, arLocalLValue}: 
-      LocalError(n.info, errExprHasNoAddress)
+      localError(n.info, errExprHasNoAddress)
     n.typ = makePtrType(c, n.sons[0].typ)
   of nkHiddenAddr, nkHiddenDeref:
     checkSonsLen(n, 1)
@@ -1993,7 +1998,7 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
   of nkVarSection: result = semVarOrLet(c, n, skVar)
   of nkLetSection: result = semVarOrLet(c, n, skLet)
   of nkConstSection: result = semConst(c, n)
-  of nkTypeSection: result = SemTypeSection(c, n)
+  of nkTypeSection: result = semTypeSection(c, n)
   of nkDiscardStmt: result = semDiscard(c, n)
   of nkWhileStmt: result = semWhile(c, n)
   of nkTryStmt: result = semTry(c, n)
@@ -2012,25 +2017,25 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode =
   of nkMacroDef: result = semMacroDef(c, n)
   of nkTemplateDef: result = semTemplateDef(c, n)
   of nkImportStmt: 
-    if not isTopLevel(c): LocalError(n.info, errXOnlyAtModuleScope, "import")
+    if not isTopLevel(c): localError(n.info, errXOnlyAtModuleScope, "import")
     result = evalImport(c, n)
   of nkImportExceptStmt:
-    if not isTopLevel(c): LocalError(n.info, errXOnlyAtModuleScope, "import")
+    if not isTopLevel(c): localError(n.info, errXOnlyAtModuleScope, "import")
     result = evalImportExcept(c, n)
   of nkFromStmt: 
-    if not isTopLevel(c): LocalError(n.info, errXOnlyAtModuleScope, "from")
+    if not isTopLevel(c): localError(n.info, errXOnlyAtModuleScope, "from")
     result = evalFrom(c, n)
   of nkIncludeStmt: 
-    if not isTopLevel(c): LocalError(n.info, errXOnlyAtModuleScope, "include")
+    if not isTopLevel(c): localError(n.info, errXOnlyAtModuleScope, "include")
     result = evalInclude(c, n)
   of nkExportStmt, nkExportExceptStmt:
-    if not isTopLevel(c): LocalError(n.info, errXOnlyAtModuleScope, "export")
+    if not isTopLevel(c): localError(n.info, errXOnlyAtModuleScope, "export")
     result = semExport(c, n)
   of nkPragmaBlock:
     result = semPragmaBlock(c, n)
   of nkStaticStmt:
     result = semStaticStmt(c, n)
   else:
-    LocalError(n.info, errInvalidExpressionX,
+    localError(n.info, errInvalidExpressionX,
                renderTree(n, {renderNoComments}))
   if result != nil: incl(result.flags, nfSem)
diff --git a/compiler/semfold.nim b/compiler/semfold.nim
index ca06ea1b6..4740ddcb3 100644
--- a/compiler/semfold.nim
+++ b/compiler/semfold.nim
@@ -66,14 +66,14 @@ proc ordinalValToString*(a: PNode): string =
   of tyEnum:
     var n = t.n
     for i in countup(0, sonsLen(n) - 1): 
-      if n.sons[i].kind != nkSym: InternalError(a.info, "ordinalValToString")
+      if n.sons[i].kind != nkSym: internalError(a.info, "ordinalValToString")
       var field = n.sons[i].sym
       if field.position == x: 
         if field.ast == nil: 
           return field.name.s
         else:
           return field.ast.strVal
-    InternalError(a.info, "no symbol for ordinal value: " & $x)
+    internalError(a.info, "no symbol for ordinal value: " & $x)
   else:
     result = $x
 
@@ -92,7 +92,7 @@ proc pickIntRange(a, b: PType): PType =
 proc isIntRangeOrLit(t: PType): bool =
   result = isIntRange(t) or isIntLit(t)
 
-proc pickMinInt(n: PNode): biggestInt =
+proc pickMinInt(n: PNode): BiggestInt =
   if n.kind in {nkIntLit..nkUInt64Lit}:
     result = n.intVal
   elif isIntLit(n.typ):
@@ -100,9 +100,9 @@ proc pickMinInt(n: PNode): biggestInt =
   elif isIntRange(n.typ):
     result = firstOrd(n.typ)
   else:
-    InternalError(n.info, "pickMinInt")
+    internalError(n.info, "pickMinInt")
 
-proc pickMaxInt(n: PNode): biggestInt =
+proc pickMaxInt(n: PNode): BiggestInt =
   if n.kind in {nkIntLit..nkUInt64Lit}:
     result = n.intVal
   elif isIntLit(n.typ):
@@ -110,9 +110,9 @@ proc pickMaxInt(n: PNode): biggestInt =
   elif isIntRange(n.typ):
     result = lastOrd(n.typ)
   else:
-    InternalError(n.info, "pickMaxInt")
+    internalError(n.info, "pickMaxInt")
 
-proc makeRange(typ: PType, first, last: biggestInt): PType = 
+proc makeRange(typ: PType, first, last: BiggestInt): PType = 
   var n = newNode(nkRange)
   addSon(n, newIntNode(nkIntLit, min(first, last)))
   addSon(n, newIntNode(nkIntLit, max(first, last)))
@@ -120,7 +120,7 @@ proc makeRange(typ: PType, first, last: biggestInt): PType =
   result.n = n
   addSonSkipIntLit(result, skipTypes(typ, {tyRange}))
 
-proc makeRangeF(typ: PType, first, last: biggestFloat): PType =
+proc makeRangeF(typ: PType, first, last: BiggestFloat): PType =
   var n = newNode(nkRange)
   addSon(n, newFloatNode(nkFloatLit, min(first.float, last.float)))
   addSon(n, newFloatNode(nkFloatLit, max(first.float, last.float)))
@@ -222,13 +222,40 @@ proc getIntervalType*(m: TMagic, n: PNode): PType =
     commutativeOp(min)
   of mMaxI, mMaxI64:
     commutativeOp(max)
-  else: nil
+  else: discard
   
 discard """
   mShlI, mShlI64,
   mShrI, mShrI64, mAddF64, mSubF64, mMulF64, mDivF64, mMaxF64, mMinF64
 """
 
+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}
+  
+  let t1 = a.sym.typ
+
+  if n[2].kind in {nkStrLit..nkTripleStrLit}:
+    case n[2].strVal.normalize
+    of "closure":
+      let t = skipTypes(t1, abstractRange)
+      result = newIntNode(nkIntLit, ord(t.kind == tyProc and
+                                        t.callConv == ccClosure and 
+                                        tfIterator notin t.flags))
+    of "iterator":
+      let t = skipTypes(t1, abstractRange)
+      result = newIntNode(nkIntLit, ord(t.kind == tyProc and
+                                        t.callConv == ccClosure and 
+                                        tfIterator in t.flags))
+  else:
+    # XXX semexprs.isOpImpl is slightly different and requires a context. yay.
+    let t2 = n[2].typ
+    var match = sameType(t1, t2)
+    result = newIntNode(nkIntLit, ord(match))
+  result.typ = n.typ
+
 proc evalOp(m: TMagic, n, a, b, c: PNode): PNode = 
   # b and c may be nil
   result = nil
@@ -276,7 +303,7 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode =
     of tyInt32: result = newIntNodeT(int32(getInt(a)) shl int32(getInt(b)), n)
     of tyInt64, tyInt, tyUInt..tyUInt64: 
       result = newIntNodeT(`shl`(getInt(a), getInt(b)), n)
-    else: InternalError(n.info, "constant folding for shl")
+    else: internalError(n.info, "constant folding for shl")
   of mShrI, mShrI64: 
     case skipTypes(n.typ, abstractRange).kind
     of tyInt8: result = newIntNodeT(int8(getInt(a)) shr int8(getInt(b)), n)
@@ -284,7 +311,7 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode =
     of tyInt32: result = newIntNodeT(int32(getInt(a)) shr int32(getInt(b)), n)
     of tyInt64, tyInt, tyUInt..tyUInt64:
       result = newIntNodeT(`shr`(getInt(a), getInt(b)), n)
-    else: InternalError(n.info, "constant folding for shr")
+    else: internalError(n.info, "constant folding for shr")
   of mDivI, mDivI64: result = newIntNodeT(getInt(a) div getInt(b), n)
   of mModI, mModI64: result = newIntNodeT(getInt(a) mod getInt(b), n)
   of mAddF64: result = newFloatNodeT(getFloat(a) + getFloat(b), n)
@@ -327,10 +354,10 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode =
   of mMulU: result = newIntNodeT(`*%`(getInt(a), getInt(b)), n)
   of mModU: result = newIntNodeT(`%%`(getInt(a), getInt(b)), n)
   of mDivU: result = newIntNodeT(`/%`(getInt(a), getInt(b)), n)
-  of mLeSet: result = newIntNodeT(Ord(containsSets(a, b)), n)
-  of mEqSet: result = newIntNodeT(Ord(equalSets(a, b)), n)
+  of mLeSet: result = newIntNodeT(ord(containsSets(a, b)), n)
+  of mEqSet: result = newIntNodeT(ord(equalSets(a, b)), n)
   of mLtSet: 
-    result = newIntNodeT(Ord(containsSets(a, b) and not equalSets(a, b)), n)
+    result = newIntNodeT(ord(containsSets(a, b) and not equalSets(a, b)), n)
   of mMulSet: 
     result = nimsets.intersectSets(a, b)
     result.info = n.info
@@ -344,7 +371,7 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode =
     result = nimsets.symdiffSets(a, b)
     result.info = n.info
   of mConStrStr: result = newStrNodeT(getStrOrChar(a) & getStrOrChar(b), n)
-  of mInSet: result = newIntNodeT(Ord(inSet(a, b)), n)
+  of mInSet: result = newIntNodeT(ord(inSet(a, b)), n)
   of mRepr:
     # BUGFIX: we cannot eval mRepr here for reasons that I forgot.
   of mIntToStr, mInt64ToStr: result = newStrNodeT($(getOrdValue(a)), n)
@@ -363,19 +390,19 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode =
     result = copyTree(a)
     result.typ = n.typ
   of mCompileOption:
-    result = newIntNodeT(Ord(commands.testCompileOption(a.getStr, n.info)), n)  
+    result = newIntNodeT(ord(commands.testCompileOption(a.getStr, n.info)), n)  
   of mCompileOptionArg:
-    result = newIntNodeT(Ord(
+    result = newIntNodeT(ord(
       testCompileOptionArg(getStr(a), getStr(b), n.info)), n)
   of mNewString, mNewStringOfCap, 
      mExit, mInc, ast.mDec, mEcho, mSwap, mAppendStrCh, 
      mAppendStrStr, mAppendSeqElem, mSetLengthStr, mSetLengthSeq, 
      mParseExprToAst, mParseStmtToAst, mExpandToAst, mTypeTrait,
      mNLen..mNError, mEqRef, mSlurp, mStaticExec, mNGenSym: 
-    nil
+    discard
   of mRand:
     result = newIntNodeT(math.random(a.getInt.int), n)
-  else: InternalError(a.info, "evalOp(" & $m & ')')
+  else: internalError(a.info, "evalOp(" & $m & ')')
   
 proc getConstIfExpr(c: PSym, n: PNode): PNode = 
   result = nil
@@ -425,13 +452,13 @@ proc leValueConv(a, b: PNode): bool =
     case b.kind
     of nkCharLit..nkUInt64Lit: result = a.intVal <= b.intVal
     of nkFloatLit..nkFloat128Lit: result = a.intVal <= round(b.floatVal)
-    else: InternalError(a.info, "leValueConv")
+    else: internalError(a.info, "leValueConv")
   of nkFloatLit..nkFloat128Lit: 
     case b.kind
     of nkFloatLit..nkFloat128Lit: result = a.floatVal <= b.floatVal
     of nkCharLit..nkUInt64Lit: result = a.floatVal <= toFloat(int(b.intVal))
-    else: InternalError(a.info, "leValueConv")
-  else: InternalError(a.info, "leValueConv")
+    else: internalError(a.info, "leValueConv")
+  else: internalError(a.info, "leValueConv")
   
 proc magicCall(m: PSym, n: PNode): PNode =
   if sonsLen(n) <= 1: return
@@ -446,8 +473,6 @@ proc magicCall(m: PSym, n: PNode): PNode =
     if sonsLen(n) > 3: 
       c = getConstExpr(m, n.sons[3])
       if c == nil: return 
-  else: 
-    b = nil
   result = evalOp(s.magic, n, a, b, c)
   
 proc getAppType(n: PNode): PNode =
@@ -460,9 +485,9 @@ proc getAppType(n: PNode): PNode =
   else:
     result = newStrNodeT("console", n)
 
-proc rangeCheck(n: PNode, value: biggestInt) =
+proc rangeCheck(n: PNode, value: BiggestInt) =
   if value < firstOrd(n.typ) or value > lastOrd(n.typ):
-    LocalError(n.info, errGenerated, "cannot convert " & $value &
+    localError(n.info, errGenerated, "cannot convert " & $value &
                                      " to " & typeToString(n.typ))
 
 proc foldConv*(n, a: PNode; check = false): PNode = 
@@ -485,7 +510,7 @@ proc foldConv*(n, a: PNode; check = false): PNode =
       result = a
       result.typ = n.typ
   of tyOpenArray, tyVarargs, tyProc: 
-    nil
+    discard
   else: 
     result = a
     result.typ = n.typ
@@ -511,19 +536,19 @@ proc foldArrayAccess(m: PSym, n: PNode): PNode =
       result = x.sons[int(idx)]
       if result.kind == nkExprColonExpr: result = result.sons[1]
     else:
-      LocalError(n.info, errIndexOutOfBounds)
+      localError(n.info, errIndexOutOfBounds)
   of nkBracket, nkMetaNode: 
     if (idx >= 0) and (idx < sonsLen(x)): result = x.sons[int(idx)]
-    else: LocalError(n.info, errIndexOutOfBounds)
+    else: localError(n.info, errIndexOutOfBounds)
   of nkStrLit..nkTripleStrLit: 
     result = newNodeIT(nkCharLit, x.info, n.typ)
     if (idx >= 0) and (idx < len(x.strVal)): 
       result.intVal = ord(x.strVal[int(idx)])
     elif idx == len(x.strVal): 
-      nil
+      discard
     else: 
-      LocalError(n.info, errIndexOutOfBounds)
-  else: nil
+      localError(n.info, errIndexOutOfBounds)
+  else: discard
   
 proc foldFieldAccess(m: PSym, n: PNode): PNode =
   # a real field access; proc calls have already been transformed
@@ -587,12 +612,13 @@ 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: nil
+    else: discard
   of nkCharLit..nkNilLit: 
     result = copyNode(n)
   of nkIfExpr: 
@@ -604,11 +630,12 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
     try:
       case s.magic
       of mNone:
-        return # XXX: if it has no sideEffect, it should be evaluated
+        # If it has no sideEffect, it should be evaluated. But not here.
+        return
       of mSizeOf:
         var a = n.sons[1]
         if computeSize(a.typ) < 0: 
-          LocalError(a.info, errCannotEvalXBecauseIncompletelyDefined, 
+          localError(a.info, errCannotEvalXBecauseIncompletelyDefined, 
                      "sizeof")
           result = nil
         elif skipTypes(a.typ, typedescInst).kind in
@@ -644,12 +671,16 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
         result = newStrNodeT(renderTree(n[1], {renderNoComments}), n)
       of mConStrStr:
         result = foldConStrStr(m, n)
+      of mIs:
+        let a = getConstExpr(m, n[1])
+        if a != nil and a.kind == nkSym and a.sym.kind == skType:
+          result = evalIs(n, a)
       else:
         result = magicCall(m, n)
     except EOverflow: 
-      LocalError(n.info, errOverOrUnderflow)
+      localError(n.info, errOverOrUnderflow)
     except EDivByZero: 
-      LocalError(n.info, errConstantDivisionByZero)
+      localError(n.info, errConstantDivisionByZero)
   of nkAddr: 
     var a = getConstExpr(m, n.sons[0])
     if a != nil: 
@@ -705,7 +736,7 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
       result = a              # a <= x and x <= b
       result.typ = n.typ
     else: 
-      LocalError(n.info, errGenerated, `%`(
+      localError(n.info, errGenerated, `%`(
           msgKindToString(errIllegalConvFromXtoY), 
           [typeToString(n.sons[0].typ), typeToString(n.typ)]))
   of nkStringToCString, nkCStringToString: 
@@ -727,4 +758,4 @@ proc getConstExpr(m: PSym, n: PNode): PNode =
   of nkBracketExpr: result = foldArrayAccess(m, n)
   of nkDotExpr: result = foldFieldAccess(m, n)
   else:
-    nil
+    discard
diff --git a/compiler/semgnrc.nim b/compiler/semgnrc.nim
index d626d2eb2..89a167b96 100644
--- a/compiler/semgnrc.nim
+++ b/compiler/semgnrc.nim
@@ -17,11 +17,6 @@
 
 # included from sem.nim
 
-type
-  TSemGenericFlag = enum
-    withinBind, withinTypeDesc, withinMixin
-  TSemGenericFlags = set[TSemGenericFlag]
-
 proc getIdentNode(n: PNode): PNode =
   case n.kind
   of nkPostfix: result = getIdentNode(n.sons[1])
@@ -31,8 +26,6 @@ proc getIdentNode(n: PNode): PNode =
     illFormedAst(n)
     result = n
   
-proc semGenericStmt(c: PContext, n: PNode, flags: TSemGenericFlags,
-                    ctx: var TIntSet): PNode
 proc semGenericStmtScope(c: PContext, n: PNode, 
                          flags: TSemGenericFlags,
                          ctx: var TIntSet): PNode = 
@@ -73,7 +66,7 @@ proc semGenericStmtSymbol(c: PContext, n: PNode, s: PSym): PNode =
       result = n
   else: result = newSymNode(s, n.info)
 
-proc Lookup(c: PContext, n: PNode, flags: TSemGenericFlags, 
+proc lookup(c: PContext, n: PNode, flags: TSemGenericFlags, 
             ctx: var TIntSet): PNode =
   result = n
   let ident = considerAcc(n)
@@ -96,10 +89,10 @@ proc semGenericStmt(c: PContext, n: PNode,
   if gCmd == cmdIdeTools: suggestStmt(c, n)
   case n.kind
   of nkIdent, nkAccQuoted:
-    result = Lookup(c, n, flags, ctx)
+    result = lookup(c, n, flags, ctx)
   of nkDotExpr:
     let luf = if withinMixin notin flags: {checkUndeclared} else: {}
-    var s = QualifiedLookUp(c, n, luf)
+    var s = qualifiedLookUp(c, n, luf)
     if s != nil: result = semGenericStmtSymbol(c, n, s)
     # XXX for example: ``result.add`` -- ``add`` needs to be looked up here...
   of nkEmpty, nkSym..nkNilLit:
@@ -110,7 +103,7 @@ proc semGenericStmt(c: PContext, n: PNode,
     # not work. Copying the symbol does not work either because we're already
     # the owner of the symbol! What we need to do is to copy the symbol
     # in the generic instantiation process...
-    nil
+    discard
   of nkBind:
     result = semGenericStmt(c, n.sons[0], flags+{withinBind}, ctx)
   of nkMixinStmt:
@@ -119,7 +112,7 @@ proc semGenericStmt(c: PContext, n: PNode,
     # check if it is an expression macro:
     checkMinSonsLen(n, 1)
     let fn = n.sons[0]
-    var s = qualifiedLookup(c, fn, {})
+    var s = qualifiedLookUp(c, fn, {})
     if s == nil and withinMixin notin flags and
         fn.kind in {nkIdent, nkAccQuoted} and considerAcc(fn).id notin ctx:
       localError(n.info, errUndeclaredIdentifier, fn.renderTree)
@@ -219,7 +212,7 @@ proc semGenericStmt(c: PContext, n: PNode,
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkIdentDefs) and (a.kind != nkVarTuple): IllFormedAst(a)
+      if (a.kind != nkIdentDefs) and (a.kind != nkVarTuple): illFormedAst(a)
       checkMinSonsLen(a, 3)
       var L = sonsLen(a)
       a.sons[L-2] = semGenericStmt(c, a.sons[L-2], flags+{withinTypeDesc}, 
@@ -230,7 +223,7 @@ proc semGenericStmt(c: PContext, n: PNode,
   of nkGenericParams: 
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
-      if (a.kind != nkIdentDefs): IllFormedAst(a)
+      if (a.kind != nkIdentDefs): illFormedAst(a)
       checkMinSonsLen(a, 3)
       var L = sonsLen(a)
       a.sons[L-2] = semGenericStmt(c, a.sons[L-2], flags+{withinTypeDesc}, 
@@ -242,7 +235,7 @@ proc semGenericStmt(c: PContext, n: PNode,
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkConstDef): IllFormedAst(a)
+      if (a.kind != nkConstDef): illFormedAst(a)
       checkSonsLen(a, 3)
       addPrelimDecl(c, newSymS(skUnknown, getIdentNode(a.sons[0]), c))
       a.sons[1] = semGenericStmt(c, a.sons[1], flags+{withinTypeDesc}, ctx)
@@ -251,13 +244,13 @@ proc semGenericStmt(c: PContext, n: PNode,
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkTypeDef): IllFormedAst(a)
+      if (a.kind != nkTypeDef): illFormedAst(a)
       checkSonsLen(a, 3)
       addPrelimDecl(c, newSymS(skUnknown, getIdentNode(a.sons[0]), c))
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkTypeDef): IllFormedAst(a)
+      if (a.kind != nkTypeDef): illFormedAst(a)
       checkSonsLen(a, 3)
       if a.sons[1].kind != nkEmpty: 
         openScope(c)
@@ -278,14 +271,14 @@ proc semGenericStmt(c: PContext, n: PNode,
         else: illFormedAst(n)
         addDecl(c, newSymS(skUnknown, getIdentNode(a.sons[i]), c))
   of nkObjectTy, nkTupleTy: 
-    nil
+    discard
   of nkFormalParams: 
     checkMinSonsLen(n, 1)
     if n.sons[0].kind != nkEmpty: 
       n.sons[0] = semGenericStmt(c, n.sons[0], flags+{withinTypeDesc}, ctx)
     for i in countup(1, sonsLen(n) - 1): 
       var a = n.sons[i]
-      if (a.kind != nkIdentDefs): IllFormedAst(a)
+      if (a.kind != nkIdentDefs): illFormedAst(a)
       checkMinSonsLen(a, 3)
       var L = sonsLen(a)
       a.sons[L-2] = semGenericStmt(c, a.sons[L-2], flags+{withinTypeDesc}, 
@@ -311,7 +304,7 @@ proc semGenericStmt(c: PContext, n: PNode,
     else: body = n.sons[bodyPos]
     n.sons[bodyPos] = semGenericStmtScope(c, body, flags, ctx)
     closeScope(c)
-  of nkPragma, nkPragmaExpr: nil
+  of nkPragma, nkPragmaExpr: discard
   of nkExprColonExpr, nkExprEqExpr:
     checkMinSonsLen(n, 2)
     result.sons[1] = semGenericStmt(c, n.sons[1], flags, ctx)
diff --git a/compiler/seminst.nim b/compiler/seminst.nim
index d7d64fd54..8faf1d21a 100644
--- a/compiler/seminst.nim
+++ b/compiler/seminst.nim
@@ -13,28 +13,28 @@
 proc instantiateGenericParamList(c: PContext, n: PNode, pt: TIdTable,
                                  entry: var TInstantiation) = 
   if n.kind != nkGenericParams: 
-    InternalError(n.info, "instantiateGenericParamList; no generic params")
+    internalError(n.info, "instantiateGenericParamList; no generic params")
   newSeq(entry.concreteTypes, n.len)
   for i in countup(0, n.len - 1):
     var a = n.sons[i]
     if a.kind != nkSym: 
-      InternalError(a.info, "instantiateGenericParamList; no symbol")
+      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}
-    var t = PType(IdTableGet(pt, q.typ))
+    var t = PType(idTableGet(pt, q.typ))
     if t == nil:
       if tfRetType in q.typ.flags:
         # keep the generic type and allow the return type to be bound 
         # later by semAsgn in return type inference scenario
         t = q.typ
       else:
-        LocalError(a.info, errCannotInstantiateX, s.name.s)
+        localError(a.info, errCannotInstantiateX, s.name.s)
         t = errorType(c)
     elif t.kind == tyGenericParam: 
-      InternalError(a.info, "instantiateGenericParamList: " & q.name.s)
+      internalError(a.info, "instantiateGenericParamList: " & q.name.s)
     elif t.kind == tyGenericInvokation:
       #t = instGenericContainer(c, a, t)
       t = generateTypeInstance(c, pt, a, t)
@@ -47,10 +47,10 @@ 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 =
+proc genericCacheGet(genericSym: PSym, entry: TInstantiation): PSym =
   if genericSym.procInstCache != nil:
     for inst in genericSym.procInstCache:
       if sameInstantiation(entry, inst[]):
@@ -75,11 +75,11 @@ proc removeDefaultParamValues(n: PNode) =
 proc freshGenSyms(n: PNode, owner: PSym, symMap: var TIdTable) =
   # we need to create a fresh set of gensym'ed symbols:
   if n.kind == nkSym and sfGenSym in n.sym.flags:
-    var x = PSym(IdTableGet(symMap, n.sym))
+    var x = PSym(idTableGet(symMap, n.sym))
     if x == nil:
       x = copySym(n.sym, false)
       x.owner = owner
-      IdTablePut(symMap, n.sym, x)
+      idTablePut(symMap, n.sym, x)
     n.sym = x
   else:
     for i in 0 .. <safeLen(n): freshGenSyms(n.sons[i], owner, symMap)
@@ -88,7 +88,7 @@ proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind)
 
 proc instantiateBody(c: PContext, n: PNode, result: PSym) =
   if n.sons[bodyPos].kind != nkEmpty:
-    inc c.InGenericInst
+    inc c.inGenericInst
     # add it here, so that recursive generic procs are possible:
     addDecl(c, result)
     pushProcCon(c, result)
@@ -101,7 +101,7 @@ proc instantiateBody(c: PContext, n: PNode, result: PSym) =
     maybeAddResult(c, result, n)
     var b = n.sons[bodyPos]
     var symMap: TIdTable
-    InitIdTable symMap
+    initIdTable symMap
     freshGenSyms(b, result, symMap)
     b = semProcBody(c, b)
     b = hloBody(c, b)
@@ -109,7 +109,7 @@ proc instantiateBody(c: PContext, n: PNode, result: PSym) =
     #echo "code instantiated ", result.name.s
     excl(result.flags, sfForward)
     popProcCon(c)
-    dec c.InGenericInst
+    dec c.inGenericInst
 
 proc fixupInstantiatedSymbols(c: PContext, s: PSym) =
   for i in countup(0, c.generics.len - 1):
@@ -126,147 +126,33 @@ proc fixupInstantiatedSymbols(c: PContext, s: PSym) =
 proc sideEffectsCheck(c: PContext, s: PSym) = 
   if {sfNoSideEffect, sfSideEffect} * s.flags ==
       {sfNoSideEffect, sfSideEffect}: 
-    LocalError(s.info, errXhasSideEffects, s.name.s)
+    localError(s.info, errXhasSideEffects, s.name.s)
   elif sfThread in s.flags and semthreads.needsGlobalAnalysis() and 
       s.ast.sons[genericParamsPos].kind == nkEmpty:
     c.threadEntries.add(s)
 
-proc lateInstantiateGeneric(c: PContext, invocation: PType, info: TLineInfo): PType =
-  InternalAssert invocation.kind == tyGenericInvokation
-  
-  let cacheHit = searchInstTypes(invocation)
-  if cacheHit != nil:
-    result = cacheHit
-  else:
-    let s = invocation.sons[0].sym
-    let oldScope = c.currentScope
-    c.currentScope = s.typScope
-    openScope(c)
-    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
-                    else: skType
-
-      var boundSym = newSym(symKind, s.typ.n[i].sym.name, s, info)
-      boundSym.typ = invocation.sons[i+1].skipTypes({tyExpr})
-      boundSym.ast = invocation.sons[i+1].n
-      addDecl(c, boundSym)
-    # XXX: copyTree would have been unnecessary here if semTypeNode
-    # didn't modify its input parameters. Currently, it does modify
-    # at least the record lists of the passed object and tuple types
-    var instantiated = semTypeNode(c, copyTree(s.ast[2]), nil)
-    popInfoContext()
-    closeScope(c)
-    c.currentScope = oldScope
-    if instantiated != nil:
-      result = invocation
-      result.kind = tyGenericInst
-      result.sons.add instantiated
-      cacheTypeInst result
-
-proc instGenericContainer(c: PContext, info: TLineInfo, header: PType): PType =
-  when oUseLateInstantiation:
-    lateInstantiateGeneric(c, header, info)
-  else:
-    var cl: TReplTypeVars
-    InitIdTable(cl.symMap)
-    InitIdTable(cl.typeMap)
-    cl.info = info
-    cl.c = c
-    result = ReplaceTypeVarsT(cl, header)
+proc instGenericContainer(c: PContext, info: TLineInfo, header: PType,
+                          allowMetaTypes = false): PType =
+  var cl: TReplTypeVars
+  initIdTable(cl.symMap)
+  initIdTable(cl.typeMap)
+  initIdTable(cl.localCache)
+  cl.info = info
+  cl.c = c
+  cl.allowMetaTypes = allowMetaTypes
+  result = replaceTypeVarsT(cl, header)
 
 proc instGenericContainer(c: PContext, n: PNode, header: PType): PType =
   result = instGenericContainer(c, n.info, header)
 
-proc fixupProcType(c: PContext, genericType: PType,
-                   inst: TInstantiation): PType =
-  # XXX: This is starting to look suspiciously like ReplaceTypeVarsT
-  # there are few apparent differences, but maybe the code could be
-  # moved over.
-  # * the code here uses the new genericSym.position property when
-  #   doing lookups. 
-  # * the handling of tyTypeDesc seems suspicious in ReplaceTypeVarsT
-  #   typedesc params were previously handled in the second pass of
-  #   semParamList
-  # * void (nkEmpty) params doesn't seem to be stripped in ReplaceTypeVarsT
-  result = genericType
-  if result == nil: return
-
-  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:
-    result = inst.concreteTypes[genericType.sym.position]
-  of tyOpenArray, tyArray, tySet, tySequence, tyTuple, tyProc,
-     tyPtr, tyVar, tyRef, tyOrdinal, tyRange, tyVarargs:
-    if genericType.sons == nil: return
-    var head = 0
-    for i in 0 .. <genericType.sons.len:
-      let origType = genericType.sons[i]
-      var changed = fixupProcType(c, origType, inst)
-      if changed != genericType.sons[i]:
-        var changed = changed.skipIntLit
-        if result == genericType:
-          # the first detected change initializes the result
-          result = copyType(genericType, genericType.owner, false)
-          if genericType.n != nil:
-            result.n = copyTree(genericType.n)
-
-        # XXX: doh, we have to treat seq and arrays as special case
-        # because sometimes the `@` magic will be applied to an empty
-        # sequence having the type tySequence(tyEmpty)
-        if changed.kind == tyEmpty and
-           genericType.kind notin {tyArray, tySequence}:
-          if genericType.kind == tyProc and i == 0:
-            # return types of procs are overwritten with nil
-            changed = nil
-          else:
-            # otherwise, `empty` is just erased from the signature
-            result.sons[i..i] = []
-            if result.n != nil: result.n.sons[i..i] = []
-            continue
-        
-        result.sons[head] = changed
-        
-        if result.n != nil:
-          if result.n.kind == nkRecList:
-            for son in result.n.sons:
-              if son.typ == origType:
-                son.typ = changed
-                son.sym = copySym(son.sym, true)
-                son.sym.typ = changed
-          if result.n.kind == nkFormalParams:
-            if i != 0:
-              let origParam = result.n.sons[head].sym
-              var param = copySym(origParam)
-              param.typ = changed
-              param.ast = origParam.ast
-              result.n.sons[head] = newSymNode(param)
-
-      # won't be advanced on empty (void) nodes
-      inc head
-  
-  of tyGenericInvokation:
-    result = newTypeWithSons(c, tyGenericInvokation, genericType.sons)
-    for i in 1 .. <genericType.sons.len:
-      result.sons[i] = fixupProcType(c, result.sons[i], inst)
-    result = instGenericContainer(c, getInfoContext(-1), result)
-  
-  else: nil
-
 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)
+  if c.instCounter > 1000: internalError(fn.ast.info, "nesting too deep")
+  inc(c.instCounter)
   # careful! we copy the whole AST including the possibly nil body!
   var n = copyTree(fn.ast)
   # NOTE: for access of private fields within generics from a different module
@@ -281,16 +167,15 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
   result.ast = n
   pushOwner(result)
   openScope(c)
-  if n.sons[genericParamsPos].kind == nkEmpty: 
-    InternalError(n.info, "generateInstance")
+  internalAssert n.sons[genericParamsPos].kind != nkEmpty
   n.sons[namePos] = newSymNode(result)
   pushInfoContext(info)
   var entry = TInstantiation.new
   entry.sym = result
   instantiateGenericParamList(c, n.sons[genericParamsPos], pt, entry[])
-  result.typ = fixupProcType(c, fn.typ, entry[])
+  result.typ = generateTypeInstance(c, pt, info, fn.typ)
   n.sons[genericParamsPos] = ast.emptyNode
-  var oldPrc = GenericCacheGet(fn, entry[])
+  var oldPrc = genericCacheGet(fn, entry[])
   if oldPrc == nil:
     fn.procInstCache.safeAdd(entry)
     c.generics.add(makeInstPair(fn, entry))
@@ -301,7 +186,7 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
     if fn.kind != skTemplate:
       instantiateBody(c, n, result)
       sideEffectsCheck(c, result)
-    ParamsTypeCheck(c, result.typ)
+    paramsTypeCheck(c, result.typ)
   else:
     result = oldPrc
   popInfoContext()
@@ -309,7 +194,5 @@ proc generateInstance(c: PContext, fn: PSym, pt: TIdTable,
   popOwner()
   #c.currentScope = oldScope
   c.friendModule = oldFriend
-  dec(c.InstCounter)
+  dec(c.instCounter)
   if result.kind == skMethod: finishMethod(c, result)
-
-
diff --git a/compiler/semmacrosanity.nim b/compiler/semmacrosanity.nim
new file mode 100644
index 000000000..1bece95c2
--- /dev/null
+++ b/compiler/semmacrosanity.nim
@@ -0,0 +1,89 @@
+#
+#
+#           The Nimrod Compiler
+#        (c) Copyright 2014 Andreas Rumpf
+#
+#    See the file "copying.txt", included in this
+#    distribution, for details about the copyright.
+#
+
+## Implements type sanity checking for ASTs resulting from macros. Lots of
+## room for improvement here.
+
+import ast, astalgo, msgs, types
+
+proc ithField(n: PNode, field: int): PSym =
+  result = nil
+  case n.kind
+  of nkRecList:
+    for i in countup(0, sonsLen(n) - 1): 
+      result = ithField(n.sons[i], field-i)
+      if result != nil: return 
+  of nkRecCase:
+    if n.sons[0].kind != nkSym: internalError(n.info, "ithField")
+    result = ithField(n.sons[0], field-1)
+    if result != nil: return
+    for i in countup(1, sonsLen(n) - 1):
+      case n.sons[i].kind
+      of nkOfBranch, nkElse:
+        result = ithField(lastSon(n.sons[i]), field-1)
+        if result != nil: return
+      else: internalError(n.info, "ithField(record case branch)")
+  of nkSym:
+    if field == 0: result = n.sym
+  else: discard
+
+proc annotateType*(n: PNode, t: PType) =
+  let x = t.skipTypes(abstractInst)
+  # Note: x can be unequal to t and we need to be careful to use 't'
+  # to not to skip tyGenericInst
+  case n.kind
+  of nkPar:
+    if x.kind == tyObject:
+      n.typ = t
+      for i in 0 .. <n.len:
+        let field = x.n.ithField(i)
+        if field.isNil: globalError n.info, "invalid field at index " & $i
+        else: annotateType(n.sons[i], field.typ)
+    elif x.kind == tyTuple:
+      n.typ = t
+      for i in 0 .. <n.len:
+        if i >= x.len: globalError n.info, "invalid field at index " & $i
+        else: annotateType(n.sons[i], x.sons[i])
+    elif x.kind == tyProc and x.callConv == ccClosure:
+      n.typ = t
+    else:
+      globalError(n.info, "() must have an object or tuple type")
+  of nkBracket:
+    if x.kind in {tyArrayConstr, tyArray, tySequence, tyOpenarray}:
+      n.typ = t
+      for m in n: annotateType(m, x.elemType)
+    else:
+      globalError(n.info, "[] must have some form of array type")
+  of nkCurly:
+    if x.kind in {tySet}:
+      n.typ = t
+      for m in n: annotateType(m, x.elemType)
+    else:
+      globalError(n.info, "{} must have the set type")
+  of nkFloatLit..nkFloat128Lit:
+    if x.kind in {tyFloat..tyFloat128}:
+      n.typ = t
+    else:
+      globalError(n.info, "float literal must have some float type")
+  of nkCharLit..nkUInt64Lit:
+    if x.kind in {tyInt..tyUInt64, tyBool, tyChar, tyEnum}:
+      n.typ = t
+    else:
+      globalError(n.info, "integer literal must have some int type")
+  of nkStrLit..nkTripleStrLit:
+    if x.kind in {tyString, tyCString}:
+      n.typ = t
+    else:
+      globalError(n.info, "string literal must be of some string type")    
+  of nkNilLit:
+    if x.kind in NilableTypes:
+      n.typ = t
+    else:
+      globalError(n.info, "nil literal must be of some pointer type")
+  else: discard
diff --git a/compiler/semmagic.nim b/compiler/semmagic.nim
index 88567b10a..4caf1fb8e 100644
--- a/compiler/semmagic.nim
+++ b/compiler/semmagic.nim
@@ -18,7 +18,7 @@ proc expectIntLit(c: PContext, n: PNode): int =
   let x = c.semConstExpr(c, n)
   case x.kind
   of nkIntLit..nkInt64Lit: result = int(x.intVal)
-  else: LocalError(n.info, errIntLiteralExpected)
+  else: localError(n.info, errIntLiteralExpected)
 
 proc semInstantiationInfo(c: PContext, n: PNode): PNode =
   result = newNodeIT(nkPar, n.info, n.typ)
@@ -26,21 +26,34 @@ proc semInstantiationInfo(c: PContext, n: PNode): PNode =
   let useFullPaths = expectIntLit(c, n.sons[2])
   let info = getInfoContext(idx)
   var filename = newNodeIT(nkStrLit, n.info, getSysType(tyString))
-  filename.strVal = if useFullPaths != 0: info.toFullPath else: info.ToFilename
+  filename.strVal = if useFullPaths != 0: info.toFullPath else: info.toFilename
   var line = newNodeIT(nkIntLit, n.info, getSysType(tyInt))
-  line.intVal = ToLinenumber(info)
+  line.intVal = toLinenumber(info)
   result.add(filename)
   result.add(line)
+ 
+proc evalTypeTrait(trait: PNode, operand: PType, context: PSym): PNode =
+  let typ = operand.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":
+    result = newIntNode(nkIntLit, typ.n.len-1)
+    result.typ = newType(tyInt, context)
+    result.info = trait.info
+  else:
+    internalAssert false
 
 proc semTypeTraits(c: PContext, n: PNode): PNode =
   checkMinSonsLen(n, 2)
-  internalAssert n.sons[1].kind == nkSym
-  let typArg = n.sons[1].sym
-  if typArg.kind == skType or
-    (typArg.kind == skParam and typArg.typ.sonsLen > 0):
+  let t = n.sons[1].typ
+  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], n[1], GetCurrOwner())
+    result = evalTypeTrait(n[0], t, getCurrOwner())
   else:
     # a typedesc variable, pass unmodified to evals
     result = n
@@ -56,23 +69,23 @@ proc semBindSym(c: PContext, n: PNode): PNode =
   
   let sl = semConstExpr(c, n.sons[1])
   if sl.kind notin {nkStrLit, nkRStrLit, nkTripleStrLit}: 
-    LocalError(n.sons[1].info, errStringLiteralExpected)
+    localError(n.sons[1].info, errStringLiteralExpected)
     return errorNode(c, n)
   
   let isMixin = semConstExpr(c, n.sons[2])
   if isMixin.kind != nkIntLit or isMixin.intVal < 0 or
       isMixin.intVal > high(TSymChoiceRule).int:
-    LocalError(n.sons[2].info, errConstExprExpected)
+    localError(n.sons[2].info, errConstExprExpected)
     return errorNode(c, n)
   
   let id = newIdentNode(getIdent(sl.strVal), n.info)
-  let s = QualifiedLookUp(c, id)
+  let s = qualifiedLookUp(c, id)
   if s != nil:
     # we need to mark all symbols:
     var sc = symChoice(c, id, s, TSymChoiceRule(isMixin.intVal))
     result.add(sc)
   else:
-    LocalError(n.sons[1].info, errUndeclaredIdentifier, sl.strVal)
+    localError(n.sons[1].info, errUndeclaredIdentifier, sl.strVal)
 
 proc semLocals(c: PContext, n: PNode): PNode =
   var counter = 0
@@ -88,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/sempass2.nim b/compiler/sempass2.nim
index 7dec557be..fb266ae3a 100644
--- a/compiler/sempass2.nim
+++ b/compiler/sempass2.nim
@@ -95,12 +95,12 @@ proc useVar(a: PEffects, n: PNode) =
     if s.id notin a.init:
       if {tfNeedsInit, tfNotNil} * s.typ.flags != {}:
         when true:
-          Message(n.info, warnProveInit, s.name.s)
+          message(n.info, warnProveInit, s.name.s)
         else:
           Message(n.info, errGenerated,
             "'$1' might not have been initialized" % s.name.s)
       else:
-        Message(n.info, warnUninit, s.name.s)
+        message(n.info, warnUninit, s.name.s)
       # prevent superfluous warnings about the same variable:
       a.init.add s.id
 
@@ -162,8 +162,8 @@ proc mergeTags(a: PEffects, b, comesFrom: PNode) =
     for effect in items(b): addTag(a, effect, useLineInfo=comesFrom != nil)
 
 proc listEffects(a: PEffects) =
-  for e in items(a.exc):  Message(e.info, hintUser, typeToString(e.typ))
-  for e in items(a.tags): Message(e.info, hintUser, typeToString(e.typ))
+  for e in items(a.exc):  message(e.info, hintUser, typeToString(e.typ))
+  for e in items(a.tags): message(e.info, hintUser, typeToString(e.typ))
 
 proc catches(tracked: PEffects, e: PType) =
   let e = skipTypes(e, skipPtrs)
@@ -305,21 +305,21 @@ proc notNilCheck(tracked: PEffects, n: PNode, paramType: PType) =
     if n.kind == nkAddr:
       # addr(x[]) can't be proven, but addr(x) can:
       if not containsNode(n, {nkDerefExpr, nkHiddenDeref}): return
-    elif n.kind == nkSym and n.sym.kind in RoutineKinds:
+    elif n.kind == nkSym and n.sym.kind in routineKinds:
       # 'p' is not nil obviously:
       return
     case impliesNotNil(tracked.guards, n)
     of impUnknown:
-      Message(n.info, errGenerated, 
+      message(n.info, errGenerated, 
               "cannot prove '$1' is not nil" % n.renderTree)
     of impNo:
-      Message(n.info, errGenerated, "'$1' is provably nil" % n.renderTree)
+      message(n.info, errGenerated, "'$1' is provably nil" % n.renderTree)
     of impYes: discard
 
 proc trackOperand(tracked: PEffects, n: PNode, paramType: PType) =
   let op = n.typ
   if op != nil and op.kind == tyProc and n.kind != nkNilLit:
-    InternalAssert op.n.sons[0].kind == nkEffectList
+    internalAssert op.n.sons[0].kind == nkEffectList
     var effectList = op.n.sons[0]
     let s = n.skipConv
     if s.kind == nkSym and s.sym.kind in routineKinds:
@@ -367,7 +367,7 @@ proc trackCase(tracked: PEffects, n: PNode) =
     for i in oldState.. <tracked.init.len:
       addToIntersection(inter, tracked.init[i])
     
-  let exh = case skipTypes(n.sons[0].Typ, abstractVarRange-{tyTypeDesc}).Kind
+  let exh = case skipTypes(n.sons[0].typ, abstractVarRange-{tyTypeDesc}).kind
             of tyFloat..tyFloat128, tyString:
               lastSon(n).kind == nkElse
             else:
@@ -549,7 +549,7 @@ proc checkRaisesSpec(spec, real: PNode, msg: string, hints: bool) =
   if hints:
     for s in 0 .. <spec.len:
       if not used.contains(s):
-        Message(spec[s].info, hintXDeclaredButNotUsed, renderTree(spec[s]))
+        message(spec[s].info, hintXDeclaredButNotUsed, renderTree(spec[s]))
 
 proc checkMethodEffects*(disp, branch: PSym) =
   ## checks for consistent effects for multi methods.
@@ -568,13 +568,13 @@ proc checkMethodEffects*(disp, branch: PSym) =
 
 proc setEffectsForProcType*(t: PType, n: PNode) =
   var effects = t.n.sons[0]
-  InternalAssert t.kind == tyProc and effects.kind == nkEffectList
+  internalAssert t.kind == tyProc and effects.kind == nkEffectList
 
   let
     raisesSpec = effectSpec(n, wRaises)
     tagsSpec = effectSpec(n, wTags)
   if not isNil(raisesSpec) or not isNil(tagsSpec):
-    InternalAssert effects.len == 0
+    internalAssert effects.len == 0
     newSeq(effects.sons, effectListLen)
     if not isNil(raisesSpec):
       effects.sons[exceptionEffects] = raisesSpec
@@ -583,7 +583,7 @@ proc setEffectsForProcType*(t: PType, n: PNode) =
 
 proc trackProc*(s: PSym, body: PNode) =
   var effects = s.typ.n.sons[0]
-  InternalAssert effects.kind == nkEffectList
+  internalAssert effects.kind == nkEffectList
   # effects already computed?
   if sfForward in s.flags: return
   if effects.len == effectListLen: return
@@ -603,7 +603,7 @@ proc trackProc*(s: PSym, body: PNode) =
       s.kind in {skProc, skConverter, skMethod}:
     var res = s.ast.sons[resultPos].sym # get result symbol
     if res.id notin t.init:
-      Message(body.info, warnProveInit, "result")
+      message(body.info, warnProveInit, "result")
   let p = s.ast.sons[pragmasPos]
   let raisesSpec = effectSpec(p, wRaises)
   if not isNil(raisesSpec):
@@ -618,4 +618,4 @@ proc trackProc*(s: PSym, body: PNode) =
                     hints=off)
     # after the check, use the formal spec:
     effects.sons[tagEffects] = tagsSpec
-    
\ No newline at end of file
+    
diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim
index a1805fdec..caa719c7e 100644
--- a/compiler/semstmts.nim
+++ b/compiler/semstmts.nim
@@ -10,7 +10,7 @@
 ## this module does the semantic checking of statements
 #  included from sem.nim
 
-var EnforceVoidContext = PType(kind: tyStmt)
+var enforceVoidContext = PType(kind: tyStmt)
 
 proc semCommand(c: PContext, n: PNode): PNode =
   result = semExprNoType(c, n)
@@ -58,10 +58,10 @@ proc semWhile(c: PContext, n: PNode): PNode =
   n.sons[1] = semStmt(c, n.sons[1])
   dec(c.p.nestedLoopCounter)
   closeScope(c)
-  if n.sons[1].typ == EnforceVoidContext:
-    result.typ = EnforceVoidContext
+  if n.sons[1].typ == enforceVoidContext:
+    result.typ = enforceVoidContext
 
-proc toCover(t: PType): biggestInt = 
+proc toCover(t: PType): BiggestInt = 
   var t2 = skipTypes(t, abstractVarRange-{tyTypeDesc})
   if t2.kind == tyEnum and enumHasHoles(t2): 
     result = sonsLen(t2.n)
@@ -70,9 +70,9 @@ proc toCover(t: PType): biggestInt =
 
 proc performProcvarCheck(c: PContext, n: PNode, s: PSym) =
   var smoduleId = getModule(s).id
-  if sfProcVar notin s.flags and s.typ.callConv == ccDefault and
+  if sfProcvar notin s.flags and s.typ.callConv == ccDefault and
       smoduleId != c.module.id and smoduleId != c.friendModule.id: 
-    LocalError(n.info, errXCannotBePassedToProcVar, s.name.s)
+    localError(n.info, errXCannotBePassedToProcVar, s.name.s)
 
 proc semProcvarCheck(c: PContext, n: PNode) =
   let n = n.skipConv
@@ -86,8 +86,8 @@ include semdestruct
 
 proc semDestructorCheck(c: PContext, n: PNode, flags: TExprFlags) {.inline.} =
   if efAllowDestructor notin flags and n.kind in nkCallKinds+{nkObjConstr}:
-    if instantiateDestructor(c, n.typ):
-      LocalError(n.info, errGenerated,
+    if instantiateDestructor(c, n.typ) != nil:
+      localError(n.info, errGenerated,
         "usage of a type with a destructor in a non destructible context")
   # This still breaks too many things:
   when false:
@@ -117,7 +117,7 @@ const
     nkElse, nkStmtListExpr, nkTryStmt, nkFinally, nkExceptBranch,
     nkElifBranch, nkElifExpr, nkElseExpr, nkBlockStmt, nkBlockExpr}
 
-proc ImplicitlyDiscardable(n: PNode): bool =
+proc implicitlyDiscardable(n: PNode): bool =
   var n = n
   while n.kind in skipForDiscardable: n = n.lastSon
   result = isCallExpr(n) and n.sons[0].kind == nkSym and 
@@ -136,19 +136,21 @@ proc discardCheck(c: PContext, result: PNode) =
   if result.typ != nil and result.typ.kind notin {tyStmt, tyEmpty}:
     if result.kind == nkNilLit:
       result.typ = nil
-    elif ImplicitlyDiscardable(result):
+      message(result.info, warnNilStatement)
+    elif implicitlyDiscardable(result):
       var n = result
       result.typ = nil
       while n.kind in skipForDiscardable:
         n = n.lastSon
         n.typ = nil
-    elif c.InTypeClass > 0 and result.typ.kind == tyBool:
+    elif c.inTypeClass > 0 and result.typ.kind == tyBool:
       let verdict = semConstExpr(c, result)
       if verdict.intVal == 0:
-        localError(result.info, "type class predicate failed.")
+        localError(result.info, "type class predicate failed")
     elif result.typ.kind != tyError and gCmd != cmdInteractive:
       if result.typ.kind == tyNil:
         fixNilType(result)
+        message(result.info, warnNilStatement)
       else:
         var n = result
         while n.kind in skipForDiscardable: n = n.lastSon
@@ -156,7 +158,7 @@ proc discardCheck(c: PContext, result: PNode) =
 
 proc semIf(c: PContext, n: PNode): PNode = 
   result = n
-  var typ = CommonTypeBegin
+  var typ = commonTypeBegin
   var hasElse = false
   for i in countup(0, sonsLen(n) - 1): 
     var it = n.sons[i]
@@ -176,7 +178,7 @@ proc semIf(c: PContext, n: PNode): PNode =
     for it in n: discardCheck(c, it.lastSon)
     result.kind = nkIfStmt
     # propagate any enforced VoidContext:
-    if typ == EnforceVoidContext: result.typ = EnforceVoidContext
+    if typ == enforceVoidContext: result.typ = enforceVoidContext
   else:
     for it in n:
       let j = it.len-1
@@ -190,16 +192,16 @@ proc semCase(c: PContext, n: PNode): PNode =
   openScope(c)
   n.sons[0] = semExprWithType(c, n.sons[0])
   var chckCovered = false
-  var covered: biggestint = 0
-  var typ = CommonTypeBegin
+  var covered: BiggestInt = 0
+  var typ = commonTypeBegin
   var hasElse = false
-  case skipTypes(n.sons[0].Typ, abstractVarRange-{tyTypeDesc}).Kind
+  case skipTypes(n.sons[0].typ, abstractVarRange-{tyTypeDesc}).kind
   of tyInt..tyInt64, tyChar, tyEnum, tyUInt..tyUInt32:
     chckCovered = true
   of tyFloat..tyFloat128, tyString, tyError:
-    nil
+    discard
   else:
-    LocalError(n.info, errSelectorMustBeOfCertainTypes)
+    localError(n.info, errSelectorMustBeOfCertainTypes)
     return
   for i in countup(1, sonsLen(n) - 1): 
     var x = n.sons[i]
@@ -236,8 +238,8 @@ proc semCase(c: PContext, n: PNode): PNode =
   if isEmptyType(typ) or typ.kind == tyNil or not hasElse:
     for i in 1..n.len-1: discardCheck(c, n.sons[i].lastSon)
     # propagate any enforced VoidContext:
-    if typ == EnforceVoidContext:
-      result.typ = EnforceVoidContext
+    if typ == enforceVoidContext:
+      result.typ = enforceVoidContext
   else:
     for i in 1..n.len-1:
       var it = n.sons[i]
@@ -249,7 +251,7 @@ proc semTry(c: PContext, n: PNode): PNode =
   result = n
   inc c.p.inTryStmt
   checkMinSonsLen(n, 2)
-  var typ = CommonTypeBegin
+  var typ = commonTypeBegin
   n.sons[0] = semExprBranchScope(c, n.sons[0])
   typ = commonType(typ, n.sons[0].typ)
   var check = initIntSet()
@@ -267,10 +269,10 @@ proc semTry(c: PContext, n: PNode): PNode =
         var typ = semTypeNode(c, a.sons[j], nil)
         if typ.kind == tyRef: typ = typ.sons[0]
         if typ.kind != tyObject:
-          LocalError(a.sons[j].info, errExprCannotBeRaised)
+          localError(a.sons[j].info, errExprCannotBeRaised)
         a.sons[j] = newNodeI(nkType, a.sons[j].info)
         a.sons[j].typ = typ
-        if ContainsOrIncl(check, typ.id):
+        if containsOrIncl(check, typ.id):
           localError(a.sons[j].info, errExceptionAlreadyHandled)
     elif a.kind != nkFinally: 
       illFormedAst(n)
@@ -281,8 +283,8 @@ proc semTry(c: PContext, n: PNode): PNode =
   if isEmptyType(typ) or typ.kind == tyNil:
     discardCheck(c, n.sons[0])
     for i in 1..n.len-1: discardCheck(c, n.sons[i].lastSon)
-    if typ == EnforceVoidContext:
-      result.typ = EnforceVoidContext
+    if typ == enforceVoidContext:
+      result.typ = enforceVoidContext
   else:
     n.sons[0] = fitNode(c, typ, n.sons[0])
     for i in 1..n.len-1:
@@ -291,7 +293,7 @@ proc semTry(c: PContext, n: PNode): PNode =
       it.sons[j] = fitNode(c, typ, it.sons[j])
     result.typ = typ
   
-proc fitRemoveHiddenConv(c: PContext, typ: Ptype, n: PNode): PNode = 
+proc fitRemoveHiddenConv(c: PContext, typ: PType, n: PNode): PNode = 
   result = fitNode(c, typ, n)
   if result.kind in {nkHiddenStdConv, nkHiddenSubConv}: 
     changeType(result.sons[1], typ, check=true)
@@ -302,7 +304,7 @@ proc fitRemoveHiddenConv(c: PContext, typ: Ptype, n: PNode): PNode =
 proc findShadowedVar(c: PContext, v: PSym): PSym =
   for scope in walkScopes(c.currentScope.parent):
     if scope == c.topLevelScope: break
-    let shadowed = StrTableGet(scope.symbols, v.name)
+    let shadowed = strTableGet(scope.symbols, v.name)
     if shadowed != nil and shadowed.kind in skLocalVars:
       return shadowed
 
@@ -322,9 +324,9 @@ proc semIdentDef(c: PContext, n: PNode, kind: TSymKind): PSym =
 proc checkNilable(v: PSym) =
   if sfGlobal in v.flags and {tfNotNil, tfNeedsInit} * v.typ.flags != {}:
     if v.ast.isNil:
-      Message(v.info, warnProveInit, v.name.s)
+      message(v.info, warnProveInit, v.name.s)
     elif tfNotNil in v.typ.flags and tfNotNil notin v.ast.typ.flags:
-      Message(v.info, warnProveInit, v.name.s)
+      message(v.info, warnProveInit, v.name.s)
 
 proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode = 
   var b: PNode
@@ -333,7 +335,7 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
     var a = n.sons[i]
     if gCmd == cmdIdeTools: suggestStmt(c, a)
     if a.kind == nkCommentStmt: continue 
-    if a.kind notin {nkIdentDefs, nkVarTuple, nkConstDef}: IllFormedAst(a)
+    if a.kind notin {nkIdentDefs, nkVarTuple, nkConstDef}: illFormedAst(a)
     checkMinSonsLen(a, 3)
     var length = sonsLen(a)
     var typ: PType
@@ -350,12 +352,12 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
       else: typ = skipIntLit(def.typ)
     else:
       def = ast.emptyNode
-      if symkind == skLet: LocalError(a.info, errLetNeedsInit)
+      if symkind == skLet: localError(a.info, errLetNeedsInit)
       
     # this can only happen for errornous var statements:
     if typ == nil: continue
     if not typeAllowed(typ, symkind): 
-      LocalError(a.info, errXisNoType, typeToString(typ))
+      localError(a.info, errXisNoType, typeToString(typ))
     var tup = skipTypes(typ, {tyGenericInst})
     if a.kind == nkVarTuple: 
       if tup.kind != tyTuple: 
@@ -370,12 +372,12 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
         addSon(result, b)
     elif tup.kind == tyTuple and def.kind == nkPar and 
         a.kind == nkIdentDefs and a.len > 3:
-      Message(a.info, warnEachIdentIsTuple)
+      message(a.info, warnEachIdentIsTuple)
     for j in countup(0, length-3):
       var v = semIdentDef(c, a.sons[j], symkind)
       if sfGenSym notin v.flags: addInterfaceDecl(c, v)
       when oKeepVariableNames:
-        if c.InUnrolledContext > 0: v.flags.incl(sfShadowed)
+        if c.inUnrolledContext > 0: v.flags.incl(sfShadowed)
         else:
           let shadowed = findShadowedVar(c, v)
           if shadowed != nil:
@@ -383,12 +385,12 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode =
             # a shadowed variable is an error unless it appears on the right
             # side of the '=':
             if warnShadowIdent in gNotes and not identWithin(def, v.name):
-              Message(a.info, warnShadowIdent, v.name.s)
+              message(a.info, warnShadowIdent, v.name.s)
       if a.kind != nkVarTuple:
         if def != nil and def.kind != nkEmpty:
           # this is needed for the evaluation pass and for the guard checking:
           v.ast = def
-          if sfThread in v.flags: LocalError(def.info, errThreadvarCannotInit)
+          if sfThread in v.flags: localError(def.info, errThreadvarCannotInit)
         v.typ = typ
         b = newNodeI(nkIdentDefs, a.info)
         if importantComments():
@@ -410,7 +412,7 @@ proc semConst(c: PContext, n: PNode): PNode =
     var a = n.sons[i]
     if gCmd == cmdIdeTools: suggestStmt(c, a)
     if a.kind == nkCommentStmt: continue 
-    if (a.kind != nkConstDef): IllFormedAst(a)
+    if (a.kind != nkConstDef): illFormedAst(a)
     checkSonsLen(a, 3)
     var v = semIdentDef(c, a.sons[0], skConst)
     var typ: PType = nil
@@ -418,16 +420,18 @@ proc semConst(c: PContext, n: PNode): PNode =
 
     var def = semConstExpr(c, a.sons[2])
     if def == nil:
-      LocalError(a.sons[2].info, errConstExprExpected)
+      localError(a.sons[2].info, errConstExprExpected)
       continue
     # check type compatibility between def.typ and typ:
     if typ != nil:
       def = fitRemoveHiddenConv(c, typ, def)
     else:
       typ = def.typ
-    if typ == nil: continue
+    if typ == nil:
+      localError(a.sons[2].info, errConstExprExpected)
+      continue
     if not typeAllowed(typ, skConst):
-      LocalError(a.info, errXisNoType, typeToString(typ))
+      localError(a.info, errXisNoType, typeToString(typ))
       continue
     v.typ = typ
     v.ast = def               # no need to copy
@@ -494,17 +498,17 @@ proc semForObjectFields(c: TFieldsCtx, typ, forLoop, father: PNode) =
     fc.field = typ.sym
     fc.replaceByFieldName = c.m == mFieldPairs
     openScope(c.c)
-    inc c.c.InUnrolledContext
+    inc c.c.inUnrolledContext
     let body = instFieldLoopBody(fc, lastSon(forLoop), forLoop)
-    father.add(SemStmt(c.c, body))
-    dec c.c.InUnrolledContext
+    father.add(semStmt(c.c, body))
+    dec c.c.inUnrolledContext
     closeScope(c.c)
-  of nkNilLit: nil
+  of nkNilLit: discard
   of nkRecCase:
     let L = forLoop.len
     let call = forLoop.sons[L-2]
     if call.len > 2:
-      LocalError(forLoop.info, errGenerated, 
+      localError(forLoop.info, errGenerated, 
                  "parallel 'fields' iterator does not work for 'case' objects")
       return
     # iterate over the selector:
@@ -533,9 +537,9 @@ proc semForFields(c: PContext, n: PNode, m: TMagic): PNode =
   # so that 'break' etc. work as expected, we produce
   # a 'while true: stmt; break' loop ...
   result = newNodeI(nkWhileStmt, n.info, 2)
-  var trueSymbol = StrTableGet(magicsys.systemModule.Tab, getIdent"true")
+  var trueSymbol = strTableGet(magicsys.systemModule.tab, getIdent"true")
   if trueSymbol == nil: 
-    LocalError(n.info, errSystemNeeds, "true")
+    localError(n.info, errSystemNeeds, "true")
     trueSymbol = newSym(skUnknown, getIdent"true", getCurrOwner(), n.info)
     trueSymbol.typ = getSysType(tyBool)
 
@@ -546,7 +550,7 @@ proc semForFields(c: PContext, n: PNode, m: TMagic): PNode =
   var length = sonsLen(n)
   var call = n.sons[length-2]
   if length-2 != sonsLen(call)-1 + ord(m==mFieldPairs):
-    LocalError(n.info, errWrongNumberOfVariables)
+    localError(n.info, errWrongNumberOfVariables)
     return result
   
   var tupleTypeA = skipTypes(call.sons[1].typ, abstractVar-{tyTypeDesc})
@@ -555,10 +559,10 @@ proc semForFields(c: PContext, n: PNode, m: TMagic): PNode =
     return result
   for i in 1..call.len-1:
     var tupleTypeB = skipTypes(call.sons[i].typ, abstractVar-{tyTypeDesc})
-    if not SameType(tupleTypeA, tupleTypeB):
+    if not sameType(tupleTypeA, tupleTypeB):
       typeMismatch(call.sons[i], tupleTypeA, tupleTypeB)
   
-  Inc(c.p.nestedLoopCounter)
+  inc(c.p.nestedLoopCounter)
   if tupleTypeA.kind == tyTuple:
     var loopBody = n.sons[length-1]
     for i in 0..sonsLen(tupleTypeA)-1:
@@ -568,16 +572,16 @@ proc semForFields(c: PContext, n: PNode, m: TMagic): PNode =
       fc.tupleIndex = i
       fc.replaceByFieldName = m == mFieldPairs
       var body = instFieldLoopBody(fc, loopBody, n)
-      inc c.InUnrolledContext
-      stmts.add(SemStmt(c, body))
-      dec c.InUnrolledContext
+      inc c.inUnrolledContext
+      stmts.add(semStmt(c, body))
+      dec c.inUnrolledContext
       closeScope(c)
   else:
     var fc: TFieldsCtx
     fc.m = m
     fc.c = c
     semForObjectFields(fc, tupleTypeA.n, n, stmts)
-  Dec(c.p.nestedLoopCounter)
+  dec(c.p.nestedLoopCounter)
   # for TR macros this 'while true: ...; break' loop is pretty bad, so
   # we avoid it now if we can:
   if hasSonWith(stmts, nkBreakStmt):
@@ -593,7 +597,7 @@ proc addForVarDecl(c: PContext, v: PSym) =
     if shadowed != nil:
       # XXX should we do this here?
       #shadowed.flags.incl(sfShadowed)
-      Message(v.info, warnShadowIdent, v.name.s)
+      message(v.info, warnShadowIdent, v.name.s)
   addDecl(c, v)
 
 proc symForVar(c: PContext, n: PNode): PSym =
@@ -617,9 +621,9 @@ proc semForVars(c: PContext, n: PNode): PNode =
       n.sons[0] = newSymNode(v)
       if sfGenSym notin v.flags: addForVarDecl(c, v)
     else:
-      LocalError(n.info, errWrongNumberOfVariables)
+      localError(n.info, errWrongNumberOfVariables)
   elif length-2 != sonsLen(iter):
-    LocalError(n.info, errWrongNumberOfVariables)
+    localError(n.info, errWrongNumberOfVariables)
   else:
     for i in countup(0, length - 3):
       var v = symForVar(c, n.sons[i])
@@ -627,9 +631,9 @@ proc semForVars(c: PContext, n: PNode): PNode =
       v.typ = iter.sons[i]
       n.sons[i] = newSymNode(v)
       if sfGenSym notin v.flags: addForVarDecl(c, v)
-  Inc(c.p.nestedLoopCounter)
-  n.sons[length-1] = SemStmt(c, n.sons[length-1])
-  Dec(c.p.nestedLoopCounter)
+  inc(c.p.nestedLoopCounter)
+  n.sons[length-1] = semStmt(c, n.sons[length-1])
+  dec(c.p.nestedLoopCounter)
 
 proc implicitIterator(c: PContext, it: string, arg: PNode): PNode =
   result = newNodeI(nkCall, arg.info)
@@ -657,7 +661,7 @@ proc semFor(c: PContext, n: PNode): PNode =
     elif length == 4:
       n.sons[length-2] = implicitIterator(c, "pairs", n.sons[length-2])
     else:
-      LocalError(n.sons[length-2].info, errIteratorExpected)
+      localError(n.sons[length-2].info, errIteratorExpected)
     result = semForVars(c, n)
   elif call.sons[0].sym.magic != mNone:
     if call.sons[0].sym.magic == mOmpParFor:
@@ -668,8 +672,8 @@ proc semFor(c: PContext, n: PNode): PNode =
   else:
     result = semForVars(c, n)
   # propagate any enforced VoidContext:
-  if n.sons[length-1].typ == EnforceVoidContext:
-    result.typ = EnforceVoidContext
+  if n.sons[length-1].typ == enforceVoidContext:
+    result.typ = enforceVoidContext
   closeScope(c)
 
 proc semRaise(c: PContext, n: PNode): PNode = 
@@ -695,7 +699,7 @@ proc typeSectionLeftSidePass(c: PContext, n: PNode) =
     var a = n.sons[i]
     if gCmd == cmdIdeTools: suggestStmt(c, a)
     if a.kind == nkCommentStmt: continue 
-    if a.kind != nkTypeDef: IllFormedAst(a)
+    if a.kind != nkTypeDef: illFormedAst(a)
     checkSonsLen(a, 3)
     var s = semIdentDef(c, a.sons[0], skType)
     s.typ = newTypeS(tyForward, c)
@@ -710,12 +714,12 @@ proc typeSectionRightSidePass(c: PContext, n: PNode) =
   for i in countup(0, sonsLen(n) - 1): 
     var a = n.sons[i]
     if a.kind == nkCommentStmt: continue 
-    if (a.kind != nkTypeDef): IllFormedAst(a)
+    if (a.kind != nkTypeDef): illFormedAst(a)
     checkSonsLen(a, 3)
-    if (a.sons[0].kind != nkSym): IllFormedAst(a)
+    if (a.sons[0].kind != nkSym): illFormedAst(a)
     var s = a.sons[0].sym
     if s.magic == mNone and a.sons[2].kind == nkEmpty: 
-      LocalError(a.info, errImplOfXexpected, s.name.s)
+      localError(a.info, errImplOfXexpected, s.name.s)
     if s.magic != mNone: processMagicType(c, s)
     if a.sons[1].kind != nkEmpty: 
       # We have a generic type declaration here. In generic types,
@@ -738,16 +742,12 @@ proc typeSectionRightSidePass(c: PContext, n: PNode) =
       # like: mydata.seq
       rawAddSon(s.typ, newTypeS(tyEmpty, c))
       s.ast = a
-      when oUseLateInstantiation:
-        var body: PType = nil
-        s.typScope = c.currentScope.parent
-      else:
-        inc c.InGenericContext
-        var body = semTypeNode(c, a.sons[2], nil)
-        dec c.InGenericContext
-        if body != nil:
-          body.sym = s
-          body.size = -1 # could not be computed properly
+      inc c.inGenericContext
+      var body = semTypeNode(c, a.sons[2], nil)
+      dec c.inGenericContext
+      if body != nil:
+        body.sym = s
+        body.size = -1 # could not be computed properly
       s.typ.sons[sonsLen(s.typ) - 1] = body
       popOwner()
       closeScope(c)
@@ -768,7 +768,7 @@ proc typeSectionFinalPass(c: PContext, n: PNode) =
   for i in countup(0, sonsLen(n) - 1): 
     var a = n.sons[i]
     if a.kind == nkCommentStmt: continue 
-    if a.sons[0].kind != nkSym: IllFormedAst(a)
+    if a.sons[0].kind != nkSym: illFormedAst(a)
     var s = a.sons[0].sym
     # compute the type's size and check for illegal recursions:
     if a.sons[1].kind == nkEmpty: 
@@ -786,12 +786,12 @@ proc typeSectionFinalPass(c: PContext, n: PNode) =
       # give anonymous object a dummy symbol:
       var st = s.typ
       if st.kind == tyGenericBody: st = st.lastSon
-      InternalAssert st.kind in {tyPtr, tyRef}
-      InternalAssert st.sons[0].sym == nil
+      internalAssert st.kind in {tyPtr, tyRef}
+      internalAssert st.sons[0].sym == nil
       st.sons[0].sym = newSym(skType, getIdent(s.name.s & ":ObjectType"),
                               getCurrOwner(), s.info)
 
-proc SemTypeSection(c: PContext, n: PNode): PNode =
+proc semTypeSection(c: PContext, n: PNode): PNode =
   typeSectionLeftSidePass(c, n)
   typeSectionRightSidePass(c, n)
   typeSectionFinalPass(c, n)
@@ -810,12 +810,12 @@ proc addParams(c: PContext, n: PNode, kind: TSymKind) =
 
 proc semBorrow(c: PContext, n: PNode, s: PSym) = 
   # search for the correct alias:
-  var b = SearchForBorrowProc(c, c.currentScope.parent, s)
+  var b = searchForBorrowProc(c, c.currentScope.parent, s)
   if b != nil: 
     # store the alias:
     n.sons[bodyPos] = newSymNode(b)
   else:
-    LocalError(n.info, errNoSymbolToBorrowFromFound) 
+    localError(n.info, errNoSymbolToBorrowFromFound) 
   
 proc addResult(c: PContext, t: PType, info: TLineInfo, owner: TSymKind) = 
   if t != nil: 
@@ -853,7 +853,7 @@ proc semProcAnnotation(c: PContext, prc: PNode): PNode =
           prc.sons[namePos] = newIdentNode(idDelegator, prc.info)
           prc.sons[pragmasPos] = copyExcept(n, i)
         else:
-          LocalError(prc.info, errOnlyACallOpCanBeDelegator)
+          localError(prc.info, errOnlyACallOpCanBeDelegator)
       continue
     # we transform ``proc p {.m, rest.}`` into ``m(do: proc p {.rest.})`` and
     # let the semantic checker deal with it:
@@ -868,6 +868,8 @@ proc semProcAnnotation(c: PContext, prc: PNode): PNode =
     return semStmt(c, x)
 
 proc semLambda(c: PContext, n: PNode, flags: TExprFlags): PNode =
+  # XXX semProcAux should be good enough for this now, we will eventually
+  # remove semLambda
   result = semProcAnnotation(c, n)
   if result != nil: return result
   result = n
@@ -885,8 +887,8 @@ proc semLambda(c: PContext, n: PNode, flags: TExprFlags): PNode =
     illFormedAst(n)           # process parameters:
   if n.sons[paramsPos].kind != nkEmpty:
     var gp = newNodeI(nkGenericParams, n.info)
-    semParamList(c, n.sons[ParamsPos], gp, s)
-    ParamsTypeCheck(c, s.typ)
+    semParamList(c, n.sons[paramsPos], gp, s)
+    paramsTypeCheck(c, s.typ)
   else:
     s.typ = newTypeS(tyProc, c)
     rawAddSon(s.typ, nil)
@@ -895,7 +897,7 @@ proc semLambda(c: PContext, n: PNode, flags: TExprFlags): PNode =
   s.options = gOptions
   if n.sons[bodyPos].kind != nkEmpty:
     if sfImportc in s.flags:
-      LocalError(n.sons[bodyPos].info, errImplOfXNotAllowed, s.name.s)
+      localError(n.sons[bodyPos].info, errImplOfXNotAllowed, s.name.s)
     #if efDetermineType notin flags:
     # XXX not good enough; see tnamedparamanonproc.nim
     pushProcCon(c, s)
@@ -906,7 +908,7 @@ proc semLambda(c: PContext, n: PNode, flags: TExprFlags): PNode =
     popProcCon(c)
     sideEffectsCheck(c, s)
   else:
-    LocalError(n.info, errImplOfXexpected, s.name.s)
+    localError(n.info, errImplOfXexpected, s.name.s)
   closeScope(c)           # close scope for parameters
   popOwner()
   result.typ = s.typ
@@ -922,7 +924,7 @@ proc activate(c: PContext, n: PNode) =
     of nkCallKinds:
       for i in 1 .. <n.len: activate(c, n[i])
     else:
-      nil
+      discard
 
 proc maybeAddResult(c: PContext, s: PSym, n: PNode) =
   if s.typ.sons[0] != nil and
@@ -937,7 +939,7 @@ type
     stepCompileBody
 
 proc isForwardDecl(s: PSym): bool =
-  InternalAssert s.kind == skProc
+  internalAssert s.kind == skProc
   result = s.ast[bodyPos].kind != nkEmpty
 
 proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
@@ -949,9 +951,15 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
   checkSonsLen(n, bodyPos + 1)
   var s: PSym
   var typeIsDetermined = false
+  var isAnon = false
   if n[namePos].kind != nkSym:
     assert phase == stepRegisterSymbol
-    s = semIdentDef(c, n.sons[0], kind)
+
+    if n[namePos].kind == nkEmpty:
+      s = newSym(kind, idAnon, getCurrOwner(), n.info)
+      isAnon = true
+    else:
+      s = semIdentDef(c, n.sons[0], kind)
     n.sons[namePos] = newSymNode(s)
     s.ast = n
     s.scope = c.currentScope
@@ -980,7 +988,7 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
     gp = newNodeI(nkGenericParams, n.info)
   # process parameters:
   if n.sons[paramsPos].kind != nkEmpty:
-    semParamList(c, n.sons[ParamsPos], gp, s)
+    semParamList(c, n.sons[paramsPos], gp, s)
     if sonsLen(gp) > 0: 
       if n.sons[genericParamsPos].kind == nkEmpty:
         # we have a list of implicit type parameters:
@@ -992,13 +1000,15 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
     rawAddSon(s.typ, nil)
   if n.sons[patternPos].kind != nkEmpty:
     n.sons[patternPos] = semPattern(c, n.sons[patternPos])
-  if s.kind == skIterator: s.typ.flags.incl(tfIterator)
+  if s.kind == skIterator: 
+    s.typ.flags.incl(tfIterator)
   
-  var proto = SearchForProc(c, s.scope, s)
+  var proto = searchForProc(c, s.scope, s)
   if proto == nil: 
-    s.typ.callConv = lastOptionEntry(c).defaultCC
+    if s.kind == skIterator and isAnon: s.typ.callConv = ccClosure
+    else: s.typ.callConv = lastOptionEntry(c).defaultCC
     # add it here, so that recursive procs are possible:
-    if sfGenSym in s.flags: nil
+    if sfGenSym in s.flags: discard
     elif kind in OverloadableSyms:
       if not typeIsDetermined:
         addInterfaceOverloadableSymAt(c, s.scope, s)
@@ -1011,9 +1021,9 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
       implictPragmas(c, s, n, validPragmas)
   else: 
     if n.sons[pragmasPos].kind != nkEmpty: 
-      LocalError(n.sons[pragmasPos].info, errPragmaOnlyInHeaderOfProc)
+      localError(n.sons[pragmasPos].info, errPragmaOnlyInHeaderOfProc)
     if sfForward notin proto.flags: 
-      WrongRedefinition(n.info, proto.name.s)
+      wrongRedefinition(n.info, proto.name.s)
     excl(proto.flags, sfForward)
     closeScope(c)         # close scope with wrong parameter symbols
     openScope(c)          # open scope for old (correct) parameter symbols
@@ -1026,7 +1036,7 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
     n.sons[genericParamsPos] = proto.ast.sons[genericParamsPos]
     n.sons[paramsPos] = proto.ast.sons[paramsPos]
     n.sons[pragmasPos] = proto.ast.sons[pragmasPos]
-    if n.sons[namePos].kind != nkSym: InternalError(n.info, "semProcAux")
+    if n.sons[namePos].kind != nkSym: internalError(n.info, "semProcAux")
     n.sons[namePos].sym = proto
     if importantComments() and not isNil(proto.ast.comment):
       n.comment = proto.ast.comment
@@ -1035,12 +1045,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: 
-      LocalError(n.sons[bodyPos].info, errImplOfXNotAllowed, s.name.s)
-    if n.sons[genericParamsPos].kind == nkEmpty: 
-      ParamsTypeCheck(c, s.typ)
+    if sfBorrow in s.flags:
+      localError(n.sons[bodyPos].info, errImplOfXNotAllowed, s.name.s)
+    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:
@@ -1050,17 +1064,17 @@ 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:
-    if proto != nil: LocalError(n.info, errImplOfXexpected, proto.name.s)
+    if proto != nil: localError(n.info, errImplOfXexpected, proto.name.s)
     if {sfImportc, sfBorrow} * s.flags == {} and s.magic == mNone: 
       incl(s.flags, sfForward)
     elif sfBorrow in s.flags: semBorrow(c, n, s)
@@ -1070,6 +1084,7 @@ proc semProcAux(c: PContext, n: PNode, kind: TSymKind,
   popOwner()
   if n.sons[patternPos].kind != nkEmpty:
     c.patterns.add(s)
+  if isAnon: result.typ = s.typ
 
 proc determineType(c: PContext, s: PSym) =
   if s.typ != nil: return
@@ -1081,7 +1096,7 @@ proc semIterator(c: PContext, n: PNode): PNode =
   var s = result.sons[namePos].sym
   var t = s.typ
   if t.sons[0] == nil and s.typ.callConv != ccClosure:
-    LocalError(n.info, errXNeedsReturnType, "iterator")
+    localError(n.info, errXNeedsReturnType, "iterator")
   # iterators are either 'inline' or 'closure'; for backwards compatibility,
   # we require first class iterators to be marked with 'closure' explicitly
   # -- at least for 0.9.2.
@@ -1095,7 +1110,7 @@ proc semIterator(c: PContext, n: PNode): PNode =
       # and they always at least use the 'env' for the state field:
       incl(s.typ.flags, tfCapturesEnv)
   if n.sons[bodyPos].kind == nkEmpty and s.magic == mNone:
-    LocalError(n.info, errImplOfXexpected, s.name.s)
+    localError(n.info, errImplOfXexpected, s.name.s)
   
 proc semProc(c: PContext, n: PNode): PNode = 
   result = semProcAux(c, n, skProc, procPragmas)
@@ -1146,11 +1161,11 @@ proc evalInclude(c: PContext, n: PNode): PNode =
   for i in countup(0, sonsLen(n) - 1): 
     var f = checkModuleName(n.sons[i])
     if f != InvalidFileIDX:
-      if ContainsOrIncl(c.includedFiles, f): 
-        LocalError(n.info, errRecursiveDependencyX, f.toFilename)
+      if containsOrIncl(c.includedFiles, f): 
+        localError(n.info, errRecursiveDependencyX, f.toFilename)
       else:
         addSon(result, semStmt(c, gIncludeFile(c.module, f)))
-        Excl(c.includedFiles, f)
+        excl(c.includedFiles, f)
   
 proc setLine(n: PNode, info: TLineInfo) =
   for i in 0 .. <safeLen(n): setLine(n.sons[i], info)
@@ -1159,20 +1174,25 @@ proc setLine(n: PNode, info: TLineInfo) =
 proc semPragmaBlock(c: PContext, n: PNode): PNode =
   let pragmaList = n.sons[0]
   pragma(c, nil, pragmaList, exprPragmas)
-  result = semStmt(c, n.sons[1])
+  result = semExpr(c, n.sons[1])
   for i in 0 .. <pragmaList.len:
     if whichPragma(pragmaList.sons[i]) == wLine:
       setLine(result, pragmaList.sons[i].info)
 
 proc semStaticStmt(c: PContext, n: PNode): PNode =
   let a = semStmt(c, n.sons[0])
-  result = evalStaticExpr(c, c.module, a, c.p.owner)
-  if result.isNil:
-    LocalError(n.info, errCannotInterpretNodeX, renderTree(n))
-    result = emptyNode
-  elif result.kind == nkEmpty:
-    result = newNodeI(nkDiscardStmt, n.info, 1)
-    result.sons[0] = emptyNode
+  n.sons[0] = a
+  evalStaticStmt(c.module, a, c.p.owner)
+  result = newNodeI(nkDiscardStmt, n.info, 1)
+  result.sons[0] = emptyNode
+  when false:
+    result = evalStaticStmt(c.module, a, c.p.owner)
+    if result.isNil:
+      LocalError(n.info, errCannotInterpretNodeX, renderTree(n))
+      result = emptyNode
+    elif result.kind == nkEmpty:
+      result = newNodeI(nkDiscardStmt, n.info, 1)
+      result.sons[0] = emptyNode
 
 proc usesResult(n: PNode): bool =
   # nkStmtList(expr) properly propagates the void context,
@@ -1224,10 +1244,10 @@ proc semStmtList(c: PContext, n: PNode): PNode =
       return
     else:
       n.sons[i] = semExpr(c, n.sons[i])
-      if n.sons[i].typ == EnforceVoidContext or usesResult(n.sons[i]):
+      if n.sons[i].typ == enforceVoidContext or usesResult(n.sons[i]):
         voidContext = true
-        n.typ = EnforceVoidContext
-      if i != last or voidContext:
+        n.typ = enforceVoidContext
+      if i != last or voidContext or c.inTypeClass > 0:
         discardCheck(c, n.sons[i])
       else:
         n.typ = n.sons[i].typ
@@ -1239,15 +1259,15 @@ proc semStmtList(c: PContext, n: PNode): PNode =
         if outer != nil:
           n.sons[i] = outer
           for j in countup(i+1, length-1):
-            inner.addSon(SemStmt(c, n.sons[j]))
+            inner.addSon(semStmt(c, n.sons[j]))
           n.sons.setLen(i+1)
           return
       of LastBlockStmts: 
         for j in countup(i + 1, length - 1): 
           case n.sons[j].kind
-          of nkPragma, nkCommentStmt, nkNilLit, nkEmpty: nil
+          of nkPragma, nkCommentStmt, nkNilLit, nkEmpty: discard
           else: localError(n.sons[j].info, errStmtInvalidAfterReturn)
-      else: nil
+      else: discard
   if result.len == 1:
     result = result.sons[0]
   when false:
@@ -1260,7 +1280,7 @@ proc semStmtList(c: PContext, n: PNode): PNode =
         #  "Last expression must be explicitly returned if it " &
         #  "is discardable or discarded")
 
-proc SemStmt(c: PContext, n: PNode): PNode = 
+proc semStmt(c: PContext, n: PNode): PNode = 
   # now: simply an alias:
   result = semExprNoType(c, n)
 
diff --git a/compiler/semtempl.nim b/compiler/semtempl.nim
index 68abc9aa6..5abc3ef33 100644
--- a/compiler/semtempl.nim
+++ b/compiler/semtempl.nim
@@ -1,7 +1,7 @@
 #
 #
 #           The Nimrod Compiler
-#        (c) Copyright 2013 Andreas Rumpf
+#        (c) Copyright 2014 Andreas Rumpf
 #
 #    See the file "copying.txt", included in this
 #    distribution, for details about the copyright.
@@ -14,7 +14,7 @@ discard """
   
     template `||` (a, b: expr): expr =
       let aa = a
-      (if aa: aa else: b)
+      if aa: aa else: b
     
     var
       a, b: T
@@ -36,9 +36,9 @@ proc symBinding(n: PNode): TSymBinding =
     var key = if it.kind == nkExprColonExpr: it.sons[0] else: it
     if key.kind == nkIdent:
       case whichKeyword(key.ident)
-      of wGenSym: return spGenSym
+      of wGensym: return spGenSym
       of wInject: return spInject
-      else: nil
+      else: discard
 
 type
   TSymChoiceRule = enum
@@ -79,7 +79,7 @@ proc semBindStmt(c: PContext, n: PNode, toBind: var TIntSet): PNode =
     # the same symbol!
     # This is however not true anymore for hygienic templates as semantic
     # processing for them changes the symbol table...
-    let s = QualifiedLookUp(c, a)
+    let s = qualifiedLookUp(c, a)
     if s != nil:
       # we need to mark all symbols:
       let sc = symChoice(c, n, s, scClosed)
@@ -106,7 +106,7 @@ proc replaceIdentBySym(n: var PNode, s: PNode) =
 type
   TemplCtx {.pure, final.} = object
     c: PContext
-    toBind, toMixin: TIntSet
+    toBind, toMixin, toInject: TIntSet
     owner: PSym
 
 proc getIdentNode(c: var TemplCtx, n: PNode): PNode =
@@ -115,7 +115,7 @@ proc getIdentNode(c: var TemplCtx, n: PNode): PNode =
   of nkPragmaExpr: result = getIdentNode(c, n.sons[0])
   of nkIdent:
     result = n
-    let s = QualifiedLookUp(c.c, n, {})
+    let s = qualifiedLookUp(c.c, n, {})
     if s != nil:
       if s.owner == c.owner and s.kind == skParam:
         result = newSymNode(s, n.info)
@@ -145,7 +145,18 @@ proc newGenSym(kind: TSymKind, n: PNode, c: var TemplCtx): PSym =
 
 proc addLocalDecl(c: var TemplCtx, n: var PNode, k: TSymKind) =
   # locals default to 'gensym':
-  if n.kind != nkPragmaExpr or symBinding(n.sons[1]) != spInject:
+  if n.kind == nkPragmaExpr and symBinding(n.sons[1]) == spInject:
+    # even if injected, don't produce a sym choice here:
+    #n = semTemplBody(c, n)
+    var x = n[0]
+    while true:
+      case x.kind
+      of nkPostfix: x = x[1]
+      of nkPragmaExpr: x = x[0]
+      of nkIdent: break
+      else: illFormedAst(x)
+    c.toInject.incl(x.ident.id)
+  else:
     let ident = getIdentNode(c, n)
     if not isTemplParam(c, ident):
       let local = newGenSym(k, ident, c)
@@ -153,8 +164,37 @@ proc addLocalDecl(c: var TemplCtx, n: var PNode, k: TSymKind) =
       replaceIdentBySym(n, newSymNode(local, n.info))
     else:
       replaceIdentBySym(n, ident)
+
+proc semTemplSymbol(c: PContext, n: PNode, s: PSym): PNode = 
+  incl(s.flags, sfUsed)
+  case s.kind
+  of skUnknown: 
+    # Introduced in this pass! Leave it as an identifier.
+    result = n
+  of skProc, skMethod, skIterator, skConverter, skTemplate, skMacro:
+    result = symChoice(c, n, s, scOpen)
+  of skGenericParam: 
+    result = newSymNodeTypeDesc(s, n.info)
+  of skParam: 
+    result = n
+  of skType: 
+    if (s.typ != nil) and (s.typ.kind != tyGenericParam): 
+      result = newSymNodeTypeDesc(s, n.info)
+    else: 
+      result = n
+  else: result = newSymNode(s, n.info)
+
+proc semRoutineInTemplName(c: var TemplCtx, n: PNode): PNode =
+  result = n
+  if n.kind == nkIdent:
+    let s = qualifiedLookUp(c.c, n, {})
+    if s != nil:
+      if s.owner == c.owner and (s.kind == skParam or sfGenSym in s.flags):
+        incl(s.flags, sfUsed)
+        result = newSymNode(s, n.info)
   else:
-    n = semTemplBody(c, n)
+    for i in countup(0, safeLen(n) - 1):
+      result.sons[i] = semRoutineInTemplName(c, n.sons[i])
 
 proc semRoutineInTemplBody(c: var TemplCtx, n: PNode, k: TSymKind): PNode =
   result = n
@@ -170,17 +210,17 @@ proc semRoutineInTemplBody(c: var TemplCtx, n: PNode, k: TSymKind): PNode =
     else:
       n.sons[namePos] = ident
   else:
-    n.sons[namePos] = semTemplBody(c, n.sons[namePos])
+    n.sons[namePos] = semRoutineInTemplName(c, n.sons[namePos])
   openScope(c)
   for i in patternPos..bodyPos:
     n.sons[i] = semTemplBody(c, n.sons[i])
   closeScope(c)
 
 proc semTemplSomeDecl(c: var TemplCtx, n: PNode, symKind: TSymKind) =
-  for i in countup(ord(symkind == skConditional), sonsLen(n) - 1):
+  for i in countup(0, sonsLen(n) - 1):
     var a = n.sons[i]
     if a.kind == nkCommentStmt: continue
-    if (a.kind != nkIdentDefs) and (a.kind != nkVarTuple): IllFormedAst(a)
+    if (a.kind != nkIdentDefs) and (a.kind != nkVarTuple): illFormedAst(a)
     checkMinSonsLen(a, 3)
     var L = sonsLen(a)
     a.sons[L-2] = semTemplBody(c, a.sons[L-2])
@@ -193,18 +233,23 @@ proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
   result = n
   case n.kind
   of nkIdent:
-    let s = QualifiedLookUp(c.c, n, {})
+    if n.ident.id in c.toInject: return n
+    let s = qualifiedLookUp(c.c, n, {})
     if s != nil:
       if s.owner == c.owner and s.kind == skParam:
         incl(s.flags, sfUsed)
         result = newSymNode(s, n.info)
-      elif Contains(c.toBind, s.id):
+      elif contains(c.toBind, s.id):
         result = symChoice(c.c, n, s, scClosed)
+      elif contains(c.toMixin, s.name.id):
+        result = symChoice(c.c, n, s, scForceOpen)
       elif s.owner == c.owner and sfGenSym in s.flags:
         # template tmp[T](x: var seq[T]) =
         # var yz: T
         incl(s.flags, sfUsed)
         result = newSymNode(s, n.info)
+      else:
+        result = semTemplSymbol(c.c, n, s)
   of nkBind:
     result = semTemplBody(c, n.sons[0])
   of nkBindStmt:
@@ -212,7 +257,7 @@ proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
   of nkMixinStmt:
     result = semMixinStmt(c.c, n, c.toMixin)
   of nkEmpty, nkSym..nkNilLit:
-    nil
+    discard
   of nkIfStmt:
     for i in countup(0, sonsLen(n)-1):
       var it = n.sons[i]
@@ -274,7 +319,7 @@ proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkConstDef): IllFormedAst(a)
+      if (a.kind != nkConstDef): illFormedAst(a)
       checkSonsLen(a, 3)
       addLocalDecl(c, a.sons[0], skConst)
       a.sons[1] = semTemplBody(c, a.sons[1])
@@ -283,13 +328,13 @@ proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
     for i in countup(0, sonsLen(n) - 1): 
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkTypeDef): IllFormedAst(a)
+      if (a.kind != nkTypeDef): illFormedAst(a)
       checkSonsLen(a, 3)
       addLocalDecl(c, a.sons[0], skType)
     for i in countup(0, sonsLen(n) - 1):
       var a = n.sons[i]
       if a.kind == nkCommentStmt: continue 
-      if (a.kind != nkTypeDef): IllFormedAst(a)
+      if (a.kind != nkTypeDef): illFormedAst(a)
       checkSonsLen(a, 3)
       if a.sons[1].kind != nkEmpty: 
         openScope(c)
@@ -310,14 +355,22 @@ proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
     result = semRoutineInTemplBody(c, n, skMacro)
   of nkConverterDef:
     result = semRoutineInTemplBody(c, n, skConverter)
+  of nkPragmaExpr:
+    result.sons[0] = semTemplBody(c, n.sons[0])
+  of nkPragma:
+    discard
   else:
     # dotExpr is ambiguous: note that we explicitely allow 'x.TemplateParam',
     # so we use the generic code for nkDotExpr too
     if n.kind == nkDotExpr or n.kind == nkAccQuoted:
-      let s = QualifiedLookUp(c.c, n, {})
+      let s = qualifiedLookUp(c.c, n, {})
       if s != nil:
-        if Contains(c.toBind, s.id):
+        if contains(c.toBind, s.id):
           return symChoice(c.c, n, s, scClosed)
+        elif contains(c.toMixin, s.name.id):
+          return symChoice(c.c, n, s, scForceOpen)
+        else:
+          return symChoice(c.c, n, s, scOpen)
     result = n
     for i in countup(0, sonsLen(n) - 1):
       result.sons[i] = semTemplBody(c, n.sons[i])
@@ -326,24 +379,24 @@ proc semTemplBodyDirty(c: var TemplCtx, n: PNode): PNode =
   result = n
   case n.kind
   of nkIdent:
-    let s = QualifiedLookUp(c.c, n, {})
+    let s = qualifiedLookUp(c.c, n, {})
     if s != nil:
       if s.owner == c.owner and s.kind == skParam:
         result = newSymNode(s, n.info)
-      elif Contains(c.toBind, s.id):
+      elif contains(c.toBind, s.id):
         result = symChoice(c.c, n, s, scClosed)
   of nkBind:
     result = semTemplBodyDirty(c, n.sons[0])
   of nkBindStmt:
     result = semBindStmt(c.c, n, c.toBind)
   of nkEmpty, nkSym..nkNilLit:
-    nil
+    discard
   else:
     # dotExpr is ambiguous: note that we explicitely allow 'x.TemplateParam',
     # so we use the generic code for nkDotExpr too
     if n.kind == nkDotExpr or n.kind == nkAccQuoted:
-      let s = QualifiedLookUp(c.c, n, {})
-      if s != nil and Contains(c.toBind, s.id):
+      let s = qualifiedLookUp(c.c, n, {})
+      if s != nil and contains(c.toBind, s.id):
         return symChoice(c.c, n, s, scClosed)
     result = n
     for i in countup(0, sonsLen(n) - 1):
@@ -358,7 +411,7 @@ proc transformToExpr(n: PNode): PNode =
     for i in countup(0, sonsLen(n) - 1): 
       case n.sons[i].kind
       of nkCommentStmt, nkEmpty, nkNilLit: 
-        nil
+        discard
       else: 
         if realStmt == - 1: realStmt = i
         else: realStmt = - 2
@@ -368,7 +421,7 @@ proc transformToExpr(n: PNode): PNode =
     n.kind = nkBlockExpr
     #nkIfStmt: n.kind = nkIfExpr // this is not correct!
   else:
-    nil
+    discard
 
 proc semTemplateDef(c: PContext, n: PNode): PNode = 
   var s: PSym
@@ -378,6 +431,7 @@ proc semTemplateDef(c: PContext, n: PNode): PNode =
   else:
     s = semIdentVis(c, skTemplate, n.sons[0], {})
   # check parameter list:
+  s.scope = c.currentScope
   pushOwner(s)
   openScope(c)
   n.sons[namePos] = newSymNode(s, n.sons[namePos].info)
@@ -392,7 +446,7 @@ proc semTemplateDef(c: PContext, n: PNode): PNode =
     gp = newNodeI(nkGenericParams, n.info)
   # process parameters:
   if n.sons[paramsPos].kind != nkEmpty:
-    semParamList(c, n.sons[ParamsPos], gp, s)
+    semParamList(c, n.sons[paramsPos], gp, s)
     if sonsLen(gp) > 0:
       if n.sons[genericParamsPos].kind == nkEmpty:
         # we have a list of implicit type parameters:
@@ -413,6 +467,7 @@ proc semTemplateDef(c: PContext, n: PNode): PNode =
   var ctx: TemplCtx
   ctx.toBind = initIntSet()
   ctx.toMixin = initIntSet()
+  ctx.toInject = initIntSet()
   ctx.c = c
   ctx.owner = s
   if sfDirty in s.flags:
@@ -427,12 +482,12 @@ proc semTemplateDef(c: PContext, n: PNode): PNode =
   s.ast = n
   result = n
   if n.sons[bodyPos].kind == nkEmpty: 
-    LocalError(n.info, errImplOfXexpected, s.name.s)
-  var proto = SearchForProc(c, c.currentScope, s)
+    localError(n.info, errImplOfXexpected, s.name.s)
+  var proto = searchForProc(c, c.currentScope, s)
   if proto == nil:
     addInterfaceOverloadableSymAt(c, c.currentScope, s)
   else:
-    SymTabReplace(c.currentScope.symbols, proto, s)
+    symTabReplace(c.currentScope.symbols, proto, s)
   if n.sons[patternPos].kind != nkEmpty:
     c.patterns.add(s)
 
@@ -455,17 +510,17 @@ proc semPatternBody(c: var TemplCtx, n: PNode): PNode =
     if s != nil:
       if s.owner == c.owner and s.kind == skParam:
         result = newParam(c, n, s)
-      elif Contains(c.toBind, s.id):
+      elif contains(c.toBind, s.id):
         result = symChoice(c.c, n, s, scClosed)
       elif templToExpand(s):
         result = semPatternBody(c, semTemplateExpr(c.c, n, s, false))
       else:
-        nil
+        discard
         # we keep the ident unbound for matching instantiated symbols and
         # more flexibility
   
   proc expectParam(c: var TemplCtx, n: PNode): PNode =
-    let s = QualifiedLookUp(c.c, n, {})
+    let s = qualifiedLookUp(c.c, n, {})
     if s != nil and s.owner == c.owner and s.kind == skParam:
       result = newParam(c, n, s)
     else:
@@ -475,11 +530,11 @@ proc semPatternBody(c: var TemplCtx, n: PNode): PNode =
   result = n
   case n.kind
   of nkIdent:
-    let s = QualifiedLookUp(c.c, n, {})
+    let s = qualifiedLookUp(c.c, n, {})
     result = handleSym(c, n, s)
   of nkBindStmt:
     result = semBindStmt(c.c, n, c.toBind)
-  of nkEmpty, nkSym..nkNilLit: nil
+  of nkEmpty, nkSym..nkNilLit: discard
   of nkCurlyExpr:
     # we support '(pattern){x}' to bind a subpattern to a parameter 'x'; 
     # '(pattern){|x}' does the same but the matches will be gathered in 'x'
@@ -498,10 +553,10 @@ proc semPatternBody(c: var TemplCtx, n: PNode): PNode =
     else:
       localError(n.info, errInvalidExpression)
   of nkCallKinds:
-    let s = QualifiedLookUp(c.c, n.sons[0], {})
+    let s = qualifiedLookUp(c.c, n.sons[0], {})
     if s != nil:
-      if s.owner == c.owner and s.kind == skParam: nil
-      elif Contains(c.toBind, s.id): nil
+      if s.owner == c.owner and s.kind == skParam: discard
+      elif contains(c.toBind, s.id): discard
       elif templToExpand(s):
         return semPatternBody(c, semTemplateExpr(c.c, n, s, false))
     
@@ -537,15 +592,15 @@ proc semPatternBody(c: var TemplCtx, n: PNode): PNode =
     # so we use the generic code for nkDotExpr too
     case n.kind 
     of nkDotExpr, nkAccQuoted:
-      let s = QualifiedLookUp(c.c, n, {})
+      let s = qualifiedLookUp(c.c, n, {})
       if s != nil:
-        if Contains(c.toBind, s.id):
+        if contains(c.toBind, s.id):
           return symChoice(c.c, n, s, scClosed)
         else:
           return newIdentNode(s.name, n.info)
     of nkPar:
       if n.len == 1: return semPatternBody(c, n.sons[0])
-    else: nil
+    else: discard
     for i in countup(0, sonsLen(n) - 1):
       result.sons[i] = semPatternBody(c, n.sons[i])
 
@@ -554,6 +609,7 @@ proc semPattern(c: PContext, n: PNode): PNode =
   var ctx: TemplCtx
   ctx.toBind = initIntSet()
   ctx.toMixin = initIntSet()
+  ctx.toInject = initIntSet()
   ctx.c = c
   ctx.owner = getCurrOwner()
   result = flattenStmts(semPatternBody(ctx, n))
@@ -561,5 +617,5 @@ proc semPattern(c: PContext, n: PNode): PNode =
     if result.len == 1:
       result = result.sons[0]
     elif result.len == 0:
-      LocalError(n.info, errInvalidExpression)
+      localError(n.info, errInvalidExpression)
   closeScope(c)
diff --git a/compiler/semthreads.nim b/compiler/semthreads.nim
index eded99325..f7322db80 100644
--- a/compiler/semthreads.nim
+++ b/compiler/semthreads.nim
@@ -97,7 +97,7 @@ proc `==`(a, b: TCall): bool =
 proc newProcCtx(owner: PSym): PProcCtx =
   assert owner != nil
   new(result)
-  result.mapping = tables.InitTable[int, TThreadOwner]()
+  result.mapping = tables.initTable[int, TThreadOwner]()
   result.owner = owner
 
 proc analyse(c: PProcCtx, n: PNode): TThreadOwner
@@ -119,7 +119,7 @@ proc analyseSym(c: PProcCtx, n: PNode): TThreadOwner =
   of skParam: 
     result = c.mapping[v.id]
     if result == toUndefined:
-      InternalError(n.info, "param not set: " & v.name.s)
+      internalError(n.info, "param not set: " & v.name.s)
   else:
     result = toNil
   c.mapping[v.id] = result
@@ -132,7 +132,7 @@ proc lvalueSym(n: PNode): PNode =
 
 proc writeAccess(c: PProcCtx, n: PNode, owner: TThreadOwner) =
   if owner notin {toNil, toMine, toTheirs}:
-    InternalError(n.info, "writeAccess: " & $owner)
+    internalError(n.info, "writeAccess: " & $owner)
   var a = lvalueSym(n)
   if a.kind == nkSym: 
     var v = a.sym
@@ -151,21 +151,21 @@ proc writeAccess(c: PProcCtx, n: PNode, owner: TThreadOwner) =
         newOwner = toMine
         # XXX BUG what if the tuple contains both ``tyRef`` and ``tyString``?
       c.mapping[v.id] = newOwner
-    of toVoid, toUndefined: InternalError(n.info, "writeAccess")
-    of toTheirs: Message(n.info, warnWriteToForeignHeap)
+    of toVoid, toUndefined: internalError(n.info, "writeAccess")
+    of toTheirs: message(n.info, warnWriteToForeignHeap)
     of toMine:
       if lastOwner != owner and owner != toNil:
-        Message(n.info, warnDifferentHeaps)
+        message(n.info, warnDifferentHeaps)
   else:
     # we could not backtrack to a concrete symbol, but that's fine:
     var lastOwner = analyse(c, n)
     case lastOwner
-    of toNil: nil # fine, toNil can be overwritten
-    of toVoid, toUndefined: InternalError(n.info, "writeAccess")
-    of toTheirs: Message(n.info, warnWriteToForeignHeap)
+    of toNil: discard # fine, toNil can be overwritten
+    of toVoid, toUndefined: internalError(n.info, "writeAccess")
+    of toTheirs: message(n.info, warnWriteToForeignHeap)
     of toMine:
       if lastOwner != owner and owner != toNil:
-        Message(n.info, warnDifferentHeaps)
+        message(n.info, warnDifferentHeaps)
 
 proc analyseAssign(c: PProcCtx, le, ri: PNode) =
   var y = analyse(c, ri) # read access; ok
@@ -192,7 +192,7 @@ proc analyseCall(c: PProcCtx, n: PNode): TThreadOwner =
     result = analyse(newCtx, prc.getBody)
     if prc.ast.sons[bodyPos].kind == nkEmpty and 
        {sfNoSideEffect, sfThread, sfImportc} * prc.flags == {}:
-      Message(n.info, warnAnalysisLoophole, renderTree(n))
+      message(n.info, warnAnalysisLoophole, renderTree(n))
       if result == toUndefined: result = toNil
     if prc.typ.sons[0] != nil:
       if prc.ast.len > resultPos:
@@ -215,12 +215,12 @@ proc analyseCall(c: PProcCtx, n: PNode): TThreadOwner =
       else: result = toNil
 
 proc analyseVarTuple(c: PProcCtx, n: PNode) =
-  if n.kind != nkVarTuple: InternalError(n.info, "analyseVarTuple")
+  if n.kind != nkVarTuple: internalError(n.info, "analyseVarTuple")
   var L = n.len
-  for i in countup(0, L-3): AnalyseAssign(c, n.sons[i], n.sons[L-1])
+  for i in countup(0, L-3): analyseAssign(c, n.sons[i], n.sons[L-1])
 
 proc analyseSingleVar(c: PProcCtx, a: PNode) =
-  if a.sons[2].kind != nkEmpty: AnalyseAssign(c, a.sons[0], a.sons[2])
+  if a.sons[2].kind != nkEmpty: analyseAssign(c, a.sons[0], a.sons[2])
 
 proc analyseVarSection(c: PProcCtx, n: PNode): TThreadOwner = 
   for i in countup(0, sonsLen(n) - 1): 
@@ -238,7 +238,7 @@ proc analyseConstSection(c: PProcCtx, t: PNode): TThreadOwner =
   for i in countup(0, sonsLen(t) - 1): 
     var it = t.sons[i]
     if it.kind == nkCommentStmt: continue 
-    if it.kind != nkConstDef: InternalError(t.info, "analyseConstSection")
+    if it.kind != nkConstDef: internalError(t.info, "analyseConstSection")
     if sfFakeConst in it.sons[0].sym.flags: analyseSingleVar(c, it)
   result = toVoid
 
@@ -246,7 +246,7 @@ template aggregateOwner(result, ana: expr) =
   var a = ana # eval once
   if result != a:
     if result == toNil: result = a
-    elif a != toNil: Message(n.info, warnDifferentHeaps)
+    elif a != toNil: message(n.info, warnDifferentHeaps)
 
 proc analyseArgs(c: PProcCtx, n: PNode, start = 1) =
   for i in start..n.len-1: discard analyse(c, n[i])
@@ -254,7 +254,7 @@ proc analyseArgs(c: PProcCtx, n: PNode, start = 1) =
 proc analyseOp(c: PProcCtx, n: PNode): TThreadOwner =
   if n[0].kind != nkSym or n[0].sym.kind != skProc:
     if {tfNoSideEffect, tfThread} * n[0].typ.flags == {}:
-      Message(n.info, warnAnalysisLoophole, renderTree(n))
+      message(n.info, warnAnalysisLoophole, renderTree(n))
     result = toNil
   else:
     var prc = n[0].sym
@@ -352,7 +352,7 @@ proc analyse(c: PProcCtx, n: PNode): TThreadOwner =
     result = analyse(c, n.sons[0])
   of nkRaiseStmt:
     var a = analyse(c, n.sons[0])
-    if a != toMine: Message(n.info, warnDifferentHeaps)
+    if a != toMine: message(n.info, warnDifferentHeaps)
     result = toVoid
   of nkVarSection, nkLetSection: result = analyseVarSection(c, n)
   of nkConstSection: result = analyseConstSection(c, n)
@@ -369,11 +369,11 @@ proc analyse(c: PProcCtx, n: PNode): TThreadOwner =
     result = toMine
   of nkAsmStmt, nkPragma, nkIteratorDef, nkProcDef, nkMethodDef,
      nkConverterDef, nkMacroDef, nkTemplateDef,
-     nkGotoState, nkState, nkBreakState, nkType:
+     nkGotoState, nkState, nkBreakState, nkType, nkIdent:
       result = toVoid
   of nkExprColonExpr:
     result = analyse(c, n.sons[1])
-  else: InternalError(n.info, "analysis not implemented for: " & $n.kind)
+  else: internalError(n.info, "analysis not implemented for: " & $n.kind)
 
 proc analyseThreadProc*(prc: PSym) =
   var c = newProcCtx(prc)
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 6c9c476d9..408b1b62e 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 =
@@ -50,13 +50,13 @@ proc semEnum(c: PContext, n: PNode, prev: PType): PType =
       of tyTuple: 
         if sonsLen(v) == 2:
           strVal = v.sons[1] # second tuple part is the string value
-          if skipTypes(strVal.typ, abstractInst).kind in {tyString, tyCstring}:
+          if skipTypes(strVal.typ, abstractInst).kind in {tyString, tyCString}:
             x = getOrdValue(v.sons[0]) # first tuple part is the ordinal
           else:
-            LocalError(strVal.info, errStringLiteralExpected)
+            localError(strVal.info, errStringLiteralExpected)
         else:
-          LocalError(v.info, errWrongNumberOfVariables)
-      of tyString, tyCstring:
+          localError(v.info, errWrongNumberOfVariables)
+      of tyString, tyCString:
         strVal = v
         x = counter
       else:
@@ -64,7 +64,7 @@ proc semEnum(c: PContext, n: PNode, prev: PType): PType =
       if i != 1:
         if x != counter: incl(result.flags, tfEnumHasHoles)
         if x < counter: 
-          LocalError(n.sons[i].info, errInvalidOrderInEnumX, e.name.s)
+          localError(n.sons[i].info, errInvalidOrderInEnumX, e.name.s)
           x = counter
       e.ast = strVal # might be nil
       counter = x
@@ -79,7 +79,7 @@ proc semEnum(c: PContext, n: PNode, prev: PType): PType =
     if result.sym != nil and sfExported in result.sym.flags:
       incl(e.flags, sfUsed)
       incl(e.flags, sfExported)
-      if not isPure: StrTableAdd(c.module.tab, e)
+      if not isPure: strTableAdd(c.module.tab, e)
     addSon(result.n, newSymNode(e))
     if sfGenSym notin e.flags and not isPure: addDecl(c, e)
     inc(counter)
@@ -93,11 +93,11 @@ proc semSet(c: PContext, n: PNode, prev: PType): PType =
     if base.kind == tyGenericInst: base = lastSon(base)
     if base.kind != tyGenericParam: 
       if not isOrdinalType(base): 
-        LocalError(n.info, errOrdinalTypeExpected)
+        localError(n.info, errOrdinalTypeExpected)
       elif lengthOrd(base) > MaxSetElements: 
-        LocalError(n.info, errSetTooBig)
+        localError(n.info, errSetTooBig)
   else:
-    LocalError(n.info, errXExpectsOneTypeParam, "set")
+    localError(n.info, errXExpectsOneTypeParam, "set")
     addSonSkipIntLit(result, errorType(c))
   
 proc semContainer(c: PContext, n: PNode, kind: TTypeKind, kindStr: string, 
@@ -107,7 +107,7 @@ proc semContainer(c: PContext, n: PNode, kind: TTypeKind, kindStr: string,
     var base = semTypeNode(c, n.sons[1], nil)
     addSonSkipIntLit(result, base)
   else: 
-    LocalError(n.info, errXExpectsOneTypeParam, kindStr)
+    localError(n.info, errXExpectsOneTypeParam, kindStr)
     addSonSkipIntLit(result, errorType(c))
 
 proc semVarargs(c: PContext, n: PNode, prev: PType): PType =
@@ -118,7 +118,7 @@ proc semVarargs(c: PContext, n: PNode, prev: PType): PType =
     if sonsLen(n) == 3:
       result.n = newIdentNode(considerAcc(n.sons[2]), n.sons[2].info)
   else:
-    LocalError(n.info, errXExpectsOneTypeParam, "varargs")
+    localError(n.info, errXExpectsOneTypeParam, "varargs")
     addSonSkipIntLit(result, errorType(c))
   
 proc semAnyRef(c: PContext, n: PNode, kind: TTypeKind, prev: PType): PType = 
@@ -134,7 +134,7 @@ proc semVarType(c: PContext, n: PNode, prev: PType): PType =
     result = newOrPrevType(tyVar, prev, c)
     var base = semTypeNode(c, n.sons[0], nil)
     if base.kind == tyVar: 
-      LocalError(n.info, errVarVarTypeNotAllowed)
+      localError(n.info, errVarVarTypeNotAllowed)
       base = base.sons[0]
     addSonSkipIntLit(result, base)
   else:
@@ -148,22 +148,22 @@ proc semDistinct(c: PContext, n: PNode, prev: PType): PType =
     result = newConstraint(c, tyDistinct)
   
 proc semRangeAux(c: PContext, n: PNode, prev: PType): PType = 
-  assert IsRange(n)
+  assert isRange(n)
   checkSonsLen(n, 3)
   result = newOrPrevType(tyRange, prev, c)
   result.n = newNodeI(nkRange, n.info)
   if (n[1].kind == nkEmpty) or (n[2].kind == nkEmpty): 
-    LocalError(n.Info, errRangeIsEmpty)
+    localError(n.info, errRangeIsEmpty)
   var a = semConstExpr(c, n[1])
   var b = semConstExpr(c, n[2])
   if not sameType(a.typ, b.typ):
-    LocalError(n.info, errPureTypeMismatch)
+    localError(n.info, errPureTypeMismatch)
   elif a.typ.kind notin {tyInt..tyInt64,tyEnum,tyBool,tyChar,
                          tyFloat..tyFloat128,tyUInt8..tyUInt32}:
-    LocalError(n.info, errOrdinalTypeExpected)
+    localError(n.info, errOrdinalTypeExpected)
   elif enumHasHoles(a.typ): 
-    LocalError(n.info, errEnumXHasHoles, a.typ.sym.name.s)
-  elif not leValue(a, b): LocalError(n.Info, errRangeIsEmpty)
+    localError(n.info, errEnumXHasHoles, a.typ.sym.name.s)
+  elif not leValue(a, b): localError(n.info, errRangeIsEmpty)
   addSon(result.n, a)
   addSon(result.n, b)
   addSonSkipIntLit(result, b.typ)
@@ -180,12 +180,17 @@ proc semRange(c: PContext, n: PNode, prev: PType): PType =
       elif n.sons[0].floatVal > 0.0 or n.sons[1].floatVal < 0.0:
         incl(result.flags, tfNeedsInit)
     else:
-      LocalError(n.sons[0].info, errRangeExpected)
+      localError(n.sons[0].info, errRangeExpected)
       result = newOrPrevType(tyError, prev, c)
   else:
-    LocalError(n.info, errXExpectsOneTypeParam, "range")
+    localError(n.info, errXExpectsOneTypeParam, "range")
     result = newOrPrevType(tyError, prev, c)
 
+proc nMinusOne(n: PNode): PNode =
+  result = newNode(nkCall, n.info, @[
+    newSymNode(getSysMagic("<", mUnaryLt)),
+    n])
+
 proc semArray(c: PContext, n: PNode, prev: PType): PType = 
   var indx, base: PType
   result = newOrPrevType(tyArray, prev, c)
@@ -194,27 +199,43 @@ proc semArray(c: PContext, n: PNode, prev: PType): PType =
     if isRange(n[1]): indx = semRangeAux(c, n[1], nil)
     else:
       let e = semExprWithType(c, n.sons[1], {efDetermineType})
-      if e.kind in {nkIntLit..nkUInt64Lit}:
+      if e.typ.kind == tyFromExpr:
+        indx = e.typ
+      elif 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
+        internalAssert c.inGenericContext > 0
         if not isOrdinalType(e.typ.lastSon):
           localError(n[1].info, errOrdinalTypeExpected)
         indx = e.typ
+      elif e.kind in nkCallKinds and hasGenericArguments(e):
+        if not isOrdinalType(e.typ):
+          localError(n[1].info, errOrdinalTypeExpected)
+        # This is an int returning call, depending on an
+        # yet unknown generic param (see tgenericshardcases).
+        # We are going to construct a range type that will be
+        # properly filled-out in semtypinst (see how tyStaticExpr
+        # is handled there).
+        let intType = getSysType(tyInt)
+        indx = newTypeS(tyRange, c)
+        indx.sons = @[intType]
+        indx.n = newNode(nkRange, n.info, @[
+          newIntTypeNode(nkIntLit, 0, intType),
+          makeStaticExpr(c, e.nMinusOne)])
       else:
         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, tyFromExpr}:
       if not isOrdinalType(indx):
-        LocalError(n.sons[1].info, errOrdinalTypeExpected)
+        localError(n.sons[1].info, errOrdinalTypeExpected)
       elif enumHasHoles(indx): 
-        LocalError(n.sons[1].info, errEnumXHasHoles, indx.sym.name.s)
+        localError(n.sons[1].info, errEnumXHasHoles, indx.sym.name.s)
     base = semTypeNode(c, n.sons[2], nil)
     addSonSkipIntLit(result, base)
   else: 
-    LocalError(n.info, errArrayExpectsTwoTypeParams)
+    localError(n.info, errArrayExpectsTwoTypeParams)
     result = newOrPrevType(tyError, prev, c)
   
 proc semOrdinal(c: PContext, n: PNode, prev: PType): PType = 
@@ -223,29 +244,29 @@ proc semOrdinal(c: PContext, n: PNode, prev: PType): PType =
     var base = semTypeNode(c, n.sons[1], nil)
     if base.kind != tyGenericParam: 
       if not isOrdinalType(base): 
-        LocalError(n.sons[1].info, errOrdinalTypeExpected)
+        localError(n.sons[1].info, errOrdinalTypeExpected)
     addSonSkipIntLit(result, base)
   else:
-    LocalError(n.info, errXExpectsOneTypeParam, "ordinal")
+    localError(n.info, errXExpectsOneTypeParam, "ordinal")
     result = newOrPrevType(tyError, prev, c)
 
 proc semTypeIdent(c: PContext, n: PNode): PSym =
   if n.kind == nkSym: 
     result = n.sym
   else:
-    result = qualifiedLookup(c, n, {checkAmbiguity, checkUndeclared})
+    result = qualifiedLookUp(c, n, {checkAmbiguity, checkUndeclared})
     if result != nil:
       markUsed(n, result)
       if result.kind == skParam and result.typ.kind == tyTypeDesc:
         # This is a typedesc param. is it already bound?
         # it's not bound when it's used multiple times in the
         # proc signature for example
-        if c.InGenericInst > 0:
+        if c.inGenericInst > 0:
           let bound = result.typ.sons[0].sym
           if bound != nil: return bound
           return result
         if result.typ.sym == nil:
-          LocalError(n.info, errTypeExpected)
+          localError(n.info, errTypeExpected)
           return errorSym(c, n)
         result = result.typ.sym.copySym
         result.typ = copyType(result.typ, result.typ.owner, true)
@@ -253,12 +274,12 @@ proc semTypeIdent(c: PContext, n: PNode): PSym =
       if result.kind != skType: 
         # this implements the wanted ``var v: V, x: V`` feature ...
         var ov: TOverloadIter
-        var amb = InitOverloadIter(ov, c, n)
+        var amb = initOverloadIter(ov, c, n)
         while amb != nil and amb.kind != skType:
           amb = nextOverloadIter(ov, c, n)
         if amb != nil: result = amb
         else:
-          if result.kind != skError: LocalError(n.info, errTypeExpected)
+          if result.kind != skError: localError(n.info, errTypeExpected)
           return errorSym(c, n)
       if result.typ.kind != tyGenericParam:
         # XXX get rid of this hack!
@@ -268,7 +289,7 @@ proc semTypeIdent(c: PContext, n: PNode): PSym =
         n.sym = result
         n.info = oldInfo
     else:
-      LocalError(n.info, errIdentifierExpected)
+      localError(n.info, errIdentifierExpected)
       result = errorSym(c, n)
   
 proc semTuple(c: PContext, n: PNode, prev: PType): PType = 
@@ -280,26 +301,27 @@ proc semTuple(c: PContext, n: PNode, prev: PType): PType =
   var counter = 0
   for i in countup(0, sonsLen(n) - 1): 
     var a = n.sons[i]
-    if (a.kind != nkIdentDefs): IllFormedAst(a)
+    if (a.kind != nkIdentDefs): illFormedAst(a)
     checkMinSonsLen(a, 3)
     var length = sonsLen(a)
     if a.sons[length - 2].kind != nkEmpty: 
       typ = semTypeNode(c, a.sons[length - 2], nil)
     else:
-      LocalError(a.info, errTypeExpected)
+      localError(a.info, errTypeExpected)
       typ = errorType(c)
     if a.sons[length - 1].kind != nkEmpty: 
-      LocalError(a.sons[length - 1].info, errInitHereNotAllowed)
+      localError(a.sons[length - 1].info, errInitHereNotAllowed)
     for j in countup(0, length - 3): 
       var field = newSymG(skField, a.sons[j], c)
       field.typ = typ
       field.position = counter
       inc(counter)
-      if ContainsOrIncl(check, field.name.id): 
-        LocalError(a.sons[j].info, errAttemptToRedefine, field.name.s)
+      if containsOrIncl(check, field.name.id): 
+        localError(a.sons[j].info, errAttemptToRedefine, field.name.s)
       else:
         addSon(result.n, newSymNode(field))
         addSonSkipIntLit(result, typ)
+      if gCmd == cmdPretty: checkDef(a.sons[j], field)
 
 proc semIdentVis(c: PContext, kind: TSymKind, n: PNode, 
                  allowed: TSymFlags): PSym = 
@@ -313,7 +335,7 @@ proc semIdentVis(c: PContext, kind: TSymKind, n: PNode,
       if sfExported in allowed and v.id == ord(wStar): 
         incl(result.flags, sfExported)
       else:
-        LocalError(n.sons[0].info, errInvalidVisibilityX, v.s)
+        localError(n.sons[0].info, errInvalidVisibilityX, v.s)
     else:
       illFormedAst(n)
   else:
@@ -331,9 +353,10 @@ proc semIdentWithPragma(c: PContext, kind: TSymKind, n: PNode,
     of skVar:   pragma(c, result, n.sons[1], varPragmas)
     of skLet:   pragma(c, result, n.sons[1], letPragmas)
     of skConst: pragma(c, result, n.sons[1], constPragmas)
-    else: nil
+    else: discard
   else:
     result = semIdentVis(c, kind, n, allowed)
+  if gCmd == cmdPretty: checkDef(n, result)
   
 proc checkForOverlap(c: PContext, t: PNode, currentEx, branchIndex: int) =
   let ex = t[branchIndex][currentEx].skipConv
@@ -341,9 +364,9 @@ proc checkForOverlap(c: PContext, t: PNode, currentEx, branchIndex: int) =
     for j in countup(0, sonsLen(t.sons[i]) - 2): 
       if i == branchIndex and j == currentEx: break
       if overlap(t.sons[i].sons[j].skipConv, ex):
-        LocalError(ex.info, errDuplicateCaseLabel)
+        localError(ex.info, errDuplicateCaseLabel)
   
-proc semBranchRange(c: PContext, t, a, b: PNode, covered: var biggestInt): PNode =
+proc semBranchRange(c: PContext, t, a, b: PNode, covered: var BiggestInt): PNode =
   checkMinSonsLen(t, 1)
   let ac = semConstExpr(c, a)
   let bc = semConstExpr(c, b)
@@ -353,16 +376,16 @@ proc semBranchRange(c: PContext, t, a, b: PNode, covered: var biggestInt): PNode
   result = newNodeI(nkRange, a.info)
   result.add(at)
   result.add(bt)
-  if emptyRange(ac, bc): LocalError(b.info, errRangeIsEmpty)
+  if emptyRange(ac, bc): localError(b.info, errRangeIsEmpty)
   else: covered = covered + getOrdValue(bc) - getOrdValue(ac) + 1
 
-proc SemCaseBranchRange(c: PContext, t, b: PNode, 
-                        covered: var biggestInt): PNode = 
+proc semCaseBranchRange(c: PContext, t, b: PNode, 
+                        covered: var BiggestInt): PNode = 
   checkSonsLen(b, 3)
   result = semBranchRange(c, t, b.sons[1], b.sons[2], covered)
 
 proc semCaseBranchSetElem(c: PContext, t, b: PNode, 
-                          covered: var biggestInt): PNode = 
+                          covered: var BiggestInt): PNode = 
   if isRange(b):
     checkSonsLen(b, 3)
     result = semBranchRange(c, t, b.sons[1], b.sons[2], covered)
@@ -374,7 +397,7 @@ proc semCaseBranchSetElem(c: PContext, t, b: PNode,
     inc(covered)
 
 proc semCaseBranch(c: PContext, t, branch: PNode, branchIndex: int, 
-                   covered: var biggestInt) = 
+                   covered: var BiggestInt) = 
   for i in countup(0, sonsLen(branch) - 2): 
     var b = branch.sons[i]
     if b.kind == nkRange:
@@ -411,14 +434,14 @@ proc semRecordCase(c: PContext, n: PNode, check: var TIntSet, pos: var int,
     internalError("semRecordCase: discriminant is no symbol")
     return
   incl(a.sons[0].sym.flags, sfDiscriminant)
-  var covered: biggestInt = 0
-  var typ = skipTypes(a.sons[0].Typ, abstractVar-{tyTypeDesc})
+  var covered: BiggestInt = 0
+  var typ = skipTypes(a.sons[0].typ, abstractVar-{tyTypeDesc})
   if not isOrdinalType(typ):
-    LocalError(n.info, errSelectorMustBeOrdinal)
+    localError(n.info, errSelectorMustBeOrdinal)
   elif firstOrd(typ) < 0:
-    LocalError(n.info, errOrdXMustNotBeNegative, a.sons[0].sym.name.s)
+    localError(n.info, errOrdXMustNotBeNegative, a.sons[0].sym.name.s)
   elif lengthOrd(typ) > 0x00007FFF:
-    LocalError(n.info, errLenXinvalid, a.sons[0].sym.name.s)
+    localError(n.info, errLenXinvalid, a.sons[0].sym.name.s)
   var chckCovered = true
   for i in countup(1, sonsLen(n) - 1):
     var b = copyTree(n.sons[i])
@@ -450,9 +473,9 @@ proc semRecordNodeAux(c: PContext, n: PNode, check: var TIntSet, pos: var int,
       case it.kind
       of nkElifBranch:
         checkSonsLen(it, 2)
-        if c.InGenericContext == 0:
+        if c.inGenericContext == 0:
           var e = semConstBoolExpr(c, it.sons[0])
-          if e.kind != nkIntLit: InternalError(e.info, "semRecordNodeAux")
+          if e.kind != nkIntLit: internalError(e.info, "semRecordNodeAux")
           elif e.intVal != 0 and branch == nil: branch = it.sons[1]
         else:
           it.sons[0] = forceBool(c, semExprWithType(c, it.sons[0]))
@@ -461,15 +484,15 @@ proc semRecordNodeAux(c: PContext, n: PNode, check: var TIntSet, pos: var int,
         if branch == nil: branch = it.sons[0]
         idx = 0
       else: illFormedAst(n)
-      if c.InGenericContext > 0:
+      if c.inGenericContext > 0:
         # use a new check intset here for each branch:
         var newCheck: TIntSet
         assign(newCheck, check)
         var newPos = pos
         var newf = newNodeI(nkRecList, n.info)
-        semRecordNodeAux(c, it.sons[idx], newcheck, newpos, newf, rectype)
+        semRecordNodeAux(c, it.sons[idx], newCheck, newPos, newf, rectype)
         it.sons[idx] = if newf.len == 1: newf[0] else: newf
-    if c.InGenericContext > 0:
+    if c.inGenericContext > 0:
       addSon(father, n)
     elif branch != nil:
       semRecordNodeAux(c, branch, check, pos, father, rectype)
@@ -493,7 +516,7 @@ proc semRecordNodeAux(c: PContext, n: PNode, check: var TIntSet, pos: var int,
       localError(n.sons[length-1].info, errInitHereNotAllowed)
     var typ: PType
     if n.sons[length-2].kind == nkEmpty: 
-      LocalError(n.info, errTypeExpected)
+      localError(n.info, errTypeExpected)
       typ = errorType(c)
     else:
       typ = semTypeNode(c, n.sons[length-2], nil)
@@ -509,19 +532,19 @@ proc semRecordNodeAux(c: PContext, n: PNode, check: var TIntSet, pos: var int,
         f.loc.r = toRope(f.name.s)
         f.flags = f.flags + ({sfImportc, sfExportc} * rec.flags)
       inc(pos)
-      if ContainsOrIncl(check, f.name.id):
+      if containsOrIncl(check, f.name.id):
         localError(n.sons[i].info, errAttemptToRedefine, f.name.s)
       if a.kind == nkEmpty: addSon(father, newSymNode(f))
       else: addSon(a, newSymNode(f))
     if a.kind != nkEmpty: addSon(father, a)
-  of nkEmpty: nil
+  of nkEmpty: discard
   else: illFormedAst(n)
   
 proc addInheritedFieldsAux(c: PContext, check: var TIntSet, pos: var int, 
                            n: PNode) =
   case n.kind
   of nkRecCase:
-    if (n.sons[0].kind != nkSym): InternalError(n.info, "addInheritedFieldsAux")
+    if (n.sons[0].kind != nkSym): internalError(n.info, "addInheritedFieldsAux")
     addInheritedFieldsAux(c, check, pos, n.sons[0])
     for i in countup(1, sonsLen(n) - 1):
       case n.sons[i].kind
@@ -532,9 +555,9 @@ proc addInheritedFieldsAux(c: PContext, check: var TIntSet, pos: var int,
     for i in countup(0, sonsLen(n) - 1):
       addInheritedFieldsAux(c, check, pos, n.sons[i])
   of nkSym:
-    Incl(check, n.sym.name.id)
+    incl(check, n.sym.name.id)
     inc(pos)
-  else: InternalError(n.info, "addInheritedFieldsAux()")
+  else: internalError(n.info, "addInheritedFieldsAux()")
   
 proc addInheritedFields(c: PContext, check: var TIntSet, pos: var int, 
                         obj: PType) = 
@@ -565,7 +588,7 @@ proc semObjectNode(c: PContext, n: PNode, prev: PType): PType =
       if concreteBase.kind != tyError:
         localError(n.sons[1].info, errInheritanceOnlyWithNonFinalObjects)
       base = nil
-  if n.kind != nkObjectTy: InternalError(n.info, "semObjectNode")
+  if n.kind != nkObjectTy: internalError(n.info, "semObjectNode")
   result = newOrPrevType(tyObject, prev, c)
   rawAddSon(result, base)
   result.n = newNodeI(nkRecList, n.info)
@@ -577,9 +600,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"
@@ -591,18 +614,22 @@ proc addParamOrResult(c: PContext, param: PSym, kind: TSymKind) =
 
 let typedescId = getIdent"typedesc"
 
+template shouldHaveMeta(t) =
+  internalAssert tfHasMeta in t.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
+  if paramType == nil: return # (e.g. proc return type)
 
   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:
@@ -613,10 +640,11 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode,
     var s = newSym(skType, finalTypId, owner, info)
     if typId == nil: s.flags.incl(sfAnon)
     s.linkTo(typeClass)
+    typeClass.flags.incl tfImplicitTypeParam
     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)
@@ -629,34 +657,38 @@ 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:
+  
+  of tySequence, tySet, tyArray, tyOpenArray,
+     tyVar, tyPtr, tyRef, tyProc:
     # XXX: this is a bit strange, but proc(s: seq)
     # produces tySequence(tyGenericParam, null).
     # This also seems to be true when creating aliases
     # like: type myseq = distinct seq.
     # 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)])
+    if paramType.kind == tySequence and paramType.lastSon == nil:
+      let typ = c.newTypeWithSons(tyBuiltInTypeClass,
+                                  @[newTypeS(paramType.kind, c)])
       result = addImplicitGeneric(typ)
     else:
       for i in 0 .. <paramType.sons.len:
@@ -664,30 +696,61 @@ 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 newTypeS(tyAnything, c)
+      # 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:
+    if paramType.lastSon.kind == tyUserTypeClass:
+      var cp = copyType(paramType, getCurrOwner(), false)
+      cp.kind = tyUserTypeClassInst
+      return addImplicitGeneric(cp)
+
     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
+
+    let liftBody = liftingWalk(paramType.lastSon)
+    if liftBody != nil:
+      result = liftBody
+      result.shouldHaveMeta
+ 
+  of tyGenericInvokation:
+    for i in 1 .. <paramType.sonsLen:
+      let lifted = liftingWalk(paramType.sons[i])
+      if lifted != nil: paramType.sons[i] = lifted
+
+    let expanded = instGenericContainer(c, info, paramType,
+                                        allowMetaTypes = true)
+    result = liftingWalk(expanded)
 
-    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))
-  else: nil
+  of tyUserTypeClass, tyBuiltInTypeClass, tyAnd, tyOr, tyNot:
+    result = addImplicitGeneric(copyType(paramType, getCurrOwner(), true))
+  
+  of tyExpr:
+    if procKind notin {skMacro, skTemplate}:
+      result = addImplicitGeneric(newTypeS(tyAnything, c))
+  
+  of tyGenericParam:
+    if tfGenericTypeParam in paramType.flags and false:
+      if paramType.sonsLen > 0:
+        result = liftingWalk(paramType.lastSon)
+      else:
+        result = addImplicitGeneric(newTypeS(tyAnything, c))
+ 
+  else: discard
 
   # result = liftingWalk(paramType)
 
@@ -719,7 +782,7 @@ proc semProcTypeNode(c: PContext, n, genericParams: PNode,
   var counter = 0
   for i in countup(1, n.len - 1):
     var a = n.sons[i]
-    if a.kind != nkIdentDefs: IllFormedAst(a)
+    if a.kind != nkIdentDefs: illFormedAst(a)
     checkMinSonsLen(a, 3)
     var
       typ: PType = nil
@@ -743,8 +806,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)
@@ -756,11 +820,13 @@ proc semProcTypeNode(c: PContext, n, genericParams: PNode,
       arg.constraint = constraint
       inc(counter)
       if def != nil and def.kind != nkEmpty: arg.ast = copyTree(def)
-      if ContainsOrIncl(check, arg.name.id): 
-        LocalError(a.sons[j].info, errAttemptToRedefine, arg.name.s)
+      if containsOrIncl(check, arg.name.id): 
+        localError(a.sons[j].info, errAttemptToRedefine, arg.name.s)
       addSon(result.n, newSymNode(arg))
       rawAddSon(result, finalType)
       addParamOrResult(c, arg, kind)
+      if gCmd == cmdPretty: checkDef(a.sons[j], arg)
+
 
   if n.sons[0].kind != nkEmpty:
     var r = semTypeNode(c, n.sons[0], nil)
@@ -788,7 +854,7 @@ proc semStmtListType(c: PContext, n: PNode, prev: PType): PType =
     result = nil
   
 proc semBlockType(c: PContext, n: PNode, prev: PType): PType = 
-  Inc(c.p.nestedBlockCounter)
+  inc(c.p.nestedBlockCounter)
   checkSonsLen(n, 2)
   openScope(c)
   if n.sons[0].kind notin {nkEmpty, nkSym}:
@@ -797,39 +863,23 @@ proc semBlockType(c: PContext, n: PNode, prev: PType): PType =
   n.sons[1].typ = result
   n.typ = result
   closeScope(c)
-  Dec(c.p.nestedBlockCounter)
+  dec(c.p.nestedBlockCounter)
 
 proc semGenericParamInInvokation(c: PContext, n: PNode): PType =
-  # XXX hack 1022 for generics ... would have been nice if the compiler had
-  # been designed with them in mind from start ...
-  when false:
-    if n.kind == nkSym:
-      # for generics we need to lookup the type var again:
-      var s = searchInScopes(c, n.sym.name)
-      if s != nil:
-        if s.kind == skType and s.typ != nil:
-          var t = n.sym.typ
-          echo "came here"
-          return t
-        else:
-          echo "s is crap:"
-          debug(s)
-      else:
-        echo "s is nil!!!!"
   result = semTypeNode(c, n, nil)
 
 proc semGeneric(c: PContext, n: PNode, s: PSym, prev: PType): PType = 
   result = newOrPrevType(tyGenericInvokation, prev, c)
   addSonSkipIntLit(result, s.typ)
-  
+
   template addToResult(typ) =
     if typ.isNil:
-      InternalAssert false
+      internalAssert false
       rawAddSon(result, typ)
     else: addSonSkipIntLit(result, typ)
 
   if s.typ == nil:
-    LocalError(n.info, errCannotInstantiateX, s.name.s)
+    localError(n.info, errCannotInstantiateX, s.name.s)
     return newOrPrevType(tyError, prev, c)
   elif s.typ.kind == tyForward:
     for i in countup(1, sonsLen(n)-1):
@@ -838,18 +888,18 @@ 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:
       var err = "cannot instantiate " & typeToString(s.typ) & "\n" &
                 "got: (" & describeArgs(c, n) & ")\n" &
                 "but expected: (" & describeArgs(c, s.typ.n, 0) & ")"
-      LocalError(n.info, errGenerated, err)
+      localError(n.info, errGenerated, err)
       return newOrPrevType(tyError, prev, c)
 
     var isConcrete = true
-  
+ 
     for i in 1 .. <m.call.len:
       let typ = m.call[i].typ.skipTypes({tyTypeDesc})
       if containsGenericType(typ): isConcrete = false
@@ -857,20 +907,18 @@ proc semGeneric(c: PContext, n: PNode, s: PSym, prev: PType): PType =
     
     if isConcrete:
       if s.ast == nil:
-        LocalError(n.info, errCannotInstantiateX, s.name.s)
+        localError(n.info, errCannotInstantiateX, s.name.s)
         result = newOrPrevType(tyError, prev, c)
       else:
-        when oUseLateInstantiation:
-          result = lateInstantiateGeneric(c, result, n.info)
-        else:
-          result = instGenericContainer(c, n, result)
+        result = instGenericContainer(c, n.info, result,
+                                      allowMetaTypes = false)
 
 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)
+    localError(n.info, errTypeExpected, n.renderTree)
 
 proc freshType(res, prev: PType): PType {.inline.} =
   if prev.isNil:
@@ -880,7 +928,7 @@ proc freshType(res, prev: PType): PType {.inline.} =
 
 proc semTypeClass(c: PContext, n: PNode, prev: PType): PType =
   # if n.sonsLen == 0: return newConstraint(c, tyTypeClass)
-  result = newOrPrevType(tyTypeClass, prev, c)
+  result = newOrPrevType(tyUserTypeClass, prev, c)
   result.n = n
 
   let
@@ -896,7 +944,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
   result = nil
   if gCmd == cmdIdeTools: suggestExpr(c, n)
   case n.kind
-  of nkEmpty: nil
+  of nkEmpty: discard
   of nkTypeOfExpr:
     # for ``type(countup(1,3))``, see ``tests/ttoseq``.
     checkSonsLen(n, 1)
@@ -905,7 +953,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     if sonsLen(n) == 1: result = semTypeNode(c, n.sons[0], prev)
     else:
       # XXX support anon tuple here
-      LocalError(n.info, errTypeExpected)
+      localError(n.info, errTypeExpected)
       result = newOrPrevType(tyError, prev, c)
   of nkCallKinds:
     if isRange(n):
@@ -917,26 +965,29 @@ 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: 
-          LocalError(n.sons[1].info, errTypeExpected)
+        if t1 == nil:
+          localError(n.sons[1].info, errTypeExpected)
           result = newOrPrevType(tyError, prev, c)
-        elif t2 == nil: 
-          LocalError(n.sons[2].info, errTypeExpected)
+        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")
+          localError(n.info, errGenerated, "invalid type")
       else:
         result = semTypeExpr(c, n)
     else:
@@ -964,13 +1015,19 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
           result.rawAddSon(semTypeNode(c, n.sons[i], nil))
     else: result = semGeneric(c, n, s, prev)
   of nkIdent, nkDotExpr, nkAccQuoted: 
+    if n.kind == nkDotExpr:
+      let head = qualifiedLookUp(c, n[0], {checkAmbiguity, checkUndeclared})
+      if head.kind in {skType}:
+        var toBind = initIntSet()
+        var preprocessed = semGenericStmt(c, n, {}, toBind)
+        return makeTypeFromExpr(c, preprocessed)
     var s = semTypeIdent(c, n)
     if s.typ == nil: 
-      if s.kind != skError: LocalError(n.info, errTypeExpected)
+      if s.kind != skError: localError(n.info, errTypeExpected)
       result = newOrPrevType(tyError, prev, c)
     elif s.kind == skParam and s.typ.kind == tyTypeDesc:
       assert s.typ.len > 0
-      InternalAssert prev == nil
+      internalAssert prev == nil
       result = s.typ.sons[0]
     elif prev == nil:
       result = s.typ
@@ -991,7 +1048,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
         result = prev
       markUsed(n, n.sym)
     else:
-      if n.sym.kind != skError: LocalError(n.info, errTypeExpected)
+      if n.sym.kind != skError: localError(n.info, errTypeExpected)
       result = newOrPrevType(tyError, prev, c)
   of nkObjectTy: result = semObjectNode(c, n, prev)
   of nkTupleTy: result = semTuple(c, n, prev)
@@ -1000,6 +1057,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)
@@ -1016,7 +1078,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
           #Message(n.info, warnImplicitClosure, renderTree(n))
       else:
         pragma(c, s, n.sons[1], procTypePragmas)
-        when useEffectSystem: SetEffectsForProcType(result, n.sons[1])
+        when useEffectSystem: setEffectsForProcType(result, n.sons[1])
       closeScope(c)
     if n.kind == nkIteratorTy:
       result.flags.incl(tfIterator)
@@ -1031,7 +1093,7 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     result = freshType(result, prev)
     result.flags.incl(tfShared)
   else:
-    LocalError(n.info, errTypeExpected)
+    localError(n.info, errTypeExpected)
     result = newOrPrevType(tyError, prev, c)
   
 proc setMagicType(m: PSym, kind: TTypeKind, size: int) = 
@@ -1080,15 +1142,11 @@ proc processMagicType(c: PContext, m: PSym) =
   of mSet: setMagicType(m, tySet, 0) 
   of mSeq: setMagicType(m, tySequence, 0)
   of mOrdinal: setMagicType(m, tyOrdinal, 0)
-  of mPNimrodNode: nil
-  else: LocalError(m.info, errTypeExpected)
+  of mPNimrodNode: discard
+  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)
@@ -1105,7 +1163,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,14 +1174,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)
@@ -1132,7 +1192,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..1158335a8 100644
--- a/compiler/semtypinst.nim
+++ b/compiler/semtypinst.nim
@@ -11,21 +11,24 @@
 
 import ast, astalgo, msgs, types, magicsys, semdata, renderer
 
+const
+  tfInstClearedFlags = {tfHasMeta}
+
 proc checkPartialConstructedType(info: TLineInfo, t: PType) =
   if tfAcyclic in t.flags and skipTypes(t, abstractInst).kind != tyObject:
-    LocalError(info, errInvalidPragmaX, "acyclic")
+    localError(info, errInvalidPragmaX, "acyclic")
   elif t.kind == tyVar and t.sons[0].kind == tyVar:
-    LocalError(info, errVarVarTypeNotAllowed)
+    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: discard
   elif tfAcyclic in t.flags and skipTypes(t, abstractInst).kind != tyObject: 
-    LocalError(info, errInvalidPragmaX, "acyclic")
+    localError(info, errInvalidPragmaX, "acyclic")
   elif t.kind == tyVar and t.sons[0].kind == tyVar: 
-    LocalError(info, errVarVarTypeNotAllowed)
-  elif computeSize(t) < 0:
-    LocalError(info, errIllegalRecursionInTypeX, typeToString(t))
+    localError(info, errVarVarTypeNotAllowed)
+  elif computeSize(t) == szIllegalRecursion:
+    localError(info, errIllegalRecursionInTypeX, typeToString(t))
   when false:
     if t.kind == tyObject and t.sons[0] != nil:
       if t.sons[0].kind != tyObject or tfFinal in t.sons[0].flags: 
@@ -33,7 +36,7 @@ proc checkConstructedType*(info: TLineInfo, typ: PType) =
 
 proc searchInstTypes*(key: PType): PType =
   let genericTyp = key.sons[0]
-  InternalAssert genericTyp.kind == tyGenericBody and
+  internalAssert genericTyp.kind == tyGenericBody and
                  key.sons[0] == genericTyp and
                  genericTyp.sym != nil
 
@@ -47,12 +50,13 @@ proc searchInstTypes*(key: PType): PType =
       # types such as TChannel[empty]. Why?
       # See the notes for PActor in handleGenericInvokation
       return
-    block MatchType:
+    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]):
-          break MatchType
-      
+        if not compareTypes(inst.sons[j], key.sons[j],
+                            flags = {ExactGenericParams}):
+          break matchType
+       
       return inst
 
 proc cacheTypeInst*(inst: PType) =
@@ -66,30 +70,89 @@ type
     c*: PContext
     typeMap*: TIdTable        # map PType to PType
     symMap*: TIdTable         # map PSym to PSym
+    localCache*: TIdTable     # local cache for remembering alraedy replaced
+                              # types during instantiation of meta types
+                              # (they are not stored in the global cache)
     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
-proc ReplaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode
+proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType
+proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym
+proc replaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode
+
+template checkMetaInvariants(cl: TReplTypeVars, t: PType) =
+  when false:
+    if t != nil and tfHasMeta in t.flags and
+       cl.allowMetaTypes == false:
+      echo "UNEXPECTED META ", t.id, " ", instantiationInfo(-1)
+      debug t
+      writeStackTrace()
+      quit 1
+
+proc replaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType =
+  result = replaceTypeVarsTAux(cl, t)
+  checkMetaInvariants(cl, result)
 
 proc prepareNode(cl: var TReplTypeVars, n: PNode): PNode =
   result = copyNode(n)
-  result.typ = ReplaceTypeVarsT(cl, n.typ)
-  if result.kind == nkSym: result.sym = ReplaceTypeVarsS(cl, n.sym)
-  for i in 0 .. safeLen(n)-1: 
-    # XXX HACK: ``f(a, b)``, avoid to instantiate `f` 
-    if i == 0: result.add(n[i])
+  result.typ = replaceTypeVarsT(cl, n.typ)
+  if result.kind == nkSym: result.sym = replaceTypeVarsS(cl, n.sym)
+  let isCall = result.kind in nkCallKinds
+  for i in 0 .. <n.safeLen:
+    # XXX HACK: ``f(a, b)``, avoid to instantiate `f`
+    if isCall and i == 0: result.add(n[i])
     else: result.add(prepareNode(cl, n[i]))
 
-proc ReplaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode =
+proc isTypeParam(n: PNode): bool =
+  # XXX: generic params should use skGenericParam instead of skType
+  return n.kind == nkSym and
+         (n.sym.kind == skGenericParam or
+           (n.sym.kind == skType and sfFromGeneric in n.sym.flags))
+
+proc hasGenericArguments*(n: PNode): bool =
+  if n.kind == nkSym:
+    return n.sym.kind == skGenericParam or
+           (n.sym.kind == skType and
+            n.sym.typ.flags * {tfGenericTypeParam, tfImplicitTypeParam} != {})
+  else:
+    for i in 0.. <n.safeLen:
+      if hasGenericArguments(n.sons[i]): return true
+    return false
+
+proc reResolveCallsWithTypedescParams(cl: var TReplTypeVars, n: PNode): PNode =
+  # This is needed fo tgenericshardcases
+  # It's possible that a generic param will be used in a proc call to a
+  # typedesc accepting proc. After generic param substitution, such procs
+  # should be optionally instantiated with the correct type. In order to
+  # perform this instantiation, we need to re-run the generateInstance path
+  # in the compiler, but it's quite complicated to do so at the moment so we
+  # resort to a mild hack; the head symbol of the call is temporary reset and
+  # overload resolution is executed again (which may trigger generateInstance).
+  if n.kind in nkCallKinds and sfFromGeneric in n[0].sym.flags:
+    var needsFixing = false
+    for i in 1 .. <n.safeLen:
+      if isTypeParam(n[i]): needsFixing = true
+    if needsFixing:
+      n.sons[0] = newSymNode(n.sons[0].sym.owner)
+      return cl.c.semOverloadedCall(cl.c, n, n, {skProc})
+  
+  for i in 0 .. <n.safeLen:
+    n.sons[i] = reResolveCallsWithTypedescParams(cl, n[i])
+
+  return n
+
+proc replaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode =
   if n == nil: return
   result = copyNode(n)
-  result.typ = ReplaceTypeVarsT(cl, n.typ)
+  if n.typ != nil:
+    result.typ = replaceTypeVarsT(cl, n.typ)
+    checkMetaInvariants(cl, result.typ)
   case n.kind
   of nkNone..pred(nkSym), succ(nkSym)..nkNilLit:
-    nil
+    discard
   of nkSym:
-    result.sym = ReplaceTypeVarsS(cl, n.sym)
+    result.sym = replaceTypeVarsS(cl, n.sym)
   of nkRecWhen:
     var branch: PNode = nil              # the branch to take
     for i in countup(0, sonsLen(n) - 1):
@@ -101,72 +164,91 @@ proc ReplaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode =
         var cond = prepareNode(cl, it.sons[0])
         var e = cl.c.semConstExpr(cl.c, cond)
         if e.kind != nkIntLit:
-          InternalError(e.info, "ReplaceTypeVarsN: when condition not a bool")
+          internalError(e.info, "ReplaceTypeVarsN: when condition not a bool")
         if e.intVal != 0 and branch == nil: branch = it.sons[1]
       of nkElse:
         checkSonsLen(it, 1)
         if branch == nil: branch = it.sons[0]
       else: illFormedAst(n)
     if branch != nil:
-      result = ReplaceTypeVarsN(cl, branch)
+      result = replaceTypeVarsN(cl, branch)
     else:
       result = newNodeI(nkRecList, n.info)
+  of nkStaticExpr:
+    var n = prepareNode(cl, n)
+    n = reResolveCallsWithTypedescParams(cl, n)
+    result = cl.c.semExpr(cl.c, n)
   else:
     var length = sonsLen(n)
     if length > 0:
       newSons(result, length)
       for i in countup(0, length - 1):
-        result.sons[i] = ReplaceTypeVarsN(cl, n.sons[i])
+        result.sons[i] = replaceTypeVarsN(cl, n.sons[i])
   
-proc ReplaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym = 
+proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym = 
   if s == nil: return nil
   result = PSym(idTableGet(cl.symMap, s))
   if result == nil: 
     result = copySym(s, false)
     incl(result.flags, sfFromGeneric)
     idTablePut(cl.symMap, s, result)
-    result.typ = ReplaceTypeVarsT(cl, s.typ)
+    result.typ = replaceTypeVarsT(cl, s.typ)
     result.owner = s.owner
-    result.ast = ReplaceTypeVarsN(cl, s.ast)
+    result.ast = replaceTypeVarsN(cl, s.ast)
 
 proc lookupTypeVar(cl: TReplTypeVars, t: PType): PType = 
   result = PType(idTableGet(cl.typeMap, t))
   if result == nil:
-    LocalError(t.sym.info, errCannotInstantiateX, typeToString(t))
+    if cl.allowMetaTypes or tfRetType in t.flags: return
+    localError(t.sym.info, errCannotInstantiateX, typeToString(t))
     result = errorType(cl.c)
-  elif result.kind == tyGenericParam: 
-    InternalError(cl.info, "substitution with generic parameter")
-  
+  elif result.kind == tyGenericParam and not cl.allowMetaTypes:
+    internalError(cl.info, "substitution with generic parameter")
+
+proc instCopyType(cl: var TReplTypeVars, t: PType): PType =
+  # XXX: relying on allowMetaTypes is a kludge
+  result = copyType(t, t.owner, cl.allowMetaTypes)
+  result.flags.incl tfFromGeneric
+  result.flags.excl tfInstClearedFlags
+
 proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType = 
   # tyGenericInvokation[A, tyGenericInvokation[A, B]]
   # is difficult to handle: 
   var body = t.sons[0]
-  if body.kind != tyGenericBody: InternalError(cl.info, "no generic body")
+  if body.kind != tyGenericBody: internalError(cl.info, "no generic body")
   var header: PType = nil
   # search for some instantiation here:
-  result = searchInstTypes(t)
+  if cl.allowMetaTypes:
+    result = PType(idTableGet(cl.localCache, t))
+  else:
+    result = searchInstTypes(t)
   if result != nil: return
   for i in countup(1, sonsLen(t) - 1):
     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 = instCopyType(cl, t)
+        header.sons[i] = x
+        propagateToOwner(header, x)
+  
   if header != nil:
     # search again after first pass:
     result = searchInstTypes(header)
     if result != nil: return
   else:
-    header = copyType(t, t.owner, false)
+    header = instCopyType(cl, t)
+  
+  result = newType(tyGenericInst, t.sons[0].owner)
+  # be careful not to propagate unnecessary flags here (don't use rawAddSon)
+  result.sons = @[header.sons[0]]
   # ugh need another pass for deeply recursive generic types (e.g. PActor)
   # we need to add the candidate here, before it's fully instantiated for
   # recursive instantions:
-  result = newType(tyGenericInst, t.sons[0].owner)
-  result.rawAddSon(header.sons[0])
-  cacheTypeInst(result)
+  if not cl.allowMetaTypes:
+    cacheTypeInst(result)
+  else:
+    idTablePut(cl.localCache, t, result)
 
   for i in countup(1, sonsLen(t) - 1):
     var x = replaceTypeVarsT(cl, t.sons[i])
@@ -175,71 +257,168 @@ proc handleGenericInvokation(cl: var TReplTypeVars, t: PType): PType =
     propagateToOwner(header, x)
     idTablePut(cl.typeMap, body.sons[i-1], x)
   
-  for i in countup(1, sonsLen(t) - 1): 
+  for i in countup(1, sonsLen(t) - 1):
     # 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
+
+  var newbody = replaceTypeVarsT(cl, lastSon(body))
+  newbody.flags = newbody.flags + (t.flags + body.flags - tfInstClearedFlags)
   result.flags = result.flags + newbody.flags
   newbody.callConv = body.callConv
-  newbody.n = ReplaceTypeVarsN(cl, lastSon(body).n)
   # This type may be a generic alias and we want to resolve it here.
   # One step is enough, because the recursive nature of
   # handleGenericInvokation will handle the alias-to-alias-to-alias case
   if newbody.isGenericAlias: newbody = newbody.skipGenericAlias
   rawAddSon(result, newbody)
   checkPartialConstructedType(cl.info, newbody)
+
+proc eraseVoidParams(t: PType) =
+  if t.sons[0] != nil and t.sons[0].kind == tyEmpty:
+    t.sons[0] = nil
   
-proc ReplaceTypeVarsT*(cl: var TReplTypeVars, t: PType): PType = 
+  for i in 1 .. <t.sonsLen:
+    # don't touch any memory unless necessary
+    if t.sons[i].kind == tyEmpty:
+      var pos = i
+      for j in i+1 .. <t.sonsLen:
+        if t.sons[j].kind != tyEmpty:
+          t.sons[pos] = t.sons[j]
+          t.n.sons[pos] = t.n.sons[j]
+          inc pos
+      setLen t.sons, pos
+      setLen t.n.sons, pos
+      return
+
+proc skipIntLiteralParams(t: PType) =
+  for i in 0 .. <t.sonsLen:
+    let p = t.sons[i]
+    if p == nil: continue
+    let skipped = p.skipIntLit
+    if skipped != p:
+      t.sons[i] = skipped
+      if i > 0: t.n.sons[i].sym.typ = skipped
+
+proc propagateFieldFlags(t: PType, n: PNode) =
+  # This is meant for objects and tuples
+  # The type must be fully instantiated!
+  internalAssert n.kind != nkRecWhen
+  case n.kind
+  of nkSym:
+    propagateToOwner(t, n.sym.typ)
+  of nkRecList, nkRecCase, nkOfBranch, nkElse:
+    if n.sons != nil:
+      for son in n.sons:
+        propagateFieldFlags(t, son)
+  else: discard
+
+proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType =
   result = t
-  if t == nil: return 
+  if t == nil: return
+
+  if t.kind in {tyStatic, tyGenericParam} + tyTypeClasses:
+    let lookup = PType(idTableGet(cl.typeMap, t))
+    if lookup != nil: return lookup
+  
   case t.kind
-  of tyTypeClass: nil
-  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 tyGenericInvokation:
     result = handleGenericInvokation(cl, t)
+
   of tyGenericBody:
-    InternalError(cl.info, "ReplaceTypeVarsT: tyGenericBody")
-    result = ReplaceTypeVarsT(cl, lastSon(t))
+    internalError(cl.info, "ReplaceTypeVarsT: tyGenericBody" )
+    result = replaceTypeVarsT(cl, lastSon(t))
+
+  of tyFromExpr:
+    var n = prepareNode(cl, t.n)
+    n = cl.c.semConstExpr(cl.c, n)
+    if n.typ.kind == tyTypeDesc:
+      # XXX: sometimes, chained typedescs enter here.
+      # It may be worth investigating why this is happening,
+      # because it may cause other bugs elsewhere.
+      result = n.typ.skipTypes({tyTypeDesc})
+      # result = n.typ.base
+    else:
+      if n.typ.kind != tyStatic:
+        # XXX: In the future, semConstExpr should
+        # return tyStatic values to let anyone make
+        # use of this knowledge. The patching here
+        # won't be necessary then.
+        result = newTypeS(tyStatic, cl.c)
+        result.sons = @[n.typ]
+        result.n = n
+      else:
+        result = n.typ
+
   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
+    elif t.sonsLen > 0:
+      result = makeTypeDesc(cl.c, replaceTypeVarsT(cl, t.sons[0]))
+ 
+  of tyUserTypeClass:
+    result = t
+
+  of tyGenericInst:
+    result = instCopyType(cl, t)
+    for i in 1 .. <result.sonsLen:
+      result.sons[i] = replaceTypeVarsT(cl, result.sons[i])
+    propagateToOwner(result, result.lastSon)
+  
   else:
-    if t.kind == tyArray:
-      let idxt = t.sons[0]
-      if idxt.kind == tyExpr 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)
     if containsGenericType(t):
-      result = copyType(t, t.owner, false)
-      incl(result.flags, tfFromGeneric)
+      result = instCopyType(cl, t)
       result.size = -1 # needs to be recomputed
+      
       for i in countup(0, sonsLen(result) - 1):
-        result.sons[i] = ReplaceTypeVarsT(cl, result.sons[i])
-      result.n = ReplaceTypeVarsN(cl, result.n)
-      if result.Kind in GenericTypes:
-        LocalError(cl.info, errCannotInstantiateX, TypeToString(t, preferName))
-      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 = 
+        if result.sons[i] != nil:
+          result.sons[i] = replaceTypeVarsT(cl, result.sons[i])
+          propagateToOwner(result, result.sons[i])
+
+      result.n = replaceTypeVarsN(cl, result.n)
+      
+      # XXX: This is not really needed?
+      # if result.kind in GenericTypes:
+      #   localError(cl.info, errCannotInstantiateX, typeToString(t, preferName))
+
+      case result.kind
+      of tyArray:
+        let idx = result.sons[0]
+        if idx.kind == tyStatic:
+          if idx.n == nil:
+            let lookup = lookupTypeVar(cl, idx)
+            internalAssert lookup != nil
+            idx.n = lookup.n
+
+          result.sons[0] = makeRangeType(cl.c, 0, idx.n.intVal - 1, idx.n.info)
+       
+      of tyObject, tyTuple:
+        propagateFieldFlags(result, result.n)
+      
+      of tyProc:
+        eraseVoidParams(result)
+        skipIntLiteralParams(result)
+      
+      else: discard
+
+proc generateTypeInstance*(p: PContext, pt: TIdTable, info: TLineInfo,
+                           t: PType): PType =
   var cl: TReplTypeVars
-  InitIdTable(cl.symMap)
+  initIdTable(cl.symMap)
   copyIdTable(cl.typeMap, pt)
-  cl.info = arg.info
+  initIdTable(cl.localCache)
+  cl.info = info
   cl.c = p
-  pushInfoContext(arg.info)
-  result = ReplaceTypeVarsT(cl, t)
+  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/service.nim b/compiler/service.nim
index 1de83af7c..42c4aa9f4 100644
--- a/compiler/service.nim
+++ b/compiler/service.nim
@@ -29,23 +29,23 @@ var
     # the arguments to be passed to the program that
     # should be run
 
-proc ProcessCmdLine*(pass: TCmdLinePass, cmd: string) =
+proc processCmdLine*(pass: TCmdLinePass, cmd: string) =
   var p = parseopt.initOptParser(cmd)
   var argsCount = 0
   while true: 
     parseopt.next(p)
     case p.kind
     of cmdEnd: break 
-    of cmdLongOption, cmdShortOption: 
+    of cmdLongoption, cmdShortOption: 
       # hint[X]:off is parsed as (p.key = "hint[X]", p.val = "off")
       # we fix this here
       var bracketLe = strutils.find(p.key, '[')
       if bracketLe >= 0: 
         var key = substr(p.key, 0, bracketLe - 1)
         var val = substr(p.key, bracketLe + 1) & ':' & p.val
-        ProcessSwitch(key, val, pass, gCmdLineInfo)
+        processSwitch(key, val, pass, gCmdLineInfo)
       else: 
-        ProcessSwitch(p.key, p.val, pass, gCmdLineInfo)
+        processSwitch(p.key, p.val, pass, gCmdLineInfo)
     of cmdArgument:
       if argsCount == 0:
         options.command = p.key
@@ -79,11 +79,11 @@ proc serve*(action: proc (){.nimcall.}) =
       if line == "quit": quit()
       execute line
       echo ""
-      FlushFile(stdout)
+      flushFile(stdout)
 
   of "tcp", "":
     when useCaas:
-      var server = Socket()
+      var server = socket()
       let p = getConfigVar("server.port")
       let port = if p.len > 0: parseInt(p).TPort else: 6000.TPort
       server.bindAddr(port, getConfigVar("server.address"))
diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim
index cacf4782e..d269e9e69 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
@@ -30,7 +31,8 @@ type
     state*: TCandidateState
     callee*: PType           # may not be nil!
     calleeSym*: PSym         # may be nil
-    calleeScope: int         # may be -1 for unknown scope
+    calleeScope*: int        # scope depth:
+                             # is this a top-level symbol or a nested proc?
     call*: PNode             # modified call
     bindings*: TIdTable      # maps types to types
     baseTypeMatch: bool      # needed for conversions from T to openarray[T]
@@ -58,7 +60,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,32 +75,44 @@ 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)
+  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
+  if callee.kind in skProcKinds and calleeScope == -1:
+    if callee.originatingModule == ctx.module:
+      let rootSym = if sfFromGeneric notin callee.flags: callee
+                    else: callee.owner
+      c.calleeScope = rootSym.scope.depthLevel
+    else:
+      c.calleeScope = 1
+  else:
+    c.calleeScope = calleeScope
   initIdTable(c.bindings)
   c.errors = nil
-  if binding != nil and callee.kind in RoutineKinds:
+  if binding != nil and callee.kind in routineKinds:
     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 bound != nil and 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 +140,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: break
     else: return 0
 
 proc complexDisambiguation(a, b: PType): int =
@@ -159,9 +175,8 @@ proc cmpCandidates*(a, b: TCandidate): int =
   if result != 0: return
   result = a.convMatches - b.convMatches
   if result != 0: return
-  if (a.calleeScope != -1) and (b.calleeScope != -1):
-    result = a.calleeScope - b.calleeScope
-    if result != 0: return
+  result = a.calleeScope - b.calleeScope
+  if result != 0: return
   # the other way round because of other semantics:
   result = b.inheritancePenalty - a.inheritancePenalty
   if result != 0: return
@@ -169,11 +184,11 @@ proc cmpCandidates*(a, b: TCandidate): int =
   result = complexDisambiguation(a.callee, b.callee)
 
 proc writeMatches*(c: TCandidate) = 
-  Writeln(stdout, "exact matches: " & $c.exactMatches)
-  Writeln(stdout, "subtype matches: " & $c.subtypeMatches)
-  Writeln(stdout, "conv matches: " & $c.convMatches)
-  Writeln(stdout, "intconv matches: " & $c.intConvMatches)
-  Writeln(stdout, "generic matches: " & $c.genericMatches)
+  writeln(stdout, "exact matches: " & $c.exactMatches)
+  writeln(stdout, "subtype matches: " & $c.subtypeMatches)
+  writeln(stdout, "conv matches: " & $c.convMatches)
+  writeln(stdout, "intconv matches: " & $c.intConvMatches)
+  writeln(stdout, "generic matches: " & $c.genericMatches)
 
 proc argTypeToString(arg: PNode): string =
   if arg.kind in nkSymChoices:
@@ -203,7 +218,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: 
@@ -223,7 +238,7 @@ proc concreteType(c: TCandidate, t: PType): PType =
         # proc sort[T](cmp: proc(a, b: T): int = cmp)
       if result.kind != tyGenericParam: break
   of tyGenericInvokation:
-    InternalError("cannot resolve type: " & typeToString(t))
+    internalError("cannot resolve type: " & typeToString(t))
     result = t
   else:
     result = t                # Note: empty is valid here
@@ -296,24 +311,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.} =
@@ -354,20 +372,16 @@ proc procTypeRel(c: var TCandidate, f, a: PType): TTypeRelation =
       return isNone
     elif f.flags * {tfIterator} != a.flags * {tfIterator}:
       return isNone
-    elif f.callconv != a.callconv:
+    elif f.callConv != a.callConv:
       # valid to pass a 'nimcall' thingie to 'closure':
-      if f.callconv == ccClosure and a.callconv == ccDefault:
+      if f.callConv == ccClosure and a.callConv == ccDefault:
         result = isConvertible
       else:
         return isNone
     when useEffectSystem:
       if not compatibleEffects(f, a): return isNone
   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
+  else: discard
 
 proc typeRangeRel(f, a: PType): TTypeRelation {.noinline.} =
   let
@@ -385,7 +399,71 @@ proc typeRangeRel(f, a: PType): TTypeRelation {.noinline.} =
   else:
     result = isNone
 
-proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
+proc matchUserTypeClass*(c: PContext, m: var TCandidate,
+                         ff, a: PType): TTypeRelation =
+  #if f.n == nil:
+  #  let r = typeRel(m, f, a)
+  #  return if r == isGeneric: arg else: nil
+
+  var body = ff.skipTypes({tyUserTypeClassInst})
+
+  # var prev = PType(idTableGet(m.bindings, f))
+  # if prev != nil:
+  #   if sameType(prev, a): return arg
+  #   else: return nil
+
+  # pushInfoContext(arg.info)
+  openScope(c)
+  inc c.inTypeClass
+
+  finally:
+    dec c.inTypeClass
+    closeScope(c)
+
+  if ff.kind == tyUserTypeClassInst:
+    for i in 1 .. <(ff.len - 1):
+      var
+        typeParamName = ff.base.sons[i-1].sym.name
+        typ = ff.sons[i]
+        param = newSym(skType, typeParamName, body.sym, body.sym.info)
+        
+      param.typ = makeTypeDesc(c, typ)
+      addDecl(c, param)
+
+  for param in body.n[0]:
+    var
+      dummyName: PNode
+      dummyType: PType
+    
+    if param.kind == nkVarTy:
+      dummyName = param[0]
+      dummyType = makeVarType(c, a)
+    else:
+      dummyName = param
+      dummyType = a
+
+    internalAssert dummyName.kind == nkIdent
+    var dummyParam = newSym(skType, dummyName.ident, body.sym, body.sym.info)
+    dummyParam.typ = dummyType
+    addDecl(c, dummyParam)
+
+  var checkedBody = c.semTryExpr(c, copyTree(body.n[3]), bufferErrors = false)
+  m.errors = bufferedMsgs
+  clearBufferedMsgs()
+  if checkedBody == nil: return isNone
+
+  if checkedBody.kind == nkStmtList:
+    for stmt in checkedBody:
+      case stmt.kind
+      of nkReturnStmt: discard
+      of nkTypeSection: discard
+      of nkConstDef: discard
+      else: discard
+    
+  return isGeneric
+  # put(m.bindings, f, a)
+
+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,22 +479,36 @@ 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)
+  
+  if f.kind == tyExpr:
+    put(c.bindings, f, aOrig)
+    return isGeneric
+
+  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:
+      let bound = aOrig.skipTypes({tyRange}).skipIntLit
+      put(c.bindings, f, bound)
     return res
- 
+
+  template considerPreviousT(body: stmt) {.immediate.} =
+    var prev = PType(idTableGet(c.bindings, f))
+    if prev == nil: body
+    else: return typeRel(c, prev, a)
+
   case a.kind
   of tyOr:
     # seq[int|string] vs seq[number]
@@ -454,13 +546,13 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
   of tyAnything:
     return if f.kind == tyAnything: isGeneric
            else: isNone
-  else: nil
+  else: discard
 
   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 +580,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
@@ -507,9 +599,9 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       result = typeRel(c, f.sons[1], a.sons[1])
       if result < isGeneric: result = isNone
       elif lengthOrd(fRange) != lengthOrd(a): result = isNone
-    else: nil
+    else: discard
   of tyOpenArray, tyVarargs:
-    case a.Kind
+    case a.kind
     of tyOpenArray, tyVarargs:
       result = typeRel(c, base(f), base(a))
       if result < isGeneric: result = isNone
@@ -528,9 +620,9 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         result = isConvertible
       elif typeRel(c, base(f), a.sons[0]) >= isGeneric: 
         result = isConvertible
-    else: nil
+    else: discard
   of tySequence:
-    case a.Kind
+    case a.kind
     of tySequence:
       if (f.sons[0].kind != tyGenericParam) and (a.sons[0].kind == tyEmpty):
         result = isSubtype
@@ -540,11 +632,10 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         elif tfNotNil in f.flags and tfNotNil notin a.flags:
           result = isNilConversion
     of tyNil: result = f.allowsNil
-    else: nil
+    else: discard
   of tyOrdinal:
     if isOrdinalType(a):
       var x = if a.kind == tyOrdinal: a.sons[0] else: a
-     
       if f.sonsLen == 0:
         result = isGeneric
       else:
@@ -552,14 +643,16 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         if result < isGeneric: result = isNone
     elif a.kind == tyGenericParam:
       result = isGeneric
-  of tyForward: InternalError("forward type in typeRel()")
+  of tyForward: internalError("forward type in typeRel()")
   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
+      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:
@@ -583,7 +676,7 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       elif tfNotNil in f.flags and tfNotNil notin a.flags:
         result = isNilConversion
     of tyNil: result = f.allowsNil
-    else: nil
+    else: discard
   of tyRef: 
     case a.kind
     of tyRef:
@@ -592,7 +685,7 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       elif tfNotNil in f.flags and tfNotNil notin a.flags:
         result = isNilConversion
     of tyNil: result = f.allowsNil
-    else: nil
+    else: discard
   of tyProc:
     result = procTypeRel(c, f, a)
     if result != isNone and tfNotNil in f.flags and tfNotNil notin a.flags:
@@ -608,7 +701,7 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
     of tyProc:
       if a.callConv != ccClosure: result = isConvertible
     of tyPtr, tyCString: result = isConvertible
-    else: nil
+    else: discard
   of tyString: 
     case a.kind
     of tyString: 
@@ -617,10 +710,10 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
       else:
         result = isEqual
     of tyNil: result = f.allowsNil
-    else: nil
+    else: discard
   of tyCString:
     # conversion from string to cstring is automatic:
-    case a.Kind
+    case a.kind
     of tyCString:
       if tfNotNil in f.flags and tfNotNil notin a.flags:
         result = isNilConversion
@@ -635,30 +728,45 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
           (skipTypes(a.sons[0], {tyRange}).kind in {tyInt..tyInt64}) and
           (a.sons[1].kind == tyChar): 
         result = isConvertible
-    else: nil
+    else: discard
 
   of tyEmpty:
     if a.kind == tyEmpty: result = isEqual
 
   of tyGenericInst:
-    result = typeRel(c, lastSon(f), a)
+    let roota = a.skipGenericAlias
+    let rootf = f.skipGenericAlias
+    if a.kind == tyGenericInst and roota.base == rootf.base :
+      for i in 1 .. rootf.sonsLen-2:
+        let ff = rootf.sons[i]
+        let aa = roota.sons[i]
+        result = typeRel(c, ff, aa)
+        if result == isNone: return        
+        if ff.kind == tyRange and result != isEqual: return isNone
+
+      result = isGeneric
+    else:
+      result = typeRel(c, lastSon(f), a)
 
   of tyGenericBody:
-    let ff = lastSon(f)
-    if ff != nil: result = typeRel(c, ff, a)
+    considerPreviousT:
+      if a.kind == tyGenericInst and a.sons[0] == f:
+        bindingRet isGeneric
+      let ff = lastSon(f)
+      if ff != nil: result = typeRel(c, ff, a)
 
   of tyGenericInvokation:
     var x = a.skipGenericAlias
     if x.kind == tyGenericInvokation or f.sons[0].kind != tyGenericBody:
       #InternalError("typeRel: tyGenericInvokation -> tyGenericInvokation")
       # simply no match for now:
-      nil
+      discard
     elif x.kind == tyGenericInst and 
           (f.sons[0] == x.sons[0]) and
           (sonsLen(x) - 1 == sonsLen(f)):
       for i in countup(1, sonsLen(f) - 1):
         if x.sons[i].kind == tyGenericParam:
-          InternalError("wrong instantiated type!")
+          internalError("wrong instantiated type!")
         elif typeRel(c, f.sons[i], x.sons[i]) <= isSubtype: return 
       result = isGeneric
     else:
@@ -668,41 +776,65 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
         for i in countup(1, sonsLen(f) - 1):
           var x = PType(idTableGet(c.bindings, f.sons[0].sons[i - 1]))
           if x == nil or x.kind in {tyGenericInvokation, tyGenericParam}:
-            InternalError("wrong instantiated type!")
+            internalError("wrong instantiated type!")
           put(c.bindings, f.sons[i], x)
   
   of tyAnd:
-    for branch in f.sons:
-      if typeRel(c, branch, a) == isNone:
-        return isNone
+    considerPreviousT:
+      for branch in f.sons:
+        if typeRel(c, branch, aOrig) == isNone:
+          return isNone
 
-    bindingRet isGeneric
+      bindingRet isGeneric
 
   of tyOr:
-    for branch in f.sons:
-      if typeRel(c, branch, a) != isNone:
-        bindingRet isGeneric
-
-    return isNone
+    considerPreviousT:
+      for branch in f.sons:
+        if typeRel(c, branch, aOrig) != isNone:
+          bindingRet isGeneric
+       
+      return isNone
 
   of tyNot:
-    for branch in f.sons:
-      if typeRel(c, branch, a) != isNone:
-        return isNone
-    
-    bindingRet isGeneric
+    considerPreviousT:
+      for branch in f.sons:
+        if typeRel(c, branch, aOrig) != isNone:
+          return isNone
+      
+      bindingRet isGeneric
 
   of tyAnything:
-    var prev = PType(idTableGet(c.bindings, f))
-    if prev == nil:
+    considerPreviousT:
       var concrete = concreteType(c, a)
       if concrete != nil and doBind:
         put(c.bindings, f, concrete)
       return isGeneric
-    else:
-      return typeRel(c, prev, a)
-    
-  of tyGenericParam, tyTypeClass:
+
+  of tyBuiltInTypeClass:
+    considerPreviousT:
+      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
+
+  of tyUserTypeClass, tyUserTypeClassInst:
+    considerPreviousT:
+      result = matchUserTypeClass(c.c, c, f, a)
+      if result == isGeneric:
+        put(c.bindings, f, a)
+
+  of tyCompositeTypeClass:
+    considerPreviousT:
+      if typeRel(c, f.sons[1], a) != isNone:
+        put(c.bindings, f, a)
+        return isGeneric
+      else:
+        return isNone
+
+  of tyGenericParam:
     var x = PType(idTableGet(c.bindings, f))
     if x == nil:
       if c.calleeSym != nil and c.calleeSym.kind == skType and
@@ -716,17 +848,17 @@ proc typeRel(c: var TCandidate, f, a: PType, doBind = true): TTypeRelation =
           if f.sons == nil or f.sons.len == 0:
             result = isGeneric
           else:
-            InternalAssert a.sons != nil and a.sons.len > 0
+            internalAssert a.sons != nil and a.sons.len > 0
             c.typedescMatched = true
             result = typeRel(c, f.sons[0], a.sons[0])
         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 +871,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,26 +886,29 @@ 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
     else:
-      InternalAssert prev.sonsLen == 1
+      internalAssert prev.sonsLen == 1
       let toMatch = if tfUnresolved in f.flags: a
                     else: a.sons[0]
       result = typeRel(c, prev.sons[0], toMatch)
-  of tyExpr, tyStmt:
+  
+  of 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 = 
@@ -773,7 +916,7 @@ proc getInstantiatedType(c: PContext, arg: PNode, m: TCandidate,
   if result == nil: 
     result = generateTypeInstance(c, m.bindings, arg, f)
   if result == nil:
-    InternalError(arg.info, "getInstantiatedType")
+    internalError(arg.info, "getInstantiatedType")
     result = errorType(c)
   
 proc implicitConv(kind: TNodeKind, f: PType, arg: PNode, m: TCandidate, 
@@ -786,7 +929,7 @@ proc implicitConv(kind: TNodeKind, f: PType, arg: PNode, m: TCandidate,
       result.typ = errorType(c)
   else:
     result.typ = f
-  if result.typ == nil: InternalError(arg.info, "implicitConv")
+  if result.typ == nil: internalError(arg.info, "implicitConv")
   addSon(result, ast.emptyNode)
   addSon(result, arg)
 
@@ -825,7 +968,7 @@ proc localConvMatch(c: PContext, m: var TCandidate, f, a: PType,
   var call = newNodeI(nkCall, arg.info)
   call.add(f.n.copyTree)
   call.add(arg.copyTree)
-  result = c.semOverloadedCall(c, call, call, RoutineKinds)
+  result = c.semOverloadedCall(c, call, call, routineKinds)
   if result != nil:
     # resulting type must be consistent with the other arguments:
     var r = typeRel(m, f.sons[0], result.typ)
@@ -836,110 +979,33 @@ proc localConvMatch(c: PContext, m: var TCandidate, f, a: PType,
       result.typ = getInstantiatedType(c, arg, m, base(f))
     m.baseTypeMatch = true
 
-proc matchUserTypeClass*(c: PContext, m: var TCandidate,
-                         arg: PNode, f, a: PType): PNode =
-  if f.n == nil:
-    let r = typeRel(m, f, a)
-    return if r == isGeneric: arg else: nil
- 
-  var prev = PType(idTableGet(m.bindings, f))
-  if prev != nil:
-    if sameType(prev, a): return arg
-    else: return nil
-
-  # pushInfoContext(arg.info)
-  openScope(c)
-  inc c.InTypeClass
-
-  finally:
-    dec c.InTypeClass
-    closeScope(c)
-
-  for param in f.n[0]:
-    var
-      dummyName: PNode
-      dummyType: PType
-    
-    if param.kind == nkVarTy:
-      dummyName = param[0]
-      dummyType = makeVarType(c, a)
-    else:
-      dummyName = param
-      dummyType = a
-
-    InternalAssert dummyName.kind == nkIdent
-    var dummyParam = newSym(skType, dummyName.ident, f.sym, f.sym.info)
-    dummyParam.typ = dummyType
-    addDecl(c, dummyParam)
-
-  for stmt in f.n[3]:
-    var e = c.semTryExpr(c, copyTree(stmt), bufferErrors = false)
-    m.errors = bufferedMsgs
-    clearBufferedMsgs()
-    if e == nil: return nil
-
-    case e.kind
-    of nkReturnStmt: nil
-    of nkTypeSection: nil
-    of nkConstDef: nil
-    else: nil
-  
-  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
+    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)
-  of tyTypeClass, tyParametricTypeClass:
-    if fMaybeExpr.n != nil:
-      let match = matchUserTypeClass(c, m, arg, fMaybeExpr, a)
-      if match != nil:
-        r = isGeneric
-        arg = match
-      else:
-        r = isNone
-    else:
-      r = typeRel(m, f, a)
-  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 +1027,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 +1071,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
@@ -1041,17 +1110,17 @@ proc ParamTypesMatch*(c: PContext, m: var TCandidate, f, a: PType,
       result = nil
     elif (y.state == csMatch) and (cmpCandidates(x, y) == 0): 
       if x.state != csMatch: 
-        InternalError(arg.info, "x.state is not csMatch") 
+        internalError(arg.info, "x.state is not csMatch") 
       # ambiguous: more than one symbol fits
       result = nil
     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) = 
-  if sonsLen(father) <= at: setlen(father.sons, at + 1)
+  if sonsLen(father) <= at: setLen(father.sons, at + 1)
   father.sons[at] = son
 
 # we are allowed to modify the calling node in the 'prepare*' procs:
@@ -1122,7 +1191,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
       # check if m.callee has such a param:
       prepareNamedParam(n.sons[a])
       if n.sons[a].sons[0].kind != nkIdent: 
-        LocalError(n.sons[a].info, errNamedParamHasToBeIdent)
+        localError(n.sons[a].info, errNamedParamHasToBeIdent)
         m.state = csNoMatch
         return 
       formal = getSymFromList(m.callee.n, n.sons[a].sons[0].ident, 1)
@@ -1130,15 +1199,15 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
         # no error message!
         m.state = csNoMatch
         return 
-      if ContainsOrIncl(marker, formal.position): 
+      if containsOrIncl(marker, formal.position): 
         # already in namedParams:
-        LocalError(n.sons[a].info, errCannotBindXTwice, formal.name.s)
+        localError(n.sons[a].info, errCannotBindXTwice, formal.name.s)
         m.state = csNoMatch
         return 
       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
@@ -1156,7 +1225,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
       # unnamed param
       if f >= formalLen:
         # too many arguments?
-        if tfVarArgs in m.callee.flags:
+        if tfVarargs in m.callee.flags:
           # is ok... but don't increment any counters...
           # we have no formal here to snoop at:
           n.sons[a] = prepareOperand(c, n.sons[a])
@@ -1168,7 +1237,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)
@@ -1181,17 +1250,17 @@ proc matchesAux(c: PContext, n, nOrig: PNode,
           return
       else:
         if m.callee.n.sons[f].kind != nkSym: 
-          InternalError(n.sons[a].info, "matches")
+          internalError(n.sons[a].info, "matches")
           return
         formal = m.callee.n.sons[f].sym
-        if ContainsOrIncl(marker, formal.position): 
+        if containsOrIncl(marker, formal.position): 
           # already in namedParams:
-          LocalError(n.sons[a].info, errCannotBindXTwice, formal.name.s)
+          localError(n.sons[a].info, errCannotBindXTwice, formal.name.s)
           m.state = csNoMatch
           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
@@ -1228,7 +1297,7 @@ proc matches*(c: PContext, n, nOrig: PNode, m: var TCandidate) =
   var f = 1
   while f < sonsLen(m.callee.n):
     var formal = m.callee.n.sons[f].sym
-    if not ContainsOrIncl(marker, formal.position):
+    if not containsOrIncl(marker, formal.position):
       if formal.ast == nil:
         if formal.typ.kind == tyVarargs:
           var container = newNodeIT(nkBracket, n.info, arrayConstr(c, n.info))
@@ -1245,8 +1314,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 +1377,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 76a6c21d9..49611f649 100644
--- a/compiler/suggest.nim
+++ b/compiler/suggest.nim
@@ -11,7 +11,7 @@
 
 # included from sigmatch.nim
 
-import algorithm, sequtils
+import algorithm, sequtils, pretty
 
 const
   sep = '\t'
@@ -28,7 +28,7 @@ proc origModuleName(m: PSym): string =
            else:
              m.name.s
 
-proc SymToStr(s: PSym, isLocal: bool, section: string, li: TLineInfo): string = 
+proc symToStr(s: PSym, isLocal: bool, section: string, li: TLineInfo): string = 
   result = section
   result.add(sep)
   result.add($s.kind)
@@ -48,15 +48,15 @@ proc SymToStr(s: PSym, isLocal: bool, section: string, li: TLineInfo): string =
   result.add(sep)
   result.add(toFullPath(li))
   result.add(sep)
-  result.add($ToLinenumber(li))
+  result.add($toLinenumber(li))
   result.add(sep)
-  result.add($ToColumn(li))
+  result.add($toColumn(li))
   result.add(sep)
   when not defined(noDocgen):
     result.add(s.extractDocComment.escape)
 
-proc SymToStr(s: PSym, isLocal: bool, section: string): string = 
-  result = SymToStr(s, isLocal, section, s.info)
+proc symToStr(s: PSym, isLocal: bool, section: string): string = 
+  result = symToStr(s, isLocal, section, s.info)
 
 proc filterSym(s: PSym): bool {.inline.} =
   result = s.name.s[0] in lexer.SymChars and s.kind != skModule
@@ -68,7 +68,7 @@ proc fieldVisible*(c: PContext, f: PSym): bool {.inline.} =
 
 proc suggestField(c: PContext, s: PSym, outputs: var int) = 
   if filterSym(s) and fieldVisible(c, s):
-    SuggestWriteln(SymToStr(s, isLocal=true, sectionSuggest))
+    suggestWriteln(symToStr(s, isLocal=true, sectionSuggest))
     inc outputs
 
 when not defined(nimhygiene):
@@ -84,7 +84,7 @@ template wholeSymTab(cond, section: expr) {.immediate.} =
     for item in entries:
       let it {.inject.} = item
       if cond:
-        SuggestWriteln(SymToStr(it, isLocal = isLocal, section))
+        suggestWriteln(symToStr(it, isLocal = isLocal, section))
         inc outputs
 
 proc suggestSymList(c: PContext, list: PNode, outputs: var int) = 
@@ -103,7 +103,7 @@ proc suggestObject(c: PContext, n: PNode, outputs: var int) =
       suggestObject(c, n.sons[0], outputs)
       for i in countup(1, L-1): suggestObject(c, lastSon(n.sons[i]), outputs)
   of nkSym: suggestField(c, n.sym, outputs)
-  else: nil
+  else: discard
 
 proc nameFits(c: PContext, s: PSym, n: PNode): bool = 
   var op = n.sons[0]
@@ -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:
@@ -144,14 +144,14 @@ proc suggestEverything(c: PContext, n: PNode, outputs: var int) =
     if scope == c.topLevelScope: isLocal = false
     for it in items(scope.symbols):
       if filterSym(it):
-        SuggestWriteln(SymToStr(it, isLocal = isLocal, sectionSuggest))
+        suggestWriteln(symToStr(it, isLocal = isLocal, sectionSuggest))
         inc outputs
     if scope == c.topLevelScope: break
 
 proc suggestFieldAccess(c: PContext, n: PNode, outputs: var int) =
   # special code that deals with ``myObj.``. `n` is NOT the nkDotExpr-node, but
   # ``myObj``.
-  var typ = n.Typ
+  var typ = n.typ
   if typ == nil:
     # a module symbol has no type for example:
     if n.kind == nkSym and n.sym.kind == skModule: 
@@ -159,12 +159,12 @@ proc suggestFieldAccess(c: PContext, n: PNode, outputs: var int) =
         # all symbols accessible, because we are in the current module:
         for it in items(c.topLevelScope.symbols):
           if filterSym(it): 
-            SuggestWriteln(SymToStr(it, isLocal=false, sectionSuggest))
+            suggestWriteln(symToStr(it, isLocal=false, sectionSuggest))
             inc outputs
       else: 
         for it in items(n.sym.tab): 
           if filterSym(it): 
-            SuggestWriteln(SymToStr(it, isLocal=false, sectionSuggest))
+            suggestWriteln(symToStr(it, isLocal=false, sectionSuggest))
             inc outputs
     else:
       # fallback:
@@ -203,7 +203,7 @@ const
   CallNodes = {nkCall, nkInfix, nkPrefix, nkPostfix, nkCommand, nkCallStrLit}
 
 proc findClosestCall(n: PNode): PNode = 
-  if n.kind in callNodes and msgs.inCheckpoint(n.info) == cpExact: 
+  if n.kind in CallNodes and msgs.inCheckpoint(n.info) == cpExact: 
     result = n
   else:
     for i in 0.. <safeLen(n):
@@ -246,16 +246,16 @@ var
 proc findUsages(node: PNode, s: PSym) =
   if usageSym == nil and isTracked(node.info, s.name.s.len):
     usageSym = s
-    SuggestWriteln(SymToStr(s, isLocal=false, sectionUsage))
+    suggestWriteln(symToStr(s, isLocal=false, sectionUsage))
   elif s == usageSym:
     if lastLineInfo != node.info:
-      SuggestWriteln(SymToStr(s, isLocal=false, sectionUsage, node.info))
+      suggestWriteln(symToStr(s, isLocal=false, sectionUsage, node.info))
     lastLineInfo = node.info
 
 proc findDefinition(node: PNode, s: PSym) =
   if isTracked(node.info, s.name.s.len):
-    SuggestWriteln(SymToStr(s, isLocal=false, sectionDef))
-    SuggestQuit()
+    suggestWriteln(symToStr(s, isLocal=false, sectionDef))
+    suggestQuit()
 
 type
   TSourceMap = object
@@ -281,7 +281,7 @@ proc resetSourceMap*(fileIdx: int32) =
   ensureIdx(gSourceMaps, fileIdx)
   gSourceMaps[fileIdx].lines = @[]
 
-proc addToSourceMap(sym: Psym, info: TLineInfo) =
+proc addToSourceMap(sym: PSym, info: TLineInfo) =
   ensureIdx(gSourceMaps, info.fileIndex)
   ensureSeq(gSourceMaps[info.fileIndex].lines)
   ensureIdx(gSourceMaps[info.fileIndex].lines, info.line)
@@ -302,7 +302,7 @@ proc defFromLine(entries: var seq[TEntry], col: int32) =
     # that the first expr that ends after the cursor column is
     # the one we are looking for.
     if e.pos >= col:
-      SuggestWriteln(SymToStr(e.sym, isLocal=false, sectionDef))
+      suggestWriteln(symToStr(e.sym, isLocal=false, sectionDef))
       return
 
 proc defFromSourceMap*(i: TLineInfo) =
@@ -324,9 +324,10 @@ proc suggestSym*(n: PNode, s: PSym) {.inline.} =
 proc markUsed(n: PNode, s: PSym) =
   incl(s.flags, sfUsed)
   if {sfDeprecated, sfError} * s.flags != {}:
-    if sfDeprecated in s.flags: Message(n.info, warnDeprecated, s.name.s)
-    if sfError in s.flags: LocalError(n.info, errWrongSymbolX, s.name.s)
+    if sfDeprecated in s.flags: message(n.info, warnDeprecated, s.name.s)
+    if sfError in s.flags: localError(n.info, errWrongSymbolX, s.name.s)
   suggestSym(n, s)
+  if gCmd == cmdPretty: checkUse(n, s)
 
 proc useSym*(sym: PSym): PNode =
   result = newSymNode(sym)
@@ -337,8 +338,8 @@ proc suggestExpr*(c: PContext, node: PNode) =
   if cp == cpNone: return
   var outputs = 0
   # This keeps semExpr() from coming here recursively:
-  if c.InCompilesContext > 0: return
-  inc(c.InCompilesContext)
+  if c.inCompilesContext > 0: return
+  inc(c.inCompilesContext)
   
   if optSuggest in gGlobalOptions:
     var n = findClosestDot(node)
@@ -368,8 +369,8 @@ proc suggestExpr*(c: PContext, node: PNode) =
         addSon(a, x)
       suggestCall(c, a, n, outputs)
   
-  dec(c.InCompilesContext)
-  if outputs > 0 and optUsages notin gGlobalOptions: SuggestQuit()
+  dec(c.inCompilesContext)
+  if outputs > 0 and optUsages notin gGlobalOptions: suggestQuit()
 
 proc suggestStmt*(c: PContext, n: PNode) = 
   suggestExpr(c, n)
diff --git a/compiler/syntaxes.nim b/compiler/syntaxes.nim
index 3965cb3fe..7c44ec0b4 100644
--- a/compiler/syntaxes.nim
+++ b/compiler/syntaxes.nim
@@ -40,17 +40,17 @@ proc parseTopLevelStmt*(p: var TParsers): PNode
 
 # implementation
 
-proc ParseFile(fileIdx: int32): PNode =
+proc parseFile(fileIdx: int32): PNode =
   var 
     p: TParsers
-    f: tfile
+    f: TFile
   let filename = fileIdx.toFullPath
   if not open(f, filename):
     rawMessage(errCannotOpenFile, filename)
     return 
-  OpenParsers(p, fileIdx, LLStreamOpen(f))
-  result = ParseAll(p)
-  CloseParsers(p)
+  openParsers(p, fileIdx, llStreamOpen(f))
+  result = parseAll(p)
+  closeParsers(p)
 
 proc parseAll(p: var TParsers): PNode = 
   case p.skin
@@ -59,7 +59,7 @@ proc parseAll(p: var TParsers): PNode =
   of skinBraces: 
     result = pbraces.parseAll(p.parser)
   of skinEndX: 
-    InternalError("parser to implement") 
+    internalError("parser to implement") 
     result = ast.emptyNode
     # skinEndX: result := pendx.parseAll(p.parser);
   
@@ -70,11 +70,11 @@ proc parseTopLevelStmt(p: var TParsers): PNode =
   of skinBraces: 
     result = pbraces.parseTopLevelStmt(p.parser)
   of skinEndX: 
-    InternalError("parser to implement") 
+    internalError("parser to implement") 
     result = ast.emptyNode
     #skinEndX: result := pendx.parseTopLevelStmt(p.parser);
   
-proc UTF8_BOM(s: string): int = 
+proc utf8Bom(s: string): int = 
   if (s[0] == '\xEF') and (s[1] == '\xBB') and (s[2] == '\xBF'): 
     result = 3
   else: 
@@ -83,37 +83,37 @@ proc UTF8_BOM(s: string): int =
 proc containsShebang(s: string, i: int): bool = 
   if (s[i] == '#') and (s[i + 1] == '!'): 
     var j = i + 2
-    while s[j] in WhiteSpace: inc(j)
+    while s[j] in Whitespace: inc(j)
     result = s[j] == '/'
 
 proc parsePipe(filename: string, inputStream: PLLStream): PNode = 
   result = ast.emptyNode
-  var s = LLStreamOpen(filename, fmRead)
+  var s = llStreamOpen(filename, fmRead)
   if s != nil: 
     var line = newStringOfCap(80)
-    discard LLStreamReadLine(s, line)
-    var i = UTF8_Bom(line)
+    discard llStreamReadLine(s, line)
+    var i = utf8Bom(line)
     if containsShebang(line, i):
-      discard LLStreamReadLine(s, line)
+      discard llStreamReadLine(s, line)
       i = 0
     if line[i] == '#' and line[i+1] == '!':
       inc(i, 2)
-      while line[i] in WhiteSpace: inc(i)
+      while line[i] in Whitespace: inc(i)
       var q: TParser
-      OpenParser(q, filename, LLStreamOpen(substr(line, i)))
+      openParser(q, filename, llStreamOpen(substr(line, i)))
       result = parser.parseAll(q)
-      CloseParser(q)
-    LLStreamClose(s)
+      closeParser(q)
+    llStreamClose(s)
 
 proc getFilter(ident: PIdent): TFilterKind = 
   for i in countup(low(TFilterKind), high(TFilterKind)): 
-    if IdentEq(ident, filterNames[i]): 
+    if identEq(ident, filterNames[i]): 
       return i
   result = filtNone
 
 proc getParser(ident: PIdent): TParserKind = 
   for i in countup(low(TParserKind), high(TParserKind)): 
-    if IdentEq(ident, parserNames[i]): 
+    if identEq(ident, parserNames[i]): 
       return i
   rawMessage(errInvalidDirectiveX, ident.s)
 
@@ -142,32 +142,32 @@ proc applyFilter(p: var TParsers, n: PNode, filename: string,
   if f != filtNone: 
     if gVerbosity >= 2: 
       rawMessage(hintCodeBegin, [])
-      MsgWriteln(result.s)
+      msgWriteln(result.s)
       rawMessage(hintCodeEnd, [])
 
 proc evalPipe(p: var TParsers, n: PNode, filename: string, 
               start: PLLStream): PLLStream = 
   result = start
   if n.kind == nkEmpty: return 
-  if (n.kind == nkInfix) and (n.sons[0].kind == nkIdent) and
-      IdentEq(n.sons[0].ident, "|"): 
-    for i in countup(1, 2): 
-      if n.sons[i].kind == nkInfix: 
+  if n.kind == nkInfix and n.sons[0].kind == nkIdent and
+      identEq(n.sons[0].ident, "|"):
+    for i in countup(1, 2):
+      if n.sons[i].kind == nkInfix:
         result = evalPipe(p, n.sons[i], filename, result)
-      else: 
+      else:
         result = applyFilter(p, n.sons[i], filename, result)
-  elif n.kind == nkStmtList: 
+  elif n.kind == nkStmtList:
     result = evalPipe(p, n.sons[0], filename, result)
-  else: 
+  else:
     result = applyFilter(p, n, filename, result)
   
 proc openParsers(p: var TParsers, fileIdx: int32, inputstream: PLLStream) = 
   var s: PLLStream
   p.skin = skinStandard
   let filename = fileIdx.toFullPath
-  var pipe = parsePipe(filename, inputStream)
-  if pipe != nil: s = evalPipe(p, pipe, filename, inputStream)
-  else: s = inputStream
+  var pipe = parsePipe(filename, inputstream)
+  if pipe != nil: s = evalPipe(p, pipe, filename, inputstream)
+  else: s = inputstream
   case p.skin
   of skinStandard, skinBraces, skinEndX:
     parser.openParser(p.parser, fileIdx, s)
diff --git a/compiler/transf.nim b/compiler/transf.nim
index 206c21c3d..deb821eff 100644
--- a/compiler/transf.nim
+++ b/compiler/transf.nim
@@ -88,7 +88,7 @@ proc pushTransCon(c: PTransf, t: PTransCon) =
   c.transCon = t
 
 proc popTransCon(c: PTransf) = 
-  if (c.transCon == nil): InternalError("popTransCon")
+  if (c.transCon == nil): internalError("popTransCon")
   c.transCon = c.transCon.next
 
 proc getCurrOwner(c: PTransf): PSym = 
@@ -113,8 +113,8 @@ proc newAsgnStmt(c: PTransf, le: PNode, ri: PTransNode): PTransNode =
   result[1] = ri
 
 proc transformSymAux(c: PTransf, n: PNode): PNode =
-  if n.sym.kind == skIterator and n.sym.typ.callConv == ccClosure:
-    return liftIterSym(n)
+  #if n.sym.kind == skIterator and n.sym.typ.callConv == ccClosure:
+  #  return liftIterSym(n)
   var b: PNode
   var tc = c.transCon
   if sfBorrow in n.sym.flags: 
@@ -126,7 +126,7 @@ proc transformSymAux(c: PTransf, n: PNode): PNode =
   else: 
     b = n
   while tc != nil: 
-    result = IdNodeTableGet(tc.mapping, b.sym)
+    result = idNodeTableGet(tc.mapping, b.sym)
     if result != nil: return
     tc = tc.next
   result = b
@@ -141,32 +141,32 @@ proc transformVarSection(c: PTransf, v: PNode): PTransNode =
     if it.kind == nkCommentStmt: 
       result[i] = PTransNode(it)
     elif it.kind == nkIdentDefs: 
-      if it.sons[0].kind != nkSym: InternalError(it.info, "transformVarSection")
-      InternalAssert(it.len == 3)
+      if it.sons[0].kind != nkSym: internalError(it.info, "transformVarSection")
+      internalAssert(it.len == 3)
       var newVar = copySym(it.sons[0].sym)
       incl(newVar.flags, sfFromGeneric)
       # fixes a strange bug for rodgen:
       #include(it.sons[0].sym.flags, sfFromGeneric);
       newVar.owner = getCurrOwner(c)
-      IdNodeTablePut(c.transCon.mapping, it.sons[0].sym, newSymNode(newVar))
+      idNodeTablePut(c.transCon.mapping, it.sons[0].sym, newSymNode(newVar))
       var defs = newTransNode(nkIdentDefs, it.info, 3)
       if importantComments():
         # keep documentation information:
-        pnode(defs).comment = it.comment
+        PNode(defs).comment = it.comment
       defs[0] = newSymNode(newVar).PTransNode
       defs[1] = it.sons[1].PTransNode
       defs[2] = transform(c, it.sons[2])
       result[i] = defs
     else: 
       if it.kind != nkVarTuple: 
-        InternalError(it.info, "transformVarSection: not nkVarTuple")
+        internalError(it.info, "transformVarSection: not nkVarTuple")
       var L = sonsLen(it)
       var defs = newTransNode(it.kind, it.info, L)
       for j in countup(0, L-3): 
         var newVar = copySym(it.sons[j].sym)
         incl(newVar.flags, sfFromGeneric)
         newVar.owner = getCurrOwner(c)
-        IdNodeTablePut(c.transCon.mapping, it.sons[j].sym, newSymNode(newVar))
+        idNodeTablePut(c.transCon.mapping, it.sons[j].sym, newSymNode(newVar))
         defs[j] = newSymNode(newVar).PTransNode
       assert(it.sons[L-2].kind == nkEmpty)
       defs[L-1] = transform(c, it.sons[L-1])
@@ -179,21 +179,21 @@ proc transformConstSection(c: PTransf, v: PNode): PTransNode =
     if it.kind == nkCommentStmt:
       result[i] = PTransNode(it)
     else:
-      if it.kind != nkConstDef: InternalError(it.info, "transformConstSection")
+      if it.kind != nkConstDef: internalError(it.info, "transformConstSection")
       if it.sons[0].kind != nkSym:
-        InternalError(it.info, "transformConstSection")
+        internalError(it.info, "transformConstSection")
       if sfFakeConst in it[0].sym.flags:
         var b = newNodeI(nkConstDef, it.info)
         addSon(b, it[0])
         addSon(b, ast.emptyNode)            # no type description
-        addSon(b, transform(c, it[2]).pnode)
+        addSon(b, transform(c, it[2]).PNode)
         result[i] = PTransNode(b)
       else:
         result[i] = PTransNode(it)
 
 proc hasContinue(n: PNode): bool = 
   case n.kind
-  of nkEmpty..nkNilLit, nkForStmt, nkParForStmt, nkWhileStmt: nil
+  of nkEmpty..nkNilLit, nkForStmt, nkParForStmt, nkWhileStmt: discard
   of nkContinueStmt: result = true
   else: 
     for i in countup(0, sonsLen(n) - 1): 
@@ -217,7 +217,7 @@ proc transformBlock(c: PTransf, n: PNode): PTransNode =
 
 proc transformBreak(c: PTransf, n: PNode): PTransNode =
   if c.inLoop > 0 or n.sons[0].kind != nkEmpty:
-    result = n.ptransNode
+    result = n.PTransNode
   else:
     let labl = c.breakSyms[c.breakSyms.high]
     result = transformSons(c, n)
@@ -292,11 +292,11 @@ proc transformYield(c: PTransf, n: PNode): PTransNode =
     add(result, c.transCon.forLoopBody)
   else: 
     # we need to introduce new local variables:
-    add(result, introduceNewLocalVars(c, c.transCon.forLoopBody.pnode))
+    add(result, introduceNewLocalVars(c, c.transCon.forLoopBody.PNode))
 
 proc transformAddrDeref(c: PTransf, n: PNode, a, b: TNodeKind): PTransNode =
   result = transformSons(c, n)
-  var n = result.pnode
+  var n = result.PNode
   case n.sons[0].kind
   of nkObjUpConv, nkObjDownConv, nkChckRange, nkChckRangeF, nkChckRange64:
     var m = n.sons[0].sons[0]
@@ -389,7 +389,7 @@ proc transformConv(c: PTransf, n: PNode): PTransNode =
       result[0] = transform(c, n.sons[1])
     else: 
       result = transform(c, n.sons[1])
-  of tyGenericParam, tyOrdinal, tyTypeClass:
+  of tyGenericParam, tyOrdinal:
     result = transform(c, n.sons[1])
     # happens sometimes for generated assignments, etc.
   else: 
@@ -429,15 +429,15 @@ proc findWrongOwners(c: PTransf, n: PNode) =
 proc transformFor(c: PTransf, n: PNode): PTransNode = 
   # generate access statements for the parameters (unless they are constant)
   # put mapping from formal parameters to actual parameters
-  if n.kind != nkForStmt: InternalError(n.info, "transformFor")
+  if n.kind != nkForStmt: internalError(n.info, "transformFor")
 
   var length = sonsLen(n)
   var call = n.sons[length - 2]
   if call.kind notin nkCallKinds or call.sons[0].kind != nkSym or 
       call.sons[0].typ.callConv == ccClosure or
       call.sons[0].sym.kind != skIterator:
-    n.sons[length-1] = transformLoopBody(c, n.sons[length-1]).pnode
-    return lambdalifting.liftForLoop(n).ptransNode
+    n.sons[length-1] = transformLoopBody(c, n.sons[length-1]).PNode
+    return lambdalifting.liftForLoop(n).PTransNode
     #InternalError(call.info, "transformFor")
 
   #echo "transforming: ", renderTree(n)
@@ -446,7 +446,7 @@ proc transformFor(c: PTransf, n: PNode): PTransNode =
   var v = newNodeI(nkVarSection, n.info)
   for i in countup(0, length - 3): 
     addVar(v, copyTree(n.sons[i])) # declare new vars
-  add(result, v.ptransNode)
+  add(result, v.PTransNode)
   
   # Bugfix: inlined locals belong to the invoking routine, not to the invoked
   # iterator!
@@ -454,24 +454,24 @@ proc transformFor(c: PTransf, n: PNode): PTransNode =
   var newC = newTransCon(getCurrOwner(c))
   newC.forStmt = n
   newC.forLoopBody = loopBody
-  if iter.kind != skIterator: InternalError(call.info, "transformFor") 
+  if iter.kind != skIterator: internalError(call.info, "transformFor") 
   # generate access statements for the parameters (unless they are constant)
   pushTransCon(c, newC)
   for i in countup(1, sonsLen(call) - 1): 
-    var arg = transform(c, call.sons[i]).pnode
+    var arg = transform(c, call.sons[i]).PNode
     var formal = skipTypes(iter.typ, abstractInst).n.sons[i].sym 
     case putArgInto(arg, formal.typ)
     of paDirectMapping: 
-      IdNodeTablePut(newC.mapping, formal, arg)
+      idNodeTablePut(newC.mapping, formal, arg)
     of paFastAsgn: 
       # generate a temporary and produce an assignment statement:
       var temp = newTemp(c, formal.typ, formal.info)
       addVar(v, newSymNode(temp))
-      add(result, newAsgnStmt(c, newSymNode(temp), arg.ptransNode))
-      IdNodeTablePut(newC.mapping, formal, newSymNode(temp))
+      add(result, newAsgnStmt(c, newSymNode(temp), arg.PTransNode))
+      idNodeTablePut(newC.mapping, formal, newSymNode(temp))
     of paVarAsgn:
       assert(skipTypes(formal.typ, abstractInst).kind == tyVar)
-      IdNodeTablePut(newC.mapping, formal, arg)
+      idNodeTablePut(newC.mapping, formal, arg)
       # XXX BUG still not correct if the arg has a side effect!
   var body = iter.getBody
   pushInfoContext(n.info)
@@ -500,20 +500,20 @@ proc transformCase(c: PTransf, n: PNode): PTransNode =
     var e = transform(c, it)
     case it.kind
     of nkElifBranch:
-      if ifs.pnode == nil:
+      if ifs.PNode == nil:
         ifs = newTransNode(nkIfStmt, it.info, 0)
       ifs.add(e)
     of nkElse:
-      if ifs.pnode == nil: result.add(e)
+      if ifs.PNode == nil: result.add(e)
       else: ifs.add(e)
     else:
       result.add(e)
-  if ifs.pnode != nil:
+  if ifs.PNode != nil:
     var elseBranch = newTransNode(nkElse, n.info, 1)
     elseBranch[0] = ifs
     result.add(elseBranch)
-  elif result.Pnode.lastSon.kind != nkElse and not (
-      skipTypes(n.sons[0].Typ, abstractVarRange).Kind in
+  elif result.PNode.lastSon.kind != nkElse and not (
+      skipTypes(n.sons[0].typ, abstractVarRange).kind in
         {tyInt..tyInt64, tyChar, tyEnum, tyUInt..tyUInt32}):
     # fix a stupid code gen bug by normalizing:
     var elseBranch = newTransNode(nkElse, n.info, 1)
@@ -523,7 +523,7 @@ proc transformCase(c: PTransf, n: PNode): PTransNode =
 proc transformArrayAccess(c: PTransf, n: PNode): PTransNode = 
   # XXX this is really bad; transf should use a proper AST visitor
   if n.sons[0].kind == nkSym and n.sons[0].sym.kind == skType:
-    result = n.ptransnode
+    result = n.PTransNode
   else:
     result = newTransNode(n)
     for i in 0 .. < n.len:
@@ -533,10 +533,10 @@ proc getMergeOp(n: PNode): PSym =
   case n.kind
   of nkCall, nkHiddenCallConv, nkCommand, nkInfix, nkPrefix, nkPostfix, 
      nkCallStrLit: 
-    if (n.sons[0].Kind == nkSym) and (n.sons[0].sym.kind == skProc) and
+    if (n.sons[0].kind == nkSym) and (n.sons[0].sym.kind == skProc) and
         (sfMerge in n.sons[0].sym.flags): 
       result = n.sons[0].sym
-  else: nil
+  else: discard
 
 proc flattenTreeAux(d, a: PNode, op: PSym) = 
   var op2 = getMergeOp(a)
@@ -563,24 +563,24 @@ proc transformCall(c: PTransf, n: PNode): PTransNode =
     add(result, transform(c, n.sons[0]))
     var j = 1
     while j < sonsLen(n): 
-      var a = transform(c, n.sons[j]).pnode
+      var a = transform(c, n.sons[j]).PNode
       inc(j)
       if isConstExpr(a): 
         while (j < sonsLen(n)):
-          let b = transform(c, n.sons[j]).pnode
+          let b = transform(c, n.sons[j]).PNode
           if not isConstExpr(b): break
           a = evalOp(op.magic, n, a, b, nil)
           inc(j)
-      add(result, a.ptransnode)
+      add(result, a.PTransNode)
     if len(result) == 2: result = result[1]
   else:
-    let s = transformSons(c, n).pnode
+    let s = transformSons(c, n).PNode
     # bugfix: check after 'transformSons' if it's still a method call:
     # use the dispatcher for the call:
     if s.sons[0].kind == nkSym and s.sons[0].sym.kind == skMethod:
-      result = methodCall(s).ptransNode
+      result = methodCall(s).PTransNode
     else:
-      result = s.ptransNode
+      result = s.PTransNode
 
 proc dontInlineConstant(orig, cnst: PNode): bool {.inline.} =
   # symbols that expand to a complex constant (array, etc.) should not be
@@ -636,6 +636,8 @@ proc transform(c: PTransf, n: PNode): PTransNode =
           s.ast.sons[bodyPos] = n.sons[bodyPos]
         #n.sons[bodyPos] = liftLambdas(s, n)
         #if n.kind == nkMethodDef: methodDef(s, false)
+    #if n.kind == nkIteratorDef and n.typ != nil:
+    #  return liftIterSym(n.sons[namePos]).PTransNode
     result = PTransNode(n)
   of nkMacroDef:
     # XXX no proper closure support yet:
@@ -683,7 +685,7 @@ proc transform(c: PTransf, n: PNode): PTransNode =
         # completely:
         result = PTransNode(newNode(nkCommentStmt))
   of nkCommentStmt, nkTemplateDef: 
-    return n.ptransNode
+    return n.PTransNode
   of nkConstSection:
     # do not replace ``const c = 3`` with ``const 3 = 3``
     return transformConstSection(c, n)
@@ -707,7 +709,8 @@ proc transform(c: PTransf, n: PNode): PTransNode =
     result = transformSons(c, n)
     # XXX comment handling really sucks:
     if importantComments():
-      pnode(result).comment = n.comment
+      PNode(result).comment = n.comment
+  of nkClosure: return PTransNode(n)
   else:
     result = transformSons(c, n)
   var cnst = getConstExpr(c.module, PNode(result))
@@ -719,7 +722,7 @@ proc processTransf(c: PTransf, n: PNode, owner: PSym): PNode =
   # Note: For interactive mode we cannot call 'passes.skipCodegen' and skip
   # this step! We have to rely that the semantic pass transforms too errornous
   # nodes into an empty node.
-  if passes.skipCodegen(n) or c.fromCache or nfTransf in n.flags: return n
+  if c.fromCache or nfTransf in n.flags: return n
   pushTransCon(c, newTransCon(owner))
   result = PNode(transform(c, n))
   popTransCon(c)
@@ -735,14 +738,11 @@ proc transformBody*(module: PSym, n: PNode, prc: PSym): PNode =
   if nfTransf in n.flags or prc.kind in {skTemplate}:
     result = n
   else:
-    #when useEffectSystem: trackProc(prc, n)
     var c = openTransf(module, "")
     result = processTransf(c, n, prc)
-    if prc.kind != skMacro:
-      # XXX no closures yet for macros:
-      result = liftLambdas(prc, result)
-    if prc.kind == skIterator and prc.typ.callConv == ccClosure:
-      result = lambdalifting.liftIterator(prc, result)
+    result = liftLambdas(prc, result)
+    #if prc.kind == skIterator and prc.typ.callConv == ccClosure:
+    #  result = lambdalifting.liftIterator(prc, result)
     incl(result.flags, nfTransf)
     when useEffectSystem: trackProc(prc, result)
 
diff --git a/compiler/trees.nim b/compiler/trees.nim
index ab5c97a19..35e9334cc 100644
--- a/compiler/trees.nim
+++ b/compiler/trees.nim
@@ -36,7 +36,7 @@ proc cyclicTree*(n: PNode): bool =
   var s = newNodeI(nkEmpty, n.info)
   result = cyclicTreeAux(n, s)
 
-proc ExprStructuralEquivalent*(a, b: PNode): bool = 
+proc exprStructuralEquivalent*(a, b: PNode): bool = 
   result = false
   if a == b: 
     result = true
@@ -53,17 +53,17 @@ proc ExprStructuralEquivalent*(a, b: PNode): bool =
     else: 
       if sonsLen(a) == sonsLen(b): 
         for i in countup(0, sonsLen(a) - 1): 
-          if not ExprStructuralEquivalent(a.sons[i], b.sons[i]): return 
+          if not exprStructuralEquivalent(a.sons[i], b.sons[i]): return 
         result = true
   
-proc sameTree*(a, b: PNode): bool = 
+proc sameTree*(a, b: PNode): bool =
   result = false
-  if a == b: 
+  if a == b:
     result = true
-  elif (a != nil) and (b != nil) and (a.kind == b.kind): 
-    if a.flags != b.flags: return 
-    if a.info.line != b.info.line: return 
-    if a.info.col != b.info.col: 
+  elif a != nil and b != nil and a.kind == b.kind:
+    if a.flags != b.flags: return
+    if a.info.line != b.info.line: return
+    if a.info.col != b.info.col:
       return                  #if a.info.fileIndex <> b.info.fileIndex then exit;
     case a.kind
     of nkSym: 
@@ -74,7 +74,7 @@ proc sameTree*(a, b: PNode): bool =
     of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal
     of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal
     of nkEmpty, nkNilLit, nkType: result = true
-    else: 
+    else:
       if sonsLen(a) == sonsLen(b): 
         for i in countup(0, sonsLen(a) - 1): 
           if not sameTree(a.sons[i], b.sons[i]): return 
@@ -84,22 +84,22 @@ proc getProcSym*(call: PNode): PSym =
   result = call.sons[0].sym
 
 proc getOpSym*(op: PNode): PSym = 
-  if not (op.kind in {nkCall, nkHiddenCallConv, nkCommand, nkCallStrLit}): 
+  if op.kind notin {nkCall, nkHiddenCallConv, nkCommand, nkCallStrLit}:
     result = nil
-  else: 
-    if (sonsLen(op) <= 0): InternalError(op.info, "getOpSym")
-    elif op.sons[0].Kind == nkSym: result = op.sons[0].sym
+  else:
+    if sonsLen(op) <= 0: internalError(op.info, "getOpSym")
+    elif op.sons[0].kind == nkSym: result = op.sons[0].sym
     else: result = nil
-  
+
 proc getMagic*(op: PNode): TMagic = 
   case op.kind
   of nkCallKinds:
-    case op.sons[0].Kind
+    case op.sons[0].kind
     of nkSym: result = op.sons[0].sym.magic
     else: result = mNone
   else: result = mNone
   
-proc TreeToSym*(t: PNode): PSym = 
+proc treeToSym*(t: PNode): PSym = 
   result = t.sym
 
 proc isConstExpr*(n: PNode): bool = 
@@ -118,7 +118,7 @@ proc isDeepConstExpr*(n: PNode): bool =
     for i in 0 .. <n.len:
       if not isDeepConstExpr(n.sons[i]): return false
     result = true
-  else: nil
+  else: discard
 
 proc flattenTreeAux(d, a: PNode, op: TMagic) = 
   if (getMagic(a) == op):     # a is a "leaf", so add it:
@@ -129,17 +129,17 @@ proc flattenTreeAux(d, a: PNode, op: TMagic) =
   
 proc flattenTree*(root: PNode, op: TMagic): PNode = 
   result = copyNode(root)
-  if (getMagic(root) == op): 
+  if getMagic(root) == op:
     # BUGFIX: forget to copy prc
     addSon(result, copyNode(root.sons[0]))
     flattenTreeAux(result, root, op)
 
-proc SwapOperands*(op: PNode) = 
+proc swapOperands*(op: PNode) = 
   var tmp = op.sons[1]
   op.sons[1] = op.sons[2]
   op.sons[2] = tmp
 
-proc IsRange*(n: PNode): bool {.inline.} = 
+proc isRange*(n: PNode): bool {.inline.} = 
   if n.kind == nkInfix:
     if n[0].kind == nkIdent and n[0].ident.id == ord(wDotDot) or
         n[0].kind in {nkClosedSymChoice, nkOpenSymChoice} and 
diff --git a/compiler/treetab.nim b/compiler/treetab.nim
index 75e3fd20a..ecb8fb083 100644
--- a/compiler/treetab.nim
+++ b/compiler/treetab.nim
@@ -17,7 +17,7 @@ proc hashTree(n: PNode): THash =
   result = ord(n.kind)
   case n.kind
   of nkEmpty, nkNilLit, nkType: 
-    nil
+    discard
   of nkIdent: 
     result = result !& n.ident.h
   of nkSym:
@@ -34,7 +34,7 @@ proc hashTree(n: PNode): THash =
     for i in countup(0, sonsLen(n) - 1): 
       result = result !& hashTree(n.sons[i])
   
-proc TreesEquivalent(a, b: PNode): bool = 
+proc treesEquivalent(a, b: PNode): bool = 
   if a == b: 
     result = true
   elif (a != nil) and (b != nil) and (a.kind == b.kind): 
@@ -48,24 +48,24 @@ proc TreesEquivalent(a, b: PNode): bool =
     else: 
       if sonsLen(a) == sonsLen(b): 
         for i in countup(0, sonsLen(a) - 1): 
-          if not TreesEquivalent(a.sons[i], b.sons[i]): return 
+          if not treesEquivalent(a.sons[i], b.sons[i]): return 
         result = true
     if result: result = sameTypeOrNil(a.typ, b.typ)
   
-proc NodeTableRawGet(t: TNodeTable, k: THash, key: PNode): int = 
+proc nodeTableRawGet(t: TNodeTable, k: THash, key: PNode): int = 
   var h: THash = k and high(t.data)
   while t.data[h].key != nil: 
-    if (t.data[h].h == k) and TreesEquivalent(t.data[h].key, key): 
+    if (t.data[h].h == k) and treesEquivalent(t.data[h].key, key): 
       return h
     h = nextTry(h, high(t.data))
   result = -1
 
-proc NodeTableGet*(t: TNodeTable, key: PNode): int = 
-  var index = NodeTableRawGet(t, hashTree(key), key)
+proc nodeTableGet*(t: TNodeTable, key: PNode): int = 
+  var index = nodeTableRawGet(t, hashTree(key), key)
   if index >= 0: result = t.data[index].val
   else: result = low(int)
   
-proc NodeTableRawInsert(data: var TNodePairSeq, k: THash, key: PNode, 
+proc nodeTableRawInsert(data: var TNodePairSeq, k: THash, key: PNode, 
                         val: int) = 
   var h: THash = k and high(data)
   while data[h].key != nil: h = nextTry(h, high(data))
@@ -74,37 +74,37 @@ proc NodeTableRawInsert(data: var TNodePairSeq, k: THash, key: PNode,
   data[h].key = key
   data[h].val = val
 
-proc NodeTablePut*(t: var TNodeTable, key: PNode, val: int) = 
+proc nodeTablePut*(t: var TNodeTable, key: PNode, val: int) = 
   var n: TNodePairSeq
   var k: THash = hashTree(key)
-  var index = NodeTableRawGet(t, k, key)
+  var index = nodeTableRawGet(t, k, key)
   if index >= 0: 
     assert(t.data[index].key != nil)
     t.data[index].val = val
   else: 
     if mustRehash(len(t.data), t.counter): 
-      newSeq(n, len(t.data) * growthFactor)
+      newSeq(n, len(t.data) * GrowthFactor)
       for i in countup(0, high(t.data)): 
         if t.data[i].key != nil: 
-          NodeTableRawInsert(n, t.data[i].h, t.data[i].key, t.data[i].val)
+          nodeTableRawInsert(n, t.data[i].h, t.data[i].key, t.data[i].val)
       swap(t.data, n)
-    NodeTableRawInsert(t.data, k, key, val)
+    nodeTableRawInsert(t.data, k, key, val)
     inc(t.counter)
 
-proc NodeTableTestOrSet*(t: var TNodeTable, key: PNode, val: int): int = 
+proc nodeTableTestOrSet*(t: var TNodeTable, key: PNode, val: int): int = 
   var n: TNodePairSeq
   var k: THash = hashTree(key)
-  var index = NodeTableRawGet(t, k, key)
+  var index = nodeTableRawGet(t, k, key)
   if index >= 0: 
     assert(t.data[index].key != nil)
     result = t.data[index].val
   else: 
     if mustRehash(len(t.data), t.counter): 
-      newSeq(n, len(t.data) * growthFactor)
+      newSeq(n, len(t.data) * GrowthFactor)
       for i in countup(0, high(t.data)): 
         if t.data[i].key != nil: 
-          NodeTableRawInsert(n, t.data[i].h, t.data[i].key, t.data[i].val)
+          nodeTableRawInsert(n, t.data[i].h, t.data[i].key, t.data[i].val)
       swap(t.data, n)
-    NodeTableRawInsert(t.data, k, key, val)
+    nodeTableRawInsert(t.data, k, key, val)
     result = val
     inc(t.counter)
diff --git a/compiler/types.nim b/compiler/types.nim
index 7e07a0667..4a53a84c9 100644
--- a/compiler/types.nim
+++ b/compiler/types.nim
@@ -10,16 +10,16 @@
 # this module contains routines for accessing and iterating over types
 
 import 
-  intsets, ast, astalgo, trees, msgs, strutils, platform
+  intsets, ast, astalgo, trees, msgs, strutils, platform, renderer
 
-proc firstOrd*(t: PType): biggestInt
-proc lastOrd*(t: PType): biggestInt
-proc lengthOrd*(t: PType): biggestInt
+proc firstOrd*(t: PType): BiggestInt
+proc lastOrd*(t: PType): BiggestInt
+proc lengthOrd*(t: PType): BiggestInt
 type 
   TPreferedDesc* = enum 
     preferName, preferDesc, preferExported
 
-proc TypeToString*(typ: PType, prefer: TPreferedDesc = preferName): string
+proc typeToString*(typ: PType, prefer: TPreferedDesc = preferName): string
 proc getProcHeader*(sym: PSym): string
 proc base*(t: PType): PType
   # ------------------- type iterator: ----------------------------------------
@@ -28,7 +28,7 @@ type
   TTypeMutator* = proc (t: PType, closure: PObject): PType {.nimcall.} # copy t and mutate it
   TTypePredicate* = proc (t: PType): bool {.nimcall.}
 
-proc IterOverType*(t: PType, iter: TTypeIter, closure: PObject): bool
+proc iterOverType*(t: PType, iter: TTypeIter, closure: PObject): bool
   # Returns result of `iter`.
 proc mutateType*(t: PType, iter: TTypeMutator, closure: PObject): PType
   # Returns result of `iter`.
@@ -64,17 +64,16 @@ const
   typedescPtrs* = abstractPtrs + {tyTypeDesc}
   typedescInst* = abstractInst + {tyTypeDesc}
 
-proc skipTypes*(t: PType, kinds: TTypeKinds): PType
 proc containsObject*(t: PType): bool
 proc containsGarbageCollectedRef*(typ: PType): bool
 proc containsHiddenPointer*(typ: PType): bool
 proc canFormAcycle*(typ: PType): bool
 proc isCompatibleToCString*(a: PType): bool
-proc getOrdValue*(n: PNode): biggestInt
-proc computeSize*(typ: PType): biggestInt
-proc getSize*(typ: PType): biggestInt
+proc getOrdValue*(n: PNode): BiggestInt
+proc computeSize*(typ: PType): BiggestInt
+proc getSize*(typ: PType): BiggestInt
 proc isPureObject*(typ: PType): bool
-proc InvalidGenericInst*(f: PType): bool
+proc invalidGenericInst*(f: PType): bool
   # for debugging
 type 
   TTypeFieldResult* = enum 
@@ -89,21 +88,21 @@ proc analyseObjectWithTypeField*(t: PType): TTypeFieldResult
 proc typeAllowed*(t: PType, kind: TSymKind): bool
 # implementation
 
-proc InvalidGenericInst(f: PType): bool = 
-  result = (f.kind == tyGenericInst) and (lastSon(f) == nil)
+proc invalidGenericInst(f: PType): bool = 
+  result = f.kind == tyGenericInst and lastSon(f) == nil
 
 proc isPureObject(typ: PType): bool = 
   var t = typ
   while t.kind == tyObject and t.sons[0] != nil: t = t.sons[0]
   result = t.sym != nil and sfPure in t.sym.flags
 
-proc getOrdValue(n: PNode): biggestInt = 
+proc getOrdValue(n: PNode): BiggestInt = 
   case n.kind
   of nkCharLit..nkInt64Lit: result = n.intVal
   of nkNilLit: result = 0
   of nkHiddenStdConv: result = getOrdValue(n.sons[1])
   else:
-    LocalError(n.info, errOrdinalTypeExpected)
+    localError(n.info, errOrdinalTypeExpected)
     result = 0
 
 proc isIntLit*(t: PType): bool {.inline.} =
@@ -132,7 +131,7 @@ proc getProcHeader(sym: PSym): string =
       add(result, typeToString(p.sym.typ))
       if i != sonsLen(n)-1: add(result, ", ")
     else:
-      InternalError("getProcHeader")
+      internalError("getProcHeader")
   add(result, ')')
   if n.sons[0].typ != nil: result.add(": " & typeToString(n.sons[0].typ))
   
@@ -148,21 +147,17 @@ proc skipGeneric(t: PType): PType =
   result = t
   while result.kind == tyGenericInst: result = lastSon(result)
       
-proc skipTypes(t: PType, kinds: TTypeKinds): PType = 
-  result = t
-  while result.kind in kinds: result = lastSon(result)
-  
 proc isOrdinalType(t: PType): bool =
   assert(t != nil)
   # caution: uint, uint64 are no ordinal types!
-  result = t.Kind in {tyChar,tyInt..tyInt64,tyUInt8..tyUInt32,tyBool,tyEnum} or
-      (t.Kind in {tyRange, tyOrdinal, tyConst, tyMutable, tyGenericInst}) and
+  result = t.kind in {tyChar,tyInt..tyInt64,tyUInt8..tyUInt32,tyBool,tyEnum} or
+      (t.kind in {tyRange, tyOrdinal, tyConst, tyMutable, tyGenericInst}) and
        isOrdinalType(t.sons[0])
 
 proc enumHasHoles(t: PType): bool = 
   var b = t
   while b.kind in {tyConst, tyMutable, tyRange, tyGenericInst}: b = b.sons[0]
-  result = b.Kind == tyEnum and tfEnumHasHoles in b.flags
+  result = b.kind == tyEnum and tfEnumHasHoles in b.flags
 
 proc iterOverTypeAux(marker: var TIntSet, t: PType, iter: TTypeIter, 
                      closure: PObject): bool
@@ -184,7 +179,7 @@ proc iterOverTypeAux(marker: var TIntSet, t: PType, iter: TTypeIter,
   if t == nil: return 
   result = iter(t, closure)
   if result: return 
-  if not ContainsOrIncl(marker, t.id): 
+  if not containsOrIncl(marker, t.id): 
     case t.kind
     of tyGenericInst, tyGenericBody: 
       result = iterOverTypeAux(marker, lastSon(t), iter, closure)
@@ -194,8 +189,8 @@ proc iterOverTypeAux(marker: var TIntSet, t: PType, iter: TTypeIter,
         if result: return 
       if t.n != nil: result = iterOverNode(marker, t.n, iter, closure)
   
-proc IterOverType(t: PType, iter: TTypeIter, closure: PObject): bool = 
-  var marker = InitIntSet()
+proc iterOverType(t: PType, iter: TTypeIter, closure: PObject): bool = 
+  var marker = initIntSet()
   result = iterOverTypeAux(marker, t, iter, closure)
 
 proc searchTypeForAux(t: PType, predicate: TTypePredicate, 
@@ -228,8 +223,8 @@ proc searchTypeForAux(t: PType, predicate: TTypePredicate,
   # iterates over VALUE types!
   result = false
   if t == nil: return 
-  if ContainsOrIncl(marker, t.id): return 
-  result = Predicate(t)
+  if containsOrIncl(marker, t.id): return 
+  result = predicate(t)
   if result: return 
   case t.kind
   of tyObject: 
@@ -242,10 +237,10 @@ proc searchTypeForAux(t: PType, predicate: TTypePredicate,
       result = searchTypeForAux(t.sons[i], predicate, marker)
       if result: return 
   else: 
-    nil
+    discard
 
 proc searchTypeFor(t: PType, predicate: TTypePredicate): bool = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = searchTypeForAux(t, predicate, marker)
 
 proc isObjectPredicate(t: PType): bool = 
@@ -284,10 +279,10 @@ proc analyseObjectWithTypeFieldAux(t: PType,
       if res != frNone: 
         return frEmbedded
   else: 
-    nil
+    discard
 
 proc analyseObjectWithTypeField(t: PType): TTypeFieldResult = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = analyseObjectWithTypeFieldAux(t, marker)
 
 proc isGCRef(t: PType): bool =
@@ -322,7 +317,7 @@ proc canFormAcycleNode(marker: var TIntSet, n: PNode, startId: int): bool =
     if not result: 
       case n.kind
       of nkNone..nkNilLit: 
-        nil
+        discard
       else: 
         for i in countup(0, sonsLen(n) - 1): 
           result = canFormAcycleNode(marker, n.sons[i], startId)
@@ -337,7 +332,7 @@ proc canFormAcycleAux(marker: var TIntSet, typ: PType, startId: int): bool =
   case t.kind
   of tyTuple, tyObject, tyRef, tySequence, tyArray, tyArrayConstr, tyOpenArray,
      tyVarargs:
-    if not ContainsOrIncl(marker, t.id): 
+    if not containsOrIncl(marker, t.id): 
       for i in countup(0, sonsLen(t) - 1): 
         result = canFormAcycleAux(marker, t.sons[i], startId)
         if result: return 
@@ -350,10 +345,10 @@ proc canFormAcycleAux(marker: var TIntSet, typ: PType, startId: int): bool =
     #  # damn inheritance may introduce cycles:
     #  result = true
   of tyProc: result = typ.callConv == ccClosure
-  else: nil
+  else: discard
 
 proc canFormAcycle(typ: PType): bool =
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = canFormAcycleAux(marker, typ, typ.id)
 
 proc mutateTypeAux(marker: var TIntSet, t: PType, iter: TTypeMutator, 
@@ -367,6 +362,7 @@ proc mutateNode(marker: var TIntSet, n: PNode, iter: TTypeMutator,
     case n.kind
     of nkNone..nkNilLit: 
       # a leaf
+      discard
     else: 
       for i in countup(0, sonsLen(n) - 1): 
         addSon(result, mutateNode(marker, n.sons[i], iter, closure))
@@ -376,17 +372,17 @@ proc mutateTypeAux(marker: var TIntSet, t: PType, iter: TTypeMutator,
   result = nil
   if t == nil: return 
   result = iter(t, closure)
-  if not ContainsOrIncl(marker, t.id): 
+  if not containsOrIncl(marker, t.id): 
     for i in countup(0, sonsLen(t) - 1): 
       result.sons[i] = mutateTypeAux(marker, result.sons[i], iter, closure)
     if t.n != nil: result.n = mutateNode(marker, t.n, iter, closure)
   assert(result != nil)
 
 proc mutateType(t: PType, iter: TTypeMutator, closure: PObject): PType =
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = mutateTypeAux(marker, t, iter, closure)
 
-proc ValueToString(a: PNode): string =
+proc valueToString(a: PNode): string =
   case a.kind
   of nkCharLit..nkUInt64Lit: result = $(a.intVal)
   of nkFloatLit..nkFloat128Lit: result = $(a.floatVal)
@@ -395,7 +391,7 @@ proc ValueToString(a: PNode): string =
 
 proc rangeToStr(n: PNode): string =
   assert(n.kind == nkRange)
-  result = ValueToString(n.sons[0]) & ".." & ValueToString(n.sons[1])
+  result = valueToString(n.sons[0]) & ".." & valueToString(n.sons[1])
 
 const 
   typeToStr: array[TTypeKind, string] = ["None", "bool", "Char", "empty",
@@ -408,29 +404,20 @@ const
     "float", "float32", "float64", "float128",
     "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)
+    "!", "varargs[$1]", "iter[$1]", "Error Type",
+    "BuiltInTypeClass", "UserTypeClass",
+    "UserTypeClassInst", "CompositeTypeClass",
+    "and", "or", "not", "any", "static", "TypeFromExpr", "FieldAccessor"]
 
-proc TypeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
+proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
   var t = typ
   result = ""
   if t == nil: return 
   if prefer == preferName and t.sym != nil and sfAnon notin t.sym.flags:
     if t.kind == tyInt and isIntLit(t):
-      return t.sym.Name.s & " literal(" & $t.n.intVal & ")"
-    return t.sym.Name.s
-  case t.Kind
+      return t.sym.name.s & " literal(" & $t.n.intVal & ")"
+    return t.sym.name.s
+  case t.kind
   of tyInt:
     if not isIntLit(t) or prefer == preferExported:
       result = typeToStr[t.kind]
@@ -444,16 +431,45 @@ proc TypeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
     add(result, ']')
   of tyTypeDesc:
     if t.len == 0: result = "typedesc"
-    else: result = "typedesc[" & constraintsToStr(t) & "]"
-  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)
+    else: result = "typedesc[" & typeToString(t.sons[0]) & "]"
+  of tyStatic:
+    internalAssert t.len > 0
+    result = "static[" & typeToString(t.sons[0]) & "]"
+  of tyUserTypeClass:
+    internalAssert t.sym != nil and t.sym.owner != nil
+    return t.sym.owner.name.s
+  of tyBuiltInTypeClass:
+    result = case t.base.kind:
+      of tyVar: "var"
+      of tyRef: "ref"
+      of tyPtr: "ptr"
+      of tySequence: "seq"
+      of tyArray: "array"
+      of tySet: "set"
+      of tyRange: "range"
+      of tyDistinct: "distinct"
+      of tyProc: "proc"
+      of tyObject: "object"
+      of tyTuple: "tuple"
+      else: (internalAssert false; "")
+  of tyUserTypeClassInst:
+    let body = t.base
+    result = body.sym.name.s & "["
+    for i in countup(1, sonsLen(t) - 2):
+      if i > 1: add(result, ", ")
+      add(result, typeToString(t.sons[i]))
+    result.add "]"
+  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 tyFromExpr, tyFieldAccessor:
+    result = renderTree(t.n)
   of tyArray: 
     if t.sons[0].kind == tyRange: 
       result = "array[" & rangeToStr(t.sons[0].n) & ", " &
@@ -500,7 +516,7 @@ proc TypeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
       add(result, typeToString(t.sons[i]))
       if i < sonsLen(t) - 1: add(result, ", ")
     add(result, ')')
-    if t.sons[0] != nil: add(result, ": " & TypeToString(t.sons[0]))
+    if t.sons[0] != nil: add(result, ": " & typeToString(t.sons[0]))
     var prag: string
     if t.callConv != ccDefault: prag = CallingConvToStr[t.callConv]
     else: prag = ""
@@ -525,7 +541,7 @@ proc resultType(t: PType): PType =
 proc base(t: PType): PType = 
   result = t.sons[0]
 
-proc firstOrd(t: PType): biggestInt = 
+proc firstOrd(t: PType): BiggestInt = 
   case t.kind
   of tyBool, tyChar, tySequence, tyOpenArray, tyString, tyVarargs, tyProxy:
     result = 0
@@ -550,13 +566,14 @@ proc firstOrd(t: PType): biggestInt =
     else: 
       assert(t.n.sons[0].kind == nkSym)
       result = t.n.sons[0].sym.position
-  of tyGenericInst, tyDistinct, tyConst, tyMutable, tyTypeDesc:
+  of tyGenericInst, tyDistinct, tyConst, tyMutable,
+     tyTypeDesc, tyFieldAccessor:
     result = firstOrd(lastSon(t))
   else: 
-    InternalError("invalid kind for first(" & $t.kind & ')')
+    internalError("invalid kind for first(" & $t.kind & ')')
     result = 0
 
-proc lastOrd(t: PType): biggestInt = 
+proc lastOrd(t: PType): BiggestInt = 
   case t.kind
   of tyBool: result = 1
   of tyChar: result = 255
@@ -583,14 +600,15 @@ proc lastOrd(t: PType): biggestInt =
   of tyEnum: 
     assert(t.n.sons[sonsLen(t.n) - 1].kind == nkSym)
     result = t.n.sons[sonsLen(t.n) - 1].sym.position
-  of tyGenericInst, tyDistinct, tyConst, tyMutable, tyTypeDesc: 
+  of tyGenericInst, tyDistinct, tyConst, tyMutable,
+     tyTypeDesc, tyFieldAccessor:
     result = lastOrd(lastSon(t))
   of tyProxy: result = 0
   else: 
-    InternalError("invalid kind for last(" & $t.kind & ')')
+    internalError("invalid kind for last(" & $t.kind & ')')
     result = 0
 
-proc lengthOrd(t: PType): biggestInt = 
+proc lengthOrd(t: PType): BiggestInt = 
   case t.kind
   of tyInt64, tyInt32, tyInt: result = lastOrd(t)
   of tyDistinct, tyConst, tyMutable: result = lengthOrd(t.sons[0])
@@ -606,8 +624,11 @@ type
     dcEqOrDistinctOf       ## a equals b or a is distinct of b
 
   TTypeCmpFlag* = enum
-    IgnoreTupleFields,
-    TypeDescExactMatch,
+    IgnoreTupleFields
+    IgnoreCC
+    ExactTypeDescValues
+    ExactGenericParams
+    ExactConstraints
     AllowCommonBase
 
   TTypeCmpFlags* = set[TTypeCmpFlag]
@@ -621,39 +642,41 @@ type
 
 proc initSameTypeClosure: TSameTypeClosure =
   # we do the initialization lazily for performance (avoids memory allocations)
-  nil
+  discard
   
 proc containsOrIncl(c: var TSameTypeClosure, a, b: PType): bool =
-  result = not IsNil(c.s) and c.s.contains((a.id, b.id))
+  result = not isNil(c.s) and c.s.contains((a.id, b.id))
   if not result:
-    if IsNil(c.s): c.s = @[]
+    if isNil(c.s): c.s = @[]
     c.s.add((a.id, b.id))
 
-proc SameTypeAux(x, y: PType, c: var TSameTypeClosure): bool
-proc SameTypeOrNilAux(a, b: PType, c: var TSameTypeClosure): bool =
+proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool
+proc sameTypeOrNilAux(a, b: PType, c: var TSameTypeClosure): bool =
   if a == b:
     result = true
   else:
     if a == nil or b == nil: result = false
-    else: result = SameTypeAux(a, b, c)
+    else: result = sameTypeAux(a, b, c)
 
-proc SameTypeOrNil*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
+proc sameType*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
+  var c = initSameTypeClosure()
+  c.flags = flags
+  result = sameTypeAux(a, b, c)
+
+proc sameTypeOrNil*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
   if a == b:
     result = true
-  else: 
+  else:
     if a == nil or b == nil: result = false
-    else:
-      var c = initSameTypeClosure()
-      c.flags = flags
-      result = SameTypeAux(a, b, c)
+    else: result = sameType(a, b, flags)
 
 proc equalParam(a, b: PSym): TParamsEquality = 
-  if SameTypeOrNil(a.typ, b.typ, {TypeDescExactMatch}) and
-      ExprStructuralEquivalent(a.constraint, b.constraint):
+  if sameTypeOrNil(a.typ, b.typ, {ExactTypeDescValues}) and
+      exprStructuralEquivalent(a.constraint, b.constraint):
     if a.ast == b.ast: 
       result = paramsEqual
     elif a.ast != nil and b.ast != nil: 
-      if ExprStructuralEquivalent(a.ast, b.ast): result = paramsEqual
+      if exprStructuralEquivalent(a.ast, b.ast): result = paramsEqual
       else: result = paramsIncompatible
     elif a.ast != nil: 
       result = paramsEqual
@@ -661,7 +684,15 @@ proc equalParam(a, b: PSym): TParamsEquality =
       result = paramsIncompatible
   else:
     result = paramsNotEqual
-  
+
+proc sameConstraints(a, b: PNode): bool =
+  internalAssert a.len == b.len
+  for i in 1 .. <a.len:
+    if not exprStructuralEquivalent(a[i].sym.constraint,
+                                    b[i].sym.constraint):
+      return false
+  return true
+
 proc equalParams(a, b: PNode): TParamsEquality = 
   result = paramsEqual
   var length = sonsLen(a)
@@ -676,7 +707,7 @@ proc equalParams(a, b: PNode): TParamsEquality =
       of paramsNotEqual: 
         return paramsNotEqual
       of paramsEqual: 
-        nil
+        discard
       of paramsIncompatible: 
         result = paramsIncompatible
       if (m.name.id != n.name.id): 
@@ -684,14 +715,14 @@ 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: 
         result = paramsIncompatible # overloading by different
                                     # result types does not work
   
-proc SameLiteral(x, y: PNode): bool = 
+proc sameLiteral(x, y: PNode): bool = 
   if x.kind == y.kind: 
     case x.kind
     of nkCharLit..nkInt64Lit: result = x.intVal == y.intVal
@@ -699,9 +730,9 @@ proc SameLiteral(x, y: PNode): bool =
     of nkNilLit: result = true
     else: assert(false)
   
-proc SameRanges(a, b: PNode): bool = 
-  result = SameLiteral(a.sons[0], b.sons[0]) and
-           SameLiteral(a.sons[1], b.sons[1])
+proc sameRanges(a, b: PNode): bool = 
+  result = sameLiteral(a.sons[0], b.sons[0]) and
+           sameLiteral(a.sons[1], b.sons[1])
 
 proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool = 
   # two tuples are equivalent iff the names, types and positions are the same;
@@ -716,7 +747,7 @@ proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool =
         x = skipTypes(x, {tyRange})
         y = skipTypes(y, {tyRange})
       
-      result = SameTypeAux(x, y, c)
+      result = sameTypeAux(x, y, c)
       if not result: return 
     if a.n != nil and b.n != nil and IgnoreTupleFields notin c.flags:
       for i in countup(0, sonsLen(a.n) - 1): 
@@ -726,11 +757,11 @@ proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool =
           var y = b.n.sons[i].sym
           result = x.name.id == y.name.id
           if not result: break 
-        else: InternalError(a.n.info, "sameTuple")
+        else: internalError(a.n.info, "sameTuple")
   else:
     result = false
 
-template IfFastObjectTypeCheckFailed(a, b: PType, body: stmt) {.immediate.} =
+template ifFastObjectTypeCheckFailed(a, b: PType, body: stmt) {.immediate.} =
   if tfFromGeneric notin a.flags + b.flags:
     # fast case: id comparison suffices:
     result = a.id == b.id
@@ -745,15 +776,15 @@ template IfFastObjectTypeCheckFailed(a, b: PType, body: stmt) {.immediate.} =
     #   TA[T] = object
     #   TB[T] = object
     # --> TA[int] != TB[int]
-    if tfFromGeneric in a.flags * b.flags and a.sym.Id == b.sym.Id:
+    if tfFromGeneric in a.flags * b.flags and a.sym.id == b.sym.id:
       # ok, we need the expensive structural check
       body
 
 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)
@@ -761,7 +792,7 @@ proc sameDistinctTypes*(a, b: PType): bool {.inline.} =
 proc sameEnumTypes*(a, b: PType): bool {.inline.} =
   result = a.id == b.id
 
-proc SameObjectTree(a, b: PNode, c: var TSameTypeClosure): bool =
+proc sameObjectTree(a, b: PNode, c: var TSameTypeClosure): bool =
   if a == b:
     result = true
   elif (a != nil) and (b != nil) and (a.kind == b.kind):
@@ -778,26 +809,26 @@ proc SameObjectTree(a, b: PNode, c: var TSameTypeClosure): bool =
       else:
         if sonsLen(a) == sonsLen(b): 
           for i in countup(0, sonsLen(a) - 1): 
-            if not SameObjectTree(a.sons[i], b.sons[i], c): return 
+            if not sameObjectTree(a.sons[i], b.sons[i], c): return 
           result = true
 
 proc sameObjectStructures(a, b: PType, c: var TSameTypeClosure): bool =
   # check base types:
   if sonsLen(a) != sonsLen(b): return
   for i in countup(0, sonsLen(a) - 1):
-    if not SameTypeOrNilAux(a.sons[i], b.sons[i], c): return
-  if not SameObjectTree(a.n, b.n, c): return
+    if not sameTypeOrNilAux(a.sons[i], b.sons[i], c): return
+  if not sameObjectTree(a.n, b.n, c): return
   result = true
 
 proc sameChildrenAux(a, b: PType, c: var TSameTypeClosure): bool =
   if sonsLen(a) != sonsLen(b): return false
   result = true
   for i in countup(0, sonsLen(a) - 1):
-    result = SameTypeOrNilAux(a.sons[i], b.sons[i], c)
+    result = sameTypeOrNilAux(a.sons[i], b.sons[i], c)
     if not result: return 
 
-proc SameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
-  template CycleCheck() =
+proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
+  template cycleCheck() =
     # believe it or not, the direct check for ``containsOrIncl(c, a, b)``
     # increases bootstrapping time from 2.4s to 3.3s on my laptop! So we cheat
     # again: Since the recursion check is only to not get caught in an endless
@@ -826,21 +857,21 @@ proc SameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     of dcEqOrDistinctOf:
       while a.kind == tyDistinct: a = a.sons[0]
       if a.kind != b.kind: return false  
-  case a.Kind
+  case a.kind
   of tyEmpty, tyChar, tyBool, tyNil, tyPointer, tyString, tyCString,
-     tyInt..tyBigNum, tyStmt:
+     tyInt..tyBigNum, tyStmt, tyExpr:
     result = sameFlags(a, b)
-  of tyExpr:
-    result = ExprStructuralEquivalent(a.n, b.n) and sameFlags(a, b)
+  of tyStatic, tyFromExpr:
+    result = exprStructuralEquivalent(a.n, b.n) and sameFlags(a, b)
   of tyObject:
-    IfFastObjectTypeCheckFailed(a, b):
-      CycleCheck()
+    ifFastObjectTypeCheckFailed(a, b):
+      cycleCheck()
       result = sameObjectStructures(a, b, c) and sameFlags(a, b)
   of tyDistinct:
-    CycleCheck()
+    cycleCheck()
     if c.cmp == dcEq:      
       if sameFlags(a, b):
-        IfFastObjectTypeCheckFailed(a, b):
+        ifFastObjectTypeCheckFailed(a, b):
           result = sameTypeAux(a.sons[0], b.sons[0], c)     
     else: 
       result = sameTypeAux(a.sons[0], b.sons[0], c) and sameFlags(a, b)
@@ -848,36 +879,38 @@ proc SameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
     # XXX generic enums do not make much sense, but require structural checking
     result = a.id == b.id and sameFlags(a, b)
   of tyTuple:
-    CycleCheck()
+    cycleCheck()
     result = sameTuple(a, b, c) and sameFlags(a, b)
   of tyGenericInst:    
     result = sameTypeAux(lastSon(a), lastSon(b), c)
   of tyTypeDesc:
     if c.cmp == dcEqIgnoreDistinct: result = false
-    elif TypeDescExactMatch in c.flags:
-      CycleCheck()
+    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 = sameChildrenAux(a, b, c) and sameFlags(a, b)
+    if result and ExactGenericParams in c.flags:
+      result = a.sym.position == b.sym.position
+  of tyGenericInvokation, tyGenericBody, tySequence,
      tyOpenArray, tySet, tyRef, tyPtr, tyVar, tyArrayConstr,
      tyArray, tyProc, tyConst, tyMutable, tyVarargs, tyIter,
-     tyOrdinal, tyTypeClasses:
-    CycleCheck()    
+     tyOrdinal, tyTypeClasses, tyFieldAccessor:
+    cycleCheck()
+    if a.kind == tyUserTypeClass and a.n != nil: return a.n == b.n
     result = sameChildrenAux(a, b, c) and sameFlags(a, b)
-    if result and (a.kind == tyProc):
-      result = a.callConv == b.callConv
+    if result and a.kind == tyProc:
+      result = ((IgnoreCC in c.flags) or a.callConv == b.callConv) and
+               ((ExactConstraints notin c.flags) or sameConstraints(a.n, b.n))
   of tyRange:
-    CycleCheck()
-    result = SameTypeOrNilAux(a.sons[0], b.sons[0], c) and
-        SameValue(a.n.sons[0], b.n.sons[0]) and
-        SameValue(a.n.sons[1], b.n.sons[1])
+    cycleCheck()
+    result = sameTypeOrNilAux(a.sons[0], b.sons[0], c) and
+        sameValue(a.n.sons[0], b.n.sons[0]) and
+        sameValue(a.n.sons[1], b.n.sons[1])
   of tyNone: result = false  
 
-proc sameType*(x, y: PType): bool =
-  var c = initSameTypeClosure()
-  result = sameTypeAux(x, y, c)
-
 proc sameBackendType*(x, y: PType): bool =
   var c = initSameTypeClosure()
   c.flags.incl IgnoreTupleFields
@@ -954,7 +987,7 @@ proc typeAllowedNode(marker: var TIntSet, n: PNode, kind: TSymKind,
     if result: 
       case n.kind
       of nkNone..nkNilLit: 
-        nil
+        discard
       else: 
         for i in countup(0, sonsLen(n) - 1): 
           result = typeAllowedNode(marker, n.sons[i], kind, flags)
@@ -965,7 +998,7 @@ proc matchType*(a: PType, pattern: openArray[tuple[k:TTypeKind, i:int]],
   var a = a
   for k, i in pattern.items:
     if a.kind != k: return false
-    if i >= a.sonslen or a.sons[i] == nil: return false
+    if i >= a.sonsLen or a.sons[i] == nil: return false
     a = a.sons[i]
   result = a.kind == last
 
@@ -975,42 +1008,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})
@@ -1018,7 +1015,7 @@ proc typeAllowedAux(marker: var TIntSet, typ: PType, kind: TSymKind,
   # evaluation if something is wrong:
   result = true
   if typ == nil: return
-  if ContainsOrIncl(marker, typ.id): return 
+  if containsOrIncl(marker, typ.id): return 
   var t = skipTypes(typ, abstractInst-{tyTypeDesc})
   case t.kind
   of tyVar:
@@ -1038,14 +1035,15 @@ 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:
     result = taField in flags
   of tyTypeClasses:
     result = true
-  of tyGenericBody, tyGenericParam, tyForward, tyNone, tyGenericInvokation:
+  of tyGenericBody, tyGenericParam, tyGenericInvokation,
+     tyNone, tyForward, tyFromExpr, tyFieldAccessor:
     result = false
   of tyNil:
     result = kind == skConst
@@ -1088,15 +1086,15 @@ proc typeAllowedAux(marker: var TIntSet, typ: PType, kind: TSymKind,
     result = true
 
 proc typeAllowed(t: PType, kind: TSymKind): bool = 
-  var marker = InitIntSet()
+  var marker = initIntSet()
   result = typeAllowedAux(marker, t, kind, {})
 
-proc align(address, alignment: biggestInt): biggestInt = 
+proc align(address, alignment: BiggestInt): BiggestInt = 
   result = (address + (alignment - 1)) and not (alignment - 1)
 
-proc computeSizeAux(typ: PType, a: var biggestInt): biggestInt
-proc computeRecSizeAux(n: PNode, a, currOffset: var biggestInt): biggestInt = 
-  var maxAlign, maxSize, b, res: biggestInt
+proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt
+proc computeRecSizeAux(n: PNode, a, currOffset: var BiggestInt): BiggestInt = 
+  var maxAlign, maxSize, b, res: BiggestInt
   case n.kind
   of nkRecCase: 
     assert(n.sons[0].kind == nkSym)
@@ -1128,25 +1126,29 @@ proc computeRecSizeAux(n: PNode, a, currOffset: var biggestInt): biggestInt =
     result = computeSizeAux(n.sym.typ, a)
     n.sym.offset = int(currOffset)
   else: 
-    InternalError("computeRecSizeAux()")
+    internalError("computeRecSizeAux()")
     a = 1
     result = - 1
 
-proc computeSizeAux(typ: PType, a: var biggestInt): biggestInt = 
-  var res, maxAlign, length, currOffset: biggestInt
-  if typ.size == - 2: 
+const 
+  szIllegalRecursion* = -2
+  szUnknownSize* = -1
+
+proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
+  var res, maxAlign, length, currOffset: BiggestInt
+  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
+    result = intSize
     a = result
   of tyInt8, tyUInt8, tyBool, tyChar: 
     result = 1
@@ -1174,8 +1176,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
@@ -1183,7 +1187,7 @@ proc computeSizeAux(typ: PType, a: var biggestInt): biggestInt =
       length = lastOrd(typ)   # BUGFIX: use lastOrd!
       if length + 1 < `shl`(1, 8): result = 1
       elif length + 1 < `shl`(1, 16): result = 2
-      elif length + 1 < `shl`(biggestInt(1), 32): result = 4
+      elif length + 1 < `shl`(BiggestInt(1), 32): result = 4
       else: result = 8
     a = result
   of tySet: 
@@ -1226,16 +1230,17 @@ 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)
 
-proc computeSize(typ: PType): biggestInt = 
-  var a: biggestInt = 1
+proc computeSize(typ: PType): BiggestInt = 
+  var a: BiggestInt = 1
   result = computeSizeAux(typ, a)
 
 proc getReturnType*(s: PSym): PType =
@@ -1243,13 +1248,20 @@ proc getReturnType*(s: PSym): PType =
   assert s.kind in {skProc, skTemplate, skMacro, skIterator}
   result = s.typ.sons[0]
 
-proc getSize(typ: PType): biggestInt = 
+proc getSize(typ: PType): BiggestInt = 
   result = computeSize(typ)
-  if result < 0: InternalError("getSize: " & $typ.kind)
+  if result < 0: internalError("getSize: " & $typ.kind)
+
+proc containsGenericTypeIter(t: PType, closure: PObject): bool =
+  if t.kind in GenericTypes + tyTypeClasses + {tyFromExpr}:
+    return true
 
+  if t.kind == tyTypeDesc:
+    if t.sonsLen == 0: return true
+    if containsGenericTypeIter(t.base, closure): return true
+    return false
   
-proc containsGenericTypeIter(t: PType, closure: PObject): bool = 
-  result = t.kind in GenericTypes
+  return t.kind == tyStatic and t.n == nil
 
 proc containsGenericType*(t: PType): bool = 
   result = iterOverType(t, containsGenericTypeIter, nil)
@@ -1288,8 +1300,8 @@ proc compatibleEffectsAux(se, re: PNode): bool =
 proc compatibleEffects*(formal, actual: PType): bool =
   # for proc type compatibility checking:
   assert formal.kind == tyProc and actual.kind == tyProc
-  InternalAssert formal.n.sons[0].kind == nkEffectList
-  InternalAssert actual.n.sons[0].kind == nkEffectList
+  internalAssert formal.n.sons[0].kind == nkEffectList
+  internalAssert actual.n.sons[0].kind == nkEffectList
   
   var spec = formal.n.sons[0]
   if spec.len != 0:
@@ -1299,7 +1311,7 @@ proc compatibleEffects*(formal, actual: PType): bool =
     # if 'se.kind == nkArgList' it is no formal type really, but a
     # computed effect and as such no spec:
     # 'r.msgHandler = if isNil(msgHandler): defaultMsgHandler else: msgHandler'
-    if not IsNil(se) and se.kind != nkArgList:
+    if not isNil(se) and se.kind != nkArgList:
       # spec requires some exception or tag, but we don't know anything:
       if real.len == 0: return false
       result = compatibleEffectsAux(se, real.sons[exceptionEffects])
@@ -1314,7 +1326,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 7705746de..deca288b5 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -10,11 +10,17 @@
 ## This file implements the new evaluation engine for Nimrod code.
 ## An instruction is 1-2 int32s in memory, it is a register based VM.
 
+import ast except getstr
+
 import
-  strutils, ast, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned,
-  parser, vmdeps, idents
+  strutils, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned,
+  parser, vmdeps, idents, trees, renderer, options
 
 from semfold import leValueConv, ordinalValToString
+from evaltempl import evalTemplate
+
+when hasFFI:
+  import evalffi
 
 type
   PStackFrame* = ref TStackFrame
@@ -34,7 +40,7 @@ proc stackTraceAux(c: PCtx; x: PStackFrame; pc: int) =
     var info = c.debug[pc]
     # we now use the same format as in system/except.nim
     var s = toFilename(info)
-    var line = toLineNumber(info)
+    var line = toLinenumber(info)
     if line > 0:
       add(s, '(')
       add(s, $line)
@@ -42,13 +48,13 @@ proc stackTraceAux(c: PCtx; x: PStackFrame; pc: int) =
     if x.prc != nil:
       for k in 1..max(1, 25-s.len): add(s, ' ')
       add(s, x.prc.name.s)
-    MsgWriteln(s)
+    msgWriteln(s)
 
 proc stackTrace(c: PCtx, tos: PStackFrame, pc: int,
                 msg: TMsgKind, arg = "") =
-  MsgWriteln("stack trace: (most recent call last)")
+  msgWriteln("stack trace: (most recent call last)")
   stackTraceAux(c, tos, pc)
-  LocalError(c.debug[pc], msg, arg)
+  localError(c.debug[pc], msg, arg)
 
 proc bailOut(c: PCtx; tos: PStackFrame) =
   stackTrace(c, tos, c.exceptionInstr, errUnhandledExceptionX,
@@ -57,15 +63,25 @@ proc bailOut(c: PCtx; tos: PStackFrame) =
 when not defined(nimComputedGoto):
   {.pragma: computedGoto.}
 
-template inc(pc: ptr TInstr, diff = 1) =
-  inc cast[TAddress](pc), TInstr.sizeof * diff
-
 proc myreset(n: PNode) =
   when defined(system.reset): 
     var oldInfo = n.info
     reset(n[])
     n.info = oldInfo
 
+proc skipMeta(n: PNode): PNode = (if n.kind != nkMetaNode: n else: n.sons[0])
+
+proc setMeta(n, child: PNode) =
+  assert n.kind == nkMetaNode
+  let child = child.skipMeta
+  if n.sons.isNil: n.sons = @[child]
+  else: n.sons[0] = child
+
+proc uast(n: PNode): PNode {.inline.} =
+  # "underlying ast"
+  assert n.kind == nkMetaNode
+  n.sons[0]
+
 template ensureKind(k: expr) {.immediate, dirty.} =
   if regs[ra].kind != k:
     myreset(regs[ra])
@@ -93,26 +109,56 @@ template decodeBx(k: expr) {.immediate, dirty.} =
   let rbx = instr.regBx - wordExcess
   ensureKind(k)
 
-template move(a, b: expr) = system.shallowCopy(a, b)
+template move(a, b: expr) {.immediate, dirty.} = system.shallowCopy(a, b)
 # XXX fix minor 'shallowCopy' overloading bug in compiler
 
-proc asgnRef(x, y: PNode) =
-  myreset(x)
-  x.kind = y.kind
+proc moveConst(x, y: PNode) =
+  if x.kind != y.kind:
+    myreset(x)
+    x.kind = y.kind
   x.typ = y.typ
   case x.kind
   of nkCharLit..nkInt64Lit: x.intVal = y.intVal
   of nkFloatLit..nkFloat64Lit: x.floatVal = y.floatVal
-  of nkStrLit..nkTripleStrLit: x.strVal = y.strVal
+  of nkStrLit..nkTripleStrLit: move(x.strVal, y.strVal)
   of nkIdent: x.ident = y.ident
   of nkSym: x.sym = y.sym
+  of nkMetaNode:
+    if x.sons.isNil: x.sons = @[y.sons[0]]
+    else: x.sons[0] = y.sons[0]
   else:
     if x.kind notin {nkEmpty..nkNilLit}:
       move(x.sons, y.sons)
 
+# this seems to be the best way to model the reference semantics
+# of PNimrodNode:
+template asgnRef(x, y: expr) = moveConst(x, y)
+
+proc copyValue(src: PNode): PNode =
+  if src == nil or nfIsRef in src.flags:
+    return src
+  result = newNode(src.kind)
+  result.info = src.info
+  result.typ = src.typ
+  result.flags = src.flags * PersistentNodeFlags
+  when defined(useNodeIds):
+    if result.id == nodeIdToDebug:
+      echo "COMES FROM ", src.id
+  case src.kind
+  of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
+  of nkFloatLit..nkFloat128Lit: result.floatVal = src.floatVal
+  of nkSym: result.sym = src.sym
+  of nkIdent: result.ident = src.ident
+  of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
+  else:
+    newSeq(result.sons, sonsLen(src))
+    for i in countup(0, sonsLen(src) - 1):
+      result.sons[i] = copyValue(src.sons[i])
+
 proc asgnComplex(x, y: PNode) =
-  myreset(x)
-  x.kind = y.kind
+  if x.kind != y.kind:
+    myreset(x)
+    x.kind = y.kind
   x.typ = y.typ
   case x.kind
   of nkCharLit..nkInt64Lit: x.intVal = y.intVal
@@ -120,13 +166,18 @@ proc asgnComplex(x, y: PNode) =
   of nkStrLit..nkTripleStrLit: x.strVal = y.strVal
   of nkIdent: x.ident = y.ident
   of nkSym: x.sym = y.sym
+  of nkMetaNode:
+    if x.sons.isNil: x.sons = @[y.sons[0]]
+    else: x.sons[0] = y.sons[0]
   else:
     if x.kind notin {nkEmpty..nkNilLit}:
-      let y = y.copyTree
-      for i in countup(0, sonsLen(y) - 1): addSon(x, y.sons[i])
+      let y = y.copyValue
+      for i in countup(0, sonsLen(y) - 1): 
+        if i < x.len: x.sons[i] = y.sons[i]
+        else: addSon(x, y.sons[i])
 
 template getstr(a: expr): expr =
-  (if a.kind == nkStrLit: a.strVal else: $chr(int(a.intVal)))
+  (if a.kind in {nkStrLit..nkTripleStrLit}: a.strVal else: $chr(int(a.intVal)))
 
 proc pushSafePoint(f: PStackFrame; pc: int) =
   if f.safePoints.isNil: f.safePoints = @[]
@@ -231,16 +282,23 @@ proc compile(c: PCtx, s: PSym): int =
   result = vmgen.genProc(c, s)
   #c.echoCode
 
-proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
+proc regsContents(regs: TNodeSeq) =
+  for i in 0.. <regs.len:
+    echo "Register ", i
+    #debug regs[i]
+
+proc rawExecute(c: PCtx, start: int, tos: PStackFrame): PNode =
   var pc = start
   var tos = tos
   var regs: TNodeSeq # alias to tos.slots for performance
   move(regs, tos.slots)
+  #echo "NEW RUN ------------------------"
   while true:
-    {.computedGoto.}
+    #{.computedGoto.}
     let instr = c.code[pc]
     let ra = instr.regA
     #echo "PC ", pc, " ", c.code[pc].opcode, " ra ", ra
+    #message(c.debug[pc], warnUser, "gah")
     case instr.opcode
     of opcEof: return regs[ra]
     of opcRet:
@@ -248,20 +306,26 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       pc = tos.comesFrom
       tos = tos.next
       let retVal = regs[0]
-      if tos.isNil: return retVal
+      if tos.isNil: 
+        #echo "RET ", retVal.rendertree
+        return retVal
       
       move(regs, tos.slots)
       assert c.code[pc].opcode in {opcIndCall, opcIndCallAsgn}
       if c.code[pc].opcode == opcIndCallAsgn:
         regs[c.code[pc].regA] = retVal
+        #echo "RET2 ", retVal.rendertree, " ", c.code[pc].regA
     of opcYldYoid: assert false
     of opcYldVal: assert false
     of opcAsgnInt:
       decodeB(nkIntLit)
       regs[ra].intVal = regs[rb].intVal
     of opcAsgnStr:
-      decodeB(nkStrLit)
-      regs[ra].strVal = regs[rb].strVal
+      if regs[instr.regB].kind == nkNilLit:
+        decodeB(nkNilLit)
+      else:
+        decodeB(nkStrLit)
+        regs[ra].strVal = regs[rb].strVal
     of opcAsgnFloat:
       decodeB(nkFloatLit)
       regs[ra].floatVal = regs[rb].floatVal
@@ -270,42 +334,63 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcAsgnRef:
       asgnRef(regs[ra], regs[instr.regB])
     of opcWrGlobalRef:
-      asgnRef(c.globals[instr.regBx-wordExcess-1], regs[ra])
+      asgnRef(c.globals.sons[instr.regBx-wordExcess-1], regs[ra])
     of opcWrGlobal:
       asgnComplex(c.globals.sons[instr.regBx-wordExcess-1], regs[ra])
     of opcLdArr:
       # a = b[c]
       let rb = instr.regB
       let rc = instr.regC
-      let idx = regs[rc].intVal
+      if regs[rc].intVal > high(int):
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
+      let idx = regs[rc].intVal.int
       # XXX what if the array is not 0-based? -> codegen should insert a sub
-      regs[ra] = regs[rb].sons[idx.int]
+      assert regs[rb].kind != nkMetaNode
+      let src = regs[rb]
+      if src.kind notin {nkEmpty..nkNilLit} and idx <% src.len:
+        asgnComplex(regs[ra], src.sons[idx])
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcLdStrIdx:
       decodeBC(nkIntLit)
-      let idx = regs[rc].intVal
-      regs[ra].intVal = regs[rb].strVal[idx.int].ord
+      let idx = regs[rc].intVal.int
+      if idx <=% regs[rb].strVal.len:
+        regs[ra].intVal = regs[rb].strVal[idx].ord
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcWrArr:
       # a[b] = c
       let rb = instr.regB
       let rc = instr.regC
-      let idx = regs[rb].intVal
-      asgnComplex(regs[ra].sons[idx.int], regs[rc])
+      let idx = regs[rb].intVal.int
+      if idx <% regs[ra].len:
+        asgnComplex(regs[ra].sons[idx], regs[rc])
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcWrArrRef:
       let rb = instr.regB
       let rc = instr.regC
-      let idx = regs[rb].intVal
-      asgnRef(regs[ra].sons[idx.int], regs[rc])
+      let idx = regs[rb].intVal.int
+      if idx <% regs[ra].len:
+        asgnRef(regs[ra].sons[idx], regs[rc])
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcLdObj:
       # a = b.c
       let rb = instr.regB
       let rc = instr.regC
       # XXX this creates a wrong alias
-      #Message(c.debug[pc], warnUser, $regs[rb].len & " " & $rc)
+      #Message(c.debug[pc], warnUser, $regs[rb].safeLen & " " & $rc)
       asgnComplex(regs[ra], regs[rb].sons[rc])
     of opcWrObj:
       # a.b = c
       let rb = instr.regB
       let rc = instr.regC
+      #if regs[ra].isNil or regs[ra].sons.isNil or rb >= len(regs[ra]):
+      #  debug regs[ra]
+      #  debug regs[rc]
+      #  echo "RB ", rb
+      #  internalError(c.debug[pc], "argl")
       asgnComplex(regs[ra].sons[rb], regs[rc])
     of opcWrObjRef:
       let rb = instr.regB
@@ -314,7 +399,10 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcWrStrIdx:
       decodeBC(nkStrLit)
       let idx = regs[rb].intVal.int
-      regs[ra].strVal[idx] = chr(regs[rc].intVal)
+      if idx <% regs[ra].strVal.len:
+        regs[ra].strVal[idx] = chr(regs[rc].intVal)
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcAddr:
       decodeB(nkRefTy)
       if regs[ra].len == 0: regs[ra].add regs[rb]
@@ -325,6 +413,7 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       if regs[rb].kind == nkNilLit:
         stackTrace(c, tos, pc, errNilAccess)
       assert regs[rb].kind == nkRefTy
+      # XXX this is not correct
       regs[ra] = regs[rb].sons[0]
     of opcAddInt:
       decodeBC(nkIntLit)
@@ -341,15 +430,24 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcLenSeq:
       decodeBImm(nkIntLit)
       #assert regs[rb].kind == nkBracket
-      # also used by mNLen
-      regs[ra].intVal = regs[rb].len - imm
+      # also used by mNLen:
+      regs[ra].intVal = regs[rb].skipMeta.len - imm
     of opcLenStr:
       decodeBImm(nkIntLit)
-      assert regs[rb].kind == nkStrLit
-      regs[ra].intVal = regs[rb].strVal.len - imm
+      if regs[rb].kind == nkNilLit:
+        stackTrace(c, tos, pc, errNilAccess)
+      else:
+        assert regs[rb].kind in {nkStrLit..nkTripleStrLit}
+        regs[ra].intVal = regs[rb].strVal.len - imm
     of opcIncl:
       decodeB(nkCurly)
       if not inSet(regs[ra], regs[rb]): addSon(regs[ra], copyTree(regs[rb]))
+    of opcInclRange:
+      decodeBC(nkCurly)
+      var r = newNode(nkRange)
+      r.add regs[rb]
+      r.add regs[rc]
+      addSon(regs[ra], r.copyTree)
     of opcExcl:
       decodeB(nkCurly)
       var b = newNodeIT(nkCurly, regs[rb].info, regs[rb].typ)
@@ -440,6 +538,9 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       regs[ra].intVal = ord((regs[rb].kind == nkNilLit and
                              regs[rc].kind == nkNilLit) or
                              regs[rb].sons == regs[rc].sons)
+    of opcEqNimrodNode:
+      decodeBC(nkIntLit)
+      regs[ra].intVal = ord(regs[rb].skipMeta == regs[rc].skipMeta)
     of opcXor:
       decodeBC(nkIntLit)
       regs[ra].intVal = ord(regs[rb].intVal != regs[rc].intVal)
@@ -461,24 +562,24 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       regs[ra].intVal = not regs[rb].intVal
     of opcEqStr:
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(regs[rb].strVal == regs[rc].strVal)
+      regs[ra].intVal = ord(regs[rb].strVal == regs[rc].strVal)
     of opcLeStr:
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(regs[rb].strVal <= regs[rc].strVal)
+      regs[ra].intVal = ord(regs[rb].strVal <= regs[rc].strVal)
     of opcLtStr:
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(regs[rb].strVal < regs[rc].strVal)
+      regs[ra].intVal = ord(regs[rb].strVal < regs[rc].strVal)
     of opcLeSet:
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(containsSets(regs[rb], regs[rc]))
+      regs[ra].intVal = ord(containsSets(regs[rb], regs[rc]))
     of opcEqSet: 
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(equalSets(regs[rb], regs[rc]))
+      regs[ra].intVal = ord(equalSets(regs[rb], regs[rc]))
     of opcLtSet:
       decodeBC(nkIntLit)
       let a = regs[rb]
       let b = regs[rc]
-      regs[ra].intVal = Ord(containsSets(a, b) and not equalSets(a, b))
+      regs[ra].intVal = ord(containsSets(a, b) and not equalSets(a, b))
     of opcMulSet:
       decodeBC(nkCurly)
       move(regs[ra].sons, nimsets.intersectSets(regs[rb], regs[rc]).sons)
@@ -488,7 +589,7 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcMinusSet:
       decodeBC(nkCurly)
       move(regs[ra].sons, nimsets.diffSets(regs[rb], regs[rc]).sons)
-    of opcSymDiffSet:
+    of opcSymdiffSet:
       decodeBC(nkCurly)
       move(regs[ra].sons, nimsets.symdiffSets(regs[rb], regs[rc]).sons)    
     of opcConcatStr:
@@ -508,12 +609,12 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcEcho:
       let rb = instr.regB
       for i in ra..ra+rb-1:
-        if regs[i].kind != nkStrLit: debug regs[i]
+        #if regs[i].kind != nkStrLit: debug regs[i]
         write(stdout, regs[i].strVal)
       writeln(stdout, "")
     of opcContainsSet:
       decodeBC(nkIntLit)
-      regs[ra].intVal = Ord(inSet(regs[rb], regs[rc]))
+      regs[ra].intVal = ord(inSet(regs[rb], regs[rc]))
     of opcSubStr:
       decodeBC(nkStrLit)
       inc pc
@@ -533,22 +634,55 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       # dest = call regStart, n; where regStart = fn, arg1, ...
       let rb = instr.regB
       let rc = instr.regC
-      let prc = regs[rb].sym
-      let newPc = compile(c, prc)
-      var newFrame = PStackFrame(prc: prc, comesFrom: pc, next: tos)
-      newSeq(newFrame.slots, prc.position)
-      if not isEmptyType(prc.typ.sons[0]):
-        newFrame.slots[0] = getNullValue(prc.typ.sons[0], prc.info)
-      # pass every parameter by var (the language definition allows this):
-      for i in 1 .. rc-1:
-        newFrame.slots[i] = regs[rb+i]
-      # allocate the temporaries:
-      for i in rc .. <prc.position:
-        newFrame.slots[i] = newNode(nkEmpty)
-      tos = newFrame
-      move(regs, newFrame.slots)
-      # -1 for the following 'inc pc'
-      pc = newPc-1
+      let isClosure = regs[rb].kind == nkPar
+      let prc = if not isClosure: regs[rb].sym else: regs[rb].sons[0].sym
+      if sfImportc in prc.flags:
+        if allowFFI notin c.features:
+          globalError(c.debug[pc], errGenerated, "VM not allowed to do FFI")
+        # we pass 'tos.slots' instead of 'regs' so that the compiler can keep
+        # 'regs' in a register:
+        when hasFFI:
+          let prcValue = c.globals.sons[prc.position-1]
+          if prcValue.kind == nkEmpty:
+            globalError(c.debug[pc], errGenerated, "canot run " & prc.name.s)
+          let newValue = callForeignFunction(prcValue, prc.typ, tos.slots,
+                                             rb+1, rc-1, c.debug[pc])
+          if newValue.kind != nkEmpty:
+            assert instr.opcode == opcIndCallAsgn
+            asgnRef(regs[ra], newValue)
+        else:
+          globalError(c.debug[pc], errGenerated, "VM not built with FFI support")
+      elif prc.kind != skTemplate:
+        let newPc = compile(c, prc)
+        #echo "new pc ", newPc, " calling: ", prc.name.s
+        var newFrame = PStackFrame(prc: prc, comesFrom: pc, next: tos)
+        newSeq(newFrame.slots, prc.offset)
+        if not isEmptyType(prc.typ.sons[0]) or prc.kind == skMacro:
+          newFrame.slots[0] = getNullValue(prc.typ.sons[0], prc.info)
+        # pass every parameter by var (the language definition allows this):
+        for i in 1 .. rc-1:
+          newFrame.slots[i] = regs[rb+i]
+        if isClosure:
+          newFrame.slots[rc] = regs[rb].sons[1]
+        # allocate the temporaries:
+        for i in rc+ord(isClosure) .. <prc.offset:
+          newFrame.slots[i] = newNode(nkEmpty)
+        tos = newFrame
+        move(regs, newFrame.slots)
+        # -1 for the following 'inc pc'
+        pc = newPc-1
+      else:
+        # for 'getAst' support we need to support template expansion here:
+        let genSymOwner = if tos.next != nil and tos.next.prc != nil:
+                            tos.next.prc
+                          else:
+                            c.module
+        var macroCall = newNodeI(nkCall, c.debug[pc])
+        macroCall.add(newSymNode(prc))
+        for i in 1 .. rc-1: macroCall.add(regs[rb+i].skipMeta)
+        let a = evalTemplate(macroCall, prc, genSymOwner)
+        ensureKind(nkMetaNode)
+        setMeta(regs[ra], a)
     of opcTJmp:
       # jump Bx if A != 0
       let rbx = instr.regBx - wordExcess - 1 # -1 for the following 'inc pc'
@@ -564,18 +698,18 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       let rbx = instr.regBx - wordExcess - 1 # -1 for the following 'inc pc'
       inc pc, rbx
     of opcBranch:
-      # we know the next instruction is a 'jmp':
+      # we know the next instruction is a 'fjmp':
       let branch = c.constants[instr.regBx-wordExcess]
       var cond = false
       for j in countup(0, sonsLen(branch) - 2): 
         if overlap(regs[ra], branch.sons[j]): 
           cond = true
           break
-      assert c.code[pc+1].opcode == opcJmp
+      assert c.code[pc+1].opcode == opcFJmp
       inc pc 
       # we skip this instruction so that the final 'inc(pc)' skips
       # the following jump
-      if cond:
+      if not cond:
         let instr2 = c.code[pc]
         let rbx = instr2.regBx - wordExcess - 1 # -1 for the following 'inc pc'
         inc pc, rbx
@@ -592,7 +726,7 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcFinallyEnd:
       if c.currentExceptionA != nil:
         # we are in a cleanup run:
-        pc = cleanupOnException(c, tos, regs)-1
+        pc = cleanUpOnException(c, tos, regs)-1
         if pc < 0: 
           bailOut(c, tos)
           return
@@ -601,23 +735,24 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       c.currentExceptionA = raised
       c.exceptionInstr = pc
       # -1 because of the following 'inc'
-      pc = cleanupOnException(c, tos, regs) - 1
+      pc = cleanUpOnException(c, tos, regs) - 1
       if pc < 0:
         bailOut(c, tos)
         return
     of opcNew:
       let typ = c.types[instr.regBx - wordExcess]
       regs[ra] = getNullValue(typ, regs[ra].info)
+      regs[ra].flags.incl nfIsRef
     of opcNewSeq:
       let typ = c.types[instr.regBx - wordExcess]
       inc pc
       ensureKind(nkBracket)
       let instr2 = c.code[pc]
-      let rb = instr2.regA
+      let count = regs[instr2.regA].intVal.int
       regs[ra].typ = typ
-      newSeq(regs[ra].sons, rb)
-      for i in 0 .. <rb:
-        regs[ra].sons[i] = getNullValue(typ, regs[ra].info)
+      newSeq(regs[ra].sons, count)
+      for i in 0 .. <count:
+        regs[ra].sons[i] = getNullValue(typ.sons[0], regs[ra].info)
     of opcNewStr:
       decodeB(nkStrLit)
       regs[ra].strVal = newString(regs[rb].intVal.int)
@@ -629,7 +764,11 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       let typ = c.types[instr.regBx - wordExcess]
       regs[ra] = getNullValue(typ, c.debug[pc])
     of opcLdConst:
-      regs[ra] = c.constants.sons[instr.regBx - wordExcess]
+      let rb = instr.regBx - wordExcess
+      if regs[ra].isNil:
+        regs[ra] = copyTree(c.constants.sons[rb])
+      else:
+        moveConst(regs[ra], c.constants.sons[rb])
     of opcAsgnConst:
       let rb = instr.regBx - wordExcess
       if regs[ra].isNil:
@@ -637,67 +776,111 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       else:
         asgnComplex(regs[ra], c.constants.sons[rb])
     of opcLdGlobal:
-      let rb = instr.regBx - wordExcess
+      let rb = instr.regBx - wordExcess - 1
       if regs[ra].isNil:
         regs[ra] = copyTree(c.globals.sons[rb])
       else:
         asgnComplex(regs[ra], c.globals.sons[rb])
-    of opcRepr, opcSetLenStr, opcSetLenSeq,
-        opcSwap, opcIsNil, opcOf,
-        opcCast, opcQuit, opcReset:
+    of opcRepr:
+      decodeB(nkStrLit)
+      regs[ra].strVal = renderTree(regs[rb].skipMeta, {renderNoComments})
+    of opcQuit:
+      if c.mode in {emRepl, emStaticExpr, emStaticStmt}:
+        message(c.debug[pc], hintQuitCalled)
+        quit(int(getOrdValue(regs[ra])))
+      else:
+        return nil
+    of opcSetLenStr:
+      decodeB(nkStrLit)
+      regs[ra].strVal.setLen(regs[rb].getOrdValue.int)
+    of opcOf:
+      decodeBC(nkIntLit)
+      let typ = c.types[regs[rc].intVal.int]
+      regs[ra].intVal = ord(inheritanceDiff(regs[rb].typ, typ) >= 0)
+    of opcIs:
+      decodeBC(nkIntLit)
+      let t1 = regs[rb].typ.skipTypes({tyTypeDesc})
+      let t2 = c.types[regs[rc].intVal.int]
+      # XXX: This should use the standard isOpImpl
+      let match = if t2.kind == tyUserTypeClass: true
+                  else: sameType(t1, t2)
+      regs[ra].intVal = ord(match)
+    of opcSetLenSeq:
+      decodeB(nkBracket)
+      let newLen = regs[rb].getOrdValue.int
+      setLen(regs[ra].sons, newLen)
+    of opcSwap, opcReset:
       internalError(c.debug[pc], "too implement")
+    of opcIsNil:
+      decodeB(nkIntLit)
+      regs[ra].intVal = ord(regs[rb].skipMeta.kind == nkNilLit)
     of opcNBindSym:
-      # trivial implementation:
-      let rb = instr.regB
-      regs[ra] = regs[rb].sons[1]
+      decodeBx(nkMetaNode)
+      setMeta(regs[ra], copyTree(c.constants.sons[rbx]))
     of opcNChild:
-      let rb = instr.regB
-      let rc = instr.regC
-      regs[ra] = regs[rb].sons[regs[rc].intVal.int]
+      decodeBC(nkMetaNode)
+      if regs[rb].kind != nkMetaNode:
+        internalError(c.debug[pc], "no MetaNode")
+      let idx = regs[rc].intVal.int
+      let src = regs[rb].uast
+      if src.kind notin {nkEmpty..nkNilLit} and idx <% src.len:
+        setMeta(regs[ra], src.sons[idx])
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcNSetChild:
-      let rb = instr.regB
-      let rc = instr.regC
-      regs[ra].sons[regs[rb].intVal.int] = regs[rc]
+      decodeBC(nkMetaNode)
+      let idx = regs[rb].intVal.int
+      var dest = regs[ra].uast
+      if dest.kind notin {nkEmpty..nkNilLit} and idx <% dest.len:
+        dest.sons[idx] = regs[rc].uast
+      else:
+        stackTrace(c, tos, pc, errIndexOutOfBounds)
     of opcNAdd:
-      declBC()
-      regs[rb].add(regs[rb])
-      regs[ra] = regs[rb]
+      decodeBC(nkMetaNode)
+      var u = regs[rb].uast
+      u.add(regs[rc].uast)
+      setMeta(regs[ra], u)
     of opcNAddMultiple:
-      declBC()
+      decodeBC(nkMetaNode)
       let x = regs[rc]
+      var u = regs[rb].uast
       # XXX can be optimized:
-      for i in 0.. <x.len: regs[rb].add(x.sons[i])
-      regs[ra] = regs[rb]
+      for i in 0.. <x.len: u.add(x.sons[i].skipMeta)
+      setMeta(regs[ra], u)
     of opcNKind:
       decodeB(nkIntLit)
-      regs[ra].intVal = ord(regs[rb].kind)
+      regs[ra].intVal = ord(regs[rb].uast.kind)
     of opcNIntVal:
       decodeB(nkIntLit)
-      let a = regs[rb]
+      let a = regs[rb].uast
       case a.kind
       of nkCharLit..nkInt64Lit: regs[ra].intVal = a.intVal
       else: stackTrace(c, tos, pc, errFieldXNotFound, "intVal")
     of opcNFloatVal:
       decodeB(nkFloatLit)
-      let a = regs[rb]
+      let a = regs[rb].uast
       case a.kind
       of nkFloatLit..nkFloat64Lit: regs[ra].floatVal = a.floatVal
       else: stackTrace(c, tos, pc, errFieldXNotFound, "floatVal")
     of opcNSymbol:
-      let rb = instr.regB
-      if regs[rb].kind != nkSym: 
+      decodeB(nkSym)
+      let a = regs[rb].uast
+      if a.kind == nkSym:
+        regs[ra].sym = a.sym
+      else:
         stackTrace(c, tos, pc, errFieldXNotFound, "symbol")
-      regs[ra] = regs[rb]
     of opcNIdent:
-      let rb = instr.regB
-      if regs[rb].kind != nkIdent: 
+      decodeB(nkIdent)
+      let a = regs[rb].uast
+      if a.kind == nkIdent:
+        regs[ra].ident = a.ident
+      else:
         stackTrace(c, tos, pc, errFieldXNotFound, "ident")
-      regs[ra] = regs[rb]
     of opcNGetType:
-      InternalError(c.debug[pc], "unknown opcode " & $instr.opcode)      
+      internalError(c.debug[pc], "unknown opcode " & $instr.opcode)
     of opcNStrVal:
       decodeB(nkStrLit)
-      let a = regs[rb]
+      let a = regs[rb].uast
       case a.kind
       of nkStrLit..nkTripleStrLit: regs[ra].strVal = a.strVal
       else: stackTrace(c, tos, pc, errFieldXNotFound, "strVal")
@@ -710,29 +893,30 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
     of opcNError:
       stackTrace(c, tos, pc, errUser, regs[ra].strVal)
     of opcNWarning:
-      Message(c.debug[pc], warnUser, regs[ra].strVal)
+      message(c.debug[pc], warnUser, regs[ra].strVal)
     of opcNHint:
-      Message(c.debug[pc], hintUser, regs[ra].strVal)
+      message(c.debug[pc], hintUser, regs[ra].strVal)
     of opcParseExprToAst:
-      let rb = instr.regB
+      decodeB(nkMetaNode)
       # c.debug[pc].line.int - countLines(regs[rb].strVal) ?
       let ast = parseString(regs[rb].strVal, c.debug[pc].toFilename,
                             c.debug[pc].line.int)
       if sonsLen(ast) != 1:
-        GlobalError(c.debug[pc], errExprExpected, "multiple statements")
-      regs[ra] = ast.sons[0]
+        globalError(c.debug[pc], errExprExpected, "multiple statements")
+      setMeta(regs[ra], ast.sons[0])
     of opcParseStmtToAst:
-      let rb = instr.regB
+      decodeB(nkMetaNode)
       let ast = parseString(regs[rb].strVal, c.debug[pc].toFilename,
                             c.debug[pc].line.int)
-      regs[ra] = ast
+      setMeta(regs[ra], ast)
     of opcCallSite:
-      if c.callsite != nil: regs[ra] = c.callsite
+      ensureKind(nkMetaNode)
+      if c.callsite != nil: setMeta(regs[ra], c.callsite)
       else: stackTrace(c, tos, pc, errFieldXNotFound, "callsite")
     of opcNLineInfo:
-      let rb = instr.regB
+      decodeB(nkStrLit)
       let n = regs[rb]
-      regs[ra] = newStrNode(nkStrLit, n.info.toFileLineCol)
+      regs[ra].strVal = n.info.toFileLineCol
       regs[ra].info = c.debug[pc]
     of opcEqIdent:
       decodeBC(nkIntLit)
@@ -741,16 +925,16 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
       else:
         regs[ra].intVal = 0
     of opcStrToIdent:
-      let rb = instr.regB
+      decodeB(nkIdent)
       if regs[rb].kind notin {nkStrLit..nkTripleStrLit}:
         stackTrace(c, tos, pc, errFieldXNotFound, "strVal")
       else:
-        regs[ra] = newNodeI(nkIdent, c.debug[pc])
+        regs[ra].info = c.debug[pc]
         regs[ra].ident = getIdent(regs[rb].strVal)
     of opcIdentToStr:
-      let rb = instr.regB
+      decodeB(nkStrLit)
       let a = regs[rb]
-      regs[ra] = newNodeI(nkStrLit, c.debug[pc])
+      regs[ra].info = c.debug[pc]
       if a.kind == nkSym:
         regs[ra].strVal = a.sym.name.s
       elif a.kind == nkIdent:
@@ -767,84 +951,119 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame) =
         stackTrace(c, tos, pc, errGenerated,
           msgKindToString(errIllegalConvFromXtoY) % [
           "unknown type" , "unknown type"])
-    of opcNSetIntVal:
+    of opcCast:
       let rb = instr.regB
-      if regs[ra].kind in {nkCharLit..nkInt64Lit} and 
+      inc pc
+      let typ = c.types[c.code[pc].regBx - wordExcess]
+      when hasFFI:
+        let dest = fficast(regs[rb], typ)
+        asgnRef(regs[ra], dest)
+      else:
+        globalError(c.debug[pc], "cannot evaluate cast")
+    of opcNSetIntVal:
+      decodeB(nkMetaNode)
+      var dest = regs[ra].uast
+      if dest.kind in {nkCharLit..nkInt64Lit} and 
          regs[rb].kind in {nkCharLit..nkInt64Lit}:
-        regs[ra].intVal = regs[rb].intVal
-      else: 
+        dest.intVal = regs[rb].intVal
+      else:
         stackTrace(c, tos, pc, errFieldXNotFound, "intVal")
     of opcNSetFloatVal:
-      let rb = instr.regB
-      if regs[ra].kind in {nkFloatLit..nkFloat64Lit} and 
+      decodeB(nkMetaNode)
+      var dest = regs[ra].uast
+      if dest.kind in {nkFloatLit..nkFloat64Lit} and 
          regs[rb].kind in {nkFloatLit..nkFloat64Lit}:
-        regs[ra].floatVal = regs[rb].floatVal
+        dest.floatVal = regs[rb].floatVal
       else: 
         stackTrace(c, tos, pc, errFieldXNotFound, "floatVal")
     of opcNSetSymbol:
-      let rb = instr.regB
-      if regs[ra].kind == nkSym and regs[rb].kind == nkSym:
-        regs[ra].sym = regs[rb].sym
+      decodeB(nkMetaNode)
+      var dest = regs[ra].uast
+      if dest.kind == nkSym and regs[rb].kind == nkSym:
+        dest.sym = regs[rb].sym
       else: 
         stackTrace(c, tos, pc, errFieldXNotFound, "symbol")
     of opcNSetIdent:
-      let rb = instr.regB
-      if regs[ra].kind == nkIdent and regs[rb].kind == nkIdent:
-        regs[ra].ident = regs[rb].ident
+      decodeB(nkMetaNode)
+      var dest = regs[ra].uast
+      if dest.kind == nkIdent and regs[rb].kind == nkIdent:
+        dest.ident = regs[rb].ident
       else: 
         stackTrace(c, tos, pc, errFieldXNotFound, "ident")
     of opcNSetType:
-      let b = regs[instr.regB]
-      InternalAssert b.kind == nkSym and b.sym.kind == skType
-      regs[ra].typ = b.sym.typ
+      decodeB(nkMetaNode)
+      let b = regs[rb].skipMeta
+      internalAssert b.kind == nkSym and b.sym.kind == skType
+      regs[ra].uast.typ = b.sym.typ
     of opcNSetStrVal:
-      let rb = instr.regB
-      if regs[ra].kind in {nkStrLit..nkTripleStrLit} and 
+      decodeB(nkMetaNode)
+      var dest = regs[ra].uast
+      if dest.kind in {nkStrLit..nkTripleStrLit} and 
          regs[rb].kind in {nkStrLit..nkTripleStrLit}:
-        regs[ra].strVal = regs[rb].strVal
+        dest.strVal = regs[rb].strVal
       else:
         stackTrace(c, tos, pc, errFieldXNotFound, "strVal")
     of opcNNewNimNode:
-      let rb = instr.regB
-      let rc = instr.regC
+      decodeBC(nkMetaNode)
       var k = regs[rb].intVal
-      if k < 0 or k > ord(high(TNodeKind)): 
+      if k < 0 or k > ord(high(TNodeKind)) or k == ord(nkMetaNode):
         internalError(c.debug[pc],
-          "request to create a NimNode with invalid kind")
-      regs[ra] = newNodeI(TNodeKind(int(k)), 
-        if regs[rc].kind == nkNilLit: c.debug[pc] else: regs[rc].info)
+          "request to create a NimNode of invalid kind")
+      let cc = regs[rc].skipMeta
+      setMeta(regs[ra], newNodeI(TNodeKind(int(k)), 
+        if cc.kind == nkNilLit: c.debug[pc] else: cc.info))
+      regs[ra].sons[0].flags.incl nfIsRef
     of opcNCopyNimNode:
-      let rb = instr.regB
-      regs[ra] = copyNode(regs[rb])
+      decodeB(nkMetaNode)
+      setMeta(regs[ra], copyNode(regs[rb]))
     of opcNCopyNimTree:
-      let rb = instr.regB
-      regs[ra] = copyTree(regs[rb])
+      decodeB(nkMetaNode)
+      setMeta(regs[ra], copyTree(regs[rb]))
     of opcNDel:
-      let rb = instr.regB
-      let rc = instr.regC
+      decodeBC(nkMetaNode)
+      let bb = regs[rb].intVal.int
       for i in countup(0, regs[rc].intVal.int-1):
-        delSon(regs[ra], regs[rb].intVal.int)
+        delSon(regs[ra].uast, bb)
     of opcGenSym:
-      let k = regs[instr.regB].intVal
-      let b = regs[instr.regC]
-      let name = if b.strVal.len == 0: ":tmp" else: b.strVal
+      decodeBC(nkMetaNode)
+      let k = regs[rb].intVal
+      let name = if regs[rc].strVal.len == 0: ":tmp" else: regs[rc].strVal
       if k < 0 or k > ord(high(TSymKind)):
         internalError(c.debug[pc], "request to create symbol of invalid kind")
-      regs[ra] = newSymNode(newSym(k.TSymKind, name.getIdent, c.module,
-                            c.debug[pc]))
-      incl(regs[ra].sym.flags, sfGenSym)
+      var sym = newSym(k.TSymKind, name.getIdent, c.module, c.debug[pc])
+      incl(sym.flags, sfGenSym)
+      setMeta(regs[ra], newSymNode(sym))
     of opcTypeTrait:
       # XXX only supports 'name' for now; we can use regC to encode the
       # type trait operation
       decodeB(nkStrLit)
       let typ = regs[rb].sym.typ.skipTypes({tyTypeDesc})
       regs[ra].strVal = typ.typeToString(preferExported)
+    of opcGlobalOnce:
+      let rb = instr.regBx
+      if c.globals.sons[rb - wordExcess - 1].kind != nkEmpty:
+        # skip initialization instructions:
+        while true:
+          inc pc
+          if c.code[pc].opcode in {opcWrGlobal, opcWrGlobalRef} and
+             c.code[pc].regBx == rb:
+            break
+    of opcGlobalAlias:
+      let rb = instr.regBx - wordExcess - 1
+      regs[ra] = c.globals.sons[rb]
     inc pc
 
-proc execute(c: PCtx, start: int) =
+proc fixType(result, n: PNode) {.inline.} =
+  # XXX do it deeply for complex values; there seems to be no simple
+  # solution except to check it deeply here.
+  #if result.typ.isNil: result.typ = n.typ
+  discard
+
+proc execute(c: PCtx, start: int): PNode =
   var tos = PStackFrame(prc: nil, comesFrom: 0, next: nil)
   newSeq(tos.slots, c.prc.maxSlots)
-  rawExecute(c, start, tos)
+  for i in 0 .. <c.prc.maxSlots: tos.slots[i] = newNode(nkEmpty)
+  result = rawExecute(c, start, tos)
 
 proc evalStmt*(c: PCtx, n: PNode) =
   let start = genStmt(c, n)
@@ -857,12 +1076,30 @@ proc evalExpr*(c: PCtx, n: PNode): PNode =
   let start = genExpr(c, n)
   assert c.code[start].opcode != opcEof
   result = execute(c, start)
+  if not result.isNil:
+    result = result.skipMeta
+    fixType(result, n)
+
+# for now we share the 'globals' environment. XXX Coming soon: An API for
+# storing&loading the 'globals' environment to get what a component system
+# requires.
+var
+  globalCtx: PCtx
+
+proc setupGlobalCtx(module: PSym) =
+  if globalCtx.isNil: globalCtx = newCtx(module)
+  else: refresh(globalCtx, module)
 
 proc myOpen(module: PSym): PPassContext =
   #var c = newEvalContext(module, emRepl)
   #c.features = {allowCast, allowFFI, allowInfiniteLoops}
   #pushStackFrame(c, newStackFrame())
-  result = newCtx(module)
+
+  # XXX produce a new 'globals' environment here:
+  setupGlobalCtx(module)
+  result = globalCtx
+  when hasFFI:
+    globalCtx.features = {allowFFI, allowCast}
 
 var oldErrorCount: int
 
@@ -875,50 +1112,71 @@ proc myProcess(c: PPassContext, n: PNode): PNode =
     result = n
   oldErrorCount = msgs.gErrorCounter
 
-const vmPass* = makePass(myOpen, nil, myProcess, myProcess)
+const evalPass* = makePass(myOpen, nil, myProcess, myProcess)
 
-proc evalConstExprAux(module, prc: PSym, e: PNode, mode: TEvalMode): PNode = 
-  var p = newCtx(module)
-  var s = newStackFrame()
-  s.call = e
-  s.prc = prc
-  pushStackFrame(p, s)
-  result = tryEval(p, e)
-  if result != nil and result.kind == nkExceptBranch: result = nil
-  popStackFrame(p)
+proc evalConstExprAux(module, prc: PSym, n: PNode, mode: TEvalMode): PNode =
+  setupGlobalCtx(module)
+  var c = globalCtx
+  c.mode = mode
+  let start = genExpr(c, n, requiresValue = mode!=emStaticStmt)
+  if c.code[start].opcode == opcEof: return emptyNode
+  assert c.code[start].opcode != opcEof
+  var tos = PStackFrame(prc: prc, comesFrom: 0, next: nil)
+  newSeq(tos.slots, c.prc.maxSlots)
+  for i in 0 .. <c.prc.maxSlots: tos.slots[i] = newNode(nkEmpty)
+  result = rawExecute(c, start, tos)
+  fixType(result, n)
 
 proc evalConstExpr*(module: PSym, e: PNode): PNode = 
   result = evalConstExprAux(module, nil, e, emConst)
 
-proc evalStaticExpr*(module: PSym, e: PNode, prc: PSym): PNode = 
-  result = evalConstExprAux(module, prc, e, emStatic)
+proc evalStaticExpr*(module: PSym, e: PNode, prc: PSym): PNode =
+  result = evalConstExprAux(module, prc, e, emStaticExpr)
+
+proc evalStaticStmt*(module: PSym, e: PNode, prc: PSym) =
+  discard evalConstExprAux(module, prc, e, emStaticStmt)
 
 proc setupMacroParam(x: PNode): PNode =
   result = x
   if result.kind in {nkHiddenSubConv, nkHiddenStdConv}: result = result.sons[1]
+  let y = result
+  y.flags.incl nfIsRef
+  result = newNode(nkMetaNode)
+  result.add y
+  result.typ = x.typ
 
-proc evalMacroCall(c: PEvalContext, n, nOrig: PNode, sym: PSym): PNode =
+var evalMacroCounter: int
+
+proc evalMacroCall*(module: PSym, n, nOrig: PNode, sym: PSym): PNode =
   # XXX GlobalError() is ugly here, but I don't know a better solution for now
-  inc(evalTemplateCounter)
-  if evalTemplateCounter > 100:
-    GlobalError(n.info, errTemplateInstantiationTooNested)
+  inc(evalMacroCounter)
+  if evalMacroCounter > 100:
+    globalError(n.info, errTemplateInstantiationTooNested)
+  setupGlobalCtx(module)
+  var c = globalCtx
 
   c.callsite = nOrig
-  let body = optBody(c, sym)
-  let start = genStmt(c, body)
+  let start = genProc(c, sym)
 
   var tos = PStackFrame(prc: sym, comesFrom: 0, next: nil)
-  newSeq(tos.slots, c.prc.maxSlots)
+  let maxSlots = sym.offset
+  newSeq(tos.slots, maxSlots)
   # setup arguments:
   var L = n.safeLen
   if L == 0: L = 1
-  InternalAssert tos.slots.len >= L
+  # This is wrong for tests/reject/tind1.nim where the passed 'else' part
+  # doesn't end up in the parameter:
+  #InternalAssert tos.slots.len >= L
   # return value:
   tos.slots[0] = newNodeIT(nkNilLit, n.info, sym.typ.sons[0])
   # setup parameters:
-  for i in 1 .. < L: tos.slots[i] = setupMacroParam(n.sons[i])
-  rawExecute(c, start, tos)
-  result = tos.slots[0]
-  if cyclicTree(result): GlobalError(n.info, errCyclicTree)
-  dec(evalTemplateCounter)
+  for i in 1 .. < min(tos.slots.len, L):
+    tos.slots[i] = setupMacroParam(n.sons[i])
+  # temporary storage:
+  for i in L .. <maxSlots: tos.slots[i] = newNode(nkEmpty)
+  result = rawExecute(c, start, tos)
+  if cyclicTree(result): globalError(n.info, errCyclicTree)
+  dec(evalMacroCounter)
+  if result != nil:
+    result = result.skipMeta
   c.callsite = nil
diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim
index d4b3d891d..480c7f31b 100644
--- a/compiler/vmdef.nim
+++ b/compiler/vmdef.nim
@@ -51,16 +51,16 @@ type
     opcLenSeq,
     opcLenStr,
 
-    opcIncl, opcExcl, opcCard, opcMulInt, opcDivInt, opcModInt,
+    opcIncl, opcInclRange, opcExcl, opcCard, opcMulInt, opcDivInt, opcModInt,
     opcAddFloat, opcSubFloat, opcMulFloat, opcDivFloat, opcShrInt, opcShlInt,
     opcBitandInt, opcBitorInt, opcBitxorInt, opcAddu, opcSubu, opcMulu, 
     opcDivu, opcModu, opcEqInt, opcLeInt, opcLtInt, opcEqFloat, 
-    opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcXor, 
+    opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcEqNimrodNode, opcXor, 
     opcNot, opcUnaryMinusInt, opcUnaryMinusFloat, opcBitnotInt, 
     opcEqStr, opcLeStr, opcLtStr, opcEqSet, opcLeSet, opcLtSet,
     opcMulSet, opcPlusSet, opcMinusSet, opcSymdiffSet, opcConcatStr,
     opcContainsSet, opcRepr, opcSetLenStr, opcSetLenSeq,
-    opcSwap, opcIsNil, opcOf,
+    opcSwap, opcIsNil, opcOf, opcIs,
     opcSubStr, opcConv, opcCast, opcQuit, opcReset,
     
     opcAddStrCh,
@@ -101,7 +101,6 @@ type
     opcRaise,
     opcNChild,
     opcNSetChild,
-    opcNBindSym, # opcodes for the AST manipulation following
     opcCallSite,
     opcNewStr,
   
@@ -120,8 +119,11 @@ type
     opcAsgnConst, # dest = copy(constants[Bx])
     opcLdGlobal,  # dest = globals[Bx]
     opcLdImmInt,  # dest = immediate value
+    opcNBindSym,
     opcWrGlobal,
     opcWrGlobalRef,
+    opcGlobalAlias, # load an alias to a global into a register
+    opcGlobalOnce,  # used to introduce an assignment to a global once
     opcSetType,   # dest.typ = types[Bx]
     opcTypeTrait
 
@@ -129,6 +131,21 @@ type
     label*: PSym
     fixups*: seq[TPosition]
 
+  TEvalMode* = enum           ## reason for evaluation
+    emRepl,                   ## evaluate because in REPL mode
+    emConst,                  ## evaluate for 'const' according to spec
+    emOptimize,               ## evaluate for optimization purposes (same as
+                              ## emConst?)
+    emStaticExpr,             ## evaluate for enforced compile time eval
+                              ## ('static' context)
+    emStaticStmt              ## 'static' as an expression
+
+  TSandboxFlag* = enum        ## what the evaluation engine should allow
+    allowCast,                ## allow unsafe language feature: 'cast'
+    allowFFI,                 ## allow the FFI
+    allowInfiniteLoops        ## allow endless loops
+  TSandboxFlags* = set[TSandboxFlag]
+
   TSlotKind* = enum   # We try to re-use slots in a smart way to
                       # minimize allocations; however the VM supports arbitrary
                       # temporary slot usage. This is required for the parameter
@@ -146,6 +163,8 @@ type
     blocks*: seq[TBlock]    # blocks; temp data structure
     slots*: array[TRegister, tuple[inUse: bool, kind: TSlotKind]]
     maxSlots*: int
+    globals*: array[TRegister, int] # hack: to support passing globals byref
+                                    # we map a slot persistently to a global
     
   PCtx* = ref TCtx
   TCtx* = object of passes.TPassContext # code gen context
@@ -160,21 +179,26 @@ type
     prc*: PProc
     module*: PSym
     callsite*: PNode
+    mode*: TEvalMode
+    features*: TSandboxFlags
 
   TPosition* = distinct int
 
   PEvalContext* = PCtx
-
   
 proc newCtx*(module: PSym): PCtx =
   PCtx(code: @[], debug: @[],
-    globals: newNode(nkStmtList), constants: newNode(nkStmtList), types: @[],
+    globals: newNode(nkStmtListExpr), constants: newNode(nkStmtList), types: @[],
     prc: PProc(blocks: @[]), module: module)
 
+proc refresh*(c: PCtx, module: PSym) =
+  c.module = module
+  c.prc = PProc(blocks: @[])
+
 const
   firstABxInstr* = opcTJmp
   largeInstrs* = { # instructions which use 2 int32s instead of 1:
-    opcSubstr, opcConv, opcCast, opcNewSeq, opcOf}
+    opcSubStr, opcConv, opcCast, opcNewSeq, opcOf}
   slotSomeTemp* = slotTempUnknown
   relativeJumps* = {opcTJmp, opcFJmp, opcJmp}
 
@@ -183,3 +207,5 @@ template regA*(x: TInstr): TRegister {.immediate.} = TRegister(x.uint32 shr 8'u3
 template regB*(x: TInstr): TRegister {.immediate.} = TRegister(x.uint32 shr 16'u32 and 0xff'u32)
 template regC*(x: TInstr): TRegister {.immediate.} = TRegister(x.uint32 shr 24'u32)
 template regBx*(x: TInstr): int {.immediate.} = (x.uint32 shr 16'u32).int
+
+template jmpDiff*(x: TInstr): int {.immediate.} = regBx(x) - wordExcess
diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim
index 2a40276d1..0e01f5031 100644
--- a/compiler/vmdeps.nim
+++ b/compiler/vmdeps.nim
@@ -25,69 +25,12 @@ proc opGorge*(cmd, input: string): string =
 
 proc opSlurp*(file: string, info: TLineInfo, module: PSym): string = 
   try:
-    let filename = file.FindFile
+    let filename = file.findFile
     result = readFile(filename)
     # we produce a fake include statement for every slurped filename, so that
     # the module dependencies are accurate:
     appendToModule(module, newNode(nkIncludeStmt, info, @[
       newStrNode(nkStrLit, filename)]))
   except EIO:
+    localError(info, errCannotOpenFile, file)
     result = ""
-    LocalError(info, errCannotOpenFile, file)
-
-when false:
-  proc opExpandToAst*(c: PEvalContext, original: PNode): PNode =
-    var
-      n = original.copyTree
-      macroCall = n.sons[1]
-      expandedSym = macroCall.sons[0].sym
-
-    for i in countup(1, macroCall.sonsLen - 1):
-      macroCall.sons[i] = evalAux(c, macroCall.sons[i], {})
-
-    case expandedSym.kind
-    of skTemplate:
-      let genSymOwner = if c.tos != nil and c.tos.prc != nil:
-                          c.tos.prc 
-                        else:
-                          c.module
-      result = evalTemplate(macroCall, expandedSym, genSymOwner)
-    of skMacro:
-      # At this point macroCall.sons[0] is nkSym node.
-      # To be completely compatible with normal macro invocation,
-      # we want to replace it with nkIdent node featuring
-      # the original unmangled macro name.
-      macroCall.sons[0] = newIdentNode(expandedSym.name, expandedSym.info)
-      result = evalMacroCall(c, macroCall, original, expandedSym)
-    else:
-      InternalError(macroCall.info,
-        "ExpandToAst: expanded symbol is no macro or template")
-      result = emptyNode
-
-  proc opIs*(n: PNode): PNode =
-    InternalAssert n.sonsLen == 3 and
-      n[1].kind == nkSym and n[1].sym.kind == skType and
-      n[2].kind in {nkStrLit..nkTripleStrLit, nkType}
-    
-    let t1 = n[1].sym.typ
-
-    if n[2].kind in {nkStrLit..nkTripleStrLit}:
-      case n[2].strVal.normalize
-      of "closure":
-        let t = skipTypes(t1, abstractRange)
-        result = newIntNode(nkIntLit, ord(t.kind == tyProc and
-                                          t.callConv == ccClosure and 
-                                          tfIterator notin t.flags))
-      of "iterator":
-        let t = skipTypes(t1, abstractRange)
-        result = newIntNode(nkIntLit, ord(t.kind == tyProc and
-                                          t.callConv == ccClosure and 
-                                          tfIterator in t.flags))
-    else:
-      let t2 = n[2].typ
-      var match = if t2.kind == tyTypeClass: matchTypeClass(t2, t1)
-                  else: sameType(t1, t2)
-      result = newIntNode(nkIntLit, ord(match))
-
-    result.typ = n.typ
-
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index 84d82e117..a41e60e7d 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -11,19 +11,22 @@
 
 import
   unsigned, strutils, ast, astalgo, types, msgs, renderer, vmdef, 
-  trees, intsets, rodread, magicsys
+  trees, intsets, rodread, magicsys, options
 
-proc codeListing(c: PCtx, result: var string) =
+when hasFFI:
+  import evalffi
+
+proc codeListing(c: PCtx, result: var string, start=0) =
   # first iteration: compute all necessary labels:
   var jumpTargets = initIntSet()
   
-  for i in 0.. < c.code.len:
+  for i in start.. < c.code.len:
     let x = c.code[i]
     if x.opcode in relativeJumps:
       jumpTargets.incl(i+x.regBx-wordExcess)
 
   # for debugging purposes
-  var i = 0
+  var i = start
   while i < c.code.len:
     if i in jumpTargets: result.addf("L$1:\n", i)
     let x = c.code[i]
@@ -45,9 +48,9 @@ proc codeListing(c: PCtx, result: var string) =
     result.add("\n")
     inc i
 
-proc echoCode*(c: PCtx) =
+proc echoCode*(c: PCtx, start=0) {.deprecated.} =
   var buf = ""
-  codeListing(c, buf)
+  codeListing(c, buf, start)
   echo buf
 
 proc gABC(ctx: PCtx; n: PNode; opc: TOpcode; a, b, c: TRegister = 0) =
@@ -58,7 +61,7 @@ proc gABC(ctx: PCtx; n: PNode; opc: TOpcode; a, b, c: TRegister = 0) =
   ctx.code.add(ins)
   ctx.debug.add(n.info)
 
-proc gABI(c: PCtx; n: PNode; opc: TOpcode; a, b: TRegister; imm: biggestInt) =
+proc gABI(c: PCtx; n: PNode; opc: TOpcode; a, b: TRegister; imm: BiggestInt) =
   let ins = (opc.uint32 or (a.uint32 shl 8'u32) or
                            (b.uint32 shl 16'u32) or
                            (imm+byteExcess).uint32 shl 24'u32).TInstr
@@ -82,7 +85,7 @@ proc genLabel(c: PCtx): TPosition =
 
 proc jmpBack(c: PCtx, n: PNode, opc: TOpcode, p = TPosition(0)) =
   let dist = p.int - c.code.len
-  InternalAssert(-0x7fff < dist and dist < 0x7fff)
+  internalAssert(-0x7fff < dist and dist < 0x7fff)
   gABx(c, n, opc, 0, dist)
 
 proc patch(c: PCtx, p: TPosition) =
@@ -90,7 +93,7 @@ proc patch(c: PCtx, p: TPosition) =
   let p = p.int
   let diff = c.code.len - p
   #c.jumpTargets.incl(c.code.len)
-  InternalAssert(-0x7fff < diff and diff < 0x7fff)
+  internalAssert(-0x7fff < diff and diff < 0x7fff)
   let oldInstr = c.code[p]
   # opcode and regA stay the same:
   c.code[p] = ((oldInstr.uint32 and 0xffff'u32).uint32 or
@@ -112,8 +115,10 @@ const
 
 proc getTemp(c: PCtx; typ: PType): TRegister =
   let c = c.prc
-  # we prefer the same slot kind here for efficiency:
-  let k = typ.getSlotKind
+  # we prefer the same slot kind here for efficiency. Unfortunately for
+  # discardable return types we may not know the desired type. This can happen
+  # for e.g. mNAdd[Multiple]:
+  let k = if typ.isNil: slotTempComplex else: typ.getSlotKind
   for i in 0 .. c.maxSlots-1:
     if c.slots[i].kind == k and not c.slots[i].inUse:
       c.slots[i].inUse = true
@@ -129,6 +134,21 @@ proc getTemp(c: PCtx; typ: PType): TRegister =
   c.slots[c.maxSlots] = (inUse: true, kind: k)
   inc c.maxSlots
 
+proc getGlobalSlot(c: PCtx; n: PNode; s: PSym): TRegister =
+  let p = c.prc
+  for i in 0 .. p.maxSlots-1:
+    if p.globals[i] == s.id: return TRegister(i)
+
+  result = TRegister(p.maxSlots)
+  p.slots[p.maxSlots] = (inUse: true, kind: slotFixedVar)
+  p.globals[p.maxSlots] = s.id
+  inc p.maxSlots
+  # XXX this is still not correct! We need to load the global in a proc init
+  # section, otherwise control flow could lead to a usage before it's been
+  # loaded.
+  c.gABx(n, opcGlobalAlias, result, s.position)
+  # XXX add some internal asserts here
+
 proc freeTemp(c: PCtx; r: TRegister) =
   let c = c.prc
   if c.slots[r].kind >= slotSomeTemp: c.slots[r].inUse = false
@@ -146,7 +166,7 @@ proc getTempRange(c: PCtx; n: int; kind: TSlotKind): TRegister =
           for k in result .. result+n-1: c.slots[k] = (inUse: true, kind: kind)
           return
   if c.maxSlots+n >= high(TRegister):
-    InternalError("cannot generate code; too many registers required")
+    internalError("cannot generate code; too many registers required")
   result = TRegister(c.maxSlots)
   inc c.maxSlots, n
   for k in result .. result+n-1: c.slots[k] = (inUse: true, kind: kind)
@@ -174,18 +194,24 @@ proc gen(c: PCtx; n: PNode; dest: var TDest)
 proc gen(c: PCtx; n: PNode; dest: TRegister) =
   var d: TDest = dest
   gen(c, n, d)
-  InternalAssert d == dest
+  internalAssert d == dest
 
 proc gen(c: PCtx; n: PNode) =
   var tmp: TDest = -1
   gen(c, n, tmp)
-  InternalAssert tmp < 0
+  #if n.typ.isEmptyType: InternalAssert tmp < 0
 
 proc genx(c: PCtx; n: PNode): TRegister =
   var tmp: TDest = -1
   gen(c, n, tmp)
+  internalAssert tmp >= 0
   result = TRegister(tmp)
 
+proc clearDest(n: PNode; dest: var TDest) {.inline.} =
+  # stmt is different from 'void' in meta programming contexts.
+  # So we only set dest to -1 if 'void':
+  if n.typ.isNil or n.typ.kind == tyEmpty: dest = -1
+
 proc isNotOpr(n: PNode): bool =
   n.kind in nkCallKinds and n.sons[0].kind == nkSym and
     n.sons[0].sym.magic == mNot
@@ -224,6 +250,7 @@ proc genWhile(c: PCtx; n: PNode) =
 proc genBlock(c: PCtx; n: PNode; dest: var TDest) =
   withBlock(n.sons[0].sym):
     c.gen(n.sons[1], dest)
+  clearDest(n, dest)
 
 proc genBreak(c: PCtx; n: PNode) =
   let L1 = c.xjmp(n, opcJmp)
@@ -233,7 +260,7 @@ proc genBreak(c: PCtx; n: PNode) =
       if c.prc.blocks[i].label == n.sons[0].sym:
         c.prc.blocks[i].fixups.add L1
         return
-    InternalError(n.info, "cannot find 'break' target")
+    internalError(n.info, "cannot find 'break' target")
   else:
     c.prc.blocks[c.prc.blocks.high].fixups.add L1
 
@@ -268,6 +295,7 @@ proc genIf(c: PCtx, n: PNode; dest: var TDest) =
     else:
       c.gen(it.sons[0], dest)
   for endPos in endings: c.patch(endPos)
+  clearDest(n, dest)
 
 proc genAndOr(c: PCtx; n: PNode; opc: TOpcode; dest: var TDest) =
   #   asgn dest, a
@@ -275,15 +303,15 @@ proc genAndOr(c: PCtx; n: PNode; opc: TOpcode; dest: var TDest) =
   #   asgn dest, b
   # L1:
   if dest < 0: dest = getTemp(c, n.typ)
-  c.gen(n.sons[0], dest)
-  let L1 = c.xjmp(n, opc)
   c.gen(n.sons[1], dest)
+  let L1 = c.xjmp(n, opc, dest)
+  c.gen(n.sons[2], dest)
   c.patch(L1)
 
 proc rawGenLiteral(c: PCtx; n: PNode): int =
   result = c.constants.len
   c.constants.add n
-  InternalAssert result < 0x7fff
+  internalAssert result < 0x7fff
 
 proc sameConstant*(a, b: PNode): bool =
   result = false
@@ -296,7 +324,8 @@ proc sameConstant*(a, b: PNode): bool =
     of nkCharLit..nkInt64Lit: result = a.intVal == b.intVal
     of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal
     of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal
-    of nkEmpty, nkNilLit, nkType: result = true
+    of nkType: result = a.typ == b.typ
+    of nkEmpty, nkNilLit: result = true
     else: 
       if sonsLen(a) == sonsLen(b): 
         for i in countup(0, sonsLen(a) - 1): 
@@ -309,6 +338,11 @@ proc genLiteral(c: PCtx; n: PNode): int =
     if sameConstant(c.constants[i], n): return i
   result = rawGenLiteral(c, n)
 
+proc unused(n: PNode; x: TDest) {.inline.} =
+  if x >= 0: 
+    #debug(n)
+    internalError(n.info, "not unused")
+
 proc genCase(c: PCtx; n: PNode; dest: var TDest) =
   #  if (!expr1) goto L1;
   #    thenPart
@@ -320,7 +354,10 @@ proc genCase(c: PCtx; n: PNode; dest: var TDest) =
   #  L2:
   #    elsePart
   #  Lend:
-  if dest < 0 and not isEmptyType(n.typ): dest = getTemp(c, n.typ)
+  if not isEmptyType(n.typ):
+    if dest < 0: dest = getTemp(c, n.typ)
+  else:
+    unused(n, dest)
   var endings: seq[TPosition] = @[]
   withTemp(tmp, n.sons[0].typ):
     c.gen(n.sons[0], tmp)
@@ -340,6 +377,7 @@ proc genCase(c: PCtx; n: PNode; dest: var TDest) =
           endings.add(c.xjmp(it.lastSon, opcJmp, 0))
         c.patch(elsePos)
   for endPos in endings: c.patch(endPos)
+  clearDest(n, dest)
 
 proc genType(c: PCtx; typ: PType): int =
   for i, t in c.types:
@@ -379,6 +417,7 @@ proc genTry(c: PCtx; n: PNode; dest: var TDest) =
   if fin.kind == nkFinally:
     c.gen(fin.sons[0], dest)
   c.gABx(fin, opcFinallyEnd, 0, 0)
+  clearDest(n, dest)
 
 proc genRaise(c: PCtx; n: PNode) =
   let dest = genx(c, n.sons[0])
@@ -393,30 +432,57 @@ proc genReturn(c: PCtx; n: PNode) =
 proc genCall(c: PCtx; n: PNode; dest: var TDest) =
   if dest < 0 and not isEmptyType(n.typ): dest = getTemp(c, n.typ)
   let x = c.getTempRange(n.len, slotTempUnknown)
-  for i in 0.. <n.len: 
+  # varargs need 'opcSetType' for the FFI support:
+  let fntyp = n.sons[0].typ
+  for i in 0.. <n.len:
     var r: TRegister = x+i
     c.gen(n.sons[i], r)
+    if i >= fntyp.len:
+      internalAssert tfVarargs in fntyp.flags
+      c.gABx(n, opcSetType, r, c.genType(n.sons[i].typ))
   if dest < 0:
     c.gABC(n, opcIndCall, 0, x, n.len)
   else:
     c.gABC(n, opcIndCallAsgn, dest, x, n.len)
   c.freeTempRange(x, n.len)
 
+proc needsAsgnPatch(n: PNode): bool = 
+  n.kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr}
+
+proc genAsgnPatch(c: PCtx; le: PNode, value: TRegister) =
+  case le.kind
+  of nkBracketExpr:
+    let dest = c.genx(le.sons[0])
+    let idx = c.genx(le.sons[1])
+    c.gABC(le, opcWrArrRef, dest, idx, value)
+  of nkDotExpr, nkCheckedFieldExpr:
+    # XXX field checks here
+    let left = if le.kind == nkDotExpr: le else: le.sons[0]
+    let dest = c.genx(left.sons[0])
+    let idx = c.genx(left.sons[1])
+    c.gABC(left, opcWrObjRef, dest, idx, value)
+  else:
+    discard
+
 proc genNew(c: PCtx; n: PNode) =
-  let dest = c.genx(n.sons[1])
+  let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(n.sons[1].typ)
+             else: c.genx(n.sons[1])
   # we use the ref's base type here as the VM conflates 'ref object' 
   # and 'object' since internally we already have a pointer.
   c.gABx(n, opcNew, dest, 
          c.genType(n.sons[1].typ.skipTypes(abstractVar).sons[0]))
+  c.genAsgnPatch(n.sons[1], dest)
   c.freeTemp(dest)
 
 proc genNewSeq(c: PCtx; n: PNode) =
-  let dest = c.genx(n.sons[1])
+  let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(n.sons[1].typ)
+             else: c.genx(n.sons[1])
   c.gABx(n, opcNewSeq, dest, c.genType(n.sons[1].typ.skipTypes(abstractVar)))
   let tmp = c.genx(n.sons[2])
   c.gABx(n, opcNewSeq, tmp, 0)
-  c.freeTemp(dest)
   c.freeTemp(tmp)
+  c.genAsgnPatch(n.sons[1], dest)
+  c.freeTemp(dest)
 
 proc genUnaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   let tmp = c.genx(n.sons[1])
@@ -463,7 +529,7 @@ proc genBinaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
   c.freeTemp(tmp)
 
 proc genUnaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
-  let tmp = c.genx(n.sons[2])
+  let tmp = c.genx(n.sons[1])
   c.gABC(n, opc, tmp, 0, 0)
   c.freeTemp(tmp)
 
@@ -493,9 +559,6 @@ proc genAddSubInt(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   else:
     genBinaryABC(c, n, dest, opc)
 
-proc unused(n: PNode; x: TDest) {.inline.} =
-  if x >= 0: InternalError(n.info, "not unused")
-
 proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) =  
   let tmp = c.genx(arg)
   c.gABx(n, opcSetType, tmp, genType(c, arg.typ))
@@ -508,7 +571,7 @@ proc genCard(c: PCtx; n: PNode; dest: var TDest) =
   let tmp = c.genx(n.sons[1])
   if dest < 0: dest = c.getTemp(n.typ)
   c.genSetType(n.sons[1], tmp)
-  c.gABC(n, opc, dest, tmp)
+  c.gABC(n, opcCard, dest, tmp)
   c.freeTemp(tmp)
 
 proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
@@ -529,6 +592,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
     unused(n, dest)
     var d = c.genx(n.sons[1]).TDest
     c.genAddSubInt(n, d, if m == mInc: opcAddInt else: opcSubInt)
+    c.genAsgnPatch(n.sons[1], d)
     c.freeTemp(d.TRegister)
   of mOrd, mChr, mArrToSeq: c.gen(n.sons[1], dest)
   of mNew, mNewFinalize:
@@ -624,6 +688,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
     var d = c.genx(n.sons[1])
     var tmp = c.genx(n.sons[2])
     c.gABC(n, if m == mSetLengthStr: opcSetLenStr else: opcSetLenSeq, d, tmp)
+    c.genAsgnPatch(n.sons[1], d)
     c.freeTemp(tmp)
   of mSwap: 
     unused(n, dest)
@@ -639,8 +704,8 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
       tmp2 = c.genx(n.sons[2])
       tmp3 = c.getTemp(n.sons[2].typ)
     c.gABC(n, opcLenStr, tmp3, tmp1)
-    c.gABC(n, opcSubstr, dest, tmp1, tmp2)
-    c.gABC(n, opcSubstr, tmp3)
+    c.gABC(n, opcSubStr, dest, tmp1, tmp2)
+    c.gABC(n, opcSubStr, tmp3)
     c.freeTemp(tmp1)
     c.freeTemp(tmp2)
     c.freeTemp(tmp3)
@@ -650,8 +715,8 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
       tmp1 = c.genx(n.sons[1])
       tmp2 = c.genx(n.sons[2])
       tmp3 = c.genx(n.sons[3])
-    c.gABC(n, opcSubstr, dest, tmp1, tmp2)
-    c.gABC(n, opcSubstr, tmp3)
+    c.gABC(n, opcSubStr, dest, tmp1, tmp2)
+    c.gABC(n, opcSubStr, tmp3)
     c.freeTemp(tmp1)
     c.freeTemp(tmp2)
     c.freeTemp(tmp3)
@@ -659,14 +724,18 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
     unused(n, dest)
     var d = c.genx(n.sons[1])
     c.gABC(n, opcReset, d)
-  of mOf: 
+  of mOf, mIs:
     if dest < 0: dest = c.getTemp(n.typ)
     var tmp = c.genx(n.sons[1])
-    c.gABC(n, opcOf, dest, tmp)
-    c.gABx(n, opcOf, 0, c.genType(n.sons[2].typ.skipTypes(abstractPtrs)))
+    var idx = c.getTemp(getSysType(tyInt))
+    var typ = n.sons[2].typ
+    if m == mOf: typ = typ.skipTypes(abstractPtrs)
+    c.gABx(n, opcLdImmInt, idx, c.genType(typ))
+    c.gABC(n, if m == mOf: opcOf else: opcIs, dest, tmp, idx)
     c.freeTemp(tmp)
+    c.freeTemp(idx)
   of mSizeOf:
-    GlobalError(n.info, errCannotInterpretNodeX, renderTree(n))
+    globalError(n.info, errCannotInterpretNodeX, renderTree(n))
   of mHigh:
     if dest < 0: dest = c.getTemp(n.typ)
     let tmp = c.genx(n.sons[1])
@@ -696,16 +765,12 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
     genUnaryABC(c, n, dest, opcParseExprToAst)
   of mParseStmtToAst:
     genUnaryABC(c, n, dest, opcParseStmtToAst)
-  of mExpandToAst:
-    InternalError(n.info, "cannot generate code for: " & $m)
   of mTypeTrait: 
     let tmp = c.genx(n.sons[1])
     if dest < 0: dest = c.getTemp(n.typ)
-    c.gABx(n, opcSetType, tmp, c.genType(n.sons[1]))
+    c.gABx(n, opcSetType, tmp, c.genType(n.sons[1].typ))
     c.gABC(n, opcTypeTrait, dest, tmp)
     c.freeTemp(tmp)
-  of mIs:
-    InternalError(n.info, "cannot generate code for: " & $m)
   of mSlurp: genUnaryABC(c, n, dest, opcSlurp)
   of mStaticExec: genBinaryABC(c, n, dest, opcGorge)
   of mNLen: genUnaryABI(c, n, dest, opcLenSeq)
@@ -750,11 +815,17 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
   of mNNewNimNode: genBinaryABC(c, n, dest, opcNNewNimNode)
   of mNCopyNimNode: genUnaryABC(c, n, dest, opcNCopyNimNode)
   of mNCopyNimTree: genUnaryABC(c, n, dest, opcNCopyNimTree)
-  of mNBindSym: genUnaryABC(c, n, dest, opcNBindSym)
+  of mNBindSym:
+    if n[1].kind in {nkClosedSymChoice, nkOpenSymChoice, nkSym}:
+      let idx = c.genLiteral(n[1])
+      if dest < 0: dest = c.getTemp(n.typ)
+      c.gABx(n, opcNBindSym, dest, idx)
+    else:
+      internalError(n.info, "invalid bindSym usage")
   of mStrToIdent: genUnaryABC(c, n, dest, opcStrToIdent)
   of mIdentToStr: genUnaryABC(c, n, dest, opcIdentToStr)
   of mEqIdent: genBinaryABC(c, n, dest, opcEqIdent)
-  of mEqNimrodNode: genBinaryABC(c, n, dest, opcEqRef)
+  of mEqNimrodNode: genBinaryABC(c, n, dest, opcEqNimrodNode)
   of mNLineInfo: genUnaryABC(c, n, dest, opcNLineInfo)
   of mNHint: 
     unused(n, dest)
@@ -771,13 +842,27 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) =
   of mNGenSym: genBinaryABC(c, n, dest, opcGenSym)
   of mMinI, mMaxI, mMinI64, mMaxI64, mAbsF64, mMinF64, mMaxF64, mAbsI, mAbsI64:
     c.genCall(n, dest)
+    clearDest(n, dest)
+  of mExpandToAst:
+    if n.len != 2:
+      globalError(n.info, errGenerated, "expandToAst requires 1 argument")
+    let arg = n.sons[1]
+    if arg.kind in nkCallKinds:
+      #if arg[0].kind != nkSym or arg[0].sym.kind notin {skTemplate, skMacro}:
+      #      "ExpandToAst: expanded symbol is no macro or template"
+      if dest < 0: dest = c.getTemp(n.typ)
+      c.genCall(arg, dest)
+      # do not call clearDest(n, dest) here as getAst has a meta-type as such
+      # produces a value
+    else:
+      globalError(n.info, "expandToAst requires a call expression")
   else:
     # mGCref, mGCunref, 
-    InternalError(n.info, "cannot generate code for: " & $m)
+    internalError(n.info, "cannot generate code for: " & $m)
 
 const
   atomicTypes = {tyBool, tyChar,
-    tyExpr, tyStmt, tyTypeDesc,
+    tyExpr, tyStmt, tyTypeDesc, tyStatic,
     tyEnum,
     tyOrdinal,
     tyRange,
@@ -823,7 +908,7 @@ proc whichAsgnOpc(n: PNode): TOpcode =
     opcAsgnStr
   of tyFloat..tyFloat128:
     opcAsgnFloat
-  of tyRef, tyNil:
+  of tyRef, tyNil, tyVar:
     opcAsgnRef
   else:
     opcAsgnComplex
@@ -839,6 +924,8 @@ proc genAsgn(c: PCtx; dest: TDest; ri: PNode; requiresCopy: bool) =
   gABC(c, ri, whichAsgnOpc(ri), dest, tmp)
   c.freeTemp(tmp)
 
+template isGlobal(s: PSym): bool = sfGlobal in s.flags and s.kind != skForVar
+
 proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
   case le.kind
   of nkBracketExpr:
@@ -850,21 +937,23 @@ proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
     else:
       c.gABC(le, whichAsgnOpc(le, opcWrArr), dest, idx, tmp)
     c.freeTemp(tmp)
-  of nkDotExpr:
-    let dest = c.genx(le.sons[0])
-    let idx = c.genx(le.sons[1])
+  of nkDotExpr, nkCheckedFieldExpr:
+    # XXX field checks here
+    let left = if le.kind == nkDotExpr: le else: le.sons[0]
+    let dest = c.genx(left.sons[0])
+    let idx = c.genx(left.sons[1])
     let tmp = c.genx(ri)
-    c.gABC(le, whichAsgnOpc(le, opcWrObj), dest, idx, tmp)
+    c.gABC(left, whichAsgnOpc(left, opcWrObj), dest, idx, tmp)
     c.freeTemp(tmp)
   of nkSym:
     let s = le.sym
-    if sfGlobal in s.flags:
+    if s.isGlobal:
       withTemp(tmp, le.typ):
         gen(c, ri, tmp)
         c.gABx(le, whichAsgnOpc(le, opcWrGlobal), tmp, s.position)
     else:
-      InternalAssert s.position > 0 or (s.position == 0 and
-                                        s.kind in {skParam, skResult})
+      internalAssert s.position > 0 or (s.position == 0 and
+                                        s.kind in {skParam,skResult,skForVar})
       var dest: TRegister = s.position + ord(s.kind == skParam)
       gen(c, ri, dest)
   else:
@@ -878,24 +967,64 @@ proc genLit(c: PCtx; n: PNode; dest: var TDest) =
   let lit = genLiteral(c, n)
   c.gABx(n, opc, dest, lit)
 
+proc genTypeLit(c: PCtx; t: PType; dest: var TDest) =
+  var n = newNode(nkType)
+  n.typ = t
+  genLit(c, n, dest)
+
+proc importcSym(c: PCtx; info: TLineInfo; s: PSym) =
+  when hasFFI:
+    if allowFFI in c.features:
+      c.globals.add(importcSymbol(s))
+      s.position = c.globals.len
+    else:
+      localError(info, errGenerated, "VM is not allowed to 'importc'")
+  else:
+    localError(info, errGenerated,
+               "cannot 'importc' variable at compile time")
+
+proc cannotEval(n: PNode) {.noinline.} =
+  globalError(n.info, errGenerated, "cannot evaluate at compile time: " &
+    n.renderTree)
+
+proc genGlobalInit(c: PCtx; n: PNode; s: PSym) =
+  c.globals.add(emptyNode.copyNode)
+  s.position = c.globals.len
+  # This is rather hard to support, due to the laziness of the VM code
+  # generator. See tests/compile/tmacro2 for why this is necesary:
+  #   var decls{.compileTime.}: seq[PNimrodNode] = @[]
+  c.gABx(n, opcGlobalOnce, 0, s.position)
+  let tmp = c.genx(s.ast)
+  c.gABx(n, whichAsgnOpc(n, opcWrGlobal), tmp, s.position)
+  c.freeTemp(tmp)
+
 proc genRdVar(c: PCtx; n: PNode; dest: var TDest) =
   let s = n.sym
-  if sfGlobal in s.flags:
-    if dest < 0: dest = c.getTemp(s.typ)
+  if s.isGlobal:
+    if sfCompileTime in s.flags or c.mode == emRepl:
+      discard
+    else:
+      cannotEval(n)
     if s.position == 0:
-      c.globals.add(s.ast)
-      s.position = c.globals.len
-      # XXX var g = codeHere() ?
-    c.gABx(n, opcLdGlobal, dest, s.position)
+      if sfImportc in s.flags: c.importcSym(n.info, s)
+      else: genGlobalInit(c, n, s)
+    if dest < 0:
+      dest = c.getGlobalSlot(n, s)
+      #c.gABx(n, opcAliasGlobal, dest, s.position)
+    else:
+      c.gABx(n, opcLdGlobal, dest, s.position)
   else:
-    if s.position > 0 or (s.position == 0 and s.kind in {skParam, skResult}):
+    if s.position > 0 or (s.position == 0 and
+                          s.kind in {skParam,skResult,skForVar}):
       if dest < 0:
         dest = s.position + ord(s.kind == skParam)
       else:
         # we need to generate an assignment:
         genAsgn(c, dest, n, c.prc.slots[dest].kind >= slotSomeTemp)
     else:
-      InternalError(n.info, s.name.s & " " & $s.position)
+      # see tests/t99bott for an example that triggers it:
+      cannotEval(n)
+      #InternalError(n.info, s.name.s & " " & $s.position)
 
 proc genAccess(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
   let a = c.genx(n.sons[0])
@@ -908,6 +1037,10 @@ proc genAccess(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
 proc genObjAccess(c: PCtx; n: PNode; dest: var TDest) =
   genAccess(c, n, dest, opcLdObj)
 
+proc genCheckedObjAccess(c: PCtx; n: PNode; dest: var TDest) =
+  # XXX implement field checks!
+  genAccess(c, n.sons[0], dest, opcLdObj)
+
 proc genArrAccess(c: PCtx; n: PNode; dest: var TDest) =
   if n.sons[0].typ.skipTypes(abstractVarRange).kind in {tyString, tyCString}:
     genAccess(c, n, dest, opcLdStrIdx)
@@ -925,7 +1058,7 @@ proc getNullValueAux(obj: PNode, result: PNode) =
       getNullValueAux(lastSon(obj.sons[i]), result)
   of nkSym:
     addSon(result, getNullValue(obj.sym.typ, result.info))
-  else: InternalError(result.info, "getNullValueAux")
+  else: internalError(result.info, "getNullValueAux")
   
 proc getNullValue(typ: PType, info: TLineInfo): PNode = 
   var t = skipTypes(typ, abstractRange-{tyTypeDesc})
@@ -936,10 +1069,17 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
   of tyUInt..tyUInt64:
     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:
+    result = newNodeIT(nkFloatLit, info, t)
+  of tyVar, tyPointer, tyPtr, tyCString, tySequence, tyString, tyExpr,
+     tyStmt, tyTypeDesc, tyStatic, tyRef:
     result = newNodeIT(nkNilLit, info, t)
+  of tyProc:
+    if t.callConv != ccClosure:
+      result = newNodeIT(nkNilLit, info, t)
+    else:
+      result = newNodeIT(nkPar, info, t)
+      result.add(newNodeIT(nkNilLit, info, t))
+      result.add(newNodeIT(nkNilLit, info, t))
   of tyObject: 
     result = newNodeIT(nkPar, info, t)
     getNullValueAux(t.n, result)
@@ -958,7 +1098,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode =
       addSon(result, getNullValue(t.sons[i], info))
   of tySet:
     result = newNodeIT(nkCurly, info, t)
-  else: InternalError("getNullValue: " & $t.kind)
+  else: internalError("getNullValue: " & $t.kind)
 
 proc setSlot(c: PCtx; v: PSym) =
   # XXX generate type initialization here?
@@ -984,11 +1124,14 @@ proc genVarSection(c: PCtx; n: PNode) =
       c.freeTemp(tmp)
     elif a.sons[0].kind == nkSym:
       let s = a.sons[0].sym
-      if sfGlobal in s.flags:
+      if s.isGlobal:
         if s.position == 0:
-          let sa = if s.ast.isNil: getNullValue(s.typ, a.info) else: s.ast
-          c.globals.add(sa)
-          s.position = c.globals.len
+          if sfImportc in s.flags: c.importcSym(a.info, s)
+          else:
+            let sa = if s.ast.isNil: getNullValue(s.typ, a.info) else: s.ast
+            c.globals.add(sa)
+            s.position = c.globals.len
+            # "Once support" is unnecessary here
         if a.sons[2].kind == nkEmpty:
           when false:
             withTemp(tmp, s.typ):
@@ -1016,23 +1159,31 @@ proc genVarSection(c: PCtx; n: PNode) =
 proc genArrayConstr(c: PCtx, n: PNode, dest: var TDest) =
   if dest < 0: dest = c.getTemp(n.typ)
   c.gABx(n, opcLdNull, dest, c.genType(n.typ))
-  let intType = getSysType(tyInt)
-  var tmp = getTemp(c, intType)
-  c.gABx(n, opcLdNull, tmp, c.genType(intType))
-  for x in n:
-    let a = c.genx(x)
-    c.gABC(n, opcWrArr, dest, a, tmp)
-    c.gABI(n, opcAddImmInt, tmp, tmp, 1)
-    c.freeTemp(a)
-  c.freeTemp(tmp)
+  if n.len > 0:
+    let intType = getSysType(tyInt)
+    var tmp = getTemp(c, intType)
+    c.gABx(n, opcLdNull, tmp, c.genType(intType))
+    for x in n:
+      let a = c.genx(x)
+      c.gABC(n, whichAsgnOpc(x, opcWrArr), dest, tmp, a)
+      c.gABI(n, opcAddImmInt, tmp, tmp, 1)
+      c.freeTemp(a)
+    c.freeTemp(tmp)
 
 proc genSetConstr(c: PCtx, n: PNode, dest: var TDest) =
   if dest < 0: dest = c.getTemp(n.typ)
   c.gABx(n, opcLdNull, dest, c.genType(n.typ))
   for x in n:
-    let a = c.genx(x)
-    c.gABC(n, opcIncl, dest, a)
-    c.freeTemp(a)
+    if x.kind == nkRange:
+      let a = c.genx(x.sons[0])
+      let b = c.genx(x.sons[1])
+      c.gABC(n, opcInclRange, dest, a, b)
+      c.freeTemp(b)
+      c.freeTemp(a)
+    else:
+      let a = c.genx(x)
+      c.gABC(n, opcIncl, dest, a)
+      c.freeTemp(a)
 
 proc genObjConstr(c: PCtx, n: PNode, dest: var TDest) =
   if dest < 0: dest = c.getTemp(n.typ)
@@ -1054,7 +1205,8 @@ proc genObjConstr(c: PCtx, n: PNode, dest: var TDest) =
 
 proc genTupleConstr(c: PCtx, n: PNode, dest: var TDest) =
   if dest < 0: dest = c.getTemp(n.typ)
-  var idx = getTemp(c, getSysType(tyInt))
+  c.gABx(n, opcLdNull, dest, c.genType(n.typ))
+  # XXX x = (x.old, 22)  produces wrong code ... stupid self assignments
   for i in 0.. <n.len:
     let it = n.sons[i]
     if it.kind == nkExprColonExpr:
@@ -1065,10 +1217,8 @@ proc genTupleConstr(c: PCtx, n: PNode, dest: var TDest) =
       c.freeTemp(idx)
     else:
       let tmp = c.genx(it)
-      c.gABx(it, opcLdImmInt, idx, i)
-      c.gABC(it, whichAsgnOpc(it, opcWrObj), dest, idx, tmp)
+      c.gABC(it, whichAsgnOpc(it, opcWrObj), dest, i.TRegister, tmp)
       c.freeTemp(tmp)
-  c.freeTemp(idx)
 
 proc genProc*(c: PCtx; s: PSym): int
 
@@ -1079,7 +1229,9 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) =
     case s.kind
     of skVar, skForVar, skTemp, skLet, skParam, skResult:
       genRdVar(c, n, dest)
-    of skProc, skConverter, skMacro, skMethod, skIterator:
+    of skProc, skConverter, skMacro, skTemplate, skMethod, skIterator:
+      # 'skTemplate' is only allowed for 'getAst' support:
+      if sfImportc in s.flags: c.importcSym(n.info, s)
       genLit(c, n, dest)
     of skConst:
       gen(c, s.ast, dest)
@@ -1091,29 +1243,36 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) =
         var lit = genLiteral(c, newIntNode(nkIntLit, s.position))
         c.gABx(n, opcLdConst, dest, lit)
     of skField:
-      InternalAssert dest < 0
+      internalAssert dest < 0
       if s.position > high(dest):
-        InternalError(n.info, 
+        internalError(n.info, 
           "too large offset! cannot generate code for: " & s.name.s)
       dest = s.position
+    of skType:
+      genTypeLit(c, s.typ, dest)
     else:
-      InternalError(n.info, "cannot generate code for: " & s.name.s)
+      internalError(n.info, "cannot generate code for: " & s.name.s)
   of nkCallKinds:
     if n.sons[0].kind == nkSym and n.sons[0].sym.magic != mNone:
       genMagic(c, n, dest)
     else:
       genCall(c, n, dest)
+      clearDest(n, dest)
   of nkCharLit..nkInt64Lit:
     if isInt16Lit(n):
       if dest < 0: dest = c.getTemp(n.typ)
       c.gABx(n, opcLdImmInt, dest, n.intVal.int)
     else:
       genLit(c, n, dest)
-  of nkUIntLit..nkNilLit: genLit(c, n, dest)
+  of nkUIntLit..pred(nkNilLit): genLit(c, n, dest)
+  of nkNilLit:
+    if not n.typ.isEmptyType: genLit(c, n, dest)
+    else: unused(n, dest)
   of nkAsgn, nkFastAsgn: 
     unused(n, dest)
     genAsgn(c, n.sons[0], n.sons[1], n.kind == nkAsgn)
   of nkDotExpr: genObjAccess(c, n, dest)
+  of nkCheckedFieldExpr: genCheckedObjAccess(c, n, dest)
   of nkBracketExpr: genArrAccess(c, n, dest)
   of nkDerefExpr, nkHiddenDeref: genAddrDeref(c, n, dest, opcDeref)
   of nkAddr, nkHiddenAddr: genAddrDeref(c, n, dest, opcAddr)
@@ -1168,7 +1327,7 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) =
     else:
       dest = tmp0
   of nkEmpty, nkCommentStmt, nkTypeSection, nkConstSection, nkPragma,
-     nkTemplateDef, nkIncludeStmt, nkImportStmt:
+     nkTemplateDef, nkIncludeStmt, nkImportStmt, nkFromStmt:
     unused(n, dest)
   of nkStringToCString, nkCStringToString:
     gen(c, n.sons[0], dest)
@@ -1176,8 +1335,13 @@ proc gen(c: PCtx; n: PNode; dest: var TDest) =
   of nkCurly: genSetConstr(c, n, dest)
   of nkObjConstr: genObjConstr(c, n, dest)
   of nkPar, nkClosure: genTupleConstr(c, n, dest)
+  of nkCast:
+    if allowCast in c.features:
+      genConv(c, n, n.sons[1], dest, opcCast)
+    else:
+      localError(n.info, errGenerated, "VM is not allowed to 'cast'")
   else:
-    InternalError n.info, "too implement " & $n.kind
+    internalError n.info, "too implement " & $n.kind
 
 proc removeLastEof(c: PCtx) =
   let last = c.code.len-1
@@ -1193,14 +1357,16 @@ proc genStmt*(c: PCtx; n: PNode): int =
   var d: TDest = -1
   c.gen(n, d)
   c.gABC(n, opcEof)
-  InternalAssert d < 0
+  if d >= 0: internalError(n.info, "some destination set")
 
-proc genExpr*(c: PCtx; n: PNode): int =
+proc genExpr*(c: PCtx; n: PNode, requiresValue = true): int =
   c.removeLastEof
   result = c.code.len
   var d: TDest = -1
   c.gen(n, d)
-  InternalAssert d >= 0
+  if d < 0:
+    if requiresValue: internalError(n.info, "no destination set")
+    d = 0
   c.gABC(n, opcEof, d)
 
 proc genParams(c: PCtx; params: PNode) =
@@ -1212,7 +1378,7 @@ proc genParams(c: PCtx; params: PNode) =
   c.prc.maxSlots = max(params.len, 1)
 
 proc finalJumpTarget(c: PCtx; pc, diff: int) =
-  InternalAssert(-0x7fff < diff and diff < 0x7fff)
+  internalAssert(-0x7fff < diff and diff < 0x7fff)
   let oldInstr = c.code[pc]
   # opcode and regA stay the same:
   c.code[pc] = ((oldInstr.uint32 and 0xffff'u32).uint32 or
@@ -1225,12 +1391,11 @@ proc optimizeJumps(c: PCtx; start: int) =
     case opc
     of opcTJmp, opcFJmp:
       var reg = c.code[i].regA
-      var d = i + c.code[i].regBx
-      var iters = maxIterations
-      while iters > 0:
+      var d = i + c.code[i].jmpDiff
+      for iters in countdown(maxIterations, 0):
         case c.code[d].opcode
         of opcJmp:
-          d = d + c.code[d].regBx
+          d = d + c.code[d].jmpDiff
         of opcTJmp, opcFJmp:
           if c.code[d].regA != reg: break
           # tjmp x, 23
@@ -1238,28 +1403,40 @@ proc optimizeJumps(c: PCtx; start: int) =
           # tjmp x, 12
           # -- we know 'x' is true, and so can jump to 12+13:
           if c.code[d].opcode == opc:
-            d = d + c.code[d].regBx
+            d = d + c.code[d].jmpDiff
           else:
             # tjmp x, 23
             # fjmp x, 22
             # We know 'x' is true so skip to the next instruction:
             d = d + 1
         else: break
-        dec iters
-      c.finalJumpTarget(i, d - i)
+      if d != i + c.code[i].jmpDiff:
+        c.finalJumpTarget(i, d - i)
     of opcJmp:
-      var d = i + c.code[i].regBx
+      var d = i + c.code[i].jmpDiff
       var iters = maxIterations
       while c.code[d].opcode == opcJmp and iters > 0:
-        d = d + c.code[d].regBx
+        d = d + c.code[d].jmpDiff
         dec iters
-      c.finalJumpTarget(i, d - i)
+      if c.code[d].opcode == opcRet:
+        # optimize 'jmp to ret' to 'ret' here
+        c.code[i] = c.code[d]
+      elif d != i + c.code[i].jmpDiff:
+        c.finalJumpTarget(i, d - i)
     else: discard
 
 proc genProc(c: PCtx; s: PSym): int =
   let x = s.ast.sons[optimizedCodePos]
   if x.kind == nkEmpty:
-    c.removeLastEof
+    #if s.name.s == "outterMacro" or s.name.s == "innerProc":
+    #  echo "GENERATING CODE FOR ", s.name.s
+    let last = c.code.len-1
+    var eofInstr: TInstr
+    if last >= 0 and c.code[last].opcode == opcEof:
+      eofInstr = c.code[last]
+      c.code.setLen(last)
+      c.debug.setLen(last)
+    #c.removeLastEof
     result = c.code.len+1 # skip the jump instruction
     s.ast.sons[optimizedCodePos] = newIntNode(nkIntLit, result)
     # thanks to the jmp we can add top level statements easily and also nest
@@ -1271,13 +1448,22 @@ proc genProc(c: PCtx; s: PSym): int =
     c.prc = p
     # iterate over the parameters and allocate space for them:
     genParams(c, s.typ.n)
+    if tfCapturesEnv in s.typ.flags:
+      #let env = s.ast.sons[paramsPos].lastSon.sym
+      #assert env.position == 2
+      c.prc.slots[c.prc.maxSlots] = (inUse: true, kind: slotFixedLet)
+      inc c.prc.maxSlots
     gen(c, body)
     # generate final 'return' statement:
     c.gABC(body, opcRet)
     c.patch(procStart)
-    c.gABC(body, opcEof)
-    s.position = c.prc.maxSlots
+    c.gABC(body, opcEof, eofInstr.regA)
+    c.optimizeJumps(result)
+    s.offset = c.prc.maxSlots
+    #if s.name.s == "rawGet":
+    #  c.echoCode(result)
+    #  echo renderTree(body)
     c.prc = oldPrc
-    #c.echoCode
   else:
+    c.prc.maxSlots = s.offset
     result = x.intVal.int
diff --git a/compiler/wordrecg.nim b/compiler/wordrecg.nim
index 39b19646e..837bb4f50 100644
--- a/compiler/wordrecg.nim
+++ b/compiler/wordrecg.nim
@@ -28,9 +28,9 @@ type
     wElif, wElse, wEnd, wEnum, wExcept, wExport,
     wFinally, wFor, wFrom, wGeneric, wIf, wImport, wIn, 
     wInclude, wInterface, wIs, wIsnot, wIterator, wLambda, wLet,
-    wMacro, wMethod, wMixin, wUsing, wMod, wNil, 
+    wMacro, wMethod, wMixin, wMod, wNil, 
     wNot, wNotin, wObject, wOf, wOr, wOut, wProc, wPtr, wRaise, wRef, wReturn, 
-    wShared, wShl, wShr, wStatic, wTemplate, wTry, wTuple, wType, wVar, 
+    wShared, wShl, wShr, wStatic, wTemplate, wTry, wTuple, wType, wUsing, wVar, 
     wWhen, wWhile, wWith, wWithout, wXor, wYield,
     
     wColon, wColonColon, wEquals, wDot, wDotDot,
@@ -95,7 +95,7 @@ const
   
   cppNimSharedKeywords* = {
     wAsm, wBreak, wCase, wConst, wContinue, wDo, wElse, wEnum, wExport,
-    wFor, wIf, wReturn, wStatic, wTemplate, wTry, wWhile, wUsing }
+    wFor, wIf, wReturn, wStatic, wTemplate, wTry, wWhile, wUsing}
 
   specialWords*: array[low(TSpecialWord)..high(TSpecialWord), string] = ["", 
     
@@ -107,11 +107,11 @@ const
     "finally", "for", "from", "generic", "if", 
     "import", "in", "include", "interface", "is", "isnot", "iterator",
     "lambda", "let",
-    "macro", "method", "mixin", "using", "mod", "nil", "not", "notin",
+    "macro", "method", "mixin", "mod", "nil", "not", "notin",
     "object", "of", "or", 
     "out", "proc", "ptr", "raise", "ref", "return",
     "shared", "shl", "shr", "static",
-    "template", "try", "tuple", "type", "var", 
+    "template", "try", "tuple", "type", "using", "var", 
     "when", "while", "with", "without", "xor",
     "yield",
 
@@ -166,7 +166,7 @@ const
     "inout", "bycopy", "byref", "oneway",
     ]
 
-proc findStr*(a: openarray[string], s: string): int = 
+proc findStr*(a: openArray[string], s: string): int = 
   for i in countup(low(a), high(a)): 
     if cmpIgnoreStyle(a[i], s) == 0: 
       return i
@@ -176,7 +176,7 @@ proc whichKeyword*(id: PIdent): TSpecialWord =
   if id.id < 0: result = wInvalid
   else: result = TSpecialWord(id.id)
 
-proc whichKeyword*(id: String): TSpecialWord = 
+proc whichKeyword*(id: string): TSpecialWord = 
   result = whichKeyword(getIdent(id))
   
 proc initSpecials() =