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

« back to all changes in this revision

Viewing changes to lib/hipe/x86/hipe_x86_ra_ls.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 -*-
1
2
%%% $Id$
2
3
%%% Linear Scan register allocator for x86
3
4
 
4
 
-module(hipe_x86_ra_ls).
 
5
-ifdef(HIPE_AMD64).
 
6
-define(HIPE_X86_RA_LS,                 hipe_amd64_ra_ls).
 
7
-define(HIPE_X86_PP,                    hipe_amd64_pp).
 
8
-define(HIPE_X86_RA_POSTCONDITIONS,     hipe_amd64_ra_postconditions).
 
9
-define(HIPE_X86_REGISTERS,             hipe_amd64_registers).
 
10
-define(HIPE_X86_SPECIFIC,              hipe_amd64_specific).
 
11
-else.
 
12
-define(HIPE_X86_RA_LS,                 hipe_x86_ra_ls).
 
13
-define(HIPE_X86_PP,                    hipe_x86_pp).
 
14
-define(HIPE_X86_RA_POSTCONDITIONS,     hipe_x86_ra_postconditions).
 
15
-define(HIPE_X86_REGISTERS,             hipe_x86_registers).
 
16
-define(HIPE_X86_SPECIFIC,              hipe_x86_specific).
 
17
-endif.
 
18
 
 
19
-module(?HIPE_X86_RA_LS).
5
20
-export([ra/3,regalloc/7]).
6
 
 
7
 
%%-define(DEBUG,1).
8
 
 
9
 
-include("hipe_x86.hrl").
10
21
-define(HIPE_INSTRUMENT_COMPILER, true). %% Turn on instrumentation.
11
22
-include("../main/hipe.hrl").
12
 
-include("../util/hipe_vector.hrl").
13
23
 
14
 
ra(X86Defun, SpillIndex, Options) ->
15
 
  ?inc_counter(ra_calls_counter,1), 
16
 
  NewDefun = X86Defun, %% hipe_x86_ra_rename:rename(X86Defun,Options),
 
24
ra(Defun, SpillIndex, Options) ->
 
25
  NewDefun = Defun, %% hipe_${ARCH}_ra_rename:rename(Defun,Options),
17
26
  CFG = hipe_x86_cfg:init(NewDefun),
18
 
  ?inc_counter(ra_caller_saves_counter,count_caller_saves(CFG)),
19
27
 
20
 
  SpillLimit = hipe_x86_specific:number_of_temporaries(
 
28
  SpillLimit = ?HIPE_X86_SPECIFIC:number_of_temporaries(
21
29
                 CFG),
22
 
 
23
30
  ?inc_counter(bbs_counter, length(hipe_x86_cfg:labels(CFG))),
24
31
  alloc(NewDefun, SpillIndex, SpillLimit, Options).
25
32
 
26
33
 
27
 
alloc(X86Defun, SpillIndex, SpillLimit, Options) ->
 
34
alloc(Defun, SpillIndex, SpillLimit, Options) ->
28
35
  ?inc_counter(ra_iteration_counter,1), 
29
 
  %% hipe_x86_pp:pp(X86Defun),  
30
 
  X86Cfg = hipe_x86_cfg:init(X86Defun),
31
 
 
 
36
  %% ?HIPE_X86_PP:pp(Defun),    
 
37
  CFG = hipe_x86_cfg:init(Defun),
32
38
  {Coloring, NewSpillIndex} = 
33
39
    regalloc(
34
 
      X86Cfg, 
35
 
      hipe_x86_registers:allocatable()--
36
 
      [hipe_x86_registers:temp1(),
37
 
        hipe_x86_registers:temp0()],
38
 
      [hipe_x86_cfg:start(X86Cfg)],
 
40
      CFG, 
 
41
      ?HIPE_X86_REGISTERS:allocatable()--
 
42
      [?HIPE_X86_REGISTERS:temp1(),
 
43
       ?HIPE_X86_REGISTERS:temp0()],
 
44
      [hipe_x86_cfg:start_label(CFG)],
39
45
      SpillIndex, SpillLimit, Options,
40
 
      hipe_x86_specific),
41
 
 
42
 
  {NewX86Defun, _, DontSpill} =
43
 
    hipe_x86_ra_ls_postconditions:check_and_rewrite(
44
 
      X86Defun, Coloring, [], Options),
45
 
  %%hipe_x86_pp:pp(NewX86Defun),
46
 
  TempMap = hipe_temp_map:cols2tuple(Coloring, hipe_x86_specific),
47
 
  {TempMap2, NewSpillIndex2} = 
48
 
    hipe_spill_minimize:stackalloc(X86Cfg, [], 
49
 
                                   SpillIndex, Options, 
50
 
                                   hipe_x86_specific, 
51
 
                                   TempMap),
52
 
               
 
46
      ?HIPE_X86_SPECIFIC),
 
47
  {NewDefun, _DidSpill} =
 
48
    ?HIPE_X86_RA_POSTCONDITIONS:check_and_rewrite(
 
49
      Defun, Coloring, 'linearscan'),
 
50
  %% ?HIPE_X86_PP:pp(NewDefun),
 
51
  TempMap = hipe_temp_map:cols2tuple(Coloring, ?HIPE_X86_SPECIFIC),
 
52
  {TempMap2,NewSpillIndex2} = 
 
53
    hipe_spillmin:stackalloc(CFG, [], SpillIndex, Options,
 
54
                             ?HIPE_X86_SPECIFIC, TempMap),
