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

« back to all changes in this revision

Viewing changes to lib/hipe/sparc/0OLD/hipe_sparc_caller_saves.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% -*- erlang-indent-level: 2 -*-
2
 
%% ====================================================================
3
 
%%  Filename :  hipe_sparc_caller_saves.erl
4
 
%%  Module   :  hipe_sparc_caller_saves
5
 
%%  Purpose  :  To add save and restore code for caller save regs
6
 
%%              at call sites.
7
 
%%  Notes    :  LastSpillPos is a bad name in this module,
8
 
%%               since it denotes the postion after the last used
9
 
%%               position.
10
 
%%  History  :  * 2001-11-16 Erik Johansson (happi@csd.uu.se): 
11
 
%%               Created.
12
 
%%  CVS      :
13
 
%%              $Author: mikpe $
14
 
%%              $Date: 2007/12/18 09:18:21 $
15
 
%%              $Revision: 1.1 $
16
 
%% ====================================================================
17
 
%%  Exports  :
18
 
%%
19
 
%%  Description:
20
 
%%
21
 
%%   1. Calculate liveness. 
22
 
%%      (Consider reusing the liveness calculated by the regalloc.)
23
 
%%
24
 
%%   2. Go through each basic block bottom up.
25
 
%%      For each call c:
26
 
%%         For each live out temp t. (that is not a retval of c)
27
 
%%             If t is spilled: Do nothing.
28
 
%%             If t is not spilled:
29
 
%%                a) Get a spillposition p for t.
30
 
%%                b) Add code for spilling t to p before the call.
31
 
%%                c) add code for unspilling t from p after the call.
32
 
%%                d) If any spillcode was added rewrite the call
33
 
%%                     If there is an exception handler: add the unspill
34
 
%%                       code to both branches of the call.
35
 
%%
36
 
%%   3. Optimization pass: Place the spillcode "optimally".
37
 
%%                        Implemented in hipe_sparc_opt_frame
38
 
%%
39
 
%%  TODO: Either make this module completely target independent or
40
 
%%        completely target dependent.
41
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
42
 
 
43
 
-module(hipe_sparc_caller_saves).
44
 
-export([rewrite/5]).
45
 
 
46
 
-define(HIPE_INSTRUMENT_COMPILER, true). %% Turn on instrumentation.
47
 
-include("../main/hipe.hrl").
48
 
-include("hipe_sparc.hrl").
49
 
 
50
 
%% XXX: Make target independent.
51
 
-define(TARGET, hipe_sparc_specific).
52
 
 
53
 
%% XXX: Make target independent.
54
 
rewrite(Cfg, TempMap, FpMap, LastSpillPos, Options) ->
55
 
  %% hipe_sparc_cfg:pp(Cfg),  
56
 
  ?opt_start_timer("Caller Saves"),
57
 
  ?start_time_caller_saves(Options),
58
 
  %% Get Info.
59
 
  Liveness = liveness(Cfg, ?TARGET),
60
 
  State = new_state(Liveness,  Cfg, TempMap, FpMap, LastSpillPos),
61
 
  BBs = hipe_sparc_cfg:predictionorder(Cfg),
62
 
 
63
 
  %% Rewrite.
64
 
  {NewCode, NextPos, NewBlocks} = traverse(BBs, State),
65
 
 
66
 
  %% Make new CFG.
67
 
  Sparc0 = hipe_sparc_cfg:linearize(Cfg),
68
 
  Sparc1 = hipe_sparc:sparc_code_update(Sparc0, NewCode),
69
 
  Sparc2 = hipe_sparc:sparc_var_range_update(
70
 
             Sparc1, {0,hipe_gensym:get_var(sparc)}),
71
 
  Sparc3 = hipe_sparc:sparc_label_range_update(
72
 
             Sparc2, {0,hipe_gensym:get_label(sparc)}),  
73
 
  Cfg1 = hipe_sparc_cfg:init(Sparc3),
74
 
 
75
 
  %% Minimize the number of loads and stores.
76
 
  ?opt_stop_timer("Caller Saves"),
77
 
  ?opt_start_timer("Opt Frame"),
78
 
  %% hipe_sparc_cfg:pp(Cfg1),
79
 
  Cfg2 = hipe_sparc_opt_frame:cfg(Cfg1),
