Skip to content

Commit

Permalink
reorganize mem
Browse files Browse the repository at this point in the history
  • Loading branch information
Ubuntu committed Aug 8, 2024
1 parent 6c40303 commit 42dea0a
Show file tree
Hide file tree
Showing 5 changed files with 106 additions and 72 deletions.
57 changes: 34 additions & 23 deletions ocaml/parser/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -51,32 +51,37 @@ let string_of_params params =
(List.rev (List.rev_map
(fun p -> string_of_type p.pty ^ " " ^ p.pname) params))

let rec string_of_operand (op : operand_t) =
let rec string_of_offset (off : offset_t) =
match off with
| Const c -> string_of_int c
| Var s -> s
| Add (off0, off1) -> string_of_offset off0 ^ " + " ^ string_of_offset off1
| Mul (off0, off1) -> string_of_offset off0 ^ " * " ^ string_of_offset off1

let rec string_of_loc loc =
"(" ^ string_of_type loc.lty ^ ")" ^ string_of_operand loc.lop ^
" + " ^ string_of_offset loc.loffset
and string_of_operand (op : operand_t) =
match op with
| Var s -> s
| Const z -> Z.to_string z
| String s -> "\"" ^ s ^ "\""
| Neg p -> "-" ^ string_of_operand p
| Element (p, op) -> string_of_operand p ^ "[" ^ string_of_operand op ^ "]"
| Member (p, op) -> string_of_operand p ^ "->" ^ string_of_operand op ^ "]"
| Mem (t, l) -> "MEM <" ^ string_of_type t ^ "> [" ^ string_of_loc l ^ "]"
| Ref p -> "&" ^ string_of_operand p
| Deref p -> "*" ^ string_of_operand p
| Ops ps -> let pstrs = List.map string_of_operand ps in
"{ " ^ (String.concat ", " pstrs) ^ " }"

let rec string_of_offset off =
match off with
| Const c -> string_of_int c
| Var s -> s
| Add (off0, off1) -> string_of_offset off0 ^ " + " ^ string_of_offset off1
| Mul (off0, off1) -> string_of_offset off0 ^ " * " ^ string_of_offset off1

let string_of_loc loc =
"(" ^ string_of_type loc.lty ^ ")" ^ string_of_operand loc.lop ^
" + " ^ string_of_offset loc.loffset

let string_of_cond cond =
match cond with
| Eq (op0, op1) -> string_of_operand op0 ^ " == " ^ string_of_operand op1
| Neq (op0, op1) -> string_of_operand op0 ^ " != " ^ string_of_operand op1
| Gt (op0, op1) -> string_of_operand op0 ^ " > " ^ string_of_operand op1
| Ge (op0, op1) -> string_of_operand op0 ^ " >= " ^ string_of_operand op1
| Lt (op0, op1) -> string_of_operand op0 ^ " < " ^ string_of_operand op1
| Le (op0, op1) -> string_of_operand op0 ^ " <= " ^ string_of_operand op1

