Skip to content

Commit

Permalink
add more gimple commands
Browse files Browse the repository at this point in the history
  • Loading branch information
ubuntu committed Aug 2, 2024
1 parent 0b25b80 commit 3a5451e
Show file tree
Hide file tree
Showing 5 changed files with 80 additions and 20 deletions.
15 changes: 13 additions & 2 deletions ocaml/parser/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,17 +45,23 @@ let string_of_params params =
(List.rev (List.rev_map
(fun p -> string_of_type p.pty ^ " " ^ p.pname) params))

let string_of_operand op =
let rec string_of_operand op =
match op with
| Var s -> s
| Const z -> Z.to_string z
| Access (s, z) -> s ^ "[" ^ Z.to_string z ^ "]"
| Consts zs -> let z_strs = List.map Z.to_string zs in
"{ " ^ (String.concat ", " z_strs) ^ " }"
| Access (s, op) -> s ^ "[" ^ string_of_operand op ^ "]"
| Ref s -> "*" ^ s

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

let string_of_cond cond =
match cond with
| Neq (op0, op1) -> string_of_operand op0 ^ " != " ^ string_of_operand op1

let string_of_instr instr =
match instr with
| Label z -> "L" ^ (Z.to_string z)
Expand Down Expand Up @@ -96,6 +102,11 @@ let string_of_instr instr =
string_of_operand b1
| Call (f, ops) -> let op_strs = List.map string_of_operand ops in
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"
| Wmadd (l, r0, r1, r2) -> string_of_operand l ^
" = WIDEN_MULT_PLUS_EXPR <" ^
Expand Down
14 changes: 9 additions & 5 deletions ocaml/parser/gimpleLexer.mll
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,11 @@
"long" , LONG;
"vector" , VECTOR;
"MEM" , MEM;
"bb" , BB;
"if" , IF;
"else" , ELSE;
"goto" , GOTO;
"return" , RETURN;
"local" , LOCAL;
"count" , COUNT;
]
}