53
55
  Coloring2 = 
54
 
    hipe_spill_minimize:mapmerge(hipe_temp_map:to_substlist(TempMap), 
55
 
                                 TempMap2),
 
56
    hipe_spillmin:mapmerge(hipe_temp_map:to_substlist(TempMap), TempMap2),
 
57
  case proplists:get_bool(verbose_spills, Options) of
 
58
    true ->
 
59
      ?msg("Stack slot size: ~p~n",[NewSpillIndex2-SpillIndex]);
 
60
    false ->
 
61
      ok
 
62
  end,
56
63
  ?add_spills(Options, NewSpillIndex),
57
 
  {NewX86Defun, Coloring2}.
58
 
 
59
 
 
60
 
 
61
 
 
62
 
%%  Purpose  :  Perform a register allocation based on the 
63
 
%%              "linear-scan algoritm".
64
 
%%  Notes    :  * This is an implementation of 
65
 
%%                "Linear Scan Register Allocation" by 
66
 
%%                Massimiliano Poletto & Vivek Sarkar described in
67
 
%%                ACM TOPLAS Vol 21, No 5, September 1999.
68
 
%%
69
 
%%              * This implementation is target-independent and
70
 
%%                requires a target specific interface module
71
 
%%                as argument.  
72
 
%%                (Still waiting for a modular module system for Erlang.)
73
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74
 
%%
75
 
%% regalloc(CFG, PhysRegs, Entrypoints, DontSpill, Options, Target) 
76
 
%%   Calculates an allocation of registers using a linear_scan algorithm.
77
 
%%   There are three steps in the algorithm:
78
 
%%    1. Calculate live-ranges for all registers.
79
 
%%    2. Calculate live-intervals for each register.
80
 
%%       The live interval consists of a start position and a end position
81
 
%%       these are the first definition and last use of the register 
82
 
%%       given as instruction numbers in a breadth-first traversal of the
83
 
%%       control-flow-graph.
84
 
%%    3. Do a linear scan allocation over the live intervals.
85
 
%%
86
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
 
64
  {NewDefun, Coloring2}.
 
65
 
87
66
regalloc(CFG,PhysRegs,Entrypoints, SpillIndex, DontSpill, Options, Target) ->
88
 
  ?debug_msg("LinearScan: ~w\n",[erlang:statistics(runtime)]),
89
 
  %%     Step 1: Calculate liveness (Call external implementation.)
90
 
  Liveness = liveness(CFG, Target),
91
 
  ?debug_msg("liveness (done)~w\n",[erlang:statistics(runtime)]),
92
 
  USIntervals = calculate_intervals(CFG, Liveness,
93
 
                                    Entrypoints, Options,
94
 
                                    Target),
95
 
  ?debug_msg("intervals (done) ~w\n",[erlang:statistics(runtime)]),
96
 
  Intervals = sort_on_start(USIntervals),
97
 
  ?debug_msg("sort intervals (done) ~w\n",[erlang:statistics(runtime)]),
98
 
  ?debug_msg("Intervals ~w\n",[Intervals]),
99
 
  ?debug_msg("No intervals: ~w\n",[length(Intervals)]),
100
 
 
101
 
 
102
 
  Allocation = allocate(Intervals,PhysRegs, SpillIndex, DontSpill, Target),
103
 
  ?debug_msg("allocation (done) ~w\n",[erlang:statistics(runtime)]),
104
 
  Allocation.
105
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
106
 
 
107
 
 
108
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
109
 
%%                                                                    %%
110
 
%%        Step 2: Calculate live-intervals for each register.         %%
111
 
%%                                                                    %%
112
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
113
 
 
114
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
115
 
%% calculate_intervals(CFG,Liveness,Entrypoints, Options, Target)
116
 
%%  CFG: The Control-Flow Graph.
117
 
%%  Liveness: A map of live-in and live-out sets for each Basic-Block.
118
 
%%  Entrypoints: A set of BB names that have external entrypoints.
119
 
%%
120
 
calculate_intervals(CFG,Liveness,_Entrypoints, Options, Target) ->
121
 
  %% Add start point for the argument registers.
122
 
  Args = arg_vars(CFG, Target),
123
 
  Interval = 
124
 
    add_def_point(Args, 0, 
125
 
                  empty_interval(Target:number_of_temporaries(CFG))),
126
 
  Worklist =
127
 
    case proplists:get_value(ls_order, Options) of
128
 
      reversepostorder ->
129
 
        Target:reverse_postorder(CFG);
130
 
      breadth ->
131
 
        Target:breadthorder(CFG);
132
 
      postorder ->
133
 
        Target:postorder(CFG);
134
 
      prediction ->
135
 
        Target:predictionorder(CFG);
136
 
      random ->
137
 
        Target:labels(CFG);
138
 
      _ ->
139
 
        Target:reverse_postorder(CFG)
140
 
    end,
141
 
 
142
 
  ?debug_msg("No BBs ~w\n",[length(Worklist)]),
143
 
  intervals(Worklist, Interval, 1, CFG, Liveness, succ_map(CFG, Target), Target).
144
 
 
145
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
146
 
%% intervals(WorkList, Intervals, InstructionNr,
147
 
%%           CFG, Liveness, SuccMap)
148
 
%%  WorkList: List of BB-names to handle.
149
 
%%  Intervals: Intervals seen so far (sorted on register names).
150
 