let string_of_instr instr =
Expand All @@ -99,30 +104,32 @@ let string_of_instr instr =
" | " ^ string_of_operand r1
| Xor (l, r0, r1) -> string_of_operand l ^ " = " ^ string_of_operand r0 ^
" ^ " ^ string_of_operand r1
| Neq (l, r0, r1) -> string_of_operand l ^ " = " ^ string_of_operand r0 ^
" != " ^ string_of_operand r1
| Rshift (l, r0, r1) -> string_of_operand l ^ " = " ^ string_of_operand r0
^ " >> " ^ string_of_operand r1
| Lshift (l, r0, r1) -> string_of_operand l ^ " = " ^ string_of_operand r0
^ " << " ^ string_of_operand r1
| Load (l, t, loc) -> string_of_operand l ^ " = MEM <" ^ string_of_type t ^ "> [" ^
string_of_loc loc ^ "]"
| Store (loc, t, r) -> "MEM <" ^ string_of_type t ^ "> [" ^
string_of_loc loc ^ "] = " ^ string_of_operand r
| Copy (t0, l, t1, r) -> "MEM <" ^ string_of_type t0 ^ "> [& " ^
string_of_operand l ^ "] = MEM <" ^
string_of_type t1 ^ "> [" ^
string_of_operand r ^ "]"
| Load (d, s) -> string_of_operand d ^ " = " ^ string_of_operand s
| Store (d, s) -> string_of_operand d ^ " = " ^ string_of_operand s
| Copy (d, s) -> string_of_operand d ^ " = " ^ string_of_operand s
| Ite (l, cond, b0, b1) -> string_of_operand l ^ " = " ^
string_of_operand cond ^ " ? " ^
string_of_operand b0 ^ " : " ^
string_of_operand b1
| Call (f, ops) -> let op_strs = List.map string_of_operand ops in
f ^ " (" ^ (String.concat "," op_strs) ^ ")"
| Call (op, f, ops) -> let op_strs = List.map string_of_operand ops in
(match op with
None -> ""
| Some p -> string_of_operand p ^ " = ") ^
f ^ " (" ^ (String.concat "," op_strs) ^ ")"
| CondBranch (c, b0, b1) -> "if (" ^ string_of_cond c ^ ")\n" ^
" goto <bb " ^ Z.to_string b0 ^ ">\n" ^
"else\n" ^
" goto <bb " ^ Z.to_string b1 ^ ">"
| Goto b -> "goto <bb" ^ Z.to_string b ^ ">"
| Return -> "return"
| Return op -> "return" ^ (match op with
| None -> ""
| Some p -> string_of_operand p)
| Wmadd (l, r0, r1, r2) -> string_of_operand l ^
" = WIDEN_MULT_PLUS_EXPR <" ^
string_of_operand r0 ^ ", " ^
Expand All @@ -138,6 +145,10 @@ let string_of_instr instr =
| VecUnpackHi (l, r) -> string_of_operand l ^
" = [vec_unpack_hi_expr] " ^ string_of_operand r
| DeferredInit v -> string_of_operand v ^ " = DEFERRED_INIT"
| VCondMask (l, p0, p1, p2) -> string_of_operand l ^ " = VCOND_MASK (" ^
string_of_operand p0 ^ ", " ^
string_of_operand p1 ^ ", " ^
string_of_operand p2 ^ ")"

let string_of_func f =
let strings_of_instrs =
Expand Down
5 changes: 4 additions & 1 deletion ocaml/parser/gimpleLexer.mll
Original file line number Diff line number Diff line change
Expand Up @@ -70,8 +70,10 @@ token = parse
| '|' { OROP }
| '^' { XOROP }
| '=' { EQOP }
| "==" { EEQOP }
| "!=" { NEQOP }
| "<=" { LEOP }
| ">=" { GEOP }
| '?' { QUESTION }
| "<<" { LSHIFT }
| ">>" { RSHIFT }
Expand All @@ -80,6 +82,7 @@ token = parse
| "WIDEN_MULT_PLUS_EXPR" { WMADDOP }
| "WIDEN_MULT_MINUS_EXPR" { WMSUBOP }
| ".DEFERRED_INIT" { DEFERRED_INIT }
| ".VCOND_MASK" { VCOND_MASK }
| "vec_unpack_lo_expr" { VEC_UNPACK_LO_EXPR }
| "vec_unpack_hi_expr" { VEC_UNPACK_HI_EXPR }
(* Types *)
Expand All @@ -97,7 +100,7 @@ token = parse
(* Offsets *)
| ('-'? (number+) as byte) "B" { BYTE (int_of_string byte) }
(* Strings *)
| '"' (([^'\r''\n'' ']+) as s) '"' { STRING s }
| '"' (([^'\r''\n']+) as s) '"' { STRING s }
(* Misc *)
| "local count" { LOCAL_COUNT }
| "Removing basic block" { REMOVING_BASIC_BLOCK }
Expand Down
62 changes: 36 additions & 26 deletions ocaml/parser/gimpleParser.mly
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,8 @@
%token COMMA SEMICOLON COLON DQUOTE
/* Operators */
%token ADDOP SUBOP MULOP WMULOP ANDOP OROP XOROP LSHIFT RSHIFT EQOP NEQOP
%token LEOP
%token WMADDOP WMSUBOP QUESTION RARROW DEFERRED_INIT
%token LEOP GEOP EEQOP
%token WMADDOP WMSUBOP QUESTION RARROW DEFERRED_INIT VCOND_MASK
%token VEC_UNPACK_LO_EXPR VEC_UNPACK_HI_EXPR
/* Types */
%token CONST VOID BOOL CHAR INT SHORT LONG SIGNED UNSIGNED VECTOR STRUCT
Expand Down Expand Up @@ -86,6 +86,7 @@ var_decl:
ground_typ:
| VOID { Void }
| BOOL { Bool }
| CHAR { Char }
| UNSIGNED CHAR { Uchar }
| SIGNED CHAR { Char }
| SHORT INT { Short }
Expand Down Expand Up @@ -126,13 +127,15 @@ instrs:
op:
| ID { Var $1 : operand_t }
| NUM { Const $1 }
| BYTE { Const (Z.of_int $1) }
| SUBOP op { Neg $2 }
| ID LSQUARE NUM RSQUARE { Element (Var $1, Const $3) }
| ID LSQUARE op RSQUARE { Element (Var $1, $3) }
| ID RARROW ID LSQUARE NUM RSQUARE { Element (Member (Var $1, Var $3),
Const $5) }
| ID RARROW ID { Member (Var $1, Var $3) }
| ANDOP op { Ref $2 }
| LBRACK ops RBRACK { Ops $2 }
| STRING { String $1 }
;

