]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmcomp/hppa/proc.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmcomp / hppa / 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 HP PA-RISC processor *)
16
17 open Misc
18 open Cmm
19 open Reg
20 open Arch
21 open Mach
22
23 (* Registers available for register allocation *)
24
25 (* Register map:
26     %r0                         always zero
27     %r1                         temporary, target of ADDIL
28     %r2                         return address
29     %r3                         allocation pointer
30     %r4                         allocation limit
31     %r5                         trap pointer
32     %r6 - %r26                  general purpose
33     %r27                        global pointer
34     %r28 - %r29                 general purpose, C function results
35     %r30                        stack pointer
36     %r31                        temporary, used by BLE
37
38     %fr0 - %fr3                 float status info
39     %fr4 - %fr30                general purpose
40     %fr31                       temporary *)
41
42 let int_reg_name = [|
43   (* 0-4 *)   "%r6"; "%r7"; "%r8"; "%r9"; "%r10"; 
44   (* 5-10 *)  "%r11"; "%r12"; "%r13"; "%r14"; "%r15"; "%r16";
45   (* 11-16 *) "%r17"; "%r18"; "%r19"; "%r20"; "%r21"; "%r22"; 
46   (* 17-20 *) "%r23"; "%r24"; "%r25"; "%r26";
47   (* 21-22 *) "%r28"; "%r29"
48 |]
49   
50 let float_reg_name = [|
51   (* 100-105 *) "%fr4"; "%fr5"; "%fr6"; "%fr7"; "%fr8"; "%fr9";
52   (* 106-111 *) "%fr10"; "%fr11"; "%fr12"; "%fr13"; "%fr14"; "%fr15";
53   (* 112-117 *) "%fr16"; "%fr17"; "%fr18"; "%fr19"; "%fr20"; "%fr21";
54   (* 118-123 *) "%fr22"; "%fr23"; "%fr24"; "%fr25"; "%fr26"; "%fr27"; 
55   (* 124-127 *) "%fr28"; "%fr29"; "%fr30"; "%fr31"
56 |]
57
58 let num_register_classes = 2
59
60 let register_class r =
61   match r.typ with
62     Int -> 0
63   | Addr -> 0
64   | Float -> 1
65
66 let num_available_registers = [| 23; 27 |]
67
68 let first_available_register = [| 0; 100 |]
69
70 let register_name r =
71   if r < 100 then int_reg_name.(r) else float_reg_name.(r - 100)
72
73 let rotate_registers = true
74
75 (* Representation of hard registers by pseudo-registers *)
76
77 let hard_int_reg =
78   let v = Array.create 23 Reg.dummy in
79   for i = 0 to 22 do v.(i) <- Reg.at_location Int (Reg i) done;
80   v
81
82 let hard_float_reg =
83   let v = Array.create 28 Reg.dummy in
84   for i = 0 to 27 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done;
85   v
86
87 let all_phys_regs =
88   Array.append hard_int_reg (Array.sub hard_float_reg 0 27)
89   (* No need to include the left/right parts of float registers *)
90
91 let phys_reg n =
92   if n < 100 then hard_int_reg.(n) else hard_float_reg.(n - 100)
93
94 let stack_slot slot ty =
95   Reg.at_location ty (Stack slot)
96
97 (* Instruction selection *)
98
99 let word_addressed = false
100
101 (* Calling conventions *)
102
103 let calling_conventions first_int last_int first_float last_float make_stack
104                         arg =
105   let loc = Array.create (Array.length arg) Reg.dummy in
106   let int = ref first_int in
107   let float = ref first_float in
108   let ofs = ref 0 in
109   for i = 0 to Array.length arg - 1 do
110     match arg.(i).typ with
111       Int | Addr as ty ->
112         if !int >= last_int then begin
113           loc.(i) <- phys_reg !int;
114           decr int
115         end else begin
116           ofs := !ofs + size_int;
117           loc.(i) <- stack_slot (make_stack !ofs) ty
118         end
119     | Float ->
120         if !float <= last_float then begin
121           loc.(i) <- phys_reg !float;
122           incr float
123         end else begin
124           ofs := Misc.align (!ofs + size_float) 8;
125           loc.(i) <- stack_slot (make_stack !ofs) Float
126         end
127   done;
128   (loc, Misc.align !ofs 8)         (* Keep stack 8-aligned *)
129
130 let incoming ofs = Incoming ofs
131 let outgoing ofs = Outgoing ofs
132 let not_supported ofs = fatal_error "Proc.loc_results: cannot call"
133
134 (* Arguments and results: %r26-%r19, %fr4-%fr11. *)
135
136 let loc_arguments arg =
137   calling_conventions 20 13 100 107 outgoing arg
138 let loc_parameters arg =
139   let (loc, ofs) = calling_conventions  20 13 100 107 incoming arg in loc
140 let loc_results res =
141   let (loc, ofs) = calling_conventions  20 13 100 107 not_supported res in loc
142
143 (* Calling C functions:
144     when all arguments are integers, use %r26 - %r23, 
145     then -52(%r30), -56(%r30), etc.
146     When some arguments are floats, we handle a couple of cases by hand
147     and fail otherwise. *)
148
149 let loc_external_arguments arg =
150   match List.map register_class (Array.to_list arg) with
151     [1] -> ([| phys_reg 101 |], 56)           (* %fr5 *)
152   | [1; 1] -> ([| phys_reg 101; phys_reg 103 |], 56) (* %fr5, %fr7 *)
153   | [1; 0] -> ([| phys_reg 101; phys_reg 18 |], 56) (* %fr5, %r24 *)
154   | [0; 1] -> ([| phys_reg 20; phys_reg 103 |], 56) (* %r26, %fr7 *)
155   | _ ->
156     let loc = Array.create (Array.length arg) Reg.dummy in
157     let int = ref 20 in
158     let ofs = ref 48 in
159     for i = 0 to Array.length arg - 1 do
160       match arg.(i).typ with
161         Int | Addr as ty ->
162           if !int >= 17 then begin
163             loc.(i) <- phys_reg (!int);
164             decr int
165           end else begin
166             ofs := !ofs + 4;
167             loc.(i) <- stack_slot (Outgoing !ofs) ty
168           end
169       | Float ->
170           fatal_error "Proc.external_calling_conventions: cannot call"
171     done;
172     (loc, Misc.align !ofs 8)
173
174 let loc_external_results res =
175   let (loc, ofs) = calling_conventions 21 21 100 100 not_supported res in loc
176
177 let loc_exn_bucket = phys_reg 20        (* %r26 *)
178
179 (* Registers destroyed by operations *)
180
181 let destroyed_at_c_call = (* %r3 - %r18, %fr12 - %fr21 preserved *)
182   Array.of_list(List.map phys_reg
183     [13;14;15;16;17;18;19;20;21;22;
184      100;101;102;103;104;105;106;107;118;119;120;121;122;123;124;125;126])
185
186 let destroyed_by_millicode = (* %r25, %r26, %r28, %r29 -- more? *)
187   [| phys_reg 19; phys_reg 20; phys_reg 21; phys_reg 22 |]
188
189 let destroyed_by_alloc = [| phys_reg 22 |] (* %r29 *)
190
191 let destroyed_at_oper = function
192     Iop(Icall_ind | Icall_imm _ | Iextcall(_, true)) -> all_phys_regs
193   | Iop(Iextcall(_, false)) -> destroyed_at_c_call
194   | Iop(Iintop(Idiv | Imod)) -> destroyed_by_millicode
195   | Iop(Ialloc _) -> destroyed_by_alloc
196   | _ -> [||]
197
198 let destroyed_at_raise = all_phys_regs
199
200 (* Maximal register pressure *)
201
202 let safe_register_pressure = function
203     Iextcall(_, _) -> 16
204   | Iintop(Idiv | Imod) -> 19
205   | _ -> 23
206
207 let max_register_pressure = function
208     Iextcall(_, _) -> [| 16; 19 |]
209   | Iintop(Idiv | Imod) -> [| 19; 27 |]
210   | _ -> [| 23; 27 |]
211
212 (* Layout of the stack *)
213
214 let num_stack_slots = [| 0; 0 |]
215 let contains_calls = ref false
216
217 (* Calling the assembler *)
218
219 let assemble_file infile outfile =
220   Ccomp.command (Config.asm ^ " -o " ^
221                  Filename.quote outfile ^ " " ^ Filename.quote infile)  
222
223 open Clflags;;
224 open Config;;