From 9495dd3a9e4aa9e27004ce9718ac39c197db13c0 Mon Sep 17 00:00:00 2001 From: Alex AUVOLAT Date: Thu, 9 Jan 2014 15:43:03 +0100 Subject: =?UTF-8?q?Donn=C3=A9es=20dans=20.text=20;=20support=20des=20cha?= =?UTF-8?q?=C3=AEnes=20ascii.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- asm/asm.ml | 7 ++++++- asm/asmlex.mll | 38 ++++++++++++++++++++++++++++++++------ asm/asmpars.mly | 20 ++++++++++++-------- asm/assembler.ml | 48 ++++++++++++++++++++++-------------------------- 4 files changed, 72 insertions(+), 41 deletions(-) diff --git a/asm/asm.ml b/asm/asm.ml index 8404654..47f5f7b 100644 --- a/asm/asm.ml +++ b/asm/asm.ml @@ -54,10 +54,13 @@ type instr = | Liu of (reg * imm) | Liuz of (reg * imm) | Lra of imm + | Byte of int + | Word of int + | Hlt module Imap = Map.Make(String) -type program = { text : instr list; data : (int * bool) list; +type program = { text : instr list; lbls : (int * bool) Imap.t } let keywords_r = [ @@ -93,3 +96,5 @@ let keywords_r = [ "swr",Swr; "sbr",Sbr ] + +exception Lexer_error diff --git a/asm/asmlex.mll b/asm/asmlex.mll index 2bd52fc..873e32d 100644 --- a/asm/asmlex.mll +++ b/asm/asmlex.mll @@ -31,7 +31,9 @@ "_input",INT 0x4100; "_output",INT 0x4102; "word",WORD; - "byte",BYTE + "byte",BYTE; + "hlt",HLT; + "ascii",ASCII ] let regs = [ @@ -47,15 +49,19 @@ "SP",7 ] + let vald d = Char.code d - (Char.code '0') + + let valh d = + let c = Char.code d in + if c >= Char.code '0' && c <= Char.code '9' then c - (Char.code '0') + else if c >= Char.code 'a' && c <= Char.code 'f' then c - (Char.code 'a') + else c - (Char.code 'A') + let read_16 n = let res = ref 0 in for i = 0 to String.length n - 1 do res := 16 * !res; - let v = - let c = Char.code n.[i] in - if c >= Char.code '0' && c <= Char.code '9' then c - (Char.code '0') - else if c >= Char.code 'a' && c <= Char.code 'f' then c - (Char.code 'a') - else c - (Char.code 'A') in + let v = valh n.[i] in res := !res + v done; !res @@ -68,6 +74,7 @@ res := !res + v done; !res + } let digit = ['0'-'9'] @@ -96,6 +103,25 @@ rule token = parse | '-' { MINUS } | '(' { LP } | ')' { RP } + | '"' { str [] lexbuf } + +and str acc = parse + | "\\\\" { str ('\\' :: acc) lexbuf } + | '"' { STR (List.rev ('\000' :: acc)) } + | "\\t" { str ('\t' :: acc) lexbuf } + | "\\n" { str ('\n' :: acc) lexbuf } + | "\\r" { str ('\r' :: acc) lexbuf } + | "\\\"" { str ('"' :: acc) lexbuf } + | "\\a" { str ((Char.chr 7) :: acc) lexbuf } + | '\\' (digit as d1) (digit as d2) (digit as d3) + { let c = 100 * (vald d1) + 10 * (vald d2) + (vald d3) in + str ((Char.chr c) :: acc) lexbuf } + | "\\x" (hexdigit as h1) (hexdigit as h2) + { let c = 16 * (valh h1) + (valh h2) in + str ((Char.chr c)::acc) lexbuf } + | eof { raise Lexer_error } + | '\n' { raise Lexer_error } + | [^ '\\' '"' '\n'] as c { str (c::acc) lexbuf } and comment = parse | eof { EOF } diff --git a/asm/asmpars.mly b/asm/asmpars.mly index 294374a..8f47c91 100644 --- a/asm/asmpars.mly +++ b/asm/asmpars.mly @@ -15,7 +15,7 @@ let pc = ref 0 - let ram = ref 0 + let ram = ref 0x8000 let add r i = r := !r + i @@ -30,14 +30,15 @@ else (add pc 4; [Lilz (r,Imm (i land 0x00FF)); Liu (r,Imm ((i land 0xFF00) lsr 8))]) | Lab id -> add pc 4; [Lilz (r,Lab id); Liu (r,Lab id)] - + %} -%token EOF,COLON,TEXT,DATA,BYTE,WORD,MINUS,MOVE,JZ,JNZ,LP,RP +%token EOF,COLON,TEXT,DATA,BYTE,WORD,MINUS,MOVE,JZ,JNZ,LP,RP,HLT,ASCII %token POP,PUSH,INCRI,SHI,JJ,JAL,JR,JALR,LW,SW,LB,SB,NOT,LIL,LILZ,LIU,LIUZ,LRA,LI %token REG %token ROP,RIOP %token ID +%token STR %token INT %start program @@ -45,18 +46,17 @@ %% program: - TEXT is=instr* d=data? EOF + TEXT is=instr* data? EOF { { text = List.flatten is; - data = (match d with Some l -> List.flatten l | None -> []); lbls = !lbls2 } } data: DATA d=datas* { d } datas: - | labeld d=datas { d } - | BYTE bs=int* { List.map (fun i -> add ram 1; i,false) bs } - | WORD bs=int* { List.map (fun i -> add ram 2; i,true) bs } + | labeld datas { () } + | BYTE n=INT { add ram n } + | WORD n=INT { add ram (2*n) } labeli: id=ID COLON { lbls2 := Imap.add id (!pc,true) !lbls2 } @@ -127,6 +127,10 @@ _instr: add pc 2; l @ [R (Jner,r,5,0)] } | POP r=REG { add pc 4; [Lw (r,7,0); Incri (7,2)] } | PUSH r=REG { add pc 4; [Incri (7,-2); Sw (r,7,0)] } + | BYTE bs=int* { List.map (fun b -> add pc 1; Byte b) bs } + | WORD ws=int* { List.map (fun w -> add pc 2; Word w) ws } + | HLT { add pc 2; [Hlt] } + | ASCII s=STR { List.map (fun c -> add pc 1; Byte (Char.code c)) s } imm: | id=ID { Lab id } diff --git a/asm/assembler.ml b/asm/assembler.ml index e3e81f4..66999fb 100644 --- a/asm/assembler.ml +++ b/asm/assembler.ml @@ -75,6 +75,10 @@ let its = function | Imm i -> string_of_int i | Lab l -> l +let size = function + | Byte _ -> 1 + | _ -> 2 + let print_program p = let pc = ref 0 in let value = function @@ -107,37 +111,29 @@ let print_program p = | Liu (r,i) -> (0b11010 lsl 11) lxor (r lsl 8) lxor ((byte 8 (value3 i)) land 0xFF), sprintf "liu %s %s" (rts r) (its i) | Liuz (r,i) -> (0b11011 lsl 11) lxor (r lsl 8) lxor ((byte 8 (value3 i)) land 0xFF), - sprintf "liuz %s %s" (rts r) (its i) in - let n = List.length p.text in + sprintf "liuz %s %s" (rts r) (its i) + | Hlt -> (0b01111 lsl 11),"hlt" + | Word w -> (byte 16 w), "" + | Byte b -> byte 8 b, "" in + let n = List.fold_left (fun n i -> size i + n) 0 p.text in let rev_lbls = Array.make n "" in Imap.iter (fun l (v,t) -> - if t then rev_lbls.(v/2) <- rev_lbls.(v/2) ^ " " ^ l) p.lbls; + if t then rev_lbls.(v) <- rev_lbls.(v) ^ " " ^ l) p.lbls; let f instr = - if rev_lbls.(!pc/2) <> "" then - printf "\t#%s:\n" rev_lbls.(!pc/2); + if rev_lbls.(!pc) <> "" then + printf "\t#%s:\n" rev_lbls.(!pc); let w,s = get_reps instr in - printf "%s\t\t# %s\n" (wts w) s; - pc := !pc + 2 in - printf "%d %d\n" (2*n) 8; + let size = size instr in + if size = 2 then ( + printf "%s" (wts w); + if s <> "" then + printf "\t\t# %s\n" s + else printf "\n"; + pc := !pc + 2 + ) else ( + printf "%s\n" (bts w) ) in + printf "%d %d\n" (n) 8; List.iter f p.text; - let n2 = List.fold_left (fun n (_,w) -> if w then n + 2 else n + 1) 0 p.data in - if n2 > 0 then ( - printf "\n%d %d\n" n2 8; - let rev_lbls = Array.make n2 "" in - Imap.iter (fun l (v,t) -> - if not t then rev_lbls.(v) <- rev_lbls.(v) ^ " " ^ l) p.lbls; - pc := 0; - let f2 (b,w) = - if rev_lbls.(!pc) <> "" then - printf "\t#%s:\n" rev_lbls.(!pc); - if w then ( - printf "%s\n" (wts (byte 16 b)); - pc := !pc + 2 - ) else ( - printf "%s\n" (bts (byte 8 b)); - pc := !pc + 1) in - List.iter f2 p.data - ); printf "\n" let print_error e sp ep = -- cgit v1.2.3