%%  InstructionNr: The number of examined insturctions.
151
 
%%  CFG: The Control-Flow Graph.
152
 
%%  Liveness: A map of live-in and live-out sets for each Basic-Block.
153
 
%%  SuccMap: A map of successors for each BB name.
154
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
155
 
intervals([L|ToDO],Intervals,InstructionNr,CFG,Liveness,SuccMap, Target) ->
156
 
  ?debug_msg("Block ~w\n",[L]),
157
 
  %% Add all variables that are live at the entry of this block
158
 
  %% to the interval data structure.
159
 
  LiveIn = livein(Liveness,L, Target),
160
 
  Intervals2 = add_def_point(LiveIn,InstructionNr,Intervals),
161
 
  LiveOut = liveout(Liveness,L, Target),
162
 
  Unchanged = ordsets:intersection(LiveIn, LiveOut),
163
 
  ?debug_msg("In ~w -> Out ~w\n",[LiveIn, LiveOut]),
164
 
  %% Traverse this block instruction by instruction and add all
165
 
  %% uses and defines to the intervals.
166
 
 
167
 
  Code = hipe_bb:code(bb(CFG,L, Target)),
168
 
  {Intervals3, NewINr} = traverse_block(Code, InstructionNr,
169
 
                                        Intervals2, Unchanged,
170
 
                                        Target),
171
 
  
172
 
  %% Add end points for the registers that are in the live-out set.
173
 
  Intervals4 = add_use_point(LiveOut, NewINr, Intervals3),
174
 
  
175
 
  intervals(ToDO, Intervals4, NewINr, CFG, Liveness, SuccMap, Target);
176
 
intervals([],Intervals,_,_,_,_, _) -> 
177
 
  %% Return the calculated intervals
178
 
  interval_to_list(Intervals).
179
 
 
180
 
 
181
 
 
182
 
 
183
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
184
 
%% traverse_block(Code, InstructionNo, Intervals, Unchanged) 
185
 
%%  Examine each instruction in the Code:
186
 
%%   For each temporary T used or defined by instruction number N:
187
 
%%    extend the interval of T to include N.
188
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
189
 
traverse_block([Instruction|Is],InstrNo,Intervals, Unchanged, Target) ->
190
 
  ?debug_msg("Unchanged ~w\n",[Unchanged]),
191
 
  ?debug_msg("~4w: ~w\n", [InstrNo, Instruction]),
192
 
  %% Get used temps.
193
 
  UsesSet = ordsets:from_list(uses(Instruction, Target)),
194
 
  ?debug_msg("    Uses ~w\n", [UsesSet]),
195
 
  %% Get defined temps.
196
 
  DefsSet = ordsets:from_list(defines(Instruction, Target)),
197
 
  ?debug_msg("    Defines ~w\n", [DefsSet]),
198
 
 
199
 
%%  %% Only consider those temps that starts or ends their lifetime 
200
 
%%  %%  within the basic block (that is remove all Unchanged temps).
201
 
%%  
202
 
%%  UpdateDef = ordsets:subtract(DefsSet, Unchanged),
203
 
 
204
 
  Intervals1 = add_def_point(%%ordsets:to_list(UpdateDef), 
205
 
        DefsSet, InstrNo, Intervals),
206
 
 
207
 
  %% UpdateUse = ordsets:subtract(UsesSet, Unchanged),
208
 
  %% Extend the intervals for these temporaries to include InstrNo.
209
 
  Intervals2 = add_use_point(%% ordsets:to_list(UpdateUse), 
210
 
        UsesSet, InstrNo, Intervals1),
211
 
 
212
 
  ?debug_msg(" I ~w\n",[  interval_to_list(Intervals2)]),
213
 
 
214
 
 
215
 
  %% Handle the next instruction.
216
 
  traverse_block(Is,InstrNo+1,Intervals2, Unchanged, Target);
217
 
 
218
 
traverse_block([], InstrNo, Intervals, _, _) -> 
219
 
  %% Return the new intervals and the number of the next instruction.
220
 
  {Intervals,InstrNo}.
221
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
222
 
 
223
 
 
224
 
 
225
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
226
 
%%                                                                    %%
227
 
%%    Step 3. Do a linear scan allocation over the live intervals.    %%
228
 
%%                                                                    %%
229
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
230
 
 
231
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
232
 
%%
233
 
%% allocate(Intervals, PhysicalRegisters, DontSpill, Target)
234
 
%%
235
 
%% This function performs the linear scan algorithm.
236
 
%%  Intervals contains the start and stop position of each register,
237
 
%%            sorted on increasing startpositions
238
 
%%  PhysicalRegisters is a list of available Physical registers to use.
239
 
%%
240
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
241
 
allocate(Intervals, PhysRegs, SpillIndex, DontSpill, Target) ->
242
 
  ActiveRegisters =[],
243
 
  AllocatedRegisters = empty_allocation(),
244
 
  allocate(Intervals, PhysRegs, ActiveRegisters,
245
 
           AllocatedRegisters, SpillIndex, DontSpill, Target).
246
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
247
 
%% allocate(Intervals, Free, Active, Allocated, SpillIndex, Target) 
248
 
%%  Iterates of each register interval.
249
 
%%   Intervals: The list of register intervals.
250
 
%%   Free: Currently available physical registers.
251
 
%%   Active: Currently used physical registers (sorted on increasing 
252
 
%%            interval enpoints)
253
 
%%   Allocated: The mapping of register names to physical registers or
254
 