ops:
Expand All @@ -155,29 +158,22 @@ instr:
| op EQOP op ANDOP op SEMICOLON { And ($1, $3, $5) }
| op EQOP op OROP op SEMICOLON { Or ($1, $3, $5) }
| op EQOP op XOROP op SEMICOLON { Xor ($1, $3, $5) }
| op EQOP op NEQOP op SEMICOLON { Neq ($1, $3, $5) }
| op EQOP op RSHIFT op SEMICOLON { Rshift ($1, $3, $5) }
| op EQOP op LSHIFT op SEMICOLON { Lshift ($1, $3, $5) }
| LANGLE BB NUM RANGLE LSQUARE LOCAL_COUNT COLON NUM RSQUARE COLON
{ Label $3 }
| op EQOP op QUESTION op COLON op SEMICOLON
{ Ite ($1, $3, $5, $7) }
| op EQOP MULOP loc SEMICOLON { Load ($1, Void, $4) }
| op EQOP MEM LSQUARE loc RSQUARE SEMICOLON
{ Load ($1, Void, $5) }
| op EQOP MEM LANGLE typ RANGLE LSQUARE loc RSQUARE SEMICOLON
{ Load ($1, $5, $8) }
| ID LPAREN ops RPAREN SEMICOLON { Call ($1, $3) }
| op EQOP mem SEMICOLON { Load ($1, $3) }
| ID LPAREN ops RPAREN SEMICOLON { Call (None, $1, $3) }
| ID LPAREN ops RPAREN SEMICOLON LSQUARE TAIL_CALL RSQUARE
{ Call ($1, $3) }
| MULOP loc EQOP op SEMICOLON { Store ($2, Void, $4) }
| MEM LSQUARE loc RSQUARE EQOP ID SEMICOLON
{ Store ($3, Void, Var $6) }
| MEM LANGLE typ RANGLE LSQUARE loc RSQUARE EQOP ID SEMICOLON
{ Store ($6, $3, Var $9) }
| MEM LANGLE typ RANGLE LSQUARE LPAREN CHAR_REF_ALL RPAREN ANDOP ID RSQUARE
EQOP MEM LANGLE typ RANGLE LSQUARE LPAREN CHAR_REF_ALL RPAREN ID RSQUARE
SEMICOLON { Copy ($3, Ref (Var $10),
$15, Var $21) }
{ Call (None, $1, $3) }
| op EQOP ID LPAREN ops RPAREN SEMICOLON { Call (Some $1, $3, $5) }
| op EQOP ID LPAREN ops RPAREN SEMICOLON LSQUARE TAIL_CALL RSQUARE
{ Call (Some $1, $3, $5) }
| mem EQOP op SEMICOLON { Store ($1, $3) }
| mem EQOP mem SEMICOLON { Copy ($1, $3) }
| op EQOP WMADDOP LANGLE op COMMA op COMMA op RANGLE SEMICOLON
{ Wmadd ($1, $5, $7, $9) }
| op EQOP WMSUBOP LANGLE op COMMA op COMMA op RANGLE SEMICOLON
Expand All @@ -189,14 +185,28 @@ instr:
| op EQOP DEFERRED_INIT LPAREN NUM COMMA NUM COMMA
ANDOP STRING LSQUARE NUM RSQUARE RPAREN SEMICOLON
{ DeferredInit ($1) }
| op EQOP VCOND_MASK LPAREN op COMMA op COMMA op RPAREN SEMICOLON
{ VCondMask ($1, $5, $7, $9) }
| IF LPAREN condition RPAREN
GOTO LANGLE BB NUM RANGLE SEMICOLON LSQUARE FLOAT PERCENT RSQUARE
ELSE
GOTO LANGLE BB NUM RANGLE SEMICOLON LSQUARE FLOAT PERCENT RSQUARE
{ CondBranch ($3, $8, $19) }
| GOTO LANGLE BB NUM RANGLE SEMICOLON LSQUARE FLOAT PERCENT RSQUARE
{ Goto $4 }
| RETURN SEMICOLON { Return }
| RETURN op SEMICOLON { Return (Some $2) }
| RETURN SEMICOLON { Return None }
;

