~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/hipe/amd64/hipe_amd64_registers.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%% -*- erlang-indent-level: 2 -*-
 
2
%%% $Id$
 
3
%%% ===========================================================================
 
4
%%%  Filename :  hipe_amd64_registers.erl
 
5
%%%  Author   :  Daniel Luna (luna@update.uu.se)
 
6
%%%  Purpose  :  
 
7
%%%  Notes    :  
 
8
%%% ===========================================================================
 
9
 
 
10
-module(hipe_amd64_registers).
 
11
 
 
12
-export([
 
13
         all_precoloured/0,
 
14
         allocatable/0,
 
15
         allocatable_sse2/0,
 
16
         allocatable_x87/0,
 
17
         arg/1,
 
18
         args/1,
 
19
         call_clobbered/0,
 
20
         fcalls/0,
 
21
         float_size/0,
 
22
         first_virtual/0,
 
23
         heap_limit/0,
 
24
         is_arg/1,
 
25
         is_fixed/1,
 
26
         is_precoloured/1,
 
27
         is_precoloured_sse2/1,
 
28
         is_precoloured_x87/1,
 
29
         live_at_return/0,
 
30
         nr_args/0,
 
31
         proc_offset/1,
 
32
         proc_pointer/0,
 
33
         rax/0,
 
34
         rcx/0,
 
35
         ret/1,
 
36
         sp/0,
 
37
         sp_limit_offset/0,
 
38
         reg_name/1,
 
39
         alignment/0,
 
40
         tailcall_clobbered/0,
 
41
         temp0/0,
 
42
         temp1/0,
 
43
%        %% fixed/0,
 
44
         wordsize/0
 
45
        ]).
 
46
 
 
47
-include("../rtl/hipe_literals.hrl").
 
48
 
 
49
-ifdef(AMD64_HP_IN_REGISTER).
 
50
-export([heap_pointer/0]).
 
51
-endif.
 
52
 
 
53
-ifdef(AMD64_FCALLS_IN_REGISTER).
 
54
fcalls_offset() -> false.
 
55
-else.
 
56
fcalls_offset() -> ?P_FCALLS.
 
57
-define(AMD64_FCALLS_REGISTER,16).
 
58
-endif.
 
59
 
 
60
-ifdef(AMD64_HEAP_LIMIT_IN_REGISTER).
 
61
heap_limit_offset() -> false.
 
62
-else.
 
63
-define(AMD64_HEAP_LIMIT_REGISTER, 17).
 
64
heap_limit_offset() -> ?P_HP_LIMIT.
 
65
-endif.
 
66
 
 
67
 
 
68
-define(RAX,  0).
 
69
-define(RCX,  1).
 
70
-define(RDX,  2).
 
71
-define(RBX,  3).
 
72
-define(RSP,  4).
 
73
-define(RBP,  5).
 
74
-define(RSI,  6).
 
75
-define(RDI,  7).
 
76
-define(R8 ,  8).
 
77
-define(R9 ,  9).
 
78
-define(R10, 10).
 
79
-define(R11, 11).
 
80
-define(R12, 12).
 
81
-define(R13, 13).
 
82
-define(R14, 14).
 
83
-define(R15, 15).
 
84
-define(FCALLS,           ?AMD64_FCALLS_REGISTER).
 
85
-define(HEAP_LIMIT,       ?AMD64_HEAP_LIMIT_REGISTER).
 
86
-define(LAST_PRECOLOURED, 17).
 
87
 
 
88
-define(ARG0, ?RSI).
 
89
-define(ARG1, ?RDX).
 
90
-define(ARG2, ?RCX).
 
91
-define(ARG3, ?R8).
 
92
-define(ARG4, ?R9).
 
93
-define(ARG5, ?RDI).
 
94
 
 
95
-define(TEMP0, ?R14).
 
96
-define(TEMP1, ?R13).
 
97
 
 
98
-define(PROC_POINTER, ?RBP).
 
99
 
 
100
reg_name(R) ->
 
101
  case R of
 
102
    ?RAX -> "%rax";
 
103
    ?RCX -> "%rcx";
 
104
    ?RDX -> "%rdx";
 
105
    ?RBX -> "%rbx";
 