%%              to spill positions.
255
 
%%   SpillIndex: The number of spilled registers. 
256
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
257
 
allocate([RegInt|RIS], Free, Active, Alloc, SpillIndex, DontSpill, Target) ->
258
 
  ?debug_msg("Alloc interval: ~w, Free ~w\n",[RegInt, Free]),
259
 
  %% Remove from the active list those registers who's intervals 
260
 
  %% ends before the start of the current interval.
261
 
  {NewActive, NewFree} = expire_old_intervals(Active, startpoint(RegInt), Free),
262
 
  
263
 
  %% Get the name of the temp in the current interval.
264
 
  Temp = reg(RegInt), 
265
 
  case is_precolored(Temp, Target) of
266
 
    true -> 
267
 
      %% This is a precolored register we don't need to find a color
268
 
      %% Get the physical name of the register.
269
 
      PhysName = physical_name(Temp, Target), 
270
 
      %% Bind it to the precolored name.
271
 
      NewAlloc = alloc(Temp, PhysName, Alloc), 
272
 
      case is_global(Temp, Target) of
273
 
        true -> 
274
 
          %% this is a global precolored register 
275
 
          allocate(RIS, NewFree, NewActive,
276
 
                   NewAlloc, SpillIndex, DontSpill, Target);
277
 
        false ->
278
 
          case is_free(PhysName, NewFree) of
279
 
            true ->
280
 
              allocate(RIS, NewFree -- [PhysName], 
281
 
                       add_active(endpoint(RegInt), PhysName, Temp, NewActive),
282
 
                       NewAlloc,
283
 
                       SpillIndex, DontSpill, Target);
284
 
            false ->
285
 
              %% Some other temp has taken this precolored register,
286
 
              %% throw it out.
287
 
 
288
 
              {OtherActive, NewActive2} = 
289
 
                deactivate(PhysName, NewActive),
290
 
              OtherTemp = active_name(OtherActive),
291
 
              OtherEnd = active_endpoint(OtherActive),
292
 
 
293
 
              NewSpillIndex = SpillIndex+1,
294
 
              {NewAlloc2, NewActive3} = 
295
 
                spill(OtherTemp, OtherEnd, NewActive2, NewAlloc,
296
 
                      NewSpillIndex, DontSpill, Target),
297
 
              allocate(RIS, 
298
 
                       NewFree, 
299
 
                       add_active(endpoint(RegInt), PhysName, Temp, NewActive3),
300
 
                       NewAlloc2, NewSpillIndex, DontSpill, Target)
301
 
          
302
 
          end
303
 
            
304
 
      end;
305
 
    false -> 
306
 
      %% This is not a precolored register.
307
 
      case NewFree of 
308
 
        [] -> 
309
 
          %% No physical registers available, we have to spill.
310
 
          NewSpillIndex = SpillIndex+1,
311
 
          {NewAlloc, NewActive2} = 
312
 
            spill(Temp, endpoint(RegInt), Active, Alloc,
313
 
                  NewSpillIndex, DontSpill, Target),
314
 
          %% io:format("Spilled ~w\n",[NewAlloc]),
315
 
          allocate(RIS, NewFree, NewActive2, NewAlloc, NewSpillIndex,
316
 
                   DontSpill, Target);
317
 
 
318
 
        [FreeReg | Regs] -> 
319
 
          %% The register FreeReg is available, let's use it.
320
 
          allocate(RIS,Regs,
321
 
                   add_active(endpoint(RegInt), FreeReg, Temp, NewActive),
322
 
                   alloc(Temp, FreeReg, Alloc),
323
 
                   SpillIndex, DontSpill, Target)
324
 
      end
325
 
  end;
326
 
allocate([],_,_,Alloc,SpillIndex, _, _) -> 
327
 
  %% No more register intervals to handle
328
 
  %%  return the result.
329
 
  {Alloc, SpillIndex}.
330
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
331
 
 
332
 
 
333
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
334
 
%%
335
 
%% expire_old_intervals(ActiveRegisters, CurrentPos, FreeRegisters) 
336
 
%%   Remove all registers that have live-ranges that ends before the
337
 
%%   current position from the active list and put them into the free
338
 
%%   list instead.
339
 
%%
340
 
%% ---------------------------------------------------------------------
341
 
expire_old_intervals([Active|Actives], CurrentPos, Free) ->
342
 
  %% Does the live-range of the first active register end before 
343
 
  %% the current position?
344
 
  %% We don't free registers that end at the current position,
345
 
  %%  since a multimove can decide to do the moves in another order...
346
 
  case active_endpoint(Active) =< CurrentPos of
347
 
    true -> %% Yes -> Then we can free that register.
348
 
 
349
 
                
350
 
      expire_old_intervals(Actives, CurrentPos,
351
 
                           %% Add the register to the free pool.
352
 
                           [active_reg(Active)|Free]);
353
 
                           
354
 
                           %% Here we could try appending the
355
 
                           %% register to get a more widespread
356
 
                           %% use of registers.
357
 
                           %% Free ++ [active_reg(Active)]);
358
 
                           %% At the moment this does not seem to
359
 
                           %%  improve performance at all,
360
 
                           %%  on the other hand, the cost is very low.
361
 
 
362
 
 
363
 
    false -> 
364
 
      %% No -> Then we cannot free any more registers.
365
 
      %%       (Since they are sorted on endpoints...)    
366
 
      {[Active|Actives],Free}
367
 
  end;
368
 