mem:
| MEM LSQUARE loc RSQUARE { Mem (Void, $3) }
| MULOP loc { Deref (Mem (Void, $2)) }
| MEM LANGLE typ RANGLE LSQUARE loc RSQUARE
{ Mem ($3, $6) }
| MEM LANGLE typ RANGLE LSQUARE LPAREN CHAR_REF_ALL RPAREN ANDOP loc RSQUARE
{ Ref (Mem ($3, $10)) }
| MEM LANGLE typ RANGLE LSQUARE LPAREN CHAR_REF_ALL RPAREN loc RSQUARE
{ Mem ($3, $9) }
;

loc:
Expand All @@ -222,10 +232,10 @@ loc:
;

condition:
ID NEQOP NUM { Neq (Var $1, Const $3) }
| ID NEQOP ID { Neq (Var $1, Var $3) }
| ID RANGLE NUM { Gt (Var $1, Const $3) }
| ID RANGLE ID { Gt (Var $1, Var $3) }
| ID LEOP ID { Le (Var $1, Var $3) }
| ID LEOP NUM { Le (Var $1, Const $3) }
| op EEQOP op { Eq ($1, $3) }
| op NEQOP op { Neq ($1, $3) }
| op RANGLE op { Gt ($1, $3) }
| op GEOP op { Ge ($1, $3) }
| op LANGLE op { Lt ($1, $3) }
| op LEOP op { Le ($1, $3) }
;
27 changes: 16 additions & 11 deletions ocaml/parser/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,17 +14,20 @@ type param_t = { pty : type_t; pname : string }

type var_t = { vty : type_t; vname : string }

type operand_t = Var of string | Const of Z.t | Neg of operand_t
| Element of operand_t * operand_t | Ref of operand_t
| Member of operand_t * operand_t | Ops of operand_t list

type offset_t = Const of int | Var of string
| Add of offset_t * offset_t | Mul of offset_t * offset_t

type loc_t = { lty : type_t; lop : operand_t; loffset : offset_t }
and operand_t = Var of string | Const of Z.t | String of string
| Neg of operand_t | Ref of operand_t | Deref of operand_t
| Element of operand_t * operand_t
| Member of operand_t * operand_t
| Mem of type_t * loc_t
| Ops of operand_t list

type cond_t = | Neq of operand_t * operand_t | Gt of operand_t * operand_t
| Le of operand_t * operand_t
type cond_t = | Eq of operand_t * operand_t | Neq of operand_t * operand_t
| Gt of operand_t * operand_t | Ge of operand_t * operand_t
| Lt of operand_t * operand_t | Le of operand_t * operand_t