80
 
  %% hipe_sparc_cfg:pp(Cfg2),
81
 
  ?opt_stop_timer("Opt Frame"),
82
 
  ?stop_time_caller_saves(Options),
83
 
  case proplists:get_value(regalloc,Options) of
84
 
    cs ->
85
 
      {Cfg2, NextPos, NewBlocks};
86
 
    _ ->
87
 
      {Cfg2, NextPos}
88
 
  end.
89
 
 
90
 
%% Go through each BasicBlock
91
 
traverse(BBs, State) ->
92
 
  State1 = lists:foldr(fun handle_bb/2,State,BBs),  
93
 
  {state__instrs(State1),state__spill_index(State1),state__newblocks(State1)}.
94
 
  
95
 
%% For each BasicBlock go through the code bottom-up.
96
 
handle_bb(BB,State) ->
97
 
  %% io:format("--------------\n",[]),
98
 
  Code =  hipe_bb:code(bb(state__cfg(State),BB, ?TARGET)),
99
 
  State1 = state__enter_bb(BB, State),
100
 
  State2 = bottom_up(Code, State1),
101
 
  %% io:format("-- Block ~w --\n",[BB]),
102
 
  state__add_instrs(hipe_sparc:label_create(BB), State2).
103
 
 
104
 
%% Go through each instruction from the last to the first.
105
 
%% (Collect liveness from live out and backwards.)
106
 
bottom_up(Is, State) ->
107
 
  lists:foldr(fun handle/2,State,Is).
108
 
 
109
 
%% For each instruction rewrite calls so that live temps are saved
110
 
handle(I,State) ->
111
 
  {FpDefs, Defs}  = defines(I, ?TARGET),
112
 
  {FpUses, Uses} = uses(I, ?TARGET),
113
 
  LiveOut = state__live(State)-- hipe_sparc_registers:global(),
114
 
  Live = (LiveOut--Defs), %% Remove killed
115
 
  LiveIn = ordsets:union(ordsets:from_list(Live),ordsets:from_list(Uses))
116
 
    -- hipe_sparc_registers:global(),
117
 
 
118
 
  FpLiveOut = state__live_fp(State),
119
 
  FpLive = (FpLiveOut--FpDefs), %% Remove killed
120
 
  FpLiveIn = ordsets:union(ordsets:from_list(FpLive),ordsets:from_list(FpUses)),
121
 
 
122
 
 
123
 
    %% io:format("~nLiveOut: ~w~n",[LiveOut-- hipe_sparc_registers:global()]),
124
 
    %% hipe_sparc_pp:pp_instr(I),
125
 
    %% io:format("LiveIn: ~w~n",[LiveIn]),
126
 
 
127
 
  %% Add save and restores if neccessary.
128
 
  State1 = update_call(I,State,Live, LiveOut, FpLive),
129
 
 
130
 
  %% Update the liveness information in the state.
131
 
  State2 = state__update_live(LiveIn, State1),
132
 
  state__update_live_fp(FpLiveIn, State2).
133
 
 
134
 
 
135
 
%% XXX: Make this target independent.
136
 
update_call(I,State,Live,_LiveOut,FpLive) ->
137
 
  case I of
138
 
    #call_link{} ->
139
 
      case {live_in_regs(Live), FpLive} of
140
 
        {[], []} -> 
141
 
          %% All live temps are allready on the stack.
142
 
          %% No need for extra saving.
143
 
          %% Just add the live-info to the stack descriptor 
144
 
          %%  of the call.
145
 
          state__add_instrs(set_live_slots(I,State,Live),State);
146
 
        {ToSpill, ToSpillFp} ->
147
 
          %% We have at least one live temp that is not on the stack
148
 
          handle_call(I,State,ToSpill,Live, ToSpillFp)
149
 
      end;
150
 
    
151
 
    _ ->
152
 
      %% This is not a call, nothing to save.
153
 
      %% Just add the instruction to the state.
154
 
      state__add_instrs(I,State)
155
 
  end.
156
 
 
157
 
 
158
 
 
159
 
%% Ugly function that finds the stack slots of all live temps
160
 
%% and adds these to the stack descriptor of the call. 
161
 
set_live_slots(Call,State,LiveOut) ->
162
 
  Live =
163
 
    [stack_pos(T,State, reg) || T <- LiveOut],