expire_old_intervals([],_,Free) ->
369
 
  {[],Free}.
370
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
371
 
 
372
 
deactivate(Reg, [Active|Actives]) ->
373
 
  case Reg =:= active_reg(Active) of
374
 
    true ->
375
 
      {Active, Actives};
376
 
    false ->
377
 
      {TheActive, NewActives} =
378
 
        deactivate(Reg, Actives),
379
 
      {TheActive, [Active|NewActives]}
380
 
  end;
381
 
deactivate(_,[]) -> {no,[]}.
382
 
 
383
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
384
 
%%
385
 
%% spill(CurrentReg, CurrentEndpoint, Active, Alloc, SpillIndex, 
386
 
%%       DontSpill, Target)
387
 
%%   Find the register with the longest live range and spill it to memory.
388
 
%%
389
 
%% ---------------------------------------------------------------------
390
 
spill(CurrentReg, CurrentEndpoint, 
391
 
      Active = [_|_], 
392
 
      Alloc, SpillIndex,
393
 
      DontSpill, Target) ->
394
 
  ?debug_msg("spilling one of ~w\nDOnt spill ~w\n",
395
 
             [[CurrentReg|Active], DontSpill]),
396
 
 
397
 
  %% Find a spill candidate (one of the active): 
398
 
  %%  The register with the longest live-range.
399
 
  {NewActive, SpillCandidate} = butlast_last(Active),
400
 
 
401
 
  SpillEndpoint = active_endpoint(SpillCandidate) ,
402
 
  SpillName = active_name(SpillCandidate),
403
 
  SpillPhysName = active_reg(SpillCandidate), 
404
 
 
405
 
  case SpillEndpoint > CurrentEndpoint of
406
 
    true -> 
407
 
      %% There is an already allocated register that has
408
 
      %% a longer live-range than the current register.
409
 
      case can_spill(SpillName, DontSpill, Target) of
410
 
        false ->
411
 
          {NewAlloc, NewActive2} = 
412
 
            spill(CurrentReg, CurrentEndpoint, NewActive, Alloc,
413
 
                  SpillIndex, DontSpill, Target),
414
 
          {NewAlloc, 
415
 
           add_active(SpillEndpoint, SpillPhysName, SpillName,
416
 
                      NewActive2)};
417
 
        true ->
418
 
          %% It is not precolored...
419
 
 
420
 
          %% Allocate SpillCandidate to spill-slot SpillIndex
421
 
          SpillAlloc = 
422
 
            spillalloc(active_name(SpillCandidate), SpillIndex, 
423
 
                       Alloc),
424
 
 
425
 
          %% Allocated the current register to the physical register
426
 
          %% used by the spill candidate.
427
 
          NewAlloc = alloc(CurrentReg, SpillPhysName, SpillAlloc),
428
 
          
429
 
          %% Add the current register to the active registers
430
 
          NewActive2 = 
431
 
            add_active(CurrentEndpoint, SpillPhysName, CurrentReg, NewActive),
432
 
          
433
 
          {NewAlloc, NewActive2}
434
 
      end;
435
 
        
436
 
    false -> 
437
 
      %% The current register has the longest live-range.
438
 
 
439
 
      case can_spill(CurrentReg, DontSpill, Target) of 
440
 
        false ->
441
 
          %% Cannot spill a precolored register
442
 
          {NewAlloc, NewActive2} = 
443
 
            spill(SpillName, SpillEndpoint, NewActive, Alloc,
444
 
                  SpillIndex, DontSpill, Target),
445
 
          NewActive3 = 
446
 
            add_active(CurrentEndpoint, SpillPhysName, CurrentReg, NewActive2),
447
 
          {NewAlloc, NewActive3};
448
 
        true ->
449
 
          %% It is not precolored...
450
 
          %% Allocate the current register to spill-slot SpillIndex
451
 
          {spillalloc(CurrentReg, SpillIndex, Alloc), Active}
452
 
      end
453
 
  end;
454
 
spill(CurrentReg, _CurrentEndpoint, [],
455
 
      Alloc, SpillIndex, DontSpill, Target) ->
456
 
  case can_spill(CurrentReg, DontSpill, Target) of 
457
 
    false -> %% Can't spill current!
458
 
      ?error_msg("Can't allocate registers\n",[]),
459
 
      ?EXIT({cannot_allocate_regs});
460
 
    true -> %% Can spill current.
461
 
      %% Allocate the current register to spill-slot SpillIndex
462
 
      {spillalloc(CurrentReg, SpillIndex, Alloc), []}
463
 
  end.
464
 
 
465
 
can_spill(Name, DontSpill, Target) ->
466
 
  (Name < DontSpill) and (not is_precolored(Name, Target)).
467
 
 
468
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
469
 
 
470
 
 
471
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
472
 
%%                                                                    %%
473
 
%%                   D A T A   S T R U C T U R E S                    %%
474
 
%%                                &                                   %%
475
 
%%               A U X I L I A R Y   F U N C T I O N S                %%
476
 
%%                                                                    %%
477
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
478
 
 
479
 
 
480
 
 
481
 
 
482
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
483
 
%%
484
 
%% The "allocation datastructure"
485
 
%%
486
 
%% This is an order list of register names paired with their allocations.
487
 
%%  {Name, Allocation}
488
 
%% The allocation is either {reg, physical register} or
489
 
%%                          {spill, spill index}
490
 
%%
491
 
%% ---------------------------------------------------------------------
492
 
