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

« back to all changes in this revision

Viewing changes to lib/hipe/sparc/hipe_sparc_regalloc.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
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2
 
%%
3
 
%% Interface for register allocating SPARC code.  Uses hipe_regalloc.erl
4
 
%%
5
 
 
6
 
-module(hipe_sparc_regalloc).
7
 
-export([alloc/1]).
8
 
 
9
 
-define(countspills,true).
10
 
 
11
 
-ifdef(countspills).
12
 
-define(count_spills(X), X).
13
 
-define(update_spillsum,
14
 
        case get(totalspill) of 
15
 
          {__Loads,__Stores} ->
16
 
            put(totalspill,{__Loads+get(loads),
17
 
                            __Stores+get(stores)}),
18
 
            case get(spilledtemps) of
19
 
              __Temps -> 
20
 
                put(spilledtemps, __Temps+get(temps));
21
 
              _ ->
22
 
                true
23
 
            end;
24
 
          _ -> true 
25
 
        end).
26
 
-else.
27
 
-define(count_spills(X), true).
28
 
-define(update_spillsum,true).
29
 
-endif.
30
 
 
31
 
%
32
 
% Calls regalloc, rewrite the code after register allocation.
33
 
%
34
 
% Coloring is given as a list of {Reg, {reg, NewReg}} or 
35
 
% {Reg, {spill, SpillIndex}}.
36
 
%
37
 
 
38
 
alloc(SparcCfg) ->
39
 
  ?count_spills({put(loads,0),put(stores,0),put(temps,0)}),
40
 
 
41
 
   {_, SpillLimit} = hipe_sparc_cfg:var_range(SparcCfg),
42
 
   alloc(SparcCfg, unspilled, 0, SpillLimit, 0).
43
 
 
44
 
alloc(SparcCfg, PrevSpillArea, SpillIndex, SpillLimit, Locs) ->
45
 
 
46
 
   {Coloring, NewSpillIndex} = 
47
 
     hipe_regalloc:regalloc(SparcCfg, SpillIndex, SpillLimit),
48
 
  ?count_spills(put(temps, get(temps)+NewSpillIndex)),
49
 
   case spilled(Coloring) of
50
 
     false ->
51
 
       ?update_spillsum,
52
 
         ColTuple = cols2tuple(Coloring),
53
 
         Labels = hipe_sparc_cfg:labels(SparcCfg),
54
 
         CFG0 = rewrite_bbs(Labels, SparcCfg, ColTuple),
55
 
         NewCFG = hipe_sparc_cfg:var_range_update(CFG0, {0, 31}),
56
 
         case SpillIndex of
57
 
            0 ->
58
 
               NewCFG;
59
 
            _ ->
60
 
                %% io:format("Spilled: ~w register(s) @ ~w sites (~w)~n", 
61
 
                %%      [SpillIndex, Locs, hipe_sparc_cfg:function(SparcCfg)]),
62
 
               NewConstTab =
63
 
                  hipe_consttab:update_block(
64
 
                    hipe_sparc_cfg:data(NewCFG),
65
 
                    PrevSpillArea,
66
 
                    4,
67
 
                    word,
68
 
                    hipe_consttab:repeat(SpillIndex, 0)),
69
 
               hipe_sparc_cfg:update_data(NewCFG, NewConstTab)
70
 
         end;
71
 
     true ->
72
 
       Labels = hipe_sparc_cfg:labels(SparcCfg),
73
 
       {Low, High} = hipe_sparc_cfg:var_range(SparcCfg),
74
 
       hipe_gensym:set_var(High),
75
 
       {CFG1, SpillArea} = 
76
 
         case PrevSpillArea of
77
 
           unspilled ->
78
 
             {NewConstTab, SpillA} =
79
 
               hipe_consttab:insert_block(hipe_sparc_cfg:data(SparcCfg),
80
 
                                          4, word, [0]),
81
 
             {hipe_sparc_cfg:update_data(SparcCfg, NewConstTab), SpillA};
82
 
           _ ->
83
 
             {SparcCfg, PrevSpillArea}
84
 
         end,
85
 
         Spills = spill_regs(Coloring),