164
 
  SD = hipe_sparc:call_link_stack_desc(Call),
165
 
  NewSD = hipe_sparc:sdesc_live_slots_update(SD, Live),
166
 
  hipe_sparc:call_link_stack_desc_update(Call,NewSD).
167
 
 
168
 
%% Helper function to set_live_slots.
169
 
%% Maps a Temp to its stack pos.
170
 
stack_pos(T,State, Type) ->
171
 
  Map = 
172
 
    case Type of
173
 
      reg -> state__tempmap(State);
174
 
      fp_reg-> state__fpmap(State)
175
 
    end,
176
 
  case hipe_temp_map:find(T, Map) of
177
 
    {spill, P} ->
178
 
      P;
179
 
    _ ->
180
 
      element(1,get_pos(T,state__extramap(State), Type))
181
 
  end.
182
 
      
183
 
%% XXX: Make target independent.
184
 
live_in_regs(Live) ->
185
 
  %% XXX: We have to save spilled regs with new call-split allocation
186
 
  %%      Make this modular so other allocators are unaffected.
187
 
  [T || T <- Live ] 
188
 
    -- hipe_sparc_registers:global().
189
 
 
190
 
 
191
 
handle_call(I,State,ToSpill,LiveOut, FpLive)->
192
 
  %% a) Get a spillposition p for t.
193
 
  %% b) Add code for spilling t to p before the call.
194
 
  %% c) add code for unspilling t from p after the call.
195
 
  %% d) If any spillcode was added rewrite the call
196
 
  %%      If there is an exception handler: add the unspill
197
 
  %%        code to both branches of the call.
198
 
 
199
 
 
200
 
  ExtraMap = state__extramap(State),
201
 
  {SpillPositions, NewExtraMap0} =
202
 
    get_spill_positions(ToSpill, ExtraMap, State, reg),
203
 
  {Saves0, Restores0} = gen_save_restore(SpillPositions, reg),
204
 
  {SpillPositions_fp, NewExtraMap} =
205
 
    get_spill_positions(FpLive, NewExtraMap0, State, fp_reg),
206
 
  {Saves1, Restores1} = gen_save_restore(SpillPositions_fp, fp_reg),
207
 
 
208
 
  State1 = state__update_extramap(NewExtraMap, State),
209
 
 
210
 
  ContLab = hipe_sparc:call_link_continuation(I),
211
 
  FailLab = hipe_sparc:call_link_fail(I),
212
 
  NewContLab = hipe_sparc:label_create_new(),
213
 
  GotoCont =  hipe_sparc:goto_create(ContLab),
214
 
  {NewI,State2} =
215
 
    case ContLab of
216
 
      [] -> {I, State1};
217
 
      _ ->
218
 
        {
219
 
        hipe_sparc:call_link_continuation_update(
220
 
          I,
221
 
          hipe_sparc:label_name(NewContLab)),
222
 
        state__add_block(hipe_sparc:label_name(NewContLab),ContLab, State1)}
223
 
    end,
224
 
 
225
 
   
226
 
  %% Update stack descriptor. Fp regs must not be marked as live.
227
 
  NewCall = set_live_slots(NewI,State2,LiveOut),
228
 
 
229
 
  case ContLab of
230
 
    [] ->
231
 
       NewCode = 
232
 
        [Saves0,
233
 
         Saves1,
234
 
         NewCall,
235
 
         Restores0,
236
 
         Restores1],
237
 
      state__add_instrs(NewCode,State2);
238
 
    _ ->
239
 
      case FailLab of
240
 
        [] ->
241
 
          NewCode = 
242
 
            [Saves0,
243
 
             Saves1,
244
 
             NewCall,
245
 
             NewContLab,
246
 
             Restores0,
247
 
             Restores1,
248
 
             GotoCont],
249
 
          state__add_instrs(NewCode,State2);
250
 
        _ ->
251
 
          NewFailLab = hipe_sparc:label_create_new(),
252
 
          GotoFail =  hipe_sparc:goto_create(FailLab),
253
 
          NewI2 = 
254
 
            hipe_sparc:call_link_fail_update(
255
 
              NewCall,
256
 
              hipe_sparc:label_name(NewFailLab)),
257
 
          State3 = 
