Skip to content

Commit

Permalink
ARM64: add and recognize specific operation for sign extension
Browse files Browse the repository at this point in the history
  • Loading branch information
xavierleroy committed Sep 22, 2020
1 parent 946b606 commit 3b7f1f8
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 1 deletion.
6 changes: 5 additions & 1 deletion asmcomp/arm64/arch.ml
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ type specific_operation =
| Isqrtf (* floating-point square root *)
| Ibswap of int (* endianness conversion *)
| Imove32 (* 32-bit integer move *)
| Isignext of int (* sign extension *)

and arith_operation =
Ishiftadd
Expand All @@ -70,7 +71,7 @@ let spacetime_node_hole_pointer_is_live_before = function
| Ifar_alloc _ | Ifar_intop_checkbound _ | Ifar_intop_imm_checkbound _
| Ishiftarith _ | Ishiftcheckbound _ | Ifar_shiftcheckbound _ -> false
| Imuladd | Imulsub | Inegmulf | Imuladdf | Inegmuladdf | Imulsubf
| Inegmulsubf | Isqrtf | Ibswap _ | Imove32 -> false
| Inegmulsubf | Isqrtf | Ibswap _ | Imove32 | Isignext _ -> false

(* Sizes, endianness *)

Expand Down Expand Up @@ -178,6 +179,9 @@ let print_specific_operation printreg op ppf arg =
| Imove32 ->
fprintf ppf "move32 %a"
printreg arg.(0)
| Isignext n ->
fprintf ppf "signext%d %a"
n printreg arg.(0)

(* Recognition of logical immediate arguments *)

Expand Down
3 changes: 3 additions & 0 deletions asmcomp/arm64/emit.mlp
Original file line number Diff line number Diff line change
Expand Up @@ -530,6 +530,7 @@ module BR = Branch_relaxation.Make (struct
| Lop (Ispecific (Ibswap 16)) -> 2
| Lop (Ispecific (Ibswap _)) -> 1
| Lop (Ispecific Imove32) -> 1
| Lop (Ispecific (Isignext _)) -> 1
| Lop (Iname_for_debugger _) -> 0
| Lreloadretaddr -> 0
| Lreturn -> epilogue_size ()
Expand Down Expand Up @@ -876,6 +877,8 @@ let emit_instr i =
| _ ->
assert false
end
| Lop(Ispecific(Isignext size)) ->
` sbfm {emit_reg i.res.(0)}, {emit_reg i.arg.(0)}, #0, #{emit_int (size - 1)}\n`
| Lop (Iname_for_debugger _) -> ()
| Lreloadretaddr ->
()
Expand Down
8 changes: 8 additions & 0 deletions asmcomp/arm64/selection.ml
Original file line number Diff line number Diff line change
Expand Up @@ -160,6 +160,14 @@ method! select_operation op args dbg =
| _ ->
super#select_operation op args dbg
end
(* Recognize sign extension *)
| Casr ->
begin match args with
[Cop(Clsl, [k; Cconst_int (n, _)], _); Cconst_int (n', _)]
when n' = n && 0 < n && n < 64 ->
(Ispecific (Isignext (64 - n)), [k])
| _ -> super#select_operation op args dbg
end
(* Recognize floating-point negate and multiply *)
| Cnegf ->
begin match args with
Expand Down

0 comments on commit 3b7f1f8

Please sign in to comment.