86
 
         {SpillCfg, Locs0} = spill_rewrite_bbs(Labels, CFG1, Spills, 
87
 
                                               SpillArea, Locs),
88
 
         CFG2 = hipe_sparc_cfg:var_range_update(SpillCfg,
89
 
                                                {Low, hipe_gensym:get_var()}),
90
 
         alloc(CFG2, SpillArea, NewSpillIndex, SpillLimit,Locs0)
91
 
   end.
92
 
 
93
 
 
94
 
%
95
 
% Check if a coloring spilled any values
96
 
%
97
 
 
98
 
spilled([]) ->
99
 
   false;
100
 
spilled([{_, {spill, _}} | Cs]) ->
101
 
   true;
102
 
spilled([_ | Cs]) ->
103
 
   spilled(Cs).
104
 
 
105
 
 
106
 
%
107
 
% Returns a list of {SpilledReg, {Tmp, LoadInstr, StoreInstr}}
108
 
%
109
 
 
110
 
spill_regs([]) ->
111
 
   [];
112
 
spill_regs([{RegNr, {reg, _}} | Colors]) ->
113
 
   spill_regs(Colors);
114
 
spill_regs([{RegNr, {spill, SpillIndex}} | Colors]) ->
115
 
   SpillIndexImm = hipe_sparc:mk_imm(SpillIndex*4),
116
 
   Info = {hipe_sparc:mk_reg(RegNr), SpillIndexImm},
117
 
   [Info | spill_regs(Colors)].
118
 
 
119
 
 
120
 
%
121
 
% Rewrite a cfg where spills occured
122
 
%
123
 
 
124
 
spill_rewrite_bbs([], CFG, Spills, SpillArea, Locs) ->
125
 
   {CFG, Locs};
126
 
spill_rewrite_bbs([Lbl|Lbls], CFG, Spills, SpillArea, Locs) ->
127
 
   BB = hipe_sparc_cfg:bb(CFG, Lbl),
128
 
   Code = hipe_bb:code(BB),
129
 
   {NewCode, Locs0} = spill_rewrite_instrs(Code, Spills, SpillArea),
130
 
   NewCFG = hipe_sparc_cfg:bb_update(CFG, Lbl,
131
 
                                     hipe_bb:code_update(BB, NewCode)),
132
 
   spill_rewrite_bbs(Lbls, NewCFG, Spills, SpillArea, Locs+Locs0).
133
 
 
134
 
 
135
 
spill_rewrite_instrs([], Spills, SpillArea) ->
136
 
   {[], 0};
137
 
spill_rewrite_instrs([I|Is], Spills, SpillArea) ->
138
 
   {NewI, Locs0} = spill_rewrite_instr(I, Spills, SpillArea),
139
 
   {NewIs, Locs1} = spill_rewrite_instrs(Is, Spills, SpillArea),
140
 
   {NewI++NewIs, Locs0+Locs1}.
141
 
 
142
 
 
143
 
spill_rewrite_instr(I, Spills, SpillArea) ->
144
 
   {Defs, Uses} = hipe_sparc:def_use(I),
145
 
   SpillUses = get_spills(Uses, Spills, Spills),
146
 
   SpillDefs = get_spills(Defs, Spills, Spills),
147
 
   case SpillUses++SpillDefs of
148
 
      [] ->
149
 
         {[I], 0};
150
 
      _ ->
151
 
       SpillAreaReg = hipe_sparc:mk_new_reg(),
152
 
       LA = hipe_sparc:load_address_create(SpillAreaReg, SpillArea, constant, []),
153
 
       {Loads, UseSubst}  = make_loads(SpillUses, [] , [], SpillAreaReg),
154
 
       {Stores, DefSubst} = make_stores(SpillDefs, [], [], SpillAreaReg),
155
 
       ?count_spills(
156
 
          {put(stores,get(stores)+length(Stores)),
157
 
           put(loads,get(loads)+length(Loads))}),
158
 
      
159
 
       C1 = hipe_sparc:comment_create('** SPILL START **', []),
160
 
       C2 = hipe_sparc:comment_create('** SPILL END **', []),
161
 
       NewI = hipe_sparc:subst_defines(hipe_sparc:subst_uses(I, UseSubst), DefSubst),