258
 
            state__add_block(hipe_sparc:label_name(NewFailLab),FailLab, State2),
259
 
          NewCode = 
260
 
            [Saves0, 
261
 
             Saves1,
262
 
             NewI2,
263
 
             NewContLab,
264
 
             Restores0,
265
 
             Restores1,
266
 
             GotoCont,
267
 
             NewFailLab,
268
 
             Restores0,
269
 
             Restores1,
270
 
             GotoFail],
271
 
          state__add_instrs(NewCode,State3)
272
 
      end
273
 
  end.
274
 
 
275
 
 
276
 
get_spill_positions([T|Temps], ExtraMap, State, Type) ->
277
 
  TempMap = 
278
 
    case Type of
279
 
      reg -> state__tempmap(State);
280
 
      fp_reg -> state__fpmap(State)
281
 
    end,
282
 
  {Pos, NewMap} = 
283
 
    case hipe_temp_map:is_spilled(T, TempMap) of
284
 
      true ->
285
 
        {stack_pos(T, State, Type),ExtraMap};
286
 
      false ->
287
 
        get_pos(T,ExtraMap, Type)
288
 
    end,
289
 
  {Positions, Map} = get_spill_positions(Temps, NewMap, State, Type),
290
 
  {[{T,Pos}|Positions], Map};
291
 
get_spill_positions([],Map,_, _) ->
292
 
  {[],Map}.
293
 
 
294
 
gen_save_restore([{T,Pos}|Positions], Type) ->
295
 
  SparcTemp = 
296
 
    case Type of
297
 
      fp_reg -> hipe_sparc:mk_fpreg(T);
298
 
      reg -> hipe_sparc:mk_reg(T)
299
 
    end,
300
 
  SparcPos = hipe_sparc:mk_imm(Pos),
301
 
  {Saves, Restores} = gen_save_restore(Positions, Type),
302
 
  Save = hipe_sparc:pseudo_spill_create(SparcTemp,SparcPos),
303
 
  Restore = hipe_sparc:pseudo_unspill_create(SparcTemp,SparcPos),
304
 
  {[Save | Saves], [Restore | Restores]};
305
 
gen_save_restore([], _) -> {[],[]}.
306
 
 
307
 
 
308
 
 
309
 
%% ================================================================= %%
310
 
%%                             A  D  T s                             %%
311
 
%% ================================================================= %%
312
 
 
313
 
 
314
 
%% ================================================================= %%
315
 
%% The ExtraMap structure
316
 
%% Maps unspilled temps to spillpositions.
317
 
%% 
318
 
 
319
 
%% ____________________________________________________________________
320
 
%%  new_extramap(LastSpillPos)    
321
 
%% Returns:     An empty ExtraMap.
322
 
%% Arguments:   LastSpillPos - The next spill will be to this pos.
323
 
%% Description: Creates an empty ExtraMap 
324
 
%% ____________________________________________________________________
325
 
new_extramap(LastSpillPos) ->
326
 
  {LastSpillPos, empty()}.
327
 
 
328
 
index(Map) ->
329
 
  %% io:format("Map: ~w\n",[Map]),
330
 
  element(1,Map).
331
 
 
332
 
%% ____________________________________________________________________
333
 
%%  get_pos(T,ExtraMap, Type)    
334
 
%% Returns:     
335
 
%% Arguments:   
336
 
%% Description: Finds the spill position of the temp T,
337
 
%%              If T is not in the map T will be added. 
338
 
%%              Type is either reg or fp_reg 
339
 
%% ____________________________________________________________________
340
 
get_pos(T,{Next,Map}, Type) ->
341
 
  case lookup(T,Map) of
342
 
    none ->
343
 
      case Type of
344
 
        fp_reg -> {Next, {Next+2,insert(T,Next,Map)}};
345
 
        reg -> {Next, {Next+1,insert(T,Next,Map)}}
346
 
      end;
347
 
    {value, Pos} ->
348
 
      {Pos, {Next,Map}}
349
 
  end.
350
 
 
351
 
 
352
 
%% ____________________________________________________________________
353
 
%% 
354
 
%% The Map kernel.
355
 
 
356
 
 
357
 
empty() ->
358
 
  gb_trees:empty().
359
 
lookup(T,Map) ->
360
 
  gb_trees:lookup(T,Map).