type label_t = Z.t

Expand All @@ -38,21 +41,23 @@ type instr_t = Nop
| And of operand_t * operand_t * operand_t
| Or of operand_t * operand_t * operand_t
| Xor of operand_t * operand_t * operand_t
| Neq of operand_t * operand_t * operand_t
| Rshift of operand_t * operand_t * operand_t
| Lshift of operand_t * operand_t * operand_t
| Load of operand_t * type_t * loc_t
| Store of loc_t * type_t * operand_t
| Copy of type_t * operand_t * type_t * operand_t
| Load of operand_t * operand_t
| Store of operand_t * operand_t
| Copy of operand_t * operand_t
| Ite of operand_t * operand_t * operand_t * operand_t
| Call of string * operand_t list
| Call of operand_t option * string * operand_t list
| CondBranch of cond_t * label_t * label_t
| Goto of label_t
| Return
| Return of operand_t option
| Wmadd of operand_t * operand_t * operand_t * operand_t
| Wmsub of operand_t * operand_t * operand_t * operand_t
| VecUnpackLo of operand_t * operand_t
| VecUnpackHi of operand_t * operand_t
| DeferredInit of operand_t
| VCondMask of operand_t * operand_t *operand_t * operand_t

type function_t = { attr : attribute_t; fty : type_t; fname : string;
params : param_t list; vars : var_t list; instrs : instr_t list }
Expand Down
27 changes: 16 additions & 11 deletions ocaml/parser/syntax.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,17 +14,20 @@ type param_t = { pty : type_t; pname : string }

type var_t = { vty : type_t; vname : string }

type operand_t = Var of string | Const of Z.t | Neg of operand_t
| Element of operand_t * operand_t | Ref of operand_t
| Member of operand_t * operand_t | Ops of operand_t list

type offset_t = Const of int | Var of string
| Add of offset_t * offset_t | Mul of offset_t * offset_t

type loc_t = { lty : type_t; lop : operand_t; loffset : offset_t }
and operand_t = Var of string | Const of Z.t | String of string
| Neg of operand_t | Ref of operand_t | Deref of operand_t
| Element of operand_t * operand_t
| Member of operand_t * operand_t
| Mem of type_t * loc_t
| Ops of operand_t list

type cond_t = | Neq of operand_t * operand_t | Gt of operand_t * operand_t
| Le of operand_t * operand_t
type cond_t = | Eq of operand_t * operand_t | Neq of operand_t * operand_t
| Gt of operand_t * operand_t | Ge of operand_t * operand_t
| Lt of operand_t * operand_t | Le of operand_t * operand_t

type label_t = Z.t

Expand All @@ -38,21 +41,23 @@ type instr_t = Nop
| And of operand_t * operand_t * operand_t
| Or of operand_t * operand_t * operand_t
| Xor of operand_t * operand_t * operand_t
| Neq of operand_t * operand_t * operand_t
| Rshift of operand_t * operand_t * operand_t
| Lshift of operand_t * operand_t * operand_t
| Load of operand_t * type_t * loc_t
| Store of loc_t * type_t * operand_t
| Copy of type_t * operand_t * type_t * operand_t
| Load of operand_t * operand_t
| Store of operand_t * operand_t
| Copy of operand_t * operand_t
| Ite of operand_t * operand_t * operand_t * operand_t
| Call of string * operand_t list
| Call of operand_t option * string * operand_t list
| CondBranch of cond_t * label_t * label_t
| Goto of label_t
| Return
| Return of operand_t option
| Wmadd of operand_t * operand_t * operand_t * operand_t
| Wmsub of operand_t * operand_t * operand_t * operand_t
| VecUnpackLo of operand_t * operand_t
| VecUnpackHi of operand_t * operand_t
| DeferredInit of operand_t
| VCondMask of operand_t * operand_t *operand_t * operand_t

type function_t = { attr : attribute_t; fty : type_t; fname : string;
params : param_t list; vars : var_t list; instrs : instr_t list }
Expand Down

0 comments on commit 42dea0a

Please sign in to comment.