]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/asmcomp/sparc/proc.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / asmcomp / sparc / proc.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: proc.ml 8462 2007-10-30 12:37:16Z xleroy $ *)
14
15 (* Description of the Sparc processor *)
16
17 open Misc
18 open Cmm
19 open Reg
20 open Arch
21 open Mach
22
23 (* Instruction selection *)
24
25 let word_addressed = false
26
27 (* Registers available for register allocation *)
28
29 (* Register map:
30     %o0 - %o5   0 - 5       function results, C functions args / res
31     %i0 - %i5   6 - 11      function arguments, preserved by C
32     %l0 - %l4   12 - 16     general purpose, preserved by C
33     %g3 - %g4   17 - 18     general purpose, not preserved by C
34
35     %l5                     exception pointer
36     %l6                     allocation pointer
37     %l7                     address of allocation limit
38
39     %g0                     always zero
40     %g1 - %g2               temporaries
41     %g5 - %g7               reserved for system libraries
42
43     %f0 - %f10  100 - 105   function arguments and results
44     %f12 - %f28 106 - 114   general purpose
45     %f30                    temporary *)
46
47 let int_reg_name = [|
48   (* 0-5 *)   "%o0"; "%o1"; "%o2"; "%o3"; "%o4"; "%o5";
49   (* 6-11 *)  "%i0"; "%i1"; "%i2"; "%i3"; "%i4"; "%i5";
50   (* 12-16 *) "%l0"; "%l1"; "%l2"; "%l3"; "%l4";
51   (* 17-18 *) "%g3"; "%g4"
52 |]
53   
54 let float_reg_name = [|
55   (* 100-105 *) "%f0"; "%f2"; "%f4"; "%f6"; "%f8"; "%f10";
56   (* 106-109 *) "%f12"; "%f14"; "%f16"; "%f18";
57   (* 110-114 *) "%f20"; "%f22"; "%f24"; "%f26"; "%f28";
58   (* 115 *)     "%f30";
59   (* Odd parts of register pairs *)
60   (* 116-121 *) "%f1"; "%f3"; "%f5"; "%f7"; "%f9"; "%f11";
61   (* 122-125 *) "%f13"; "%f15"; "%f17"; "%f19";
62   (* 126-130 *) "%f21"; "%f23"; "%f25"; "%f27"; "%f29";
63   (* 131 *)     "%f31"
64 |]
65
66 let num_register_classes = 2
67
68 let register_class r =
69   match r.typ with
70     Int -> 0
71   | Addr -> 0
72   | Float -> 1
73
74 let num_available_registers = [| 19; 15 |]
75
76 let first_available_register = [| 0; 100 |]
77
78 let register_name r =
79   if r < 100 then int_reg_name.(r) else float_reg_name.(r - 100)
80
81 let rotate_registers = true
82
83 (* Representation of hard registers by pseudo-registers *)
84
85 let hard_int_reg =
86   let v = Array.create 19 Reg.dummy in
87   for i = 0 to 18 do v.(i) <- Reg.at_location Int (Reg i) done;
88   v
89
90 let hard_float_reg =
91   let v = Array.create 32 Reg.dummy in
92   for i = 0 to 31 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done;
93   v
94
95 let all_phys_regs =
96   Array.append hard_int_reg (Array.sub hard_float_reg 0 15)
97   (* No need to include the odd parts of float register pairs,
98      nor the temporary register %f30 *)
99
100 let phys_reg n =
101   if n < 100 then hard_int_reg.(n) else hard_float_reg.(n - 100)
102
103 let stack_slot slot ty =
104   Reg.at_location ty (Stack slot)
105
106 (* Calling conventions *)
107
108 let calling_conventions first_int last_int first_float last_float make_stack
109                         arg =
110   let loc = Array.create (Array.length arg) Reg.dummy in
111   let int = ref first_int in
112   let float = ref first_float in
113   let ofs = ref 0 in
114   for i = 0 to Array.length arg - 1 do
115     match arg.(i).typ with
116       Int | Addr as ty ->
117         if !int <= last_int then begin
118           loc.(i) <- phys_reg !int;
119           incr int
120         end else begin
121           loc.(i) <- stack_slot (make_stack !ofs) ty;
122           ofs := !ofs + size_int
123         end
124     | Float ->
125         if !float <= last_float then begin
126           loc.(i) <- phys_reg !float;
127           incr float
128         end else begin
129           loc.(i) <- stack_slot (make_stack !ofs) Float;
130           ofs := !ofs + size_float
131         end
132   done;
133   (loc, Misc.align !ofs 8)         (* Keep stack 8-aligned *)
134
135 let incoming ofs = Incoming ofs
136 let outgoing ofs = Outgoing ofs
137 let not_supported ofs = fatal_error "Proc.loc_results: cannot call"
138
139 let loc_arguments arg =
140   calling_conventions 6 15 100 105 outgoing arg
141 let loc_parameters arg =
142   let (loc, ofs) = calling_conventions 6 15 100 105 incoming arg in loc
143 let loc_results res =
144   let (loc, ofs) = calling_conventions 0 5 100 105 not_supported res in loc
145
146 (* On the Sparc, all arguments to C functions, even floating-point arguments,
147    are passed in %o0..%o5, then on the stack *)
148
149 let loc_external_arguments arg =
150   let loc = ref [] in
151   let reg = ref 0 (* %o0 *) in
152   let ofs = ref (-4) in              (* start at sp + 92 = sp + 96 - 4 *)
153   for i = 0 to Array.length arg - 1 do
154     if !reg <= 5 (* %o5 *) then begin
155       match arg.(i).typ with
156         Int | Addr ->
157           loc := phys_reg !reg :: !loc;
158           incr reg
159       | Float ->
160           if !reg = 5 then fatal_error "Proc_sparc: cannot call";
161           loc := phys_reg (!reg + 1) :: phys_reg !reg :: !loc;
162           reg := !reg + 2
163     end else begin
164       loc := stack_slot (outgoing !ofs) arg.(i).typ :: !loc;
165       ofs := !ofs + size_component arg.(i).typ
166     end
167   done;
168   (* Keep stack 8-aligned *)
169   (Array.of_list(List.rev !loc), Misc.align (!ofs + 4) 8)
170
171 let loc_external_results res =
172   let (loc, ofs) = calling_conventions 0 0 100 100 not_supported res in loc
173
174 let loc_exn_bucket = phys_reg 0         (* $o0 *)
175
176 (* Registers destroyed by operations *)
177
178 let destroyed_at_c_call = (* %l0-%l4, %i0-%i5 preserved *)
179   Array.of_list(List.map phys_reg
180     [0; 1; 2; 3; 4; 5; 17; 18;
181      100; 101; 102; 103; 104; 105; 106; 107;
182      108; 109; 110; 111; 112; 113; 114])
183
184 let destroyed_at_oper = function
185     Iop(Icall_ind | Icall_imm _ | Iextcall(_, true)) -> all_phys_regs
186   | Iop(Iextcall(_, false)) -> destroyed_at_c_call
187   | _ -> [||]
188
189 let destroyed_at_raise = all_phys_regs
190
191 (* Maximal register pressure *)
192
193 let safe_register_pressure = function
194     Iextcall(_, _) -> 0
195   | _ -> 15
196
197 let max_register_pressure = function
198     Iextcall(_, _) -> [| 11; 0 |]
199   | _ -> [| 19; 15 |]
200
201 (* Layout of the stack *)
202
203 let num_stack_slots = [| 0; 0 |]
204 let contains_calls = ref false
205
206 (* Calling the assembler and the archiver *)
207
208 let assemble_file infile outfile =
209   let asflags = begin match !arch_version with
210     SPARC_V7 -> " -o "
211   | SPARC_V8 -> " -xarch=v8 -o "
212   | SPARC_V9 -> " -xarch=v8plus -o "
213   end in
214   Ccomp.command (Config.asm ^ asflags ^
215                  Filename.quote outfile ^ " " ^ Filename.quote infile)