empty_allocation() -> [].
493
 
 
494
 
alloc(Name,Reg,[{Name,_}|A]) ->
495
 
  [{Name,{reg,Reg}}|A];
496
 
alloc(Name,Reg,[{Name2,Binding}|Bindings]) when Name > Name2 ->
497
 
  [{Name2,Binding}|alloc(Name,Reg,Bindings)];
498
 
alloc(Name,Reg,Bindings) ->
499
 
  [{Name,{reg,Reg}}|Bindings].
500
 
 
501
 
spillalloc(Name,N,[{Name,_}|A]) ->
502
 
  [{Name,{spill,N}}|A];
503
 
spillalloc(Name,N,[{Name2,Binding}|Bindings]) when Name > Name2 ->
504
 
  [{Name2,Binding}|spillalloc(Name,N,Bindings)];
505
 
spillalloc(Name,N,Bindings) ->
506
 
  [{Name,{spill,N}}|Bindings].
507
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
508
 
 
509
 
 
510
 
 
511
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
512
 
%%
513
 
%%
514
 
butlast_last([X]) ->
515
 
   {[],X};
516
 
butlast_last([X|Y]) ->
517
 
  {L,Last} = butlast_last(Y),
518
 
  {[X|L],Last}.
519
 
 
520
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
521
 
%% 
522
 
%%  The active datastructure.
523
 
%%   Keeps tracks of currently active (allocated) physical registers.
524
 
%%   It is sorted on end points in the intervals
525
 
%%
526
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
527
 
add_active(Endpoint, PhysReg, RegName, [{P1,R1,O1}|Active]) when P1 < Endpoint ->
528
 
  [{P1,R1,O1}|add_active(Endpoint, PhysReg, RegName, Active)];
529
 
add_active(Endpoint, PhysReg, RegName, Active) ->
530
 
  [{Endpoint, PhysReg, RegName}|Active].
531
 
 
532
 
active_reg({_,PhysReg,_}) ->
533
 
  PhysReg.
534
 
active_endpoint({EndPoint,_,_}) ->
535
 
  EndPoint.
536
 
active_name({_,_,RegName})->
537
 
  RegName.
538
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
539
 
 
540
 
 
541
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
542
 
%% The Interval data structure.
543
 
%%
544
 
%%
545
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
546
 
 
547
 
%% mk_interval(Name, Start, End) ->
548
 
%%  {Name, { Start, End}}.
549
 
 
550
 
endpoint({_R,{_S,Endpoint}}) ->
551
 
  Endpoint.
552
 
startpoint({_R,{Startpoint,_E}}) ->
553
 
  Startpoint.
554
 
reg({RegName,{_S,_E}}) ->
555
 
  RegName.
556
 
 
557
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
558
 
%% The Intervals data structure.
559
 
%%
560
 
sort_on_start(I)->
561
 
 lists:keysort(2,I).
562
 
 
563
 
-define(gb_intervals,true).
564
 
-ifdef(gb_intervals).
565
 
empty_interval(_) ->
566
 
  gb_trees:empty().
567
 
 
568
 
interval_to_list(Intervals) ->
569
 
  lists:flatten(
570
 
    lists:map(
571
 
      fun({T, I}) when list(I) ->
572
 
          lists:map(
573
 
            fun ({none, End}) -> 
574
 
                {T,{End,End}};
575
 
                ({Beg, none}) ->
576
 
                {T,{Beg, Beg}}
577
 
            end,
578
 
            I);
579
 
         (I) -> I
580
 
      end,
581
 
      gb_trees:to_list(Intervals))).
582
 
 
583
 
add_use_point([Temp|Temps],Pos,Intervals) ->
584
 
  %% Extend the old interval...
585
 
  NewInterval =
586
 
    case gb_trees:lookup(Temp, Intervals) of
587
 
      %% This temp has an old interval...
588
 
      {value, Value} ->
589
 
        %% ... extend it.
590
 
        extend_use_interval(Pos, Value);
591
 
 
592
 
      %% This is the first time we see this temp...
593
 
      none ->
594
 
        %% ... create a new interval
595
 
        [{none, Pos}]
596
 
    end,
597
 
 
598
 
  %% Add or update the extended interval.
599
 
  Intervals2 = gb_trees:enter(Temp, NewInterval, Intervals),
600
 
 
601
 
  %% Add the rest of teh temporaries.
602
 
  add_use_point(Temps, Pos, Intervals2);
603
 
 
604
 
add_use_point([], _, I) ->
605
 
  %% No more to add return the interval.
606
 
  I.
607
 
 
608
 
add_def_point([Temp|Temps],Pos,Intervals) ->
609
 
 
610
 
   
611
 
  %% Extend the old interval...
612
 
  NewInterval =
613
 
    case gb_trees:lookup(Temp, Intervals) of
614
 
      %% This temp has an old interval...
615
 
      {value, Value} ->
616
 
        %% ... extend it.
617
 
        extend_def_interval(Pos, Value);
618
 
 
619
 
      %% This is the first time we see this temp...
620
 
      none ->
621
 
        %% ... create a new interval
622
 
        [{Pos, none}]
623
 
    end,
624
 
 
625
 
  %% Add or update the extended interval.
626
 
  Intervals2 = gb_trees:enter(Temp, NewInterval, Intervals),
627
 
 
628
 
  %% Add the rest of the temporaries.
629
 
  add_def_point(Temps, Pos, Intervals2);