106
    ?RSP -> "%rsp";
 
107
    ?RBP -> "%rbp";
 
108
    ?RSI -> "%rsi";
 
109
    ?RDI -> "%rdi";
 
110
    ?FCALLS -> "%fcalls";
 
111
    ?HEAP_LIMIT -> "%hplim";
 
112
    Other -> "%r" ++ integer_to_list(Other)
 
113
  end.
 
114
 
 
115
alignment() -> 8.  
 
116
 
 
117
float_size() -> 8.  
 
118
 
 
119
first_virtual() -> ?LAST_PRECOLOURED + 1.
 
120
 
 
121
is_precoloured(X) -> X =< ?LAST_PRECOLOURED.
 
122
 
 
123
is_precoloured_sse2(X) -> X =< 15.
 
124
 
 
125
is_precoloured_x87(X) -> X =< 6.
 
126
 
 
127
all_precoloured() ->
 
128
  [?RAX,
 
129
   ?RCX,
 
130
   ?RDX,
 
131
   ?RBX,
 
132
   ?RSP,
 
133
   ?RBP,
 
134
   ?RSI,
 
135
   ?RDI,
 
136
   ?R8 ,
 
137
   ?R9 ,
 
138
   ?R10,
 
139
   ?R11,
 
140
   ?R12,
 
141
   ?R13,
 
142
   ?R14,
 
143
   ?R15,
 
144
   ?FCALLS,
 
145
   ?HEAP_LIMIT].
 
146
 
 
147
rax() -> ?RAX.
 
148
rcx() -> ?RCX.
 
149
temp0() -> ?TEMP0.
 
150
temp1() -> ?TEMP1.
 
151
sp() -> ?RSP.
 
152
proc_pointer() -> ?PROC_POINTER.
 
153
fcalls() -> ?FCALLS.
 
154
heap_limit() -> ?HEAP_LIMIT.
 
155
 
 
156
 
 
157
-ifdef(AMD64_HP_IN_REGISTER).
 
158
-define(HEAP_POINTER, ?AMD64_HEAP_POINTER).
 
159
heap_pointer() -> ?HEAP_POINTER.
 
160
-define(LIST_HP_LIVE_AT_RETURN,[{?HEAP_POINTER,untagged}]).
 
161
is_heap_pointer(?HEAP_POINTER) -> true;
 
162
is_heap_pointer(_) -> false.
 
163
%% -define(LIST_HP_FIXED,[?HEAP_POINTER]).
 
164
 
 
165
-else.
 
166
-define(HEAP_POINTER, -1).
 
167
is_heap_pointer(_) -> false.
 
168
%% -define(LIST_HP_FIXED,[]).
 
169
-define(LIST_HP_LIVE_AT_RETURN,[]).
 
170
-endif.
 
171
 
 
172
proc_offset(?FCALLS) -> fcalls_offset();
 
173
proc_offset(?HEAP_LIMIT) -> heap_limit_offset();
 
174
proc_offset(_) -> false.
 
175
 
 
176
sp_limit_offset() -> ?P_NSP_LIMIT.
 
177
 
 
178
is_fixed(?RSP) -> true;
 
179
is_fixed(?PROC_POINTER) -> true;
 
180
is_fixed(?FCALLS) -> true;
 
181
is_fixed(?HEAP_LIMIT) -> true;
 
182
is_fixed(R) -> is_heap_pointer(R).
 
183
 
 
184
% %% fixed() ->
 
185
% %%     [?ESP, ?PROC_POINTER, ?FCALLS, ?HEAP_LIMIT | ?LIST_HP_FIXED].
 
186
 
 
187
allocatable() ->
 
188
  [?RDX, ?RCX, ?RBX, ?RAX, ?RSI, ?RDI,
 
189
   ?R8 , ?R9 , ?R10, ?R11, ?R12, ?R13, ?R14, ?R15]
 
190
    -- [?FCALLS, ?HEAP_POINTER, ?HEAP_LIMIT].
 
191
 
 
192
allocatable_sse2() ->
 
193
  [00,01,02,03,04,05,06,07,08,09,10,11,12,13,14,15]. %% xmm0 - xmm15
 
194
 
 
195
allocatable_x87() ->
 