162
 
       case length(Stores) of %% Should perhaps check if the
163
 
         %%  instruction is a branch.
164
 
         0 -> 
165
 
           {[C1, LA] ++ Loads ++ [C2, NewI], length(UseSubst)+length(DefSubst)};
166
 
         Other ->
167
 
           {[C1, LA] ++ Loads ++ [NewI] ++ Stores ++ [C2], length(UseSubst)+length(DefSubst)}
168
 
       end
169
 
   end.
170
 
 
171
 
make_loads([{Ru, Offsetu}|Rest], AccLoads, AccSubsts, SpillAreaReg) ->
172
 
  Tmpu = hipe_sparc:mk_new_reg(),
173
 
  make_loads(Rest,
174
 
             [hipe_sparc:load_create(Tmpu, uw, SpillAreaReg, Offsetu, [])|
175
 
              AccLoads],
176
 
             [{Ru, Tmpu}|AccSubsts],
177
 
             SpillAreaReg);
178
 
make_loads([], AccLoads, AccSubsts, _) ->
179
 
  {AccLoads, AccSubsts}.
180
 
 
181
 
make_stores([{Rd, Offsetd}|Rest], AccStores, AccSubsts, SpillAreaReg) ->
182
 
  Tmpd = hipe_sparc:mk_new_reg(),
183
 
  make_stores(Rest,
184
 
              [hipe_sparc:store_create(SpillAreaReg, Offsetd, uw, Tmpd, [])|
185
 
              AccStores],
186
 
              [{Rd, Tmpd}|AccSubsts],
187
 
              SpillAreaReg);
188
 
make_stores([], AccStores, AccSubsts, _) ->
189
 
  {AccStores, AccSubsts}.
190
 
 
191
 
get_spills([], _, _) ->
192
 
   [];
193
 
get_spills([R|Rs], [], Spills) ->
194
 
   get_spills(Rs, Spills, Spills);
195
 
get_spills([R|Rs], [{R, Info}|_], Spills) ->
196
 
   [{R, Info} | get_spills(Rs, Spills, Spills)];
197
 
get_spills(Rs, [_|Ss], Spills) ->
198
 
   get_spills(Rs, Ss, Spills).
199
 
 
200
 
 
201
 
%
202
 
% Convert a list of [{R1, C1}, {R2, C2}, ...} to a tuple {C17, C23, ...}.
203
 
%
204
 
% The N's must be unique but do not have to be sorted and they can be sparse.
205
 
%
206
 
 
207
 
cols2tuple(Map) ->
208
 
   cols2tuple(1, lists:keysort(1, Map), []).
209
 
 
210
 
cols2tuple(N, [], Vs) ->
211
 
   list_to_tuple(lists:reverse(Vs));
212
 
cols2tuple(N, [{R, C}|Ms], Vs) when N =:= R ->
213
 
   cols2tuple(N+1, Ms, [C|Vs]);
214
 
cols2tuple(N, Ms, Vs) ->
215
 
   cols2tuple(N+1, Ms, [unknown|Vs]).
216
 
 
217
 
%
218
 
% Rewrite a cfg to use the allocated registers
219
 
%
220
 
 
221
 
rewrite_bbs([], CFG, ColTuple) ->
222
 
   CFG;
223
 
rewrite_bbs([Lbl|Lbls], CFG, ColTuple) ->
224
 
   BB = hipe_sparc_cfg:bb(CFG, Lbl),
225
 
   Code = hipe_bb:code(BB),
226
 
   NewCode = rewrite_instrs(Code, ColTuple),
227
 
   NewCFG = hipe_sparc_cfg:bb_update(CFG, Lbl,
228
 
                                     hipe_bb:code_update(BB, NewCode)),
229
 
   rewrite_bbs(Lbls, NewCFG, ColTuple).
230
 
 
231
 
 
232
 
rewrite_instrs([], ColTuple) ->
233
 
   [];
234
 
rewrite_instrs([I|Is], ColTuple) ->
235
 
   [rewrite_instr(I, ColTuple) | rewrite_instrs(Is, ColTuple)].
236
 
 
237
 
 
238
 
