changeset 212:62386bcee1ba

Added parser combinator lib
author Windel Bouwman
date Sun, 30 Jun 2013 19:00:41 +0200
parents 99164160fb0b
children 003c8a976fff
files python/arm_cm3.py python/c3/astnodes.py python/codegenarm.py python/ks/__init__.py python/ks/builtin.py python/ks/irgenerator.py python/ks/lexer.py python/ks/nodes.py python/ks/parser.py python/ks/symboltable.py python/parserlib.py python/stm32f4/blink.c3 python/testasm.py python/testparserlib.py
diffstat 14 files changed, 234 insertions(+), 1467 deletions(-) [+]
line wrap: on
line diff
--- a/python/arm_cm3.py	Sat Jun 29 10:10:45 2013 +0200
+++ b/python/arm_cm3.py	Sun Jun 30 19:00:41 2013 +0200
@@ -49,6 +49,34 @@
             regs.append(r)
     return regs
 
+class MemoryOp:
+    def __init__(self, basereg, offset):
+        assert type(basereg) is ArmReg
+        self.basereg = basereg
+        self.offset = offset
+
+    @classmethod
+    def Create(cls, vop):
+        if type(vop) is AUnop and vop.operation == '[]':
+            vop = vop.arg # descent
+            if type(vop) is ABinop:
+                if vop.op == '+' and type(vop.arg1) is ASymbol and type(vop.arg2) is ANumber:
+                    offset = vop.arg2.number
+                    basereg = RegOp.Create(vop.arg1)
+                    if not basereg:
+                        return
+                else:
+                    return
+            elif type(vop) is ASymbol:
+                offset = 0
+                basereg = RegOp.Create(vop)
+                if not basereg:
+                    return
+            else:
+                return
+            return cls(getRegNum(basereg.num), offset)
+        pass
+
 class RegisterSet:
     def __init__(self, regs):
         assert type(regs) is set
@@ -124,6 +152,42 @@
         return u32(self.expr)
 
 @armtarget.instruction
+class storeimm5_ins(ArmInstruction):
+    """ str Rt, [Rn, imm5], store value into memory """
+    mnemonic = 'str'
+    operands = (RegOp, MemoryOp)
+    def __init__(self, rt, memop):
+        assert memop.offset % 4 == 0
+        self.imm5 = memop.offset >> 2
+        self.rn = memop.basereg.num
+        self.rt = rt.num
+
+    def encode(self):
+        Rn = self.rn
+        Rt = self.rt
+        imm5 = self.imm5
+        h = (0xC << 11) | (imm5 << 6) | (Rn << 3) | Rt
+        return u16(h)
+
+@armtarget.instruction
+class loadimm5_ins(ArmInstruction):
+    """ str Rt, [Rn, imm5], store value into memory """
+    mnemonic = 'ldr'
+    operands = (RegOp, MemoryOp)
+    def __init__(self, rt, memop):
+        assert memop.offset % 4 == 0
+        self.imm5 = memop.offset >> 2
+        self.rn = memop.basereg.num
+        self.rt = rt.num
+
+    def encode(self):
+        Rn = self.rn
+        Rt = self.rt
+        imm5 = self.imm5
+        h = (0xD << 11) | (imm5 << 6) | (Rn << 3) | Rt
+        return u16(h)
+
+@armtarget.instruction
 class mov_ins(ArmInstruction):
     """ mov Rd, imm8, move immediate value into register """
     mnemonic = 'mov'
--- a/python/c3/astnodes.py	Sat Jun 29 10:10:45 2013 +0200
+++ b/python/c3/astnodes.py	Sun Jun 30 19:00:41 2013 +0200
@@ -9,7 +9,7 @@
    def __init__(self, tname):
       self.tname = tname
    def __repr__(self):
