1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*             Xavier Leroy, projet Gallium, INRIA Rocquencourt           *)
6(*                 Benedikt Meurer, University of Siegen                  *)
7(*                                                                        *)
8(*   Copyright 2013 Institut National de Recherche en Informatique et     *)
9(*     en Automatique.                                                    *)
10(*   Copyright 2012 Benedikt Meurer.                                      *)
11(*                                                                        *)
12(*   All rights reserved.  This file is distributed under the terms of    *)
13(*   the GNU Lesser General Public License version 2.1, with the          *)
14(*   special exception on linking described in the file LICENSE.          *)
15(*                                                                        *)
16(**************************************************************************)
17
18(* Description of the ARM processor in 64-bit mode *)
19
20open Misc
21open Cmm
22open Reg
23open Arch
24open Mach
25
26(* Instruction selection *)
27
28let word_addressed = false
29
30(* Registers available for register allocation *)
31
32(* Integer register map:
33    x0 - x15              general purpose (caller-save)
34    x16, x17              temporaries (used by call veeners)
35    x18                   platform register (reserved)
36    x19 - x25             general purpose (callee-save)
37    x26                   trap pointer
38    x27                   alloc pointer
39    x28                   alloc limit
40    x29                   frame pointer
41    x30                   return address
42    sp / xzr              stack pointer / zero register
43   Floating-point register map:
44    d0 - d7               general purpose (caller-save)
45    d8 - d15              general purpose (callee-save)
46    d16 - d31             generat purpose (caller-save)
47*)
48
49let int_reg_name =
50  [| "x0";  "x1";  "x2";  "x3";  "x4";  "x5";  "x6";  "x7";
51     "x8";  "x9";  "x10"; "x11"; "x12"; "x13"; "x14"; "x15";
52     "x19"; "x20"; "x21"; "x22"; "x23"; "x24"; "x25";
53     "x26"; "x27"; "x28"; "x16"; "x17" |]
54
55let float_reg_name =
56  [| "d0";  "d1";  "d2";  "d3";  "d4";  "d5";  "d6";  "d7";
57     "d8";  "d9";  "d10"; "d11"; "d12"; "d13"; "d14"; "d15";
58     "d16"; "d17"; "d18"; "d19"; "d20"; "d21"; "d22"; "d23";
59     "d24"; "d25"; "d26"; "d27"; "d28"; "d29"; "d30"; "d31" |]
60
61let num_register_classes = 2
62
63let register_class r =
64  match r.typ with
65  | Val | Int | Addr  -> 0
66  | Float -> 1
67
68let num_available_registers =
69  [| 23; 32 |] (* first 23 int regs allocatable; all float regs allocatable *)
70
71let first_available_register =
72  [| 0; 100 |]
73
74let register_name r =
75  if r < 100 then int_reg_name.(r) else float_reg_name.(r - 100)
76
77let rotate_registers = true
78
79(* Representation of hard registers by pseudo-registers *)
80
81let hard_int_reg =
82  let v = Array.make 28 Reg.dummy in
83  for i = 0 to 27 do
84    v.(i) <- Reg.at_location Int (Reg i)
85  done;
86  v
87
88let hard_float_reg =
89  let v = Array.make 32 Reg.dummy in
90  for i = 0 to 31 do
91    v.(i) <- Reg.at_location Float (Reg(100 + i))
92  done;
93  v
94
95let all_phys_regs =
96  Array.append hard_int_reg hard_float_reg
97
98let phys_reg n =
99  if n < 100 then hard_int_reg.(n) else hard_float_reg.(n - 100)
100
101let reg_x15 = phys_reg 15
102let reg_d7 = phys_reg 107
103
104let stack_slot slot ty =
105  Reg.at_location ty (Stack slot)
106
107let loc_spacetime_node_hole = Reg.dummy  (* Spacetime unsupported *)
108
109(* Calling conventions *)
110
111let calling_conventions
112    first_int last_int first_float last_float make_stack arg =
113  let loc = Array.make (Array.length arg) Reg.dummy in
114  let int = ref first_int in
115  let float = ref first_float in
116  let ofs = ref 0 in
117  for i = 0 to Array.length arg - 1 do
118    match arg.(i).typ with
119    | Val | Int | Addr as ty ->
120        if !int <= last_int then begin
121          loc.(i) <- phys_reg !int;
122          incr int
123        end else begin
124          loc.(i) <- stack_slot (make_stack !ofs) ty;
125          ofs := !ofs + size_int
126        end
127    | Float ->
128        if !float <= last_float then begin
129          loc.(i) <- phys_reg !float;
130          incr float
131        end else begin
132          loc.(i) <- stack_slot (make_stack !ofs) Float;
133          ofs := !ofs + size_float
134        end
135  done;
136  (loc, Misc.align !ofs 16)  (* keep stack 16-aligned *)
137
138let incoming ofs = Incoming ofs
139let outgoing ofs = Outgoing ofs
140let not_supported _ofs = fatal_error "Proc.loc_results: cannot call"
141
142(* OCaml calling convention:
143     first integer args in r0...r15
144     first float args in d0...d15
145     remaining args on stack.
146   Return values in r0...r15 or d0...d15. *)
147
148let max_arguments_for_tailcalls = 16
149
150let loc_arguments arg =
151  calling_conventions 0 15 100 115 outgoing arg
152let loc_parameters arg =
153  let (loc, _) = calling_conventions 0 15 100 115 incoming arg in loc
154let loc_results res =
155  let (loc, _) = calling_conventions 0 15 100 115 not_supported res in loc
156
157(* C calling convention:
158     first integer args in r0...r7
159     first float args in d0...d7
160     remaining args on stack.
161   Return values in r0...r1 or d0. *)
162
163let loc_external_arguments arg =
164  let arg =
165    Array.map (fun regs -> assert (Array.length regs = 1); regs.(0)) arg
166  in
167  let loc, alignment = calling_conventions 0 7 100 107 outgoing arg in
168  Array.map (fun reg -> [|reg|]) loc, alignment
169let loc_external_results res =
170  let (loc, _) = calling_conventions 0 1 100 100 not_supported res in loc
171
172let loc_exn_bucket = phys_reg 0
173
174(* Volatile registers: none *)
175
176let regs_are_volatile _rs = false
177
178(* Registers destroyed by operations *)
179
180let destroyed_at_c_call =
181  (* x19-x28, d8-d15 preserved *)
182  Array.of_list (List.map phys_reg
183    [0;1;2;3;4;5;6;7;8;9;10;11;12;13;14;15;
184     100;101;102;103;104;105;106;107;
185     116;117;118;119;120;121;122;123;
186     124;125;126;127;128;129;130;131])
187
188let destroyed_at_oper = function
189  | Iop(Icall_ind _ | Icall_imm _) | Iop(Iextcall { alloc = true; }) ->
190      all_phys_regs
191  | Iop(Iextcall { alloc = false; }) ->
192      destroyed_at_c_call
193  | Iop(Ialloc _) ->
194      [| reg_x15 |]
195  | Iop(Iintoffloat | Ifloatofint | Iload(Single, _) | Istore(Single, _, _)) ->
196      [| reg_d7 |]            (* d7 / s7 destroyed *)
197  | _ -> [||]
198
199let destroyed_at_raise = all_phys_regs
200
201(* Maximal register pressure *)
202
203let safe_register_pressure = function
204  | Iextcall _ -> 8
205  | Ialloc _ -> 25
206  | _ -> 26
207
208let max_register_pressure = function
209  | Iextcall _ -> [| 10; 8 |]
210  | Ialloc _ -> [| 25; 32 |]
211  | Iintoffloat | Ifloatofint
212  | Iload(Single, _) | Istore(Single, _, _) -> [| 26; 31 |]
213  | _ -> [| 26; 32 |]
214
215(* Pure operations (without any side effect besides updating their result
216   registers). *)
217
218let op_is_pure = function
219  | Icall_ind _ | Icall_imm _ | Itailcall_ind _ | Itailcall_imm _
220  | Iextcall _ | Istackoffset _ | Istore _ | Ialloc _
221  | Iintop(Icheckbound _) | Iintop_imm(Icheckbound _, _)
222  | Ispecific(Ishiftcheckbound _) -> false
223  | _ -> true
224
225(* Layout of the stack *)
226
227let num_stack_slots = [| 0; 0 |]
228let contains_calls = ref false
229
230(* Calling the assembler *)
231
232let assemble_file infile outfile =
233  Ccomp.command (Config.asm ^ " -o " ^
234                 Filename.quote outfile ^ " " ^ Filename.quote infile)
235
236
237let init () = ()
238