rewrite_instr(Ins, ColTuple) ->
239
 
   case hipe_sparc:type(Ins) of
240
 
      label -> Ins;
241
 
      nop -> Ins;
242
 
      block -> Ins;
243
 
      align -> Ins;
244
 
      comment -> Ins;
245
 
      b -> Ins;
246
 
      goto -> Ins;
247
 
      move ->
248
 
         NewDst = color_arg(hipe_sparc:move_dest(Ins), ColTuple),
249
 
         NewSrc = color_arg(hipe_sparc:move_src(Ins), ColTuple),
250
 
         hipe_sparc:move_dest_update(hipe_sparc:move_src_update(Ins, NewSrc),
251
 
                                     NewDst);
252
 
      cmov_cc ->
253
 
         NewDst = color_arg(hipe_sparc:cmov_cc_dest(Ins), ColTuple),
254
 
         NewSrc = color_arg(hipe_sparc:cmov_cc_src(Ins), ColTuple),
255
 
         I0 = hipe_sparc:cmov_cc_src_update(Ins, NewSrc),
256
 
         hipe_sparc:cmov_cc_dest_update(I0, NewDst);
257
 
      cmov_r ->
258
 
         NewDst = color_arg(hipe_sparc:cmov_r_dest(Ins), ColTuple),
259
 
         NewSrc = color_arg(hipe_sparc:cmov_r_src(Ins), ColTuple),
260
 
         NewReg = color_arg(hipe_sparc:cmov_r_reg(Ins), ColTuple),
261
 
         I0 = hipe_sparc:cmov_r_dest_update(Ins, NewDst),
262
 
         I1 = hipe_sparc:cmov_r_src_update(I0, NewSrc),
263
 
         hipe_sparc:cmov_r_reg_update(I1, NewReg);
264
 
      alu ->
265
 
         NewSrc1 = color_arg(hipe_sparc:alu_src1(Ins), ColTuple),
266
 
         NewSrc2 = color_arg(hipe_sparc:alu_src2(Ins), ColTuple),
267
 
         NewDst = color_arg(hipe_sparc:alu_dest(Ins), ColTuple),
268
 
         I0 = hipe_sparc:alu_src1_update(Ins, NewSrc1),
269
 
         I1 = hipe_sparc:alu_src2_update(I0, NewSrc2),
270
 
         hipe_sparc:alu_dest_update(I1, NewDst);
271
 
      alu_cc ->
272
 
         NewSrc1 = color_arg(hipe_sparc:alu_cc_src1(Ins), ColTuple),
273
 
         NewSrc2 = color_arg(hipe_sparc:alu_cc_src2(Ins), ColTuple),
274
 
         NewDst = color_arg(hipe_sparc:alu_cc_dest(Ins), ColTuple),
275
 
         I0 = hipe_sparc:alu_cc_src1_update(Ins, NewSrc1),
276
 
         I1 = hipe_sparc:alu_cc_src2_update(I0, NewSrc2),
277
 
         hipe_sparc:alu_cc_dest_update(I1, NewDst);
278
 
      sethi ->
279
 
         NewDest = color_arg(hipe_sparc:sethi_dest(Ins), ColTuple),
280
 
         hipe_sparc:sethi_dest_update(Ins, NewDest);
281
 
 
282
 
      load ->
283
 
         NewDest = color_arg(hipe_sparc:load_dest(Ins), ColTuple),
284
 
         NewSrc = color_arg(hipe_sparc:load_src(Ins), ColTuple),
285
 
         NewOff = color_arg(hipe_sparc:load_off(Ins), ColTuple),
286
 
         I0 = hipe_sparc:load_dest_update(Ins, NewDest),
287
 
         I1 = hipe_sparc:load_src_update(I0, NewSrc),
288
 
         hipe_sparc:load_off_update(I1, NewOff);
289
 
      store ->
290
 
         NewDest = color_arg(hipe_sparc:store_dest(Ins), ColTuple),
291
 
         NewSrc = color_arg(hipe_sparc:store_src(Ins), ColTuple),
292
 
         NewOff = color_arg(hipe_sparc:store_off(Ins), ColTuple),
293
 
         I0 = hipe_sparc:store_dest_update(Ins, NewDest),
