|
|
8e013d |
From bf083b3beeb9a622017137c246d2cfa863056cc0 Mon Sep 17 00:00:00 2001
|
|
|
8e013d |
From: Nicolas Ojeda Bar <n.oje.bar@gmail.com>
|
|
|
8e013d |
Date: Tue, 22 Nov 2016 22:30:35 +0100
|
|
|
8e013d |
Subject: [PATCH 10/12] Fix immediates' range when adjusting/indexing sp
|
|
|
8e013d |
|
|
|
8e013d |
---
|
|
|
8e013d |
asmcomp/riscv/arch.ml | 3 +++
|
|
|
8e013d |
asmcomp/riscv/emit.mlp | 53 ++++++++++++++++++++++++++++++++++------------
|
|
|
8e013d |
asmcomp/riscv/selection.ml | 2 +-
|
|
|
8e013d |
3 files changed, 44 insertions(+), 14 deletions(-)
|
|
|
8e013d |
|
|
|
8e013d |
diff --git a/asmcomp/riscv/arch.ml b/asmcomp/riscv/arch.ml
|
|
|
8e013d |
index 61a38b1dd..22c807c49 100644
|
|
|
8e013d |
--- a/asmcomp/riscv/arch.ml
|
|
|
8e013d |
+++ b/asmcomp/riscv/arch.ml
|
|
|
8e013d |
@@ -32,6 +32,9 @@ let spacetime_node_hole_pointer_is_live_before = function
|
|
|
8e013d |
type addressing_mode =
|
|
|
8e013d |
| Iindexed of int (* reg + displ *)
|
|
|
8e013d |
|
|
|
8e013d |
+let is_immediate n =
|
|
|
8e013d |
+ (n <= 2047) && (n >= -2048)
|
|
|
8e013d |
+
|
|
|
8e013d |
(* Sizes, endianness *)
|
|
|
8e013d |
|
|
|
8e013d |
let big_endian = false
|
|
|
8e013d |
diff --git a/asmcomp/riscv/emit.mlp b/asmcomp/riscv/emit.mlp
|
|
|
8e013d |
index 6d0e3aefd..97c49ce80 100644
|
|
|
8e013d |
--- a/asmcomp/riscv/emit.mlp
|
|
|
8e013d |
+++ b/asmcomp/riscv/emit.mlp
|
|
|
8e013d |
@@ -93,6 +93,34 @@ let emit_stack r =
|
|
|
8e013d |
let ofs = slot_offset s (register_class r) in `{emit_int ofs}(sp)`
|
|
|
8e013d |
| _ -> fatal_error "Emit.emit_stack"
|
|
|
8e013d |
|
|
|
8e013d |
+(* Adjust sp by the given byte amount *)
|
|
|
8e013d |
+
|
|
|
8e013d |
+let emit_stack_adjustment = function
|
|
|
8e013d |
+ | 0 -> ()
|
|
|
8e013d |
+ | n when is_immediate n ->
|
|
|
8e013d |
+ ` addi sp, sp, {emit_int n}\n`
|
|
|
8e013d |
+ | n ->
|
|
|
8e013d |
+ ` li {emit_reg reg_tmp1}, {emit_int n}\n`;
|
|
|
8e013d |
+ ` add sp, sp, {emit_reg reg_tmp1}\n`
|
|
|
8e013d |
+
|
|
|
8e013d |
+let emit_store src ofs =
|
|
|
8e013d |
+ if is_immediate ofs then
|
|
|
8e013d |
+ ` {emit_string stg} {emit_reg src}, {emit_int ofs}(sp)\n`
|
|
|
8e013d |
+ else begin
|
|
|
8e013d |
+ ` li {emit_reg reg_tmp1}, {emit_int ofs}\n`;
|
|
|
8e013d |
+ ` add {emit_reg reg_tmp1}, sp, {emit_reg reg_tmp1}\n`;
|
|
|
8e013d |
+ ` {emit_string stg} {emit_reg src}, 0({emit_reg reg_tmp1})\n`
|
|
|
8e013d |
+ end
|
|
|
8e013d |
+
|
|
|
8e013d |
+let emit_load dst ofs =
|
|
|
8e013d |
+ if is_immediate ofs then
|
|
|
8e013d |
+ ` {emit_string lg} {emit_reg dst}, {emit_int ofs}(sp)\n`
|
|
|
8e013d |
+ else begin
|
|
|
8e013d |
+ ` li {emit_reg reg_tmp1}, {emit_int ofs}\n`;
|
|
|
8e013d |
+ ` add {emit_reg reg_tmp1}, sp, {emit_reg reg_tmp1}\n`;
|
|
|
8e013d |
+ ` {emit_string lg} {emit_reg dst}, 0({emit_reg reg_tmp1})\n`
|
|
|
8e013d |
+ end
|
|
|
8e013d |
+
|
|
|
8e013d |
(* Record live pointers at call points *)
|
|
|
8e013d |
|
|
|
8e013d |
let record_frame_label ?label live raise_ dbg =
|
|
|
8e013d |
@@ -218,6 +246,7 @@ let name_for_specific = function
|
|
|
8e013d |
|
|
|
8e013d |
(* Name of current function *)
|
|
|
8e013d |
let function_name = ref ""
|
|
|
8e013d |
+
|
|
|
8e013d |
(* Entry point for tail recursive calls *)
|
|
|
8e013d |
let tailrec_entry_point = ref 0
|
|
|
8e013d |
|
|
|
8e013d |
@@ -234,12 +263,14 @@ let emit_instr i =
|
|
|
8e013d |
` mv {emit_reg dst}, {emit_reg src}\n`
|
|
|
8e013d |
| {loc = Reg _; typ = Float}, {loc = Reg _; typ = Float} ->
|
|
|
8e013d |
` fmv.d {emit_reg dst}, {emit_reg src}\n`
|
|
|
8e013d |
- | {loc = Reg _; typ = (Val | Int | Addr)}, {loc = Stack _} ->
|
|
|
8e013d |
- ` {emit_string stg} {emit_reg src}, {emit_stack dst}\n`
|
|
|
8e013d |
+ | {loc = Reg _; typ = (Val | Int | Addr)}, {loc = Stack s} ->
|
|
|
8e013d |
+ let ofs = slot_offset s (register_class dst) in
|
|
|
8e013d |
+ emit_store src ofs
|
|
|
8e013d |
| {loc = Reg _; typ = Float}, {loc = Stack _} ->
|
|
|
8e013d |
` fsd {emit_reg src}, {emit_stack dst}\n`
|
|
|
8e013d |
- | {loc = Stack _; typ = (Val | Int | Addr)}, {loc = Reg _ } ->
|
|
|
8e013d |
- ` {emit_string lg} {emit_reg dst}, {emit_stack src}\n`
|
|
|
8e013d |
+ | {loc = Stack s; typ = (Val | Int | Addr)}, {loc = Reg _} ->
|
|
|
8e013d |
+ let ofs = slot_offset s (register_class src) in
|
|
|
8e013d |
+ emit_load dst ofs
|
|
|
8e013d |
| {loc = Stack _; typ = Float}, {loc = Reg _} ->
|
|
|
8e013d |
` fld {emit_reg dst}, {emit_stack src}\n`
|
|
|
8e013d |
| _ ->
|
|
|
8e013d |
@@ -263,8 +294,7 @@ let emit_instr i =
|
|
|
8e013d |
let n = frame_size() in
|
|
|
8e013d |
if !contains_calls then
|
|
|
8e013d |
` {emit_string lg} ra, {emit_int(n - size_addr)}(sp)\n`;
|
|
|
8e013d |
- if n > 0 then
|
|
|
8e013d |
- ` addi sp, sp, {emit_int n}\n`;
|
|
|
8e013d |
+ emit_stack_adjustment n;
|
|
|
8e013d |
` jr {emit_reg i.arg.(0)}\n`
|
|
|
8e013d |
| Lop(Itailcall_imm {func; label_after = _}) ->
|
|
|
8e013d |
if func = !function_name then begin
|
|
|
8e013d |
@@ -273,8 +303,7 @@ let emit_instr i =
|
|
|
8e013d |
let n = frame_size() in
|
|
|
8e013d |
if !contains_calls then
|
|
|
8e013d |
` {emit_string lg} ra, {emit_int(n - size_addr)}(sp)\n`;
|
|
|
8e013d |
- if n > 0 then
|
|
|
8e013d |
- ` addi sp, sp, {emit_int n}\n`;
|
|
|
8e013d |
+ emit_stack_adjustment n;
|
|
|
8e013d |
` tail {emit_symbol func}\n`
|
|
|
8e013d |
end
|
|
|
8e013d |
| Lop(Iextcall{func; alloc = true; label_after = label}) ->
|
|
|
8e013d |
@@ -285,7 +314,7 @@ let emit_instr i =
|
|
|
8e013d |
` call {emit_symbol func}\n`
|
|
|
8e013d |
| Lop(Istackoffset n) ->
|
|
|
8e013d |
assert (n mod 16 = 0);
|
|
|
8e013d |
- ` addi sp, sp, {emit_int (-n)}\n`;
|
|
|
8e013d |
+ emit_stack_adjustment (-n);
|
|
|
8e013d |
stack_offset := !stack_offset + n
|
|
|
8e013d |
| Lop(Iload(Single, Iindexed ofs)) ->
|
|
|
8e013d |
` flw {emit_reg i.res.(0)}, {emit_int ofs}({emit_reg i.arg.(0)})\n`;
|
|
|
8e013d |
@@ -398,8 +427,7 @@ let emit_instr i =
|
|
|
8e013d |
` {emit_string lg} ra, {emit_int(n - size_addr)}(sp)\n`
|
|
|
8e013d |
| Lreturn ->
|
|
|
8e013d |
let n = frame_size() in
|
|
|
8e013d |
- if n > 0 then
|
|
|
8e013d |
- ` addi sp, sp, {emit_int n}\n`;
|
|
|
8e013d |
+ emit_stack_adjustment n;
|
|
|
8e013d |
` ret\n`
|
|
|
8e013d |
| Llabel lbl ->
|
|
|
8e013d |
`{emit_label lbl}:\n`
|
|
|
8e013d |
@@ -513,8 +541,7 @@ let fundecl fundecl =
|
|
|
8e013d |
` .align 2\n`;
|
|
|
8e013d |
`{emit_symbol fundecl.fun_name}:\n`;
|
|
|
8e013d |
let n = frame_size() in
|
|
|
8e013d |
- if n > 0 then
|
|
|
8e013d |
- ` addi sp, sp, {emit_int(-n)}\n`;
|
|
|
8e013d |
+ emit_stack_adjustment (-n);
|
|
|
8e013d |
if !contains_calls then
|
|
|
8e013d |
` {emit_string stg} ra, {emit_int(n - size_addr)}(sp)\n`;
|
|
|
8e013d |
`{emit_label !tailrec_entry_point}:\n`;
|
|
|
8e013d |
diff --git a/asmcomp/riscv/selection.ml b/asmcomp/riscv/selection.ml
|
|
|
8e013d |
index ad2b26e9b..283233679 100644
|
|
|
8e013d |
--- a/asmcomp/riscv/selection.ml
|
|
|
8e013d |
+++ b/asmcomp/riscv/selection.ml
|
|
|
8e013d |
@@ -22,7 +22,7 @@ class selector = object (self)
|
|
|
8e013d |
|
|
|
8e013d |
inherit Selectgen.selector_generic as super
|
|
|
8e013d |
|
|
|
8e013d |
-method is_immediate n = (n <= 0x7FF) && (n >= -0x800)
|
|
|
8e013d |
+method is_immediate n = is_immediate n
|
|
|
8e013d |
|
|
|
8e013d |
method select_addressing _ = function
|
|
|
8e013d |
| Cop(Cadda, [arg; Cconst_int n]) when self#is_immediate n ->
|
|
|
8e013d |
--
|
|
|
8e013d |
2.13.2
|
|
|
8e013d |
|