196
  [0,1,2,3,4,5,6].
 
197
 
 
198
nr_args() -> ?AMD64_NR_ARG_REGS.
 
199
 
 
200
arg(N) ->
 
201
  if N < ?AMD64_NR_ARG_REGS ->
 
202
      case N of
 
203
        0 -> ?ARG0;
 
204
        1 -> ?ARG1;
 
205
        2 -> ?ARG2;
 
206
        3 -> ?ARG3;
 
207
        4 -> ?ARG4;
 
208
        5 -> ?ARG5;
 
209
        _ -> exit({?MODULE, arg, N})
 
210
      end;
 
211
     true ->
 
212
      exit({?MODULE, arg, N})
 
213
  end.
 
214
 
 
215
is_arg(R) ->
 
216
  case R of
 
217
    ?ARG0 -> ?AMD64_NR_ARG_REGS > 0;
 
218
    ?ARG1 -> ?AMD64_NR_ARG_REGS > 1;
 
219
    ?ARG2 -> ?AMD64_NR_ARG_REGS > 2;
 
220
    ?ARG3 -> ?AMD64_NR_ARG_REGS > 3;
 
221
    ?ARG4 -> ?AMD64_NR_ARG_REGS > 4;
 
222
    ?ARG5 -> ?AMD64_NR_ARG_REGS > 5;
 
223
    _ -> false
 
224
  end.
 
225
 
 
226
args(Arity) ->
 
227
  Max = ?AMD64_NR_ARG_REGS,
 
228
  N = if Arity > Max -> Max; true -> Arity end,
 
229
  args(N-1, []).
 
230
 
 
231
args(I, Rest) when I < 0 -> Rest;
 
232
args(I, Rest) -> args(I-1, [arg(I) | Rest]).
 
233
 
 
234
ret(N) ->
 
235
  case N of
 
236
    0 -> ?RAX;
 
237
    _ -> exit({?MODULE, ret, N})
 
238
  end.
 
239
 
 
240
call_clobbered() ->
 
241
  [{?RAX,tagged},{?RAX,untagged},       % does the RA strip the type or not?
 
242
   {?RDX,tagged},{?RDX,untagged},
 
243
   {?RCX,tagged},{?RCX,untagged},
 
244
   {?RBX,tagged},{?RBX,untagged},
 
245
   {?RDI,tagged},{?RDI,untagged},
 
246
   {?RSI,tagged},{?RSI,untagged},
 
247
   {?R8 ,tagged},{?R8 ,untagged},
 
248
   {?R9 ,tagged},{?R9 ,untagged},
 
249
   {?R10,tagged},{?R10,untagged},
 
250
   {?R11,tagged},{?R11,untagged},
 
251
   {?R12,tagged},{?R12,untagged},
 
252
   {?R13,tagged},{?R13,untagged},
 
253
   {?R14,tagged},{?R14,untagged},
 
254
   {?R15,tagged},{?R15,untagged}
 
255
   | fp_call_clobbered()]
 
256
    --
 
257
    [{?FCALLS,tagged},{?FCALLS,untagged},
 
258
     {?HEAP_POINTER,tagged},{?HEAP_POINTER,untagged},
 
259
     {?HEAP_LIMIT,tagged},{?HEAP_LIMIT,untagged}
 
260
    ].
 
261
 
 
262
fp_call_clobbered() -> %% sse2 since it has more registers than x87
 
263
  [{Reg,double} || Reg <- allocatable_sse2()].
 
264
 
 
265
tailcall_clobbered() ->         % tailcall crapola needs two temps
 
266
  [{?TEMP0,tagged},{?TEMP0,untagged},
 
267
   {?TEMP1,tagged},{?TEMP1,untagged}
 
268
  | fp_call_clobbered()].
 
269
 
 
270
live_at_return() ->
 
271
    [{?RAX,tagged}
 
272
     ,{?RSP,untagged}
 
273
     ,{?PROC_POINTER,untagged}
 
274
     ,{?FCALLS,untagged}
 
275
     ,{?HEAP_LIMIT,untagged}
 
276
     | ?LIST_HP_LIVE_AT_RETURN
 
277
    ].
 
278
 
 
279
wordsize() -> 8.