diff options
-rw-r--r-- | .gitignore | 1 | ||||
-rw-r--r-- | asm/Makefile | 10 | ||||
-rw-r--r-- | asm/_tags | 2 | ||||
-rw-r--r-- | asm/asm.ml | 3 | ||||
-rw-r--r-- | asm/asmlex.mll | 17 | ||||
-rw-r--r-- | asm/asmpars.mly | 208 | ||||
-rw-r--r-- | asm/assembler.ml | 1 | ||||
-rw-r--r-- | asm/test.asm | 28 |
8 files changed, 172 insertions, 98 deletions
@@ -5,6 +5,7 @@ csim/csim sched/sched monitor/mon +asm/asm *.o *.ps */*.net diff --git a/asm/Makefile b/asm/Makefile new file mode 100644 index 0000000..8ac2004 --- /dev/null +++ b/asm/Makefile @@ -0,0 +1,10 @@ + +all: asm + +asm: assembler.ml asm.ml asmlex.mll asmpars.mly + ocamlbuild assembler.native + mv assembler.native asm + +clean: + rm asm + rm -r _build @@ -1,2 +1,4 @@ true: use_menhir +<*.ml>: debug +<*.byte>: use_unix, debug @@ -1,3 +1,5 @@ +exception Asm_error of string + type reg = int type imm = @@ -54,6 +56,7 @@ type instr = | Liu of (reg * imm) | Liuz of (reg * imm) | Lra of imm + | TwoRawBytes of (int * int) module Imap = Map.Make(String) diff --git a/asm/asmlex.mll b/asm/asmlex.mll index 2bd52fc..1c7e3e7 100644 --- a/asm/asmlex.mll +++ b/asm/asmlex.mll @@ -23,10 +23,12 @@ "liu",LIU; "liuz",LIUZ; "lra",LRA; + "la",LA; "li",LI; "move",MOVE; "jz",JZ; "jnz",JNZ; + "asciiz",ASCIIZ; "_clock",INT 0x4000; "_input",INT 0x4100; "_output",INT 0x4102; @@ -54,8 +56,8 @@ 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 + else if c >= Char.code 'a' && c <= Char.code 'f' then c - (Char.code 'a') + 10 + else c - (Char.code 'A') + 10 in res := !res + v done; !res @@ -89,7 +91,8 @@ rule token = parse { INT (read_16 n) } | (digit)+ as n { INT (int_of_string n) } | "0b" (['0' '1']+ as n) { INT (read_2 n) } - | ['A'-'Z']+ as name { REG (List.assoc name regs) } + | '"' { STR (lex_str "" lexbuf) } + | ['A'-'Z']+ as name { try REG (List.assoc name regs) with Not_found -> raise (Asm_error ("no reg " ^ name))} | '$' (['0'-'7'] as n) { REG (Char.code n - (Char.code '0')) } | ".text" { TEXT } | ".data" { DATA } @@ -101,3 +104,11 @@ and comment = parse | eof { EOF } | '\n' { Lexing.new_line lexbuf; token lexbuf } | _ { comment lexbuf } + +and lex_str q = parse + | eof { q } + | '"' { q } + | "\\\"" { lex_str (q ^ "\"") lexbuf } + | "\\\\" { lex_str (q ^ "\\") lexbuf } + | "\\n" { lex_str (q ^ "\n") lexbuf } + | _ as c { lex_str (q ^ String.make 1 c) lexbuf } diff --git a/asm/asmpars.mly b/asm/asmpars.mly index 294374a..46ca7a7 100644 --- a/asm/asmpars.mly +++ b/asm/asmpars.mly @@ -1,26 +1,26 @@ %{ - open Asm - - let unsigned = function - | Addu - | Subu - | Mulu - | Divu - | Sltu - | Sleu - | Jltru - | Jleru - -> true - | _ -> false - - let pc = ref 0 - - let ram = ref 0 - - let add r i = r := !r + i - - let lbls2 = ref (Imap.empty) - + open Asm + + let unsigned = function + | Addu + | Subu + | Mulu + | Divu + | Sltu + | Sleu + | Jltru + | Jleru + -> true + | _ -> false + + let pc = ref 0 + + let ram = ref 0 + + let add r i = r := !r + i + + let lbls2 = ref (Imap.empty) + let li u r = function | Imm i -> let c = @@ -30,29 +30,35 @@ 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)] - + + + let explode s = (* string -> char list *) + let rec exp i l = + if i < 0 then l else exp (i - 1) (s.[i] :: l) in + exp (String.length s - 1) [];; %} -%token EOF,COLON,TEXT,DATA,BYTE,WORD,MINUS,MOVE,JZ,JNZ,LP,RP -%token POP,PUSH,INCRI,SHI,JJ,JAL,JR,JALR,LW,SW,LB,SB,NOT,LIL,LILZ,LIU,LIUZ,LRA,LI +%token EOF,COLON,TEXT,DATA,BYTE,WORD,ASCIIZ,MINUS,MOVE,JZ,JNZ,LP,RP +%token POP,PUSH,INCRI,SHI,JJ,JAL,JR,JALR,LW,SW,LB,SB,NOT,LIL,LILZ,LIU,LIUZ,LRA,LA,LI %token<Asm.reg> REG %token<Asm.fmt_r> ROP,RIOP %token<string> ID %token<int> INT +%token<string> STR %start<Asm.program> program %% program: - TEXT is=instr* d=data? EOF - { { text = List.flatten is; - data = (match d with Some l -> List.flatten l | None -> []); - lbls = !lbls2 } } - + TEXT is=instr* d=data? EOF + { { text = List.flatten is; + data = (match d with Some l -> List.flatten l | None -> []); + lbls = !lbls2 } } + data: - DATA d=datas* { d } - + DATA d=datas* { d } + datas: | labeld d=datas { d } | BYTE bs=int* { List.map (fun i -> add ram 1; i,false) bs } @@ -69,69 +75,81 @@ instr: | i=_instr { i } _instr: - | o=ROP r1=REG r2=REG r3=REG { add pc 2; [R (o,r1,r2,r3)] } - | o=RIOP r1=REG r2=REG imm=imm - { let l = li (unsigned o) 5 imm in - add pc 2; l @ [R (o,r1,r2,5)] } - | INCRI r=REG i=int { - if i >= - (1 lsl 7) && i < 1 lsl 7 then - (add pc 2; [Incri (r,i)]) - else let l = li false 5 (Imm i) in - (add pc 2; l @ [R (Add,r,r,5)]) } - | SHI r=REG i=int { add pc 2; [Shi (r,i)] } - | JJ i=imm { add pc 2; [J i] } - | LI r=REG i=imm { li false r i } - | JR r=REG { add pc 2; [Jr r] } - | JAL i=imm { add pc 2; [Jal i] } - | JALR r=REG { add pc 2; [Jalr r] } - | LW r1=REG i=int LP r2=REG RP { - if i >= - (1 lsl 4) && i < 1 lsl 4 then - (add pc 2; [Lw (r1,r2,i)]) - else let l = li false 5 (Imm i) in - (add pc 2; l @ [R (Lwr,r1,r2,5)]) } - | SW r1=REG i=int LP r2=REG RP { - if i >= - (1 lsl 4) && i < 1 lsl 4 then - (add pc 2; [Sw (r1,r2,i)]) - else let l = li false 5 (Imm i) in - (add pc 2; l @ [R (Swr,r1,r2,5)]) } - | LB r1=REG i=int LP r2=REG RP { - if i >= - (1 lsl 4) && i < 1 lsl 4 then - (add pc 2; [Lb (r1,r2,i)]) - else let l = li false 5 (Imm i) in - (add pc 2; l @ [R (Lbr,r1,r2,5)]) } - | SB r1=REG i=int LP r2=REG RP { - if i >= - (1 lsl 4) && i < 1 lsl 4 then - (add pc 2; [Sb (r1,r2,i)]) - else let l = li false 5 (Imm i) in - (add pc 2; l @ [R (Sbr,r1,r2,5)]) } - | LW r1=REG l=ID { let l = li false 5 (Lab l) in - add pc 2; l @ [Lw (r1,5,0)] } - | LB r1=REG l=ID { let l = li false 5 (Lab l) in - add pc 2; l @ [Lb (r1,5,0)] } - | SW r1=REG l=ID { let l = li false 5 (Lab l) in - add pc 2; l @ [Sw (r1,5,0)] } - | SB r1=REG l=ID { let l = li false 5 (Lab l) in - add pc 2; l @ [Sb (r1,5,0)] } - | LRA i=int { assert (i > -(1 lsl 10) && i < 1 lsl 10); - add pc 2; [Lra (Imm i)] } - | LRA l=ID { add pc 2; [Lra (Lab l)] } - | LIL r=REG i=int { add pc 2; [Lil (r,Imm i)] } - | LILZ r=REG i=int { add pc 2; [Lilz (r,Imm i)] } - | LIU r=REG i=int { add pc 2; [Liu (r,Imm i)] } - | LIUZ r=REG i=int { add pc 2; [Liuz (r,Imm i)] } - | MOVE r1=REG r2=REG { add pc 2; [R (Add,r1,r2,0)] } - | NOT r1=REG r2=REG { add pc 2; [R (Nor,r1,r2,0)] } - | JZ r=REG l=ID { let l = li false 5 (Lab l) in - add pc 2; l @ [R (Jer,r,5,0)] } - | JNZ r=REG l=ID { let l = li false 5 (Lab l) in - 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)] } - + | o=ROP r1=REG r2=REG r3=REG { add pc 2; [R (o,r1,r2,r3)] } + | o=RIOP r1=REG r2=REG imm=imm + { let l = li (unsigned o) 5 imm in + add pc 2; l @ [R (o,r1,r2,5)] } + | INCRI r=REG i=int { + if i >= - (1 lsl 7) && i < 1 lsl 7 then + (add pc 2; [Incri (r,i)]) + else let l = li false 5 (Imm i) in + (add pc 2; l @ [R (Add,r,r,5)]) } + | SHI r=REG i=int { add pc 2; [Shi (r,i)] } + | JJ i=imm { add pc 2; [J i] } + | LI r=REG i=imm { li false r i } + | JR r=REG { add pc 2; [Jr r] } + | JAL i=imm { add pc 2; [Jal i] } + | JALR r=REG { add pc 2; [Jalr r] } + | LW r1=REG i=int LP r2=REG RP { + if i >= - (1 lsl 4) && i < 1 lsl 4 then + (add pc 2; [Lw (r1,r2,i)]) + else let l = li false 5 (Imm i) in + (add pc 2; l @ [R (Lwr,r1,r2,5)]) } + | SW r1=REG i=int LP r2=REG RP { + if i >= - (1 lsl 4) && i < 1 lsl 4 then + (add pc 2; [Sw (r1,r2,i)]) + else let l = li false 5 (Imm i) in + (add pc 2; l @ [R (Swr,r1,r2,5)]) } + | LB r1=REG i=int LP r2=REG RP { + if i >= - (1 lsl 4) && i < 1 lsl 4 then + (add pc 2; [Lb (r1,r2,i)]) + else let l = li false 5 (Imm i) in + (add pc 2; l @ [R (Lbr,r1,r2,5)]) } + | SB r1=REG i=int LP r2=REG RP { + if i >= - (1 lsl 4) && i < 1 lsl 4 then + (add pc 2; [Sb (r1,r2,i)]) + else let l = li false 5 (Imm i) in + (add pc 2; l @ [R (Sbr,r1,r2,5)]) } + | LW r1=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [Lw (r1,5,0)] } + | LB r1=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [Lb (r1,5,0)] } + | SW r1=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [Sw (r1,5,0)] } + | SB r1=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [Sb (r1,5,0)] } + | LRA i=int { assert (i > -(1 lsl 10) && i < 1 lsl 10); + add pc 2; [Lra (Imm i)] } + | LRA l=ID { add pc 2; [Lra (Lab l)] } + | LA r=REG l=ID { li false r (Lab l) } + | LIL r=REG i=int { add pc 2; [Lil (r,Imm i)] } + | LILZ r=REG i=int { add pc 2; [Lilz (r,Imm i)] } + | LIU r=REG i=int { add pc 2; [Liu (r,Imm i)] } + | LIUZ r=REG i=int { add pc 2; [Liuz (r,Imm i)] } + | MOVE r1=REG r2=REG { add pc 2; [R (Add,r1,r2,0)] } + | NOT r1=REG r2=REG { add pc 2; [R (Nor,r1,r2,0)] } + | JZ r=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [R (Jer,5,r,0)] } + | JNZ r=REG l=ID { let l = li false 5 (Lab l) in + add pc 2; l @ [R (Jner,5,r,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)] } + | ASCIIZ s=STR { + let bytes = List.map Char.code (explode s) @ [0] in + let rec pair = function + | a::b::q -> (a, b)::(pair q) + | [a] -> [(a, 0)] + | [] -> [] + in + let words = pair bytes in + add pc (List.length bytes); + List.map (fun (a, b) -> TwoRawBytes (a, b)) words + } + imm: - | id=ID { Lab id } - | n=int { Imm n } + | id=ID { Lab id } + | n=int { Imm n } int: - | n=INT { n } - | MINUS n=INT { - n } + | n=INT { n } + | MINUS n=INT { - n } diff --git a/asm/assembler.ml b/asm/assembler.ml index e3e81f4..48049ef 100644 --- a/asm/assembler.ml +++ b/asm/assembler.ml @@ -87,6 +87,7 @@ let print_program p = | Imm i -> i | Lab l -> (byte 16 (fst (Imap.find l p.lbls))) lsr 8 in let get_reps = function + | TwoRawBytes(a, b) -> (a) lxor (b lsl 8), sprintf "bytes %d %d" a b | R (o,r1,r2,r3) -> r (code o) r1 r2 r3, sprintf "%s %s %s %s" (List.assoc o rev_keywords) (rts r1) (rts r2) (rts r3) | Incri (r,d) -> i 0b00110 r d, sprintf "incri %s %d" (rts r) d diff --git a/asm/test.asm b/asm/test.asm new file mode 100644 index 0000000..d37ca61 --- /dev/null +++ b/asm/test.asm @@ -0,0 +1,28 @@ +.text + liuz SP 0xFF + add D Z Z +init: + liuz B 0x40 + lw B 0(B) + jz B init + add D D B + push D + la A msgtick + jal ser_out_msg + pop D + j init + +ser_out_msg: + liuz C 0x41 + lil C 0x02 +ser_out_msg_loop: + lb B 0(A) + jz B ser_out_msg_ret + sb B 0(C) + incri A 1 + j ser_out_msg_loop +ser_out_msg_ret: + jr RA + +msgtick: + asciiz "Tick!" |