-      return 'DESIGNATOR {0}'.format(self.tname)
+      return 'DESIGNATOR {}'.format(self.tname)
 
 """
 Type classes
@@ -23,7 +23,7 @@
   def __init__(self, name):
     self.name = name
   def __repr__(self):
-    return '{0}'.format(self.name)
+    return '{}'.format(self.name)
 
 class FunctionType(Type):
    def __init__(self, parametertypes, returntype):
@@ -68,7 +68,7 @@
       self.isReadOnly = False
       self.isParameter = False
    def __repr__(self):
-      return '{0}'.format(self.name)
+      return '{}'.format(self.name)
 
 # Procedure types
 class Function(Symbol):
@@ -76,7 +76,7 @@
    def __init__(self, name):
       super().__init__(name)
    def __repr__(self):
-      return '{0}'.format(self.name)
+      return '{}'.format(self.name)
 
 # Operations / Expressions:
 class Unop(Node):
@@ -84,7 +84,7 @@
       self.a = a
       self.op = op 
    def __repr__(self):
-      return 'UNOP {0}'.format(self.op)
+      return 'UNOP {}'.format(self.op)
 
 class Binop(Node):
    def __init__(self, a, op, b):
@@ -92,27 +92,27 @@
       self.b = b
       self.op = op # Operation: '+', '-', '*', '/', 'mod'
    def __repr__(self):
-      return 'BINOP {0}'.format(self.op)
+      return 'BINOP {}'.format(self.op)
 
 class VariableUse(Node):
    def __init__(self, target):
       self.target = target
    def __repr__(self):
       nm = self.target.name if hasattr(self.target, 'name') else ''
-      return 'VAR USE {0}'.format(nm)
+      return 'VAR USE {}'.format(nm)
 
 class Literal(Node):
    def __init__(self, val):
       self.val = val
    def __repr__(self):
-      return 'LITERAL {0}'.format(self.val)
+      return 'LITERAL {}'.format(self.val)
 
 # Modules
 class Package(Node):
    def __init__(self, name):
       self.name = name
    def __repr__(self):
-      return 'PACKAGE {0}'.format(self.name)
+      return 'PACKAGE {}'.format(self.name)
 
 # Statements
 class CompoundStatement(Node):
--- a/python/codegenarm.py	Sat Jun 29 10:10:45 2013 +0200
+++ b/python/codegenarm.py	Sun Jun 30 19:00:41 2013 +0200
@@ -35,6 +35,11 @@
             self.emit(arm.jmp_ins(ins.target))
         elif type(ins) is ir.ImmLoad and ins.value < 255:
             self.emit(arm.mov_ins(arm.r0, arm.Imm8(ins.value)))
+            # determine stack frame..
+            self.emit(arm.mov_ins(arm.r1, arm.Imm8(9)))
+            #self.emit(arm.
+        elif type(ins) is ir.ImmLoad and ins.value < (2**32):
+            print(ins)
         elif type(ins) is ir.Store:
             print(ins)
         elif type(ins) is ir.Return:
@@ -43,6 +48,8 @@
             print(ins)
         elif type(ins) is ir.BinaryOperator:
             print(ins)
+        elif type(ins) is ir.ConditionalBranch:
+            print(ins)
         else:
             print(ins)
             raise CompilerError('IR "{}" not covered'.format(ins))
--- a/python/ks/__init__.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,28 +0,0 @@
-
-from .parser import KsParser
-from .irgenerator import KsIrGenerator
-
-class KsFrontend:
-   """
-    Frontend for the K# language.
-
-    This module can parse K# code and create LLVM intermediate code.
-   """
-   def __init__(self, context):
-      self.context = context
-   def compilesource(self, src):
-      """ Front end that handles parsing and Module generation """
-      self.errorlist = []
-      # Pass 1: parsing and type checking
-      p = KsParser(src)
-      ast = p.parseModule() # Parse source into an AST
-      print(ast)
-
-      # Store ast:
-      self.ast = ast
-
-      # Generate ir (a core.Module):
-      ir = KsIrGenerator().generateIr(self.context, ast)
-
-      return ir
-
--- a/python/ks/builtin.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,10 +0,0 @@
-from .nodes import *
-
-boolean = BaseType('boolean', 8)
-integer = BaseType('integer', 8)
-real = BaseType('real', 8)
-char = BaseType('char', 1)
-void = BaseType('void', 0)
-
-chr_func = BuiltinProcedure('chr', ProcedureType([Parameter('value', 'x', integer)], char))
-
--- a/python/ks/irgenerator.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,142 +0,0 @@
-"""
-  Generates ir code from ast tree.
-"""
-
-from .nodes import *
-from .builtin import real, integer, boolean, char, void
-
-def coreType(typ):
-   """ Return the correct core type given a type """
-   if type(typ) is BaseType:
-      if typ is integer:
-         return core.i32
-      if typ is void:
-         return core.void
-   elif type(typ) is ProcedureType:
-      rType = coreType(typ.returntype)
-      fpTypes = [coreType(p.typ) for p in typ.parameters]
-      return core.FunctionType(rType, fpTypes)
-   print(typ)
-   raise NotImplementedError()
-
-class KsIrGenerator:
-   def __init__(self):
-      self.builder = core.IRBuilder()
-   # Code generation functions:
-   def genexprcode(self, node):
-      """ Generate code for expressions! """
-      if isinstance(node, Binop):
-         """ Handle a binary operation (two arguments) of some kind """
-         lhs = self.genexprcode(node.a)
-         rhs = self.genexprcode(node.b)
-
-         if node.op == '*':
-            if node.typ.isType(integer):
-               return self.builder.createMul(lhs, rhs)
-         elif node.op == '+':
-            if node.typ.isType(integer):
-               return self.builder.createAdd(lhs, rhs)
-         elif node.op == '-':
-            if node.typ.isType(integer):
-               return self.builder.createSub(lhs, rhs)
-         Error('Unknown binop or type {0}'.format(node))
-
-      elif isinstance(node, Designator):
-         # dereference, array index. Make sure that the result comes into a register
-         if len(node.selectors) > 0:
-            Error('Only integer types implemented')
-         else:
-            # No selectors, load variable directly
-            print(node)
-            #Error('Cannot load variable type {0}'.format(node.typ))
-      elif type(node) is Constant:
-         return core.Constant(node.value, coreType(node.typ))
-      else:
-         Error('Cannot generate expression code for: {0}'.format(node))
-
-   def gencode(self, node):
-      """ Code generation function for AST nodes """
-      if isinstance(node, Module):
-         # Create module:
-         self.mod = core.Module(node.name) 
-
-         globs = node.symtable.getAllLocal(Variable)
-         for g in globs:
-            print('global:', g)
-         # Loop over all functions:
-         print(node.symtable)
-         node.symtable.printTable()
-         funcs = node.symtable.getAllLocal(Procedure)
-         for f in funcs:
-            self.gencode(f)
-         # Create a function called init for this module:
-         self.mod.dump()
-         return self.mod
-
-      elif type(node) is Procedure:
-            ftype = coreType(node.typ)
-            print('function', node, ftype)
-            func = core.Function(ftype, node.name, self.mod)
-            bb = core.BasicBlock()
-            func.basicblocks.append(bb)
-            self.builder.setInsertPoint(bb)
-            self.gencode(node.block)
-            self.builder.setInsertPoint(None)
-            variables = node.symtable.getAllLocal(Variable)
-            print(variables)
-
-      elif isinstance(node, StatementSequence):
-         for s in node.statements:
-            self.gencode(s)
-
-      elif type(node) is ProcedureCall:
-         # Prepare parameters on the stack:
-         print("TODO")
-
-      elif type(node) is Assignment:
-         if node.lval.typ.isType(integer):
-           print('assign')
-           rhs = self.genexprcode(node.rval) # Calculate the value that has to be stored.
-           #self.gencode(node.lval)
-           print("TODO: assigment")
-           
-         else:
-            Error('Assignments of other types not implemented')
-
-      elif type(node) is IfStatement:
-        self.genexprcode(node.condition)
-        print("TODO IF")
-        if node.falsestatement:
-           # If with else clause
-           pass
-        else:
-           # If without else clause
-           pass
-
-      elif isinstance(node, WhileStatement):
-        self.genexprcode(node.condition)
-        self.gencode(node.dostatements)
-      elif type(node) is ForStatement:
-         # Initial load of iterator variable:
-         self.genexprcode(node.begin)
-         self.genexprcode(node.end)
-         self.gencode(node.statements)
-         Error('No implementation of FOR statement')
-
-      elif isinstance(node, EmptyStatement):
-         pass # That was easy :)
-
-      elif type(node) is StringConstant:
-        self.strings.append(node)
-
-      elif type(node) is Designator:
-         Error('Can only gencode for designator with selectors')
-      else:
-         print('not generating code for {0}'.format(node))
-
-   def generateIr(self, context, ast):
-     """ ir generation front end """
-     # Create a new context for this code.
-     self.context = context
-     return self.gencode(ast)
-
--- a/python/ks/lexer.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,69 +0,0 @@
-import collections, re
-
-"""
- Lexical analyzer part. Splits the input character stream into tokens.
-"""
-
-# Token is used in the lexical analyzer:
-Token = collections.namedtuple('Token', 'typ val row col')
-
-keywords = ['and', 'array', 'begin', 'by', 'case', 'const', 'div', 'do', \
-   'else', 'elsif', 'end', 'false', 'for', 'if', 'import', 'in', 'is', \
-   'mod', 'module', 'nil', 'not', 'of', 'or', 'pointer', 'procedure', \
-   'record', 'repeat', 'return', 'then', 'to', 'true', 'type', 'until', 'var', \
-   'while', 'asm' ]
-
-def tokenize(s):
-     """
-       Tokenizer, generates an iterator that
-       returns tokens!
-
-       This GREAT example was taken from python re doc page!
-     """
-     tok_spec = [
-       ('REAL', r'\d+\.\d+'),
-       ('HEXNUMBER', r'0x[\da-fA-F]+'),
-       ('NUMBER', r'\d+'),
-       ('ID', r'[A-Za-z][A-Za-z\d_]*'),
-       ('NEWLINE', r'\n'),
-       ('SKIP', r'[ \t]'),
-       ('COMMENTS', r'{.*}'),
-       ('LEESTEKEN', r':=|[\.,=:;\-+*\[\]/\(\)]|>=|<=|<>|>|<'),
-       ('STRING', r"'.*?'")
-     ]
-     tok_re = '|'.join('(?P<%s>%s)' % pair for pair in tok_spec)
-     gettok = re.compile(tok_re).match
-     line = 1
-     pos = line_start = 0
-     mo = gettok(s)
-     while mo is not None:
-       typ = mo.lastgroup
-       val = mo.group(typ)
-       if typ == 'NEWLINE':
-         line_start = pos
-         line += 1
-       elif typ == 'COMMENTS':
-         pass
-       elif typ != 'SKIP':
-         if typ == 'ID':
-           if val in keywords:
-             typ = val
-         elif typ == 'LEESTEKEN':
-           typ = val
-         elif typ == 'NUMBER':
-           val = int(val)
-         elif typ == 'HEXNUMBER':
-           val = int(val[2:], 16)
-           typ = 'NUMBER'
-         elif typ == 'REAL':
-           val = float(val)
-         elif typ == 'STRING':
-           val = val[1:-1]
-         yield Token(typ, val, line, mo.start()-line_start)
-       pos = mo.end()
-       mo = gettok(s, pos)
-     if pos != len(s):
-       col = pos - line_start
-       raise CompilerException('Unexpected character {0}'.format(s[pos]), line, col)
-     yield Token('END', '', line, 0)
-
--- a/python/ks/nodes.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,311 +0,0 @@
-"""
-AST nodes for the K# language.
-"""
-
-class Node:
-   location = None
-   def getChildren(self):
-      children = []
-      members = dir(self)
-      for member in members:
-         member = getattr(self, member)
-         if isinstance(member, Node):
-            children.append(member)
-         elif type(member) is list:
-            for mi in member:
-               if isinstance(mi, Node):
-                  children.append(mi)
-      return children
-
-class Symbol(Node):
-   pass
-
-class Id(Node):
-   def __init__(self, name):
-      self.name = name
-   def __repr__(self):
-      return 'ID {0}'.format(self.name)
-
-# Selectors:
-class Field(Node):
-   def __init__(self, fieldname):
-      self.fieldname = fieldname
-   def __repr__(self):
-      return 'FIELD {0}'.format(self.fieldname)
-
-class Index(Node):
-   def __init__(self, index, typ):
-      self.index = index
-      self.typ = typ
-   def __repr__(self):
-      return 'INDEX {0}'.format(self.index)
-
-class Deref(Node):
-   pass
-
-class Designator(Node):
-   def __init__(self, obj, selectors, typ):
-      self.obj = obj
-      self.selectors = selectors
-      self.typ = typ
-   def __repr__(self):
-      return 'DESIGNATOR {0}, selectors {1}, type {2}'.format(self.obj, self.selectors, self.typ)
-
-"""
-Type classes
-"""
-def isType(a, b):
-   """ Compare types a and b and check if they are equal """
-   if type(a) is type(b):
-      if type(a) is BaseType:
-         return (a.name == b.name) and (a.size == b.size)
-      elif type(a) is ArrayType:
-         return (a.dimension == b.dimension) and isType(a.elementType, b.elementType)
-      elif type(a) is ProcedureType:
-         if len(a.parameters) != len(b.parameters):
-            print('Number of parameters does not match')
-            return False
-         for aparam, bparam in zip(a.parameters, b.parameters):
-            if not isType(aparam.typ, bparam.typ):
-               print('Parameter {0} does not match parameter {1}'.format(aparam, bparam))
-               return False
-         if a.result is None:
-            # TODO: how to handle a None return type??
-            pass
-         if not isType(a.result, b.result):
-            print('Procedure return value mismatch {0} != {1}'.format(a.result, b.result))
-            return False
-         return True
-      else:
-         print(a)
-         print(b)
-         Error('Not implemented {0}'.format(a))
-   else:
-      return False
-
-class Type:
-   def isType(self, b):
-      return isType(self, b)
-
-class BaseType(Type):
-  def __init__(self, name, size):
-    self.name = name
-    self.size = size
-  def __repr__(self):
-    return '[TYPE {0}]'.format(self.name)
-
-class NilType(Node):
-   # TODO: how to handle nil values??
-   def __repr__(self):
-      return 'NILTYPE'
-
-class ArrayType(Type):
-  def __init__(self, dimension, elementType):
-    self.dimension = dimension
-    self.elementType = elementType
-    self.size = elementType.size * dimension
-  def __repr__(self):
-    return '[ARRAY {0} of {1}]'.format(self.dimension, self.elementType)
-
-class RecordType(Type):
-   def __init__(self, fields):
-      self.fields = fields
-      self.size = 0
-      for fieldname in self.fields:
-         self.size += self.fields[fieldname].size
-   def __repr__(self):
-      return '[RECORD {0}]'.format(self.fields)
-
-class PointerType(Type):
-   def __init__(self, pointedType):
-      self.pointedType = pointedType
-      self.size = 8
-   def __repr__(self):
-      return '[POINTER {0}]'.format(self.pointedType)
-
-class ProcedureType(Type):
-   def __init__(self, parameters, returntype):
-      self.parameters = parameters
-      self.returntype = returntype
-   def __repr__(self):
-      return '[PROCTYPE {0} RET {1}]'.format(self.parameters, self.returntype)
-
-class DefinedType(Type):
-   def __init__(self, name, typ):
-      self.name = name
-      self.typ = typ
-   def __repr__(self):
-      return 'Named type {0} of type {1}'.format(self.name, self.typ)
-
-# Classes for constants like numbers and strings:
-class StringConstant(Symbol):
-  def __init__(self, txt):
-    self.txt = txt
-    self.typ = 'string'
-  def __repr__(self):
-    return "STRING '{0}'".format(self.txt)
-
-# Variables, parameters, local variables, constants:
-class Constant(Symbol):
-   def __init__(self, value, typ, name=None, public=False):
-      self.name = name
-      self.value = value
-      self.typ = typ
-      self.public = public
-   def __repr__(self):
-      return 'CONSTANT {0} = {1}'.format(self.name, self.value)
-
-class Variable(Symbol):
-   def __init__(self, name, typ, public):
-      self.name = name
-      self.typ = typ
-      self.public = public
-      self.isLocal = False
-      self.isReadOnly = False
-      self.isParameter = False
-   def __repr__(self):
-      txt = '[public] ' if self.public else ''
-      return '{2}VAR {0} : {1}'.format(self.name, self.typ, txt)
-
-class Parameter(Node):
-   """ A parameter has a passing method, name and typ """
-   def __init__(self, kind, name, typ):
-      self.kind = kind
-      self.name = name
-      self.typ = typ
-   def __repr__(self):
-      return 'PARAM {0} {1} {2}'.format(self.kind, self.name, self.typ)
-
-# Operations:
-class Unop(Node):
-   def __init__(self, a, op, typ):
-      self.a = a
-      self.op = op # Operation: '+', '-', '*', '/', 'mod'
-      self.typ = typ
-      self.place = None
-   def __repr__(self):
-      return 'UNOP {0}'.format(self.op)
-
-class Binop(Node):
-   def __init__(self, a, op, b, typ):
-      self.a = a
-      self.b = b
-      self.op = op # Operation: '+', '-', '*', '/', 'mod'
-      self.typ = typ # Resulting type :)
-      self.place = None
-   def __repr__(self):
-      return 'BINOP {0} {1}'.format(self.op, self.typ)
-
-class Relop(Node):
-   def __init__(self, a, relop, b, typ):
-      self.a = a
-      self.relop = relop
-      self.b = b
-      self.typ = typ
-   def __repr__(self):
-      return 'RELOP {0}'.format(self.relop)
-
-# Modules
-class Module(Node):
-   def __init__(self, name):
-      self.name = name
-   def __repr__(self):
-      return 'MODULE {0}'.format(self.name)
-
-# Imports and Exports:
-class ImportedSymbol(Node):
-   def __init__(self, modname, name):
-      self.modname = modname
-      self.name  = name
-   def __repr__(self):
-      return 'IMPORTED SYMBOL {0}'.format(self.name)
-
-class ExportedSymbol(Node):
-   def __init__(self, name, typ):
-      self.name  = name
-      self.typ = typ
-   def __repr__(self):
-      return 'EXPORTED PROCEDURE {0} : {1}'.format(self.name, self.typ)
-
-# Procedure types
-class BuiltinProcedure(Node):
-   def __init__(self, name, typ):
-      self.name  = name
-      self.typ = typ
-   def __repr__(self):
-      return 'BUILTIN PROCEDURE {0} : {1}'.format(self.name, self.typ)
-
-class Procedure(Symbol):
-   """ Actual implementation of a function """
-   def __init__(self, name, typ, block, symtable, retexpr):
-      self.name = name
-      self.block = block
-      self.symtable = symtable
-      self.typ = typ
-      self.retexpr = retexpr
-   def __repr__(self):
-      return 'PROCEDURE {0} {1}'.format(self.name, self.typ)
-
-# Statements
-class StatementSequence(Node):
-   def __init__(self, statements):
-      self.statements = statements
-   def __repr__(self):
-      return 'STATEMENTSEQUENCE'
-
-class EmptyStatement(Node):
-   def __repr__(self):
-      return 'EMPTY STATEMENT'
-
-class Assignment(Node):
-   def __init__(self, lval, rval):
-      self.lval = lval
-      self.rval = rval
-   def __repr__(self):
-      return 'ASSIGNMENT'
-
-class ProcedureCall(Node):
-  def __init__(self, proc, args):
-    self.proc = proc
-    self.args = args
-    self.typ = proc.typ.returntype
-  def __repr__(self):
-    return 'CALL {0} '.format(self.proc)
-
-class IfStatement(Node):
-   def __init__(self, condition, truestatement, falsestatement=None):
-      self.condition = condition
-      self.truestatement = truestatement
-      self.falsestatement = falsestatement
-   def __repr__(self):
-      return 'IF-statement'
-
-class CaseStatement(Node):
-   def __init__(self, condition):
-      self.condition = condition
-   def __repr__(self):
-     return 'CASE-statement'
-
-class WhileStatement(Node):
-   def __init__(self, condition, statements):
-      self.condition = condition
-      self.dostatements = statements
-   def __repr__(self):
-      return 'WHILE-statement'
-
-class ForStatement(Node):
-   def __init__(self, variable, begin, end, increment, statements):
-      self.variable = variable
-      self.begin = begin
-      self.end = end
-      self.increment = increment
-      self.statements = statements
-   def __repr__(self):
-      return 'FOR-statement'
-
-class AsmCode(Node):
-   def __init__(self, asmcode):
-      self.asmcode = asmcode
-   def __repr__(self):
-      return 'ASM CODE'
-
--- a/python/ks/parser.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,815 +0,0 @@
-from .symboltable import SymbolTable
-from .nodes import *
-from .builtin import *
-from .lexer import tokenize
-
-class KsParser:
-   """ This module parses source code into an abstract syntax tree (AST) """
-   def __init__(self, source):
-      """ provide the parser with the tokens iterator from the lexer. """
-      self.tokens = tokenize(source) # Lexical stage
-      self.NextToken()
-      self.errorlist = []
-
-   def Error(self, msg):
-     raise CompilerException(msg, self.token.row, self.token.col)
-
-   # Lexer helpers:
-   def Consume(self, typ=''):
-     if self.token.typ == typ or typ == '':
-       v = self.token.val
-       self.NextToken()
-       return v
-     else:
-       self.Error('Excected: "{0}", got "{1}"'.format(typ, self.token.val))
-
-   def hasConsumed(self, typ):
-      if self.token.typ == typ:
-         self.Consume(typ)
-         return True
-      return False
-     
-   def NextToken(self):
-     self.token = self.tokens.__next__()
-     # TODO: store filename in location?
-     self.location = (self.token.row, self.token.col)
-
-   # Helpers to find location of the error in the code:
-   def setLocation(self, obj, location):
-      obj.location = location
-      return obj
-   def getLocation(self):
-      return self.location
-
-   """
-     Recursive descent parser functions:
-        A set of mutual recursive functions.
-        Starting symbol is the Module.
-   """
-   def parseModule(self):
-       """ Top level parsing routine """
-       self.imports = []
-       loc = self.getLocation()
-       self.Consume('module')
-       modname = self.Consume('ID')
-       self.Consume(';')
-       mod = Module(modname)
-
-       # Construct a symbol table for this program
-       mod.symtable = SymbolTable()
-       # Add built in types and functions:
-       for x in [real, integer, boolean, char, chr_func]:
-          mod.symtable.addSymbol(x)
-
-       self.cst = mod.symtable
-       self.parseImportList()
-
-       self.parseDeclarationSequence()
-       # Procedures only allowed in this scope
-       self.parseProcedureDeclarations()
-
-       if self.hasConsumed('begin'):
-          mod.initcode = self.parseStatementSequence()
-       else:
-          mod.initcode = EmptyStatement()
-
-       self.Consume('end')
-       endname = self.Consume('ID')
-       if endname != modname:
-          self.Error('end denoter must be module name')
-       self.Consume('.')
-
-       mod.imports = self.imports
-       return self.setLocation(mod, loc)
-
-   # Import part
-   def parseImportList(self):
-      if self.hasConsumed('import'):
-         self.parseImport()
-         while self.hasConsumed(','):
-            self.parseImport()
-         self.Consume(';')
-
-   def parseImport(self):
-      loc = self.getLocation()
-      modname = self.Consume('ID')
-      # TODO: fix
-      #mod = loadModule(modname)
-      self.setLocation(mod, loc)
-      self.cst.addSymbol(mod)
-
-   # Helper to parse an identifier defenitions
-   def parseIdentDef(self):
-      loc = self.getLocation()
-      name = self.Consume('ID')
-      ispublic = self.hasConsumed('*')
-      # Make a node of this thing:
-      i = Id(name)
-      i.ispublic = ispublic
-      return self.setLocation(i, loc)
-
-   def parseIdentList(self):
-      ids = [ self.parseIdentDef() ]
-      while self.hasConsumed(','):
-         ids.append( self.parseIdentDef() )
-      return ids
-
-   def parseQualIdent(self):
-      """ Parse a qualified identifier """
-      name = self.Consume('ID')
-      if self.cst.has(Module, name):
-         modname = name
-         mod = self.cst.get(Module, modname)
-         self.Consume('.')
-         name = self.Consume('ID')
-         # Try to find existing imported symbol:
-         for imp in self.imports:
-            if imp.modname == modname and imp.name == name:
-               return imp
-         # Try to find the symbol in the modules exports:
-         for sym in mod.exports:
-            if sym.name == name:
-               impsym = ImportedSymbol(modname, name)
-               impsym.typ = sym.typ
-               impsym.signature = mod.signature
-               self.imports.append(impsym)
-               return impsym
-         self.Error("Cannot find symbol {0}".format(name))
-      else:
-         return self.cst.getSymbol(name)
-
-   # Helper to parse a designator
-   def parseDesignator(self):
-      """ A designator designates an object.
-           The base location in memory is denoted by the qualified identifier
-           The actual address depends on the selector.
-      """
-      loc = self.getLocation()
-      obj = self.parseQualIdent()
-      typ = obj.typ
-      selectors = []
-      while self.token.typ in ['.', '[', '^']:
-         if self.hasConsumed('.'):
-            field = self.Consume('ID')
-            if typ is PointerType:
-               selectors.append(Deref())
-               typ = typ.pointedType
-            if not type(typ) is RecordType:
-               self.Error("field reference, type not record but {0}".format(typ))
-            typ = typ.fields[field]
-            selectors.append(Field(field))
-         elif self.hasConsumed('['):
-            indexes = self.parseExpressionList()
-            self.Consume(']')
-            for idx in indexes:
-               if not type(typ) is ArrayType:
-                  self.Error('Cannot index non array type')
-               if not isType(idx.typ, integer):
-                  self.Error('Only integer expressions can be used as an index')
-               selectors.append(Index(idx, typ))
-               typ = typ.elementType
-         elif self.hasConsumed('^'):
-            selectors.append(Deref())
-            typ = typ.pointedType
-      return self.setLocation(Designator(obj, selectors, typ), loc)
-
-   # Declaration sequence
-   def parseDeclarationSequence(self):
-      """ 1. constants, 2. types, 3. variables """
-      self.parseConstantDeclarations()
-      self.parseTypeDeclarations()
-      self.parseVariableDeclarations()
-
-   # Constants
-   def evalExpression(self, expr):
-      if type(expr) is Binop:
-         a = self.evalExpression(expr.a)
-         b = self.evalExpression(expr.b)
-         if expr.op == '+':
-            return a + b
-         elif expr.op == '-':
-            return a - b
-         elif expr.op == '*':
-            return a * b
-         elif expr.op == '/':
-            return float(a) / float(b)
-         elif expr.op == 'mod':
-            return int(a % b)
-         elif expr.op == 'div':
-            return int(a / b)
-         elif expr.op == 'or':
-            return a or b
-         elif expr.op == 'and':
-            return a and b
-         else:
-            self.Error('Cannot evaluate expression with {0}'.format(expr.op))
-      elif type(expr) is Constant:
-         return expr.value
-      elif type(expr) is Designator:
-         if type(expr.obj) is Constant:
-            return self.evalExpression(expr.obj)
-         else:
-            self.Error('Cannot evaluate designated object {0}'.format(expr.obj))
-      elif type(expr) is Unop:
-         a = self.evalExpression(expr.a)
-         if expr.op == 'not':
-            return not a
-         elif expr.op == '-':
-            return -a 
-         else:
-            self.Error('Unimplemented unary operation {0}'.format(expr.op))
-      else:
-         self.Error('Cannot evaluate expression {0}'.format(expr))
-
-   def parseConstant(self):
-      e = self.parseExpression()
-      val = self.evalExpression(e)
-      return Constant(val, e.typ)
-
-   def parseConstantDeclarations(self):
-      """ Parse const part of a module """
-      if self.hasConsumed('const'):
-         while self.token.typ == 'ID':
-            i = self.parseIdentDef()
-            self.Consume('=')
-            c = self.parseConstant()
-            self.Consume(';')
-            c.name = i.name
-            c.public = i.ispublic
-            self.setLocation(c, i.location)
-            self.cst.addSymbol(c)
-     
-   # Type system
-   def parseTypeDeclarations(self):
-      if self.hasConsumed('type'):
-         while self.token.typ == 'ID':
-            typename, export = self.parseIdentDef()
-            self.Consume('=')
-            typ = self.parseStructuredType()
-            self.Consume(';')
-            t = DefinedType(typename, typ)
-            self.cst.addSymbol(t)
-
-   def parseType(self):
-      if self.token.typ == 'ID':
-         typename = self.Consume('ID')
-         if self.cst.has(Type, typename):
-            typ = self.cst.get(Type, typename)
-            while type(typ) is DefinedType:
-               typ = typ.typ
-            return typ
-         else:
-            self.Error('Cannot find type {0}'.format(typename))
-      else:
-         return self.parseStructuredType()
-
-   def parseStructuredType(self):
-      if self.hasConsumed('array'):
-         dimensions = []
-         dimensions.append( self.parseConstant() )
-         while self.hasConsumed(','):
-             dimensions.append( self.parseConstant() )
-         self.Consume('of')
-         arr = self.parseType()
-         for dimension in reversed(dimensions):
-            if not isType(dimension.typ, integer):
-               self.Error('array dimension must be an integer type (not {0})'.format(consttyp))
-            if dimension.value < 2:
-               self.Error('array dimension must be bigger than 1 (not {0})'.format(dimension.value))
-            arr = ArrayType(dimension.value, arr)
-         return arr
-      elif self.hasConsumed('record'):
-         fields = {}
-         while self.token.typ == 'ID':
-            # parse a fieldlist:
-            identifiers = self.parseIdentList()
-            self.Consume(':')
-            typ = self.parseType()
-            self.Consume(';')
-            for i in identifiers:
-               if i.name in fields.keys():
-                  self.Error('record field "{0}" multiple defined.'.format(i.name))
-               fields[i.name] = typ
-            # TODO store this in another way, symbol table?
-         self.Consume('end')
-         return RecordType(fields)
-      elif self.hasConsumed('pointer'):
-         self.Consume('to')
-         typ = self.parseType()
-         return PointerType(typ)
-      elif self.hasConsumed('procedure'):
-         parameters, returntype = self.parseFormalParameters()
-         return ProcedureType(parameters, returntype)
-      else:
-         self.Error('Unknown structured type "{0}"'.format(self.token.val))
-
-   # Variable declarations:
-   def parseVariableDeclarations(self):
-      if self.hasConsumed('var'):
-         if self.token.typ == 'ID':
-            while self.token.typ == 'ID':
-               ids = self.parseIdentList()
-               self.Consume(':')
-               typename = self.parseType()
-               self.Consume(';')
-               for i in ids:
-                  v = Variable(i.name, typename, public=i.ispublic)
-                  self.setLocation(v, i.location)
-                  self.cst.addSymbol(v)
-         else:
-            self.Error('Expected ID, got'+str(self.token))
-
-   # Procedures
-   def parseFPsection(self):
-      if self.hasConsumed('const'):
-         kind = 'const'
-      elif self.hasConsumed('var'):
-         kind = 'var'
-      else:
-         kind = 'value'
-      names = [ self.Consume('ID') ]
-      while self.hasConsumed(','):
-         names.append( self.Consume('ID') )
-      self.Consume(':')
-      typ = self.parseType()
-      parameters = [Parameter(kind, name, typ)
-            for name in names]
-      return parameters
-
-   def parseFormalParameters(self):
-      parameters = []
-      self.Consume('(')
-      if not self.hasConsumed(')'):
-         parameters += self.parseFPsection()
-         while self.hasConsumed(';'):
-            parameters += self.parseFPsection()
-         self.Consume(')')
-      if self.hasConsumed(':'):
-         returntype = self.parseQualIdent()
-      else:
-         returntype = void
-      return ProcedureType(parameters, returntype)
-
-   def parseProcedureDeclarations(self):
-     procedures = []
-     while self.token.typ == 'procedure':
-       p = self.parseProcedureDeclaration()
-       procedures.append(p)
-       self.Consume(';')
-     return procedures
-
-   def parseProcedureDeclaration(self):
-     loc = self.getLocation()
-     self.Consume('procedure')
-     i = self.parseIdentDef()
-     procname = i.name
-     proctyp = self.parseFormalParameters()
-     procsymtable = SymbolTable(parent = self.cst)
-     self.cst = procsymtable    # Switch symbol table:
-     # Add parameters as variables to symbol table:
-     for parameter in proctyp.parameters:
-        vname = parameter.name
-        vtyp = parameter.typ
-        if parameter.kind == 'var':
-           vtyp = PointerType(vtyp)
-        variable = Variable(vname, vtyp, False)
-        if parameter.kind == 'const':
-           variable.isReadOnly = True
-        variable.isParameter = True
-        self.cst.addSymbol(variable)
-     self.Consume(';')
-     self.parseDeclarationSequence()
-     # Mark all variables as local:
-     for variable in self.cst.getAllLocal(Variable):
-        variable.isLocal = True
-
-     if self.hasConsumed('begin'):
-        block = self.parseStatementSequence()
-     if self.hasConsumed('return'):
-        returnexpression = self.parseExpression()
-     else:
-        returnexpression = None
-
-     if proctyp.returntype.isType(void):
-        if not returnexpression is None:
-           self.Error('Void procedure cannot return a value')
-     else:
-        if returnexpression is None:
-           self.Error('Procedure must return a value')
-        if not isType(returnexpression.typ, proctyp.returntype):
-           self.Error('Returned type {0} does not match function return type {1}'.format(returnexpression.typ, proctyp.returntype))
-
-     self.Consume('end')
-     endname = self.Consume('ID')
-     if endname != procname:
-        self.Error('endname should match {0}'.format(name))
-     self.cst = procsymtable.parent    # Switch back to parent symbol table
-     proc = Procedure(procname, proctyp, block, procsymtable, returnexpression)
-     self.setLocation(proc, loc)
-     self.cst.addSymbol(proc)
-     proc.public = i.ispublic
-     return proc
-
-   # Statements:
-   def parseAssignment(self, lval):
-      loc = self.getLocation()
-      self.Consume(':=')
-      rval = self.parseExpression()
-      if isType(lval.typ, real) and isType(rval.typ, integer):
-         rval = Unop(rval, 'INTTOREAL', real)
-      if type(rval.typ) is NilType:
-         if not type(lval.typ) is ProcedureType and not type(lval.typ) is PointerType:
-            self.Error('Can assign nil only to pointers or procedure types, not {0}'.format(lval))
-      elif not isType(lval.typ, rval.typ):
-         self.Error('Type mismatch {0} != {1}'.format(lval.typ, rval.typ))
-      return self.setLocation(Assignment(lval, rval), loc)
-
-   def parseExpressionList(self):
-      expressions = [ self.parseExpression() ]
-      while self.hasConsumed(','):
-         expressions.append( self.parseExpression() )
-      return expressions
-
-   def parseProcedureCall(self, procedure):
-      self.Consume('(')
-      if self.token.typ != ')':
-         args = self.parseExpressionList()
-      else:
-         args = []
-      self.Consume(')')
-      # Type checking:
-      parameters = procedure.typ.parameters
-      if len(args) != len(parameters):
-         self.Error("Procedure requires {0} arguments, {1} given".format(len(parameters), len(args)))
-      for arg, param in zip(args, parameters):
-         if not arg.typ.isType(param.typ):
-            print(arg.typ, param.typ)
-            self.Error('Mismatch in parameter')
-      return ProcedureCall(procedure, args)
-
-   def parseIfStatement(self):
-     loc = self.getLocation()
-     self.Consume('if')
-     ifs = []
-     condition = self.parseExpression()
-     if not isType(condition.typ, boolean):
-         self.Error('condition of if statement must be boolean')
-     self.Consume('then')
-     truestatement = self.parseStatementSequence()
-     ifs.append( (condition, truestatement) )
-     while self.hasConsumed('elsif'):
-        condition = self.parseExpression()
-        if not isType(condition.typ, boolean):
-            self.Error('condition of if statement must be boolean')
-        self.Consume('then')
-        truestatement = self.parseStatementSequence()
-        ifs.append( (condition, truestatement) )
-     if self.hasConsumed('else'):
-        statement = self.parseStatementSequence()
-     else:
-        statement = None
-     self.Consume('end')
-     for condition, truestatement in reversed(ifs):
-         statement = IfStatement(condition, truestatement, statement)
-     return self.setLocation(statement, loc)
-
-   def parseCase(self):
-      # TODO
-      pass
-
-   def parseCaseStatement(self):
-      self.Consume('case')
-      expr = self.parseExpression()
-      self.Consume('of')
-      self.parseCase()
-      while self.hasConsumed('|'):
-         self.parseCase()
-      self.Consume('end')
-
-   def parseWhileStatement(self):
-      loc = self.getLocation()
-      self.Consume('while')
-      condition = self.parseExpression()
-      self.Consume('do')
-      statements = self.parseStatementSequence()
-      if self.hasConsumed('elsif'):
-         self.Error('elsif in while not yet implemented')
-      self.Consume('end')
-      return self.setLocation(WhileStatement(condition, statements), loc)
-
-   def parseRepeatStatement(self):
-      self.Consume('repeat')
-      stmt = self.parseStatementSequence()
-      self.Consume('until')
-      cond = self.parseBoolExpression()
-      # TODO
-
-   def parseForStatement(self):
-      loc = self.getLocation()
-      self.Consume('for')
-      variable = self.parseDesignator()
-      if not variable.typ.isType(integer):
-         self.Error('loop variable of for statement must have integer type')
-      assert(variable.typ.isType(integer))
-      self.Consume(':=')
-      begin = self.parseExpression()
-      if not begin.typ.isType(integer):
-         self.Error('begin expression of a for statement must have integer type')
-      self.Consume('to')
-      end = self.parseExpression()
-      if not end.typ.isType(integer):
-         self.Error('end expression of a for statement must have integer type')
-      if self.hasConsumed('by'):
-         increment = self.parseConstant()
-         if not increment.typ.isType(integer):
-            self.Error('Increment must be integer')
-         increment = increment.value
-      else:
-         increment = 1
-      assert(type(increment) is int)
-      self.Consume('do')
-      statements = self.parseStatementSequence()
-      self.Consume('end')
-      return self.setLocation(ForStatement(variable, begin, end, increment, statements), loc)
-
-   def parseAsmcode(self):
-      # TODO: move this to seperate file
-      # TODO: determine what to do with inline asm?
-      def parseOpcode():
-         return self.Consume('ID')
-      def parseOperand():
-         if self.hasConsumed('['):
-            memref = []
-            memref.append(parseOperand())
-            self.Consume(']')
-            return memref
-         else:
-            if self.token.typ == 'NUMBER':
-               return self.Consume('NUMBER')
-            else:
-               ID = self.Consume('ID')
-               if self.cst.has(Variable, ID):
-                  return self.cst.get(Variable, ID)
-               else:
-                  return ID
-               
-      def parseOperands(n):
-         operands = []
-         if n > 0:
-            operands.append( parseOperand() )
-            n = n - 1
-            while n > 0:
-               self.Consume(',')
-               operands.append(parseOperand())
-               n = n - 1
-         return operands
-      self.Consume('asm')
-      asmcode = []
-      while self.token.typ != 'end':
-         opcode = parseOpcode()
-         func, numargs = assembler.opcodes[opcode]
-         operands = parseOperands(numargs)
-         asmcode.append( (opcode, operands) )
-         #print('opcode', opcode, operands)
-      self.Consume('end')
-      return AsmCode(asmcode)
-
-   def parseStatement(self):
-     try:
-        # Determine statement type based on the pending token:
-        if self.token.typ == 'if':
-           return self.parseIfStatement()
-        elif self.token.typ == 'case':
-           return self.parseCaseStatement()
-        elif self.token.typ == 'while':
-          return self.parseWhileStatement()
-        elif self.token.typ == 'repeat':
-           return self.parseRepeatStatement()
-        elif self.token.typ == 'for':
-           return self.parseForStatement()
-        elif self.token.typ == 'asm':
-           return self.parseAsmcode()
-        elif self.token.typ == 'ID':
-           # Assignment or procedure call
-           designator = self.parseDesignator()
-           if self.token.typ == '(' and type(designator.typ) is ProcedureType:
-              return self.parseProcedureCall(designator)
-           elif self.token.typ == ':=':
-              return self.parseAssignment(designator)
-           else:
-              self.Error('Unknown statement following designator: {0}'.format(self.token))
-        else:
-           # TODO: return empty statement??:
-           return EmptyStatement()
-           self.Error('Unknown statement {0}'.format(self.token))
-     except CompilerException as e:
-         print(e)
-         self.errorlist.append( (e.row, e.col, e.msg))
-         # Do error recovery by skipping all tokens until next ; or end
-         while not (self.token.typ == ';' or self.token.typ == 'end'):
-            self.Consume(self.token.typ)
-         return EmptyStatement()
-
-   def parseStatementSequence(self):
-       """ Sequence of statements seperated by ';' """
-       statements = [self.parseStatement()]
-       while self.hasConsumed(';'):
-         statements.append(self.parseStatement())
-       return StatementSequence(statements)
-
-   # Parsing expressions:
-   """
-     grammar of expressions:
-     expression       = SimpleExpression [ reloperator SimpleExpression ]
-     reloperator      = '=' | '<=' | '>=' | '<>'
-     Simpleexpression = [ '+' | '-' ] term { addoperator term }
-     addoperator      = '+' | '-' | 'or'
-     term             = factor { muloperator factor }
-     muloperator      = '*' | '/' | 'div' | 'mod' | 'and'
-     factor           = number | nil | true | false | "(" expression ")" | 
-                        designator [ actualparameters ] | 'not' factor
-   """
-   def getTokenPrecedence(self):
-      binopPrecs = {}
-      binopPrecs['and'] = 8
-      binopPrecs['or'] = 6
-      binopPrecs['<'] = 10
-      binopPrecs['>'] = 10
-      binopPrecs['='] = 10
-      binopPrecs['<='] = 10
-      binopPrecs['>='] = 10
-      binopPrecs['<>'] = 10
-      binopPrecs['+'] = 20
-      binopPrecs['-'] = 20
-      binopPrecs['*'] = 40
-      binopPrecs['/'] = 40
-      binopPrecs['div'] = 40
-      binopPrecs['mod'] = 40
-
-      typ = self.token.typ
-      if typ in binopPrecs:
-         return binopPrecs[typ]
-      return 0
-   def parsePrimary(self):
-      pass
-   def parseExpression(self):
-      """ The connector between the boolean and expression domain """
-      # TODO: implement precedence bindin
-      #lhs = self.parsePrimary()
-      #return self.parseBinopRhs(lhs)
-
-      expr = self.parseSimpleExpression()
-      if self.token.typ in ['>=','<=','<','>','<>','=']:
-         relop = self.Consume()
-         expr2 = self.parseSimpleExpression()
-         # Automatic type convert to reals:
-         if isType(expr.typ, real) and isType(expr2.typ, integer):
-            expr2 = Unop(expr2, 'INTTOREAL', real)
-         if isType(expr2.typ, real) and isType(expr.typ, integer):
-            expr = Unop(expr, 'INTTOREAL', real)
-         # Type check:
-         if not isType(expr.typ, expr2.typ):
-            self.Error('Type mismatch in relop')
-         if isType(expr.typ, real) and relop in ['<>', '=']:
-            self.Error('Cannot check real values for equality')
-         expr = Relop(expr, relop, expr2, boolean)
-      return expr
-
-   # Parsing arithmatic expressions:
-   def parseTerm(self):
-       a = self.parseFactor()
-       while self.token.typ in ['*', '/', 'mod', 'div', 'and']:
-           loc = self.getLocation()
-           op = self.Consume()
-           b = self.parseTerm()
-           # Type determination and checking:
-           if op in ['mod', 'div']:
-              if not isType(a.typ, integer):
-                 self.Error('First operand should be integer, not {0}'.format(a.typ))
-              if not isType(b.typ, integer):
-                 self.Error('Second operand should be integer, not {0}'.format(b.typ))
-              typ = integer
-           elif op == '*':
-              if isType(a.typ, integer) and isType(b.typ, integer):
-                 typ = integer
-              elif isType(a.typ, real) or isType(b.typ, real):
-                 if isType(a.typ, integer):
-                    # Automatic type cast
-                    a = Unop(a, 'INTTOREAL', real)
-                 if isType(b.typ, integer):
-                    b = Unop(b, 'INTTOREAL', real)
-                 if not isType(a.typ, real):
-                    self.Error('first operand must be a real!')
-                 if not isType(b.typ, real):
-                    self.Error('second operand must be a real!')
-                 typ = real
-              else:
-                 self.Error('Unknown operands for multiply: {0}, {1}'.format(a, b))
-           elif op == '/':
-              # Division always yields a real result, for integer division use div
-              if isType(a.typ, integer):
-                 # Automatic type cast
-                 a = Unop(a, 'INTTOREAL', real)
-              if isType(b.typ, integer):
-                 b = Unop(b, 'INTTOREAL', real)
-              if not isType(a.typ, real):
-                 self.Error('first operand must be a real!')
-              if not isType(b.typ, real):
-                 self.Error('second operand must be a real!')
-              typ = real
-           elif op == 'and':
-              if not isType(a.typ, boolean):
-                 self.Error('First operand of and must be boolean')
-              if not isType(b.typ, boolean):
-                 self.Error('Second operand of and must be boolean')
-              typ = boolean
-           else:
-              self.Error('Unknown operand {0}'.format(op))
-
-           a = self.setLocation(Binop(a, op, b, typ), loc)
-       return a
-
-   def parseFactor(self):
-      if self.hasConsumed('('):
-         e = self.parseExpression()
-         self.Consume(')')
-         return e
-      elif self.token.typ == 'NUMBER':
-         loc = self.getLocation() 
-         val = self.Consume('NUMBER')
-         return self.setLocation(Constant(val, integer), loc)
-      elif self.token.typ == 'REAL':
-         loc = self.getLocation()
-         val = self.Consume('REAL')
-         return self.setLocation(Constant(val, real), loc)
-      elif self.token.typ == 'CHAR':
-          val = self.Consume('CHAR')
-          return Constant(val, char)
-      elif self.token.typ == 'STRING':
-         txt = self.Consume('STRING')
-         return StringConstant(txt)
-      elif self.hasConsumed('true'):
-         return Constant(True, boolean)
-      elif self.hasConsumed('false'):
-         return Constant(False, boolean)
-      elif self.hasConsumed('nil'):
-         return Constant(0, NilType())
-      elif self.hasConsumed('not'):
-         f = self.parseFactor()
-         if not isType(f.typ, boolean):
-            self.Error('argument of boolean negation must be boolean type')
-         return Unop(f, 'not', boolean)
-      elif self.token.typ == 'ID':
-          designator = self.parseDesignator()
-          # TODO: handle functions different here?
-          if self.token.typ == '(' and type(designator.typ) is ProcedureType:
-             return self.parseProcedureCall(designator)
-          else:
-             return designator
-      else:
-         self.Error('Expected NUMBER, ID or ( expr ), got'+str(self.token))
-
-   def parseSimpleExpression(self):
-      """ Arithmatic expression """
-      if self.token.typ in ['+', '-']:
-         # Handle the unary minus
-         op = self.Consume()
-         a = self.parseTerm()
-         typ = a.typ
-         if not isType(typ,real) and not isType(typ, integer):
-            self.Error('Unary minus or plus can be only applied to real or integers')
-         if op == '-':
-            a = Unop(a, op, typ)
-      else:
-         a = self.parseTerm()
-      while self.token.typ in ['+', '-', 'or']:
-           loc = self.getLocation()
-           op = self.Consume()
-           b = self.parseTerm()
-           if op in ['+', '-']:
-              if isType(a.typ, real) or isType(b.typ, real):
-                 typ = real
-                 if isType(a.typ, integer):
-                    # Automatic type cast
-                    a = Unop(a, 'INTTOREAL', real)
-                 if not isType(a.typ, real):
-                    self.Error('first operand must be a real!')
-                 if isType(b.typ, integer):
-                    b = Unop(b, 'INTTOREAL', real)
-                 if not isType(b.typ, real):
-                    self.Error('second operand must be a real!')
-              elif isType(a.typ, integer) and isType(b.typ, integer):
-                 typ = integer
-              else:
-                 self.Error('Invalid types {0} and {1}'.format(a.typ, b.typ))
-           elif op == 'or':
-              if not isType(a.typ, boolean):
-                 self.Error('first operand must be boolean for or operation')
-              if not isType(b.typ, boolean):
-                 self.Error('second operand must be boolean for or operation')
-              typ = boolean
-           else:
-              self.Error('Unknown operand {0}'.format(op))
-           a = self.setLocation(Binop(a, op, b, typ), loc)
-      return a
-
--- a/python/ks/symboltable.py	Sat Jun 29 10:10:45 2013 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,79 +0,0 @@
-from .nodes import *
-
-class SymbolTable:
-  """
-   Symbol table for a current scope.
-   It has functions:
-    - hasname for checking for a name in current scope or above
-    - addSymbol to add an object
-  """
-  def __init__(self, parent=None):
-    self.parent = parent
-    self.syms = {}
-
-  def __repr__(self):
-    return 'Symboltable with {0} symbols\n'.format(len(self.syms))
-
-  def printTable(self, indent=0):
-    for name in self.syms:
-      print(self.syms[name])
-
-  def getAllLocal(self, cls):
-     """ Get all local objects of a specific type """
-     r = []
-     for key in self.syms.keys():
-        sym = self.syms[key]
-        if issubclass(type(sym), cls):
-           r.append(sym)
-     return r
-
-  def getLocal(self, cls, name):
-      if name in self.syms.keys():
-         sym = self.syms[name]
-         if isinstance(sym, cls):
-            return sym
-         else:
-            Error('Wrong type found')
-      else:
-         Error('Symbol not found')
-
-  # Retrieving of specific classes of items:
-  def get(self, cls, name):
-    if self.hasSymbol(name):
-      sym = self.getSymbol(name)
-      if issubclass(type(sym), cls):
-        return sym
-    raise SymbolException('type {0} undefined'.format(typename))
-
-  def has(self, cls, name):
-    if self.hasSymbol(name):
-      sym = self.getSymbol(name)
-      if issubclass(type(sym), cls):
-        return True
-    return False
-
-  # Adding and retrieving of symbols in general:
-  def addSymbol(self, sym):
-    if sym.name in self.syms.keys():
-      raise Exception('Symbol "{0}" redefined'.format(sym.name))
-    else:
-      self.syms[sym.name] = sym
-
-  def getSymbol(self, name):
-     if name in self.syms.keys():
-      return self.syms[name]
-     else:
-      if self.parent:
-        return self.parent.getSymbol(name)
-      else:
-         raise Exception('Symbol "{0}" undeclared!'.format(name))
-
-  def hasSymbol(self, name):
-    if name in self.syms.keys():
-      return True
-    else:
-      if self.parent:
-        return self.parent.hasSymbol(name)
-      else:
-        return False
-
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/python/parserlib.py	Sun Jun 30 19:00:41 2013 +0200
@@ -0,0 +1,83 @@
+
+
+
+class Token:
+    pass
+
+# Base functions:
+class Pbase:
+    def __init__(self):
+        self.pa = None
+    def parse(self, txt):
+        r = self.do(txt)
+        if r:
+            match, rest = r
+            # Apply action:
+            if self.ParseAction:
+                match = self.ParseAction(match)
+            return match, rest
+        else:
+            # TODO: fail in some way
+            pass
+    def getParseAction(self):
+        return self.pa
+    def setParseAction(self, pa):
+        self.pa = pa
+
+    ParseAction = property(getParseAction, setParseAction)
+
+# basic elements:
+
+class Literal(Pbase):
+    def __init__(self, s):
+        super().__init__()
+        self.pat = s
+    def do(self, txt):
+        if txt.startswith(self.pat):
+            return self.pat, txt[len(self.pat):]
+
+class Or(Pbase):
+    def __init__(self, options):
+        super().__init__()
+        self.options = options
+    def do(self, txt):
+        for option in self.options:
+            r = option.parse(txt)
+            if r:
+                return r
+
+class And:
+    def __init__(self, options):
+        self.options = options
+
+class Sequence(Pbase):
+    def __init__(self, seq):
+        super().__init__()
+        self.seq = seq
+    def do(self, txt):
+        results = []
+        for thung in self.seq:
+            r = thung.parse(txt)
+            if r:
+                res, txt = r
+                results.append(res)
+            else:
+                return
+        return results, txt
+
+class Optional(Pbase):
+    def __init__(self, thung):
+        super().__init__()
+        self.thung = thung
+    def do(self, txt):
+        r = self.thung.do(txt)
+        if r:
+            return r
+        return (0, txt)
+
+# Contraptions of basic blocks:
+
+def OneOrMore():
+    def __init__(self, thingy):
+        pass
+
--- a/python/stm32f4/blink.c3	Sat Jun 29 10:10:45 2013 +0200
+++ b/python/stm32f4/blink.c3	Sun Jun 30 19:00:41 2013 +0200
@@ -8,7 +8,7 @@
 
 // Globals:
 var int divider;
-//const TIM2_s *TIM2;
+//const TIM2_s *TIM2;// = (TIM2_s*)0x40004;
 
 // Functions:
 function void tim2_handler()
@@ -17,13 +17,11 @@
     if (true)
 	{
 		divider = divider + 1;
-        /*
 		if (divider > 100000)
 		{
 			divider = 0;
-			GPIOD->ODR ^= (1 << 13);
+			//GPIOD->ODR ^= (1 << 13);
 		}
-        */
 	}
 }
 
--- a/python/testasm.py	Sat Jun 29 10:10:45 2013 +0200
+++ b/python/testasm.py	Sun Jun 30 19:00:41 2013 +0200
@@ -178,6 +178,14 @@
         self.feed('pop {r4-r6, pc}')
         self.check('70bd')
 
+    def testStr5(self):
+        self.feed('str r4, [r1 + 0]')
+        self.check('0c60')
+
+    def testLdr5(self):
+        self.feed('ldr r4, [r0 + 0]')
+        self.check('0468')
+
     def testSequence1(self):
         self.feed('mov r5, 3')
         self.feed('add r4, r5, 0')
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/python/testparserlib.py	Sun Jun 30 19:00:41 2013 +0200
@@ -0,0 +1,61 @@
+import unittest
+from parserlib import OneOrMore, Literal, Or, Sequence, Optional
+
+class ParserCombinatorTestCase(unittest.TestCase):
+    def test1(self):
+        #p = Parser()
+        # parse and interpret:
+        n40 = Literal('40')
+        plus = Literal('+')
+        n2 = Literal('2')
+        n40.ParseAction = int
+        plus.ParseAction = replaceWith(0)
+        n2.ParseAction = int
+        p = Sequence([n40,plus,n2])
+        p.ParseAction = wordsum
+
+        result = p.parse('40+2')
+        self.assertEqual(42, result[0])
+
+def replaceWith(s):
+    def _repFunc(*args):
+        return s
+    return _repFunc
+
+wordsum = lambda t: sum(t)
+
+class WordToNumTestCase(unittest.TestCase):
+    def setUp(self):
+        numWords = OneOrMore()
+        def makeLit(s, val):
+            ret = Literal(s)
+            ret.ParseAction = replaceWith(val)
+            return ret
+        unitDefs = [('zero', 0), ('three', 3), ('one', 1)]
+        units = Or( [makeLit(s, v) for s, v in unitDefs] )
+        tensDefs = [('twenty', 20)]
+        tens = Or( [makeLit(s, v) for s, v in tensDefs] )
+
+        numPart = Sequence([Optional(tens), units])
+        numPart.ParseAction = wordsum
+        self.p = numPart
+
+    def check(self, i, o):
+        result = self.p.parse(i)[0]
+        self.assertEqual(o, result)
+
+    def test0(self):
+        self.check('zero', 0)
+        
+    def test23(self):
+        self.check('twentythree', 23)
+
+    @unittest.skip
+    def test321(self):
+        # TODO
+        self.check('three hundred and twenty one', 321)
+        
+
+if __name__ == '__main__':
+    unittest.main()
+