Expand Down Expand Up @@ -56,6 +58,7 @@ token = parse
| ':' { COLON }
| ';' { SEMICOLON }
| '"' { DQUOTE }
| '%' { PERCENT }
(* Operators *)
| '+' { ADDOP }
| '-' { SUBOP }
Expand All @@ -65,10 +68,10 @@ token = parse
| '|' { OROP }
| '^' { XOROP }
| '=' { EQOP }
| "!=" { NEQOP }
| '?' { QUESTION }
| "<<" { LSHIFT }
| ">>" { RSHIFT }
| "bb" { BB }
(* intrinsics *)
| "WIDEN_MULT_PLUS_EXPR" { WMADDOP }
| "WIDEN_MULT_MINUS_EXPR" { WMSUBOP }
Expand All @@ -78,13 +81,14 @@ token = parse
| "int" ((number+) as w) "_t" { SINT (int_of_string w) }
| "__int" ((number+) as w) { SINT (int_of_string w) }
(* Numbers *)
| (number+) as num { NUM (Z.of_string num) }
| ("-" (number+)) as num { NUM (Z.of_string num) }
| ('-'? number+) as num { NUM (Z.of_string num) }
| (number+ '.' number+) as num { FLOAT (float_of_string num) }
(* Offsets *)
| ((number+) as byte) "B" { BYTE (int_of_string byte) }
(* Strings *)
| '"' (([^'\r''\n'' ']+) as s) '"' { STRING s }
(* Misc *)
| "local count" { LOCAL_COUNT }
| "Removing basic block" { REMOVING_BASIC_BLOCK }
| "char * {ref-all}" { CHAR_REF_ALL }
| identity as id { try
Expand Down
47 changes: 40 additions & 7 deletions ocaml/parser/gimpleParser.mly
Original file line number Diff line number Diff line change
Expand Up @@ -11,19 +11,20 @@

%token <string> COMMENT
%token <Z.t> NUM
%token <float> FLOAT
%token <string> ID STRING
%token <int> UINT SINT BYTE

%token LPAREN RPAREN LSQUARE RSQUARE LBRACK RBRACK LANGLE RANGLE
%token COMMA SEMICOLON COLON DQUOTE
/* Operators */
%token ADDOP SUBOP MULOP WMULOP ANDOP OROP XOROP LSHIFT RSHIFT EQOP
%token ADDOP SUBOP MULOP WMULOP ANDOP OROP XOROP LSHIFT RSHIFT EQOP NEQOP
%token WMADDOP WMSUBOP QUESTION
/* Types */
%token CONST VOID BOOL CHAR INT SIGNED UNSIGNED LONG VECTOR
/* Others */
%token ATTRIBUTE ACCESS MEM EOF RETURN LOCAL COUNT BB
%token REMOVING_BASIC_BLOCK CHAR_REF_ALL
%token ATTRIBUTE ACCESS MEM EOF RETURN BB IF ELSE GOTO
%token REMOVING_BASIC_BLOCK CHAR_REF_ALL PERCENT LOCAL_COUNT

%start gimple
%type <Syntax.function_t list> gimple
Expand Down Expand Up @@ -111,29 +112,45 @@ instrs:
instr:
| ID EQOP LPAREN typ RPAREN ID SEMICOLON { Assign (Var $1, $4, Var $6) }
| ID EQOP LBRACK args RBRACK SEMICOLON { Vassign (Var $1, $4) }
| ID EQOP ID LSQUARE ID RSQUARE SEMICOLON { Assign (Var $1, Void,
Access ($3, Var $5)) }
| ID EQOP ID LSQUARE NUM RSQUARE SEMICOLON{ Assign (Var $1, Void,
Access ($3, $5)) }
| ID LSQUARE NUM RSQUARE EQOP ID SEMICOLON{ Assign (Access ($1, $3), Void,
Var $6) }
Access ($3, Const $5)) }
| ID LSQUARE NUM RSQUARE EQOP ID SEMICOLON{ Assign (Access ($1, Const $3),
Void, Var $6) }
| ID EQOP ID ADDOP ID SEMICOLON { Add (Var $1, Var $3, Var $5) }
| ID EQOP ID ADDOP NUM SEMICOLON { Add (Var $1, Var $3, Const $5) }
| ID EQOP ID ADDOP LBRACK nums RBRACK SEMICOLON
{ Add (Var $1, Var $3, Consts $6) }
| ID EQOP ID SUBOP ID SEMICOLON { Sub (Var $1, Var $3, Var $5) }
| ID EQOP ID SUBOP NUM SEMICOLON { Sub (Var $1, Var $3, Const $5) }
| ID EQOP ID SUBOP LBRACK nums RBRACK SEMICOLON
{ Sub (Var $1, Var $3, Consts $6) }
| ID EQOP ID WMULOP ID SEMICOLON { Wmul (Var $1, Var $3, Var $5) }
| ID EQOP ID WMULOP NUM SEMICOLON { Wmul (Var $1, Var $3, Const $5) }
| ID EQOP ID WMULOP LBRACK nums RBRACK SEMICOLON
{ Wmul (Var $1, Var $3, Consts $6) }
| ID EQOP ID MULOP ID SEMICOLON { Mul (Var $1, Var $3, Var $5) }
| ID EQOP ID MULOP NUM SEMICOLON { Mul (Var $1, Var $3, Const $5) }
| ID EQOP ID MULOP LBRACK nums RBRACK SEMICOLON
{ Mul (Var $1, Var $3, Consts $6) }
| ID EQOP ID ANDOP ID SEMICOLON { And (Var $1, Var $3, Var $5) }
| ID EQOP ID ANDOP NUM SEMICOLON { And (Var $1, Var $3, Const $5) }
| ID EQOP ID ANDOP LBRACK nums RBRACK SEMICOLON
{ And (Var $1, Var $3, Consts $6) }
| ID EQOP ID OROP ID SEMICOLON { Or (Var $1, Var $3, Var $5) }
| ID EQOP ID OROP NUM SEMICOLON { Or (Var $1, Var $3, Const $5) }
| ID EQOP ID OROP LBRACK nums RBRACK SEMICOLON
{ Or (Var $1, Var $3, Consts $6) }
| ID EQOP ID XOROP ID SEMICOLON { Xor (Var $1, Var $3, Var $5) }
| ID EQOP ID XOROP NUM SEMICOLON { Xor (Var $1, Var $3, Const $5) }
| ID EQOP ID XOROP LBRACK nums RBRACK SEMICOLON
{ Xor (Var $1, Var $3, Consts $6) }
| ID EQOP ID RSHIFT ID SEMICOLON { Rshift (Var $1, Var $3, Var $5) }
| ID EQOP ID RSHIFT NUM SEMICOLON { Rshift (Var $1, Var $3, Const $5) }
| ID EQOP ID LSHIFT ID SEMICOLON { Lshift (Var $1, Var $3, Var $5) }
| ID EQOP ID LSHIFT NUM SEMICOLON { Lshift (Var $1, Var $3, Const $5) }
| LANGLE BB NUM RANGLE LSQUARE LOCAL COUNT COLON NUM RSQUARE COLON
| LANGLE BB NUM RANGLE LSQUARE LOCAL_COUNT COLON NUM RSQUARE COLON
{ Label $3 }
| ID EQOP ID QUESTION ID COLON ID SEMICOLON
{ Ite (Var $1,Var $3,Var $5,Var $7) }
Expand All @@ -159,9 +176,21 @@ instr:
{ Wmsub (Var $1, Var $5, Var $7, Var $9) }
| ID EQOP WMSUBOP LANGLE ID COMMA NUM COMMA ID RANGLE SEMICOLON
{ Wmsub (Var $1, Var $5, Const $7, Var $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 }
;

nums:
NUM { [ $1 ] }
| NUM COMMA nums { $1::$3 }
;

args:
ID { [ Var $1 ] }
| ID COMMA args { Var $1::$3 }
Expand All @@ -181,3 +210,7 @@ loc:
| LPAREN typ RPAREN ANDOP ID ADDOP BYTE { { lty = $2; lop = Ref $5;
loffset = $7 } }
;

condition:
ID NEQOP NUM { Neq (Var $1, Const $3) }
;
12 changes: 9 additions & 3 deletions ocaml/parser/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,16 @@ 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
| Access of string * Z.t | Ref of string
type operand_t = Var of string | Const of Z.t | Consts of Z.t list
| Access of string * operand_t | Ref of string

type loc_t = { lty : type_t; lop : operand_t; loffset : int }

type instr_t = Label of Z.t
type cond_t = Neq of operand_t * operand_t

type label_t = Z.t

type instr_t = Label of label_t
| Assign of operand_t * type_t * operand_t
| Vassign of operand_t * operand_t list
| Add of operand_t * operand_t * operand_t
Expand All @@ -35,6 +39,8 @@ type instr_t = Label of Z.t
| Copy of type_t * operand_t * type_t * operand_t
| Ite of operand_t * operand_t * operand_t * operand_t
| Call of string * operand_t list
| CondBranch of cond_t * label_t * label_t
| Goto of label_t
| Return
| Wmadd of operand_t * operand_t * operand_t * operand_t
| Wmsub of operand_t * operand_t * operand_t * operand_t
Expand Down
12 changes: 9 additions & 3 deletions ocaml/parser/syntax.mli
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,16 @@ 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
| Access of string * Z.t | Ref of string
type operand_t = Var of string | Const of Z.t | Consts of Z.t list
| Access of string * operand_t | Ref of string

type loc_t = { lty : type_t; lop : operand_t; loffset : int }

type instr_t = Label of Z.t
type cond_t = Neq of operand_t * operand_t

type label_t = Z.t

type instr_t = Label of label_t
| Assign of operand_t * type_t * operand_t
| Vassign of operand_t * operand_t list
| Add of operand_t * operand_t * operand_t
Expand All @@ -35,6 +39,8 @@ type instr_t = Label of Z.t
| Copy of type_t * operand_t * type_t * operand_t
| Ite of operand_t * operand_t * operand_t * operand_t
| Call of string * operand_t list
| CondBranch of cond_t * label_t * label_t
| Goto of label_t
| Return
| Wmadd of operand_t * operand_t * operand_t * operand_t
| Wmsub of operand_t * operand_t * operand_t * operand_t
Expand Down

0 comments on commit 3a5451e

Please sign in to comment.