361
 
insert(T,Next,Map) ->
362
 
  gb_trees:insert(T,Next,Map).
363
 
 
364
 
 
365
 
 
366
 
%% ================================================================= %%
367
 
%%
368
 
%% The state structure
369
 
%%
370
 
%% ================================================================= %%
371
 
 
372
 
%% ____________________________________________________________________
373
 
%% The state record.
374
 
-record(state, {instrs, extramap, live, live_fp, liveness, cfg, tempmap, fpmap, newblocks}).
375
 
 
376
 
%% Create a new state.
377
 
new_state(Liveness,  Cfg, TempMap, FpMap, LastSpillPos) ->
378
 
  #state{instrs = [], 
379
 
         extramap = new_extramap(LastSpillPos), 
380
 
         live = [],
381
 
         live_fp = [],
382
 
         liveness = Liveness,  
383
 
         cfg = Cfg,
384
 
         tempmap = TempMap,
385
 
         fpmap = FpMap,
386
 
         newblocks = []}.
387
 
 
388
 
%% ____________________________________________________________________
389
 
%% Selectors
390
 
 
391
 
state__instrs(#state{instrs=Instrs}) -> lists:flatten(Instrs).
392
 
state__extramap(#state{extramap=ExtraMap}) -> ExtraMap.
393
 
state__live(#state{live=Live}) -> Live.
394
 
state__live_fp(#state{live_fp=LiveFP}) -> LiveFP.
395
 
state__liveness(#state{liveness=Liveness}) -> Liveness.
396
 
state__cfg(#state{cfg=CFG}) -> CFG.
397
 
state__tempmap(#state{tempmap=TempMap}) -> TempMap.
398
 
state__fpmap(#state{fpmap=FpMap}) -> FpMap.
399
 
state__newblocks(#state{newblocks=NewBlocks}) -> NewBlocks.
400
 
 
401
 
state__spill_index(State) -> index(state__extramap(State)).
402
 
 
403
 
%% ____________________________________________________________________
404
 
%% Updates
405
 
 
406
 
state__enter_bb(BB, State) ->
407
 
  {FpReg, Reg} = liveout(state__liveness(State), BB, hipe_sparc_specific),
408
 
  State#state{live=ordsets:from_list(Reg), live_fp=ordsets:from_list(FpReg)}.
409
 
state__add_instrs(I,State) ->
410
 
  State#state{instrs=[I|state__instrs(State)]}.
411
 
state__update_extramap(NewExtraMap, State) ->
412
 
  State#state{extramap=NewExtraMap}.
413
 
state__update_live(NewLive, State) ->
414
 
  State#state{live=NewLive}.
415
 
state__update_live_fp(NewLive, State) ->
416
 
  State#state{live_fp=NewLive}.
417
 
state__add_block(New,Old, State) ->
418
 
   State#state{newblocks=[{New,Old}|state__newblocks(State)]}.
419
 
 
420
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
421
 
%%
422
 
%% Interface to target specific external functions.
423
 
%% XXX: Make this efficient somehow...
424
 
%% 
425
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
426
 
 
427
 
liveness(CFG, Target) ->
428
 
   Target:analyze(CFG).
429
 
 
430
 
bb(CFG, L, Target) ->
431
 
  Target:bb(CFG,L).
432
 
 
433
 
liveout(Liveness,L, Target)->
434
 
  regnames(Target:liveout(Liveness,L), Target).
435
 
 
436
 
uses(I, Target)->
437
 
  regnames(Target:uses(I), Target).
438
 
 
439
 
defines(I, Target) ->
440
 
  regnames(Target:defines(I), Target).
441
 
 
442
 
regnames(Regs, _Target) ->
443
 
  regnames(Regs, [], []).
444
 
 
445
 
regnames([Reg|Rest], Fp_regs, Regs) ->
446
 
  case hipe_sparc:is_fpreg(Reg) of
447
 
    true->
448
 
      regnames(Rest, [hipe_sparc:fpreg_nr(Reg) | Fp_regs], Regs);
449
 
    _ ->
450
 
      regnames(Rest, Fp_regs, [hipe_sparc:reg_nr(Reg) | Regs])
451
 
  end;
452
 
regnames([], Fp_regs, Regs) ->
453
 
  {Fp_regs, Regs}.
454