# HG changeset patch # User Windel Bouwman # Date 1394733546 -3600 # Node ID 5477e499b03969f3c89fe3cbf096ca581810ef75 # Parent b8ad45b3a573144566b63096b8c16648efe9ea34 Added some sort of string functionality diff -r b8ad45b3a573 -r 5477e499b039 kernel/arch/vexpressA9.c3 --- a/kernel/arch/vexpressA9.c3 Sun Mar 09 18:49:10 2014 +0100 +++ b/kernel/arch/vexpressA9.c3 Thu Mar 13 18:59:06 2014 +0100 @@ -2,7 +2,7 @@ function void init() { - putc(0x65) + // putc(65) } function void putc(int c) diff -r b8ad45b3a573 -r 5477e499b039 kernel/kernel.c3 --- a/kernel/kernel.c3 Sun Mar 09 18:49:10 2014 +0100 +++ b/kernel/kernel.c3 Thu Mar 13 18:59:06 2014 +0100 @@ -21,26 +21,14 @@ while(true) {} } -function int strlen(string txt) -{ - -} - -function int getchar(string txt, int index) -{ - if (index < strlen(txt)) - { - } -} - function void print(string txt) { var int i; i = 0; - while (i < strlen(txt)) + while (i < txt->len) { - arch.putc(getchar(txt, i)); + arch.putc(cast(txt->txt[i])); i = i + 1; } } diff -r b8ad45b3a573 -r 5477e499b039 kernel/make.sh --- a/kernel/make.sh Sun Mar 09 18:49:10 2014 +0100 +++ b/kernel/make.sh Thu Mar 13 18:59:06 2014 +0100 @@ -1,5 +1,5 @@ #!/bin/bash -../python/zcc.py recipe thumb.yaml +# ../python/zcc.py recipe thumb.yaml ../python/zcc.py --report log.txt recipe arm.yaml diff -r b8ad45b3a573 -r 5477e499b039 kernel/monitor.sh --- a/kernel/monitor.sh Sun Mar 09 18:49:10 2014 +0100 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,3 +0,0 @@ -#!/bin/bash - -socat stdio UNIX-CONNECT:vm.sock diff -r b8ad45b3a573 -r 5477e499b039 kernel/qemutst.sh --- a/kernel/qemutst.sh Sun Mar 09 18:49:10 2014 +0100 +++ b/kernel/qemutst.sh Thu Mar 13 18:59:06 2014 +0100 @@ -7,8 +7,8 @@ echo "Trying to run test on stellaris qemu machine" # -S means halt at start: -qemu-system-arm -M vexpress-a9 -m 128M -kernel kernel.bin \ - -monitor unix:vm.sock,server -serial file:output.txt -S -s +qemu-system-arm -M vexpress-a9 -m 128M -kernel kernel_arm.bin \ + -serial stdio -s #sleep 1 diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/buildtasks.py --- a/python/ppci/buildtasks.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/buildtasks.py Thu Mar 13 18:59:06 2014 +0100 @@ -57,7 +57,8 @@ for ircode in c3b.build(self.sources, self.includes): if not ircode: - return + # Something went wrong, do not continue the code generation + continue d = {'ircode':ircode} self.logger.debug('Verifying code {}'.format(ircode), extra=d) diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/c3/astnodes.py --- a/python/ppci/c3/astnodes.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/c3/astnodes.py Thu Mar 13 18:59:06 2014 +0100 @@ -125,6 +125,16 @@ return 'STRUCT' +class ArrayType(Type): + """ Array type """ + def __init__(self, element_type, size): + self.element_type = element_type + self.size = size + + def __repr__(self): + return 'ARRAY {}'.format(self.size) + + class DefinedType(NamedType): """ A named type indicating another type """ def __init__(self, name, typ, loc): @@ -225,6 +235,17 @@ return 'MEMBER {}.{}'.format(self.base, self.field) +class Index(Expression): + """ Index something, for example an array """ + def __init__(self, base, i, loc): + super().__init__(loc) + self.base = base + self.i = i + + def __repr__(self): + return 'Index {}'.format(self.i) + + class Unop(Expression): """ Operation on one operand """ def __init__(self, op, a, loc): diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/c3/builder.py --- a/python/ppci/c3/builder.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/c3/builder.py Thu Mar 13 18:59:06 2014 +0100 @@ -130,4 +130,3 @@ yield self.cg.gencode(pkg) if not all(pkg.ok for pkg in all_pkgs): self.ok = False - return diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/c3/codegenerator.py --- a/python/ppci/c3/codegenerator.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/c3/codegenerator.py Thu Mar 13 18:59:06 2014 +0100 @@ -1,4 +1,5 @@ import logging +import struct from .. import ir from .. import irutils from . import astnodes as ast @@ -200,6 +201,8 @@ self.emit(ir.Jump(bbfalse)) else: raise NotImplementedError('Unknown cond {}'.format(expr)) + + # Check that the condition is a boolean value: if not self.equalTypes(expr.typ, self.boolType): self.error('Condition must be boolean', expr.loc) @@ -272,6 +275,23 @@ bt = self.the_type(expr.base.typ) offset = ir.Const(bt.fieldOffset(expr.field)) return ir.Mem(ir.Add(base.e, offset)) + elif type(expr) is ast.Index: + """ Array indexing """ + base = self.genExprCode(expr.base) + idx = self.genExprCode(expr.i) + base_typ = self.the_type(expr.base.typ) + if not isinstance(base_typ, ast.ArrayType): + raise SemanticError('Cannot index non-array type {}'.format(base_typ), expr.base.loc) + idx_type = self.the_type(expr.i.typ) + if not self.equalTypes(idx_type, self.intType): + raise SemanticError('Index must be int not {}'.format(idx_type), expr.i.loc) + assert type(base) is ir.Mem + element_type = self.the_type(base_typ.element_type) + element_size = self.size_of(element_type) + expr.typ = base_typ.element_type + expr.lvalue = True + + return ir.Mem(ir.Add(base.e, ir.Mul(idx, ir.Const(element_size)))) elif type(expr) is ast.Literal: expr.lvalue = False typemap = {int: 'int', float: 'double', bool: 'bool', str:'string'} @@ -279,7 +299,12 @@ expr.typ = self.pkg.scope[typemap[type(expr.val)]] else: raise SemanticError('Unknown literal type {}'.format(expr.val), expr.loc) - return ir.Const(expr.val) + # Construct correct const value: + if type(expr.val) is str: + cval = struct.pack('') self.Consume('(') ce = self.Expression() @@ -363,7 +390,9 @@ pfe = self.PrimaryExpression() while self.Peak in ['[', '.', '->', '(', '++']: if self.hasConsumed('['): - raise NotImplementedError('Array not yet implemented') + i = self.Expression() + self.Consume(']') + pfe = Index(pfe, i, i.loc) elif self.hasConsumed('->'): field = self.Consume('ID') pfe = Deref(pfe, pfe.loc) @@ -410,3 +439,4 @@ elif self.Peak == 'ID': return self.parseDesignator() self.Error('Expected NUM, ID or (expr), got {0}'.format(self.Peak)) + diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/c3/scope.py --- a/python/ppci/c3/scope.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/c3/scope.py Thu Mar 13 18:59:06 2014 +0100 @@ -1,4 +1,6 @@ from .astnodes import Constant, Variable, Function, BaseType, Symbol +from .astnodes import ArrayType, StructureType, DefinedType, PointerType +from .astnodes import StructField class Scope: @@ -72,6 +74,13 @@ scope.addSymbol(BaseType('double')) scope.addSymbol(BaseType('void')) scope.addSymbol(BaseType('bool')) - scope.addSymbol(BaseType('string')) - scope.addSymbol(BaseType('byte')) + byteType = BaseType('byte') + byteType.bytesize = target.byte_sizes['byte'] + scope.addSymbol(byteType) + + # Construct string type from others: + ln = StructField('len', intType) + txt = StructField('txt', ArrayType(byteType, 0)) + strType = DefinedType('string', PointerType(StructureType([ln, txt])), None) + scope.addSymbol(strType) return scope diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/c3/visitor.py --- a/python/ppci/c3/visitor.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/c3/visitor.py Thu Mar 13 18:59:06 2014 +0100 @@ -61,6 +61,9 @@ self.do(node.to_type) elif type(node) is Member: self.do(node.base) + elif type(node) is Index: + self.do(node.base) + self.do(node.i) elif type(node) is Deref: self.do(node.ptr) elif type(node) is Constant: @@ -75,6 +78,9 @@ elif type(node) is StructureType: for m in node.mems: self.do(m.typ) + elif type(node) is ArrayType: + self.do(node.element_type) + self.do(node.size) elif type(node) is FunctionType: for pt in node.parametertypes: self.do(pt) diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/codegen/canon.py --- a/python/ppci/codegen/canon.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/codegen/canon.py Thu Mar 13 18:59:06 2014 +0100 @@ -64,13 +64,16 @@ elif isinstance(exp, ir.Mem): exp.e = rewriteExp(exp.e, frame) return exp + elif isinstance(exp, ir.Addr): + exp.e = rewriteExp(exp.e, frame) + return exp elif isinstance(exp, ir.Call): exp.arguments = [rewriteExp(p, frame) for p in exp.arguments] # Rewrite call into eseq: t = newTemp() return ir.Eseq(ir.Move(t, exp), t) else: - raise NotImplementedError('NI: {}'.format(exp)) + raise NotImplementedError('NI: {}, {}'.format(exp, type(exp))) # The flatten functions pull out seq instructions to the sequence list. @@ -86,6 +89,9 @@ elif isinstance(exp, ir.Mem): exp.e, s = flattenExp(exp.e) return exp, s + elif isinstance(exp, ir.Addr): + exp.e, s = flattenExp(exp.e) + return exp, s elif isinstance(exp, ir.Eseq): s = flattenStmt(exp.stmt) exp.e, se = flattenExp(exp.e) diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/ir.py --- a/python/ppci/ir.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/ir.py Thu Mar 13 18:59:06 2014 +0100 @@ -214,7 +214,7 @@ self.arguments = arguments def __repr__(self): - args = ', '.join([str(arg) for arg in self.arguments]) + args = ', '.join(str(arg) for arg in self.arguments) return '{}({})'.format(self.f, args) @@ -309,6 +309,15 @@ return '[{}]'.format(self.e) +class Addr(Expression): + """ Address of label """ + def __init__(self, e): + self.e = e + + def __repr__(self): + return '&{}'.format(self.e) + + class Statement: """ Base class for all instructions. """ @property diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/ir2tree.py --- a/python/ppci/ir2tree.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/ir2tree.py Thu Mar 13 18:59:06 2014 +0100 @@ -27,14 +27,26 @@ @register(ir.Const) def const_to_tree(e): - t = Tree('CONSTI32') - t.value = e.value - return t + if type(e.value) is bytes: + t = Tree('CONSTDATA') + t.value = e.value + print(t.value) + return t + elif type(e.value) is int: + t = Tree('CONSTI32') + t.value = e.value + return t + else: + raise Exception('{} not implemented'.format(type(e.value))) @register(ir.Mem) def mem_to_tree(e): return Tree('MEMI32', makeTree(e.e)) +@register(ir.Addr) +def mem_to_tree(e): + return Tree('ADR', makeTree(e.e)) + @register(ir.Call) def call_to_tree(e): t = Tree('CALL') diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/linker.py --- a/python/ppci/linker.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/linker.py Thu Mar 13 18:59:06 2014 +0100 @@ -103,6 +103,21 @@ section.data[reloc.offset+1] |= (offset >> 8) & 0xF section.data[reloc.offset+0] = offset & 0xFF +@reloc('adr_imm12') +def apply_adr_imm12(reloc, sym, section, reloc_value): + assert sym.value % 4 == 0 + assert reloc_value % 4 == 0 + offset = (sym.value - (reloc_value + 8)) + U = 2 + if offset < 0: + offset = -offset + U = 1 + assert offset < 4096 + section.data[reloc.offset+2] |= (U << 6) #(rel24 >> 16) & 0xFF + section.data[reloc.offset+1] |= (offset >> 8) & 0xF + section.data[reloc.offset+0] = offset & 0xFF + + class Linker: """ Merges the sections of several object files and performs relocation """ diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/target/arm/__init__.py --- a/python/ppci/target/arm/__init__.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/target/arm/__init__.py Thu Mar 13 18:59:06 2014 +0100 @@ -4,9 +4,9 @@ from ..arm.registers import R8, R9, R10, R11, R12, SP, LR, PC from ..arm.registers import register_range -from .instructions import Dcd, Mov, Add, Sub, Orr1, Mul, Mov2, Add1 +from .instructions import Dcd, Mov, Add, Sub, Orr1, Mul, Mov2, Add1, Mul1 from .instructions import B, Bl, Ble, Bgt, Beq, Blt, Cmp, Cmp2 -from .instructions import Push, Pop, Str, Ldr, Ldr3, Str1, Ldr1 +from .instructions import Push, Pop, Str, Ldr, Ldr3, Str1, Ldr1, Adr from .selector import ArmInstructionSelector from .frame import ArmFrame @@ -20,9 +20,11 @@ self.add_lowering(Ldr3, lambda im: Ldr3(im.dst[0], im.others[0])) self.add_lowering(Str1, lambda im: Str1(im.src[1], im.src[0], im.others[0])) self.add_lowering(Ldr1, lambda im: Ldr1(im.dst[0], im.src[0], im.others[0])) + self.add_lowering(Adr, lambda im: Adr(im.dst[0], im.others[0])) self.add_lowering(Mov2, lambda im: Mov2(im.dst[0], im.src[0])) self.add_lowering(Cmp2, lambda im: Cmp2(im.src[0], im.src[1])) self.add_lowering(Add1, lambda im: Add1(im.dst[0], im.src[0], im.src[1])) + self.add_lowering(Mul1, lambda im: Mul1(im.dst[0], im.src[0], im.src[1])) def make_parser(self): # Assembly grammar: @@ -134,6 +136,10 @@ self.add_instruction(['str', 'reg', ',', '[', 'reg', ',', 'reg', ']'], lambda rhs: Str(rhs[1], rhs[4], rhs[6])) + self.add_keyword('adr') + self.add_instruction(['adr', 'reg', ',', 'ID'], + lambda rhs: Adr(rhs[1], rhs[3].val)) + # Register list grammar: self.add_rule('reg_list', ['{', 'reg_list_inner', '}'], lambda rhs: rhs[1]) diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/target/arm/arm.brg --- a/python/ppci/target/arm/arm.brg Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/target/arm/arm.brg Thu Mar 13 18:59:06 2014 +0100 @@ -1,18 +1,20 @@ -from ppci.target.arm.instructions import Add1, Sub1, Ldr1, Ldr3 +from ppci.target.arm.instructions import Add1, Sub1, Mul1 +from ppci.target.arm.instructions import Ldr1, Ldr3, Adr %% -%terminal ADDI32 SUBI32 MULI32 +%terminal ADDI32 SUBI32 MULI32 ADR %terminal ORI32 SHLI32 -%terminal CONSTI32 MEMI32 REGI32 CALL +%terminal CONSTI32 CONSTDATA MEMI32 REGI32 CALL %terminal MOVI32 %% reg: ADDI32(reg, reg) 2 (. d = self.newTmp(); self.emit(Add1, dst=[d], src=[$1, $2]); return d .) reg: SUBI32(reg, reg) 2 (. d = self.newTmp(); self.emit(Sub1, dst=[d], src=[$1, $2]); return d .) -reg: SUBI32(reg, reg) 2 (. d = self.newTmp(); self.emit(Sub1, dst=[d], src=[$1, $2]); return d .) +reg: MULI32(reg, reg) 2 (. d = self.newTmp(); self.emit(Mul1, dst=[d], src=[$1, $2]); return d .) + reg: MEMI32(ADDI32(reg, cn)) 2 (. d = self.newTmp(); self.emit(Ldr1, dst=[d], src=[$1], others=[$2]); return d .) reg: MEMI32(reg) 2 (. d = self.newTmp(); self.emit(Ldr1, dst=[d], src=[$1], others=[0]); return d .) @@ -20,6 +22,9 @@ cn: CONSTI32 0 (. return $$.value .) reg: CONSTI32 3 (. d = self.newTmp(); ln = self.selector.frame.add_constant($$.value); self.emit(Ldr3, dst=[d], others=[ln]); return d .) + +reg: ADR(CONSTDATA) 2 (. d = self.newTmp(); ln = self.selector.frame.add_constant($$.children[0].value); self.emit(Adr, dst=[d], others=[ln]); return d .) + reg: REGI32 1 (. return $$.value .) reg: CALL 1 (. return self.selector.munchCall($$.value) .) diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/target/arm/frame.py --- a/python/ppci/target/arm/frame.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/target/arm/frame.py Thu Mar 13 18:59:06 2014 +0100 @@ -52,6 +52,7 @@ return self.locVars[lvar] def add_constant(self, value): + assert type(value) in [int, bytes] lab_name = '{}_literal_{}'.format(self.name, len(self.constants)) self.constants.append((lab_name, value)) return lab_name @@ -83,13 +84,13 @@ for ln, v in self.constants: if isinstance(v, int): post.extend([Label(ln), Dcd(v)]) - elif isinstance(v, str): - post.extend([Label(ln), Dcd(len(v))]) + elif isinstance(v, bytes): + post.append(Label(ln)) for c in v: - post.append(Db(ord(c))) + post.append(Db(c)) post.append(Alignment(4)) # Align at 4 bytes else: - raise Exception() + raise Exception('Constant of type {} not supported'.format(v)) return post def EntryExitGlue3(self): diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/target/arm/instructions.py --- a/python/ppci/target/arm/instructions.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/target/arm/instructions.py Thu Mar 13 18:59:06 2014 +0100 @@ -173,7 +173,7 @@ return Mul1(args[0], args[1], args[2]) -class Mul(ArmInstruction): +class Mul1(ArmInstruction): def __init__(self, rd, rn, rm): super().__init__() self.rd = rd @@ -211,18 +211,21 @@ return self.token.encode() def __repr__(self): - return 'add {}, {}, {}'.format(self.rd, self.rn, self.rm) + return '{} {}, {}, {}'.format(self.mnemonic, self.rd, self.rn, self.rm) class Add1(OpRegRegReg): + mnemonic = 'ADD' opcode = 0b0000100 class Sub1(OpRegRegReg): + mnemonic = 'SUB' opcode = 0b0000010 class Orr1(OpRegRegReg): + mnemonic = 'ORR' opcode = 0b0001100 @@ -245,14 +248,16 @@ return self.token.encode() def __repr__(self): - return 'add {}, {}, {}'.format(self.rd, self.rn, self.imm) + return '{} {}, {}, {}'.format(self.mnemonic, self.rd, self.rn, self.imm) class Add2(OpRegRegImm): + mnemonic = 'ADD' opcode = 0b0010100 class Sub2(OpRegRegImm): + mnemonic = 'SUB' opcode = 0b0010010 @@ -393,6 +398,7 @@ return '{} {}, [{}, {}]'.format(self.mnemonic, self.rt, self.rn, hex(self.offset)) + class Str1(LdrStrBase): opcode = 0b010 bit20 = 0 @@ -405,6 +411,27 @@ mnemonic = 'LDR' +class Adr(ArmInstruction): + def __init__(self, rd, label): + super().__init__() + self.rd = rd + self.label = label + + def __repr__(self): + return 'ADR {}, {}'.format(self.rd, self.label) + + def relocations(self): + return [(self.label, 'adr_imm12')] + + def encode(self): + self.token.cond = AL + self.token[0:12] = 0 # Filled by linker + self.token[12:16] = self.rd.num + self.token[16:20] = 0b1111 + self.token[25] = 1 + return self.token.encode() + + class Ldr3(ArmInstruction): """ Load PC relative constant value LDR rt, label diff -r b8ad45b3a573 -r 5477e499b039 python/ppci/target/basetarget.py --- a/python/ppci/target/basetarget.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/ppci/target/basetarget.py Thu Mar 13 18:59:06 2014 +0100 @@ -21,6 +21,9 @@ def encode(self): return bytes() + def __repr__(self): + return 'NOP' + class PseudoInstruction(Instruction): pass @@ -84,6 +87,7 @@ self.desc = desc self.registers = [] self.byte_sizes = {'int' : 4} # For front end! + self.byte_sizes['byte'] = 1 # For lowering: self.lower_functions = {} diff -r b8ad45b3a573 -r 5477e499b039 python/pyburg.py --- a/python/pyburg.py Sun Mar 09 18:49:10 2014 +0100 +++ b/python/pyburg.py Thu Mar 13 18:59:06 2014 +0100 @@ -252,11 +252,12 @@ # TODO: check for rules fullfilled (by not using 999999) self.print(' nts = self.nts({})'.format(rule.nr)) self.print(' kids = self.kids(tree, {})'.format(rule.nr)) - self.print(' c = sum(x.state.get_cost(y) for x, y in zip(kids, nts)) + {}'.format(rule.cost)) - self.print(' tree.state.set_cost("{}", c, {})'.format(rule.non_term, rule.nr)) + self.print(' if all(x.state.has_goal(y) for x, y in zip(kids, nts)):') + self.print(' c = sum(x.state.get_cost(y) for x, y in zip(kids, nts)) + {}'.format(rule.cost)) + self.print(' tree.state.set_cost("{}", c, {})'.format(rule.non_term, rule.nr)) for cr in self.system.symbols[rule.non_term].chain_rules: - self.print(' # Chain rule: {}'.format(cr)) - self.print(' tree.state.set_cost("{}", c + {}, {})'.format(cr.non_term, cr.cost, cr.nr)) + self.print(' # Chain rule: {}'.format(cr)) + self.print(' tree.state.set_cost("{}", c + {}, {})'.format(cr.non_term, cr.cost, cr.nr)) def emit_state(self): """ Emit a function that assigns a new state to a node """ diff -r b8ad45b3a573 -r 5477e499b039 test/testarmasm.py --- a/test/testarmasm.py Sun Mar 09 18:49:10 2014 +0100 +++ b/test/testarmasm.py Thu Mar 13 18:59:06 2014 +0100 @@ -95,6 +95,16 @@ self.feed('mul r4,r5,r2') self.check('174045e2 ffffffba 950204e0') + def testAdr(self): + self.feed('adr r5, cval') + self.feed('adr r9, cval') + self.feed('adr r8, cval') + self.feed('cval:') + self.feed('adr r11, cval') + self.feed('adr r12, cval') + self.feed('adr r1, cval') + self.check('04508fe2 00908fe2 04804fe2 08b04fe2 0cc04fe2 10104fe2') + if __name__ == '__main__': unittest.main() diff -r b8ad45b3a573 -r 5477e499b039 test/testc3.py --- a/test/testc3.py Sun Mar 09 18:49:10 2014 +0100 +++ b/test/testc3.py Thu Mar 13 18:59:06 2014 +0100 @@ -343,6 +343,45 @@ """ self.expectErrors(snippet, [5]) + def testArray(self): + snippet = """ + module testarray; + function void t() + { + var int[100] x; + var int a, b; + a = 2; + b = x[a*2+9 - a] * x[22+12]; + x[1] = x[2]; + } + """ + self.expectOK(snippet) + + def testArrayFail(self): + snippet = """ + module testarray; + function void t() + { + var bool c; + c = false; + var int[100] x; + x[1] = x[c]; + } + """ + self.expectErrors(snippet, [8]) + + def testArrayFail2(self): + snippet = """ + module testarray; + function void t() + { + var int c; + var int x; + c = x[2]; + } + """ + self.expectErrors(snippet, [7]) + def testStructCall(self): snippet = """ module teststruct1; diff -r b8ad45b3a573 -r 5477e499b039 test/testemulation.py --- a/test/testemulation.py Sun Mar 09 18:49:10 2014 +0100 +++ b/test/testemulation.py Thu Mar 13 18:59:06 2014 +0100 @@ -80,7 +80,7 @@ recipe = os.path.join(testdir, '..', 'kernel', 'arm.yaml') self.buildRecipe(recipe) data = self.runQemu('../kernel/kernel_arm.bin', machine='vexpress-a9') - self.assertEqual('e', data[0]) + self.assertEqual('Welcome to lcfos!', data) if __name__ == '__main__': diff -r b8ad45b3a573 -r 5477e499b039 util/test_patterns.txt --- a/util/test_patterns.txt Sun Mar 09 18:49:10 2014 +0100 +++ b/util/test_patterns.txt Thu Mar 13 18:59:06 2014 +0100 @@ -28,3 +28,12 @@ === cmp r4, r11 cmp r5, #0x50000 +=== +adr r5, cval +adr r9, cval +adr r8, cval +cval: +adr r11, cval +adr r12, cval +adr r1, cval +pop {r2}