630
 
 
631
 
add_def_point([], _, I) ->
632
 
  %% No more to add return the interval.
633
 
  I.
634
 
 
635
 
extend_use_interval(Pos, {Beginning, End}) ->
636
 
  %% If this position occures after the end
637
 
  %%  of the interval, then extend the end to
638
 
  %%  this position.
639
 
  NewEnd = 
640
 
    if Pos > End -> Pos;
641
 
       true      -> End
642
 
    end,
643
 
 
644
 
  {Beginning, NewEnd};
645
 
extend_use_interval(Pos, [{none,End}|More]) ->
646
 
  {[{none,Pos},{none,End}|More]};
647
 
extend_use_interval(Pos, Intervals) ->
648
 
  {Beginning,none} = lists:last(Intervals),
649
 
  {Beginning, Pos}.
650
 
 
651
 
 
652
 
extend_def_interval(Pos, {Beginning, End}) ->
653
 
  %% If this position occures before the beginning
654
 
  %%  of the interval, then extend the beginning to
655
 
  %%  this position.
656
 
 
657
 
  NewBeginning = 
658
 
    if Pos < Beginning -> Pos;
659
 
       true            -> Beginning
660
 
    end,
661
 
  %% If this position occures after the end
662
 
  %%  of the interval, then extend the end to
663
 
  %%  this position.
664
 
  NewEnd = 
665
 
    if Pos > End -> Pos;
666
 
       true      -> End
667
 
    end,
668
 
  {NewBeginning, NewEnd}; 
669
 
extend_def_interval(Pos, [{Beginning,none}|More]) ->
670
 
  [{Pos,none}, {Beginning,none}|More];
671
 
extend_def_interval(Pos, _Intervals) ->
672
 
  {Pos, Pos}.
673
 
 
674
 
%% ____________________________________________________________________
675
 
-else. %% isdef gb_intervals
676
 
 
677
 
empty_interval(N) ->
678
 
  ?vector_new(N, none).
679
 
 
680
 
interval_to_list(Intervals) ->
681
 
  lists:flatten(
682
 
    lists:map(
683
 
      fun({T, I}) when is_list(I) ->
684
 
          lists:map(
685
 
            fun ({none, End}) -> 
686
 
                {T,{End,End}};
687
 
                ({Beg, none}) ->
688
 
                {T,{Beg, Beg}}
689
 
            end,
690
 
            I);
691
 
         ({_,none}) ->
692
 
          [];
693
 
         (I) -> I
694
 
      end,
695
 
      add_indices(?vector_to_list(Intervals),0))).
696
 
 
697
 
add_indices([],_N) -> [];
698
 
add_indices([X|Xs],N) ->
699
 
    [{N,X}|add_indices(Xs,N+1)].
700
 
 
701
 
add_use_point([Temp|Temps],Pos,Intervals) ->
702
 
  %% Extend the old interval...
703
 
  NewInterval =
704
 
    case ?vector_get(Temp+1, Intervals) of
705
 
      %% This is the first time we see this temp...
706
 
      none ->
707
 
        %% ... create a new interval
708
 
        [{none, Pos}];
709
 
      %% This temp has an old interval...
710
 
      Value ->
711
 
        %% ... extend it.
712
 
        extend_use_interval(Pos, Value)
713
 
    end,
714
 
 
715
 
  %% Add or update the extended interval.
716
 
  Intervals2 = ?vector_set(Temp+1, Intervals, NewInterval),
717
 
 
718
 
  %% Add the rest of the temporaries.
719
 
  add_use_point(Temps, Pos, Intervals2);
720
 
 
721
 
add_use_point([], _, I) ->
722
 
  %% No more to add return the interval.
723
 
  I.
724
 
 
725
 
add_def_point([Temp|Temps],Pos,Intervals) ->
726
 
  %% io:format("Add ~w~n",[Temp]),
727
 
  %% Extend the old interval...
728
 
  NewInterval =
729
 
    case ?vector_get(Temp+1, Intervals) of
730
 
      %% This is the first time we see this temp...
731
 
      none ->
732
 
        %% ... create a new interval
733
 
        [{Pos, none}];
734
 
      %% This temp has an old interval...
735
 
      Value ->
736
 
        %% ... extend it.
737
 
        extend_def_interval(Pos, Value)
738
 
    end,
739
 
  %% io:format("Old ~w New ~w~n",[?vector_get(Temp+1, Intervals) ,NewInterval]),
740
 
  %% Add or update the extended interval.
741
 
  Intervals2 = ?vector_set(Temp+1, Intervals, NewInterval), 
742
 
 
743
 
  %% Add the rest of teh temporaries.
744
 
  add_def_point(Temps, Pos, Intervals2);
745
 
 
746
 
add_def_point([], _, I) ->
747
 
  %% No more to add return the interval.
748
 
  I.
749
 
 
750
 
extend_use_interval(Pos, {Beginning, End}) ->
751
 
  %% If this position occures before the beginning
752
 
  %%  of the interval, then extend the beginning to
753
 
  %%  this position.
754
 
 
755
 
  NewBeginning = 
756
 
    if Pos < Beginning -> Pos;
757
 
       true            -> Beginning
758
 
    end,
759
 
  %% If this position occures after the end
760
 
  %%  of the interval, then extend the end to
761
 
  %%  this position.
762
 
  NewEnd = 
763
 
    if Pos > End -> Pos;
764
 
       true      -> End
765
 
    end,