294
 
         I1 = hipe_sparc:store_src_update(I0, NewSrc),
295
 
         hipe_sparc:store_off_update(I1, NewOff);
296
 
      br ->
297
 
         NewReg = color_arg(hipe_sparc:br_reg(Ins), ColTuple),
298
 
         hipe_sparc:br_reg_update(Ins, NewReg);
299
 
      %% Warning, not complete
300
 
      jmp_link ->
301
 
         NewTarget = color_arg(hipe_sparc:jmp_link_target(Ins), ColTuple),
302
 
         NewOff = color_arg(hipe_sparc:jmp_link_off(Ins), ColTuple),
303
 
         I0 = hipe_sparc:jmp_link_target_update(Ins, NewTarget),
304
 
         hipe_sparc:jmp_link_off_update(I0, NewOff);
305
 
      jmp ->
306
 
         NewTarget = color_arg(hipe_sparc:jmp_target(Ins), ColTuple),
307
 
         NewOff = color_arg(hipe_sparc:jmp_off(Ins), ColTuple),
308
 
         I0 = hipe_sparc:jmp_target_update(Ins, NewTarget),
309
 
         hipe_sparc:jmp_off_update(I0, NewOff);
310
 
      call_link ->
311
 
         Ins1 =
312
 
         case hipe_sparc:call_link_type(Ins) of
313
 
           closure ->
314
 
             NewTarget = color_arg(hipe_sparc:call_link_target(Ins), ColTuple),
315
 
             hipe_sparc:call_link_target_update(Ins, NewTarget);
316
 
           _ -> Ins
317
 
         end,
318
 
         NewLink = color_arg(hipe_sparc:call_link_link(Ins1), ColTuple),
319
 
         hipe_sparc:call_link_link_update(Ins1, NewLink);
320
 
      %% end warning
321
 
      load_atom ->
322
 
         NewDest = color_arg(hipe_sparc:load_atom_dest(Ins), ColTuple),
323
 
         hipe_sparc:load_atom_dest_update(Ins, NewDest);
324
 
      load_word_index ->
325
 
         NewDest = color_arg(hipe_sparc:load_word_index_dest(Ins), ColTuple),
326
 
         hipe_sparc:load_word_index_dest_update(Ins, NewDest);
327
 
      load_address ->
328
 
         NewDest = color_arg(hipe_sparc:load_address_dest(Ins), ColTuple),
329
 
         hipe_sparc:load_address_dest_update(Ins, NewDest);
330
 
 
331
 
      multimove ->
332
 
         NewDst = color_all_args(hipe_sparc:move_dest(Ins), ColTuple),
333
 
         NewSrc = color_all_args(hipe_sparc:move_src(Ins), ColTuple),
334
 
         hipe_sparc:multimove_dest_update(hipe_sparc:multimove_src_update(Ins, NewSrc), NewDst);
335
 
      _ -> 
336
 
       %% If we don't know how to handle this instruction do a generic substitution
337
 
       hipe_sparc:subst(Ins, coltuple_to_substlist(ColTuple))
338
 
             
339
 
   end.
340
 
 
341
 
coltuple_to_substlist(ColTuple) ->
342
 
  T = tuple_to_list(ColTuple),
343
 
  mapping(T,1).
344
 
 
345
 
mapping([R|Rs], Temp) ->
346
 
  [{Temp, R}| mapping(Rs, Temp+1)];
347
 
mapping([], _ ) -> [].
348
 
 
349
 
color_arg(Arg, ColTuple) ->
350
 
   case hipe_sparc:is_reg(Arg) of
351
 
      true ->
352
 
         case element(hipe_sparc:reg_nr(Arg), ColTuple) of
353
 
            {reg, NewRgNr} ->
354
 
               hipe_sparc:mk_reg(NewRgNr);
355
 
            {spill, SpillIndex} ->
356
 
               exit({sparc, spilled})
357
 
         end;
358
 
      false ->
359
 
         Arg
360
 
   end.
361
 
 
362
 
color_all_args([Arg|Args], ColTuple) ->
363
 
  [color_arg(Arg, ColTuple)|color_all_args(Args, ColTuple)];
364
 
color_all_args([], _ ) -> [].
365