766
 
 
767
 
  {NewBeginning, NewEnd};
768
 
extend_use_interval(Pos, [{none,End}|More]) ->
769
 
  {[{none,Pos},{none,End}|More]};
770
 
extend_use_interval(Pos,  Intervals) ->
771
 
  {Beginning,none} = lists:last(Intervals),
772
 
  {Beginning, Pos}.
773
 
 
774
 
 
775
 
extend_def_interval(Pos, {Beginning, End}) ->
776
 
  %% If this position occures before the beginning
777
 
  %%  of the interval, then extend the beginning to
778
 
  %%  this position.
779
 
 
780
 
  NewBeginning = 
781
 
    if Pos < Beginning -> Pos;
782
 
       true            -> Beginning
783
 
    end,
784
 
  %% If this position occures after the end
785
 
  %%  of the interval, then extend the end to
786
 
  %%  this position.
787
 
  NewEnd = 
788
 
    if Pos > End -> Pos;
789
 
       true      -> End
790
 
    end,
791
 
 
792
 
  {NewBeginning, NewEnd}; 
793
 
extend_def_interval(Pos, [{Beginning,none}|More]) ->
794
 
  [{Pos,none}, {Beginning,none}|More];
795
 
extend_def_interval(Pos, _Intervals) ->
796
 
  {Pos, Pos}.
797
 
-endif. %% gb_intervals
798
 
 
799
 
 
800
 
 
801
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
802
 
%% The Free data structure.
803
 
%%
804
 
%%
805
 
%%-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -
806
 
 
807
 
is_free(R, [R|_]) ->
808
 
  true;
809
 
is_free(R, [_|Rs]) ->
810
 
  is_free(R, Rs);
811
 
is_free(_, [] ) ->
812
 
  false.
813
 
 
814
 
%%^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
815
 
 
816
 
 
817
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
818
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
819
 
%%
820
 
%% Interface to external functions.
821
 
%% XXX: Make this efficient somehow...
822
 
%% 
823
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
824
 
 
825
 
%%function(CFG, Target) ->
826
 
%%  Target:function(CFG).
827
 
 
828
 
succ_map(CFG, Target) ->
829
 
  Target:succ_map(CFG).
830
 
 
831
 
liveness(CFG, Target) ->
832
 
   Target:analyze(CFG).
833
 
 
834
 
bb(CFG, L, Target) ->
835
 
  Target:bb(CFG,L).
836
 
 
837
 
livein(Liveness,L, Target) ->
838
 
  regnames(Target:livein(Liveness,L), Target).
839
 
 
840
 
liveout(Liveness,L, Target)->
841
 
  regnames(Target:liveout(Liveness,L), Target).
842
 
 
843
 
uses(I, Target)->
844
 
  regnames(Target:uses(I), Target).
845
 
 
846
 
defines(I, Target) ->
847
 
  regnames(Target:defines(I), Target).
848
 
 
849
 
is_precolored(R, Target) ->
850
 
  Target:is_precolored(R).
851
 
 
852
 
is_global(_, hipe_x86_specific_fp) ->
853
 
   false;
854
 
is_global(R, Target) ->
855
 
  hipe_x86_registers:temp1() =:=R orelse 
856
 
  hipe_x86_registers:temp0() =:=R orelse
857
 
  Target:is_global(R).
858
 
 
859
 
physical_name(R, Target) ->
860
 
  Target:physical_name(R).
861
 
 
862
 
regnames(Regs, Target) ->
863
 
  [Target:reg_nr(X) || X <- Regs]. 
864
 
 
865
 
arg_vars(CFG, Target) ->
866
 
  Target:args(CFG).
867
 
 
868
 
count_caller_saves(CFG) ->
869
 
  Liveness = hipe_x86_liveness:analyze(CFG),
870
 
  count_caller_saves(CFG, Liveness, hipe_x86_specific).
871
 
 
872
 
count_caller_saves(CFG,Liveness, T) ->
873
 
 Ls =
874
 
    lists:foldr(
875
 
      fun (L,CallerSaves) ->
876
 
        [ X || 
877
 
        X <- element(2,lists:foldr(
878
 
                    fun(I,{LiveOut,CS}) ->
879
 
                        UsesSet = ordsets:from_list(uses(I,T)),
880
 
                        DefsSet = ordsets:from_list(defines(I,T)),
881
 
                        LiveOverI = ordsets:subtract(LiveOut,
882
 
                                                      DefsSet),      
883
 
                        NewCS = 
884
 
                          case hipe_x86:insn_type(I) of
885
 
                            pseudo_call ->
886
 
                              ordsets:union(CS,LiveOverI);
887
 
                            _ -> CS
888
 
                          end,
889
 
                        NewLiveOut = ordsets:union(
890
 
                                       LiveOverI,
891
 
                                       UsesSet),
892
 
                        {NewLiveOut,NewCS}
893
 
                    end,
894
 
                    {ordsets:from_list(liveout(Liveness,L,T)),
895
 
                     CallerSaves},
896
 
                    hipe_bb:code(T:bb(CFG,L)))),
897
 
        not is_precolored(X,T)] 
898
 
      end,
899
 
      [],
900
 
      T:labels(CFG)),
901
 
  %% io:format("Caller saves: ~w~n",[Ls]),      
902
 
  length(Ls).   
 
67
  hipe_ls_regalloc:regalloc(CFG,PhysRegs,Entrypoints, SpillIndex, 
 
68
                            DontSpill, Options, Target).