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

« back to all changes in this revision

Viewing changes to lib/hipe/regalloc/hipe_coalescing_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:
11
11
%%-----------------------------------------------------------------------
12
12
 
13
13
-module(hipe_coalescing_regalloc).
14
 
-author(['Thorild Sel�n', 'Andreas Wallin', 'Ingemar �berg']).
15
 
 
16
 
-export([regalloc/4]).
 
14
-export([regalloc/5]).
17
15
 
18
16
%%-ifndef(DEBUG).
19
17
%%-define(DEBUG,true).
36
34
%%   Coloring    -- A coloring for specified CFG
37
35
%%   SpillIndex0 -- A new spill index
38
36
%%-----------------------------------------------------------------------
39
 
regalloc(CFG, SpillIndex, SpillLimit, Target) ->
 
37
regalloc(CFG, SpillIndex, SpillLimit, Target, _Options) ->
40
38
  %% Build interference graph
41
39
  ?debug_msg("Build IG\n",[]),
42
40
  IG = hipe_ig:build(CFG, Target),
43
41
  %% io:format("IG: ~p\n",[IG]),
44
42
 
45
43
  ?debug_msg("Init\n",[]),
46
 
  {Min_temporary, Max_temporary} = Target:var_range(CFG),
47
44
  No_temporaries = Target:number_of_temporaries(CFG),
48
45
  ?debug_msg("Coalescing RA: num_temps = ~p~n", [No_temporaries]),
49
 
  All_colors = ordsets:from_list(Target:allocatable()),
50
 
  K = length(All_colors),
 
46
  Allocatable = Target:allocatable(),
 
47
  K = length(Allocatable),
 
48
  All_colors = colset_from_list(Allocatable),
51
49
 
52
 
  ?debug_msg("Init node sets\n",[]),
53
 
  Node_sets = hipe_node_sets:new(Target, Min_temporary, Max_temporary,
54
 
                                Target:non_alloc(CFG)),
55
 
  %% io:format("NodeSet: ~w\n NonAlloc ~w\n",[Node_sets,Target:non_alloc(CFG)]),
56
50
  %% Add registers with their own coloring
57
51
  ?debug_msg("Moves\n",[]),
58
52
  Move_sets = hipe_moves:new(IG),
59
53
 
60
54
  ?debug_msg("Build Worklist\n",[]),
61
 
  Worklists = hipe_reg_worklists:new(IG, Node_sets, Move_sets, K),
62
 
  SelStk = stack_new(),
 
55
  Worklists = hipe_reg_worklists:new(IG, Target, CFG, Move_sets, K, No_temporaries),
63
56
  Alias = initAlias(No_temporaries),
64
57
 
65
58
  ?debug_msg("Do coloring\n~p~n",[Worklists]),
66
 
  {_IG0, _Worklists0, _Moves0, Alias0, Node_sets0, SelStk0} = 
67
 
    do_coloring(IG, Worklists, Node_sets, Move_sets, Alias,
68
 
                SelStk, K, SpillLimit, Target),
 
59
  {_IG0, Worklists0, _Moves0, Alias0} = 
 
60
    do_coloring(IG, Worklists, Move_sets, Alias,
 
61
                K, SpillLimit, Target),
69
62
  %% io:format("SelStk0 ~w\n",[SelStk0]),
 
63
  ?debug_msg("Init node sets\n",[]),
 
64
  Node_sets = hipe_node_sets:new(),
 
65
  %% io:format("NodeSet: ~w\n NonAlloc ~w\n",[Node_sets,Target:non_alloc(CFG)]),
70
66
  ?debug_msg("Default coloring\n",[]),
71
67
  {Color0,Node_sets1} = 
72
 
    defaultColoring(hipe_node_sets:precolored(Node_sets0),
73
 
                    initColor(No_temporaries), Node_sets0, Target),
 
68
    defaultColoring(Target:all_precoloured(),
 
69
                    initColor(No_temporaries), Node_sets, Target),
74
70
 
75
71
  ?debug_msg("Assign colors\n",[]),
76
72
  {Color1,Node_sets2} =
77
 
    assignColors(stack(SelStk0), Node_sets1, Color0, 
 
73
    assignColors(hipe_reg_worklists:stack(Worklists0), Node_sets1, Color0, 
78
74
                 Alias0, All_colors, Target),
79
 
  %% io:format("color0:~w\nColor1:~w\nNodes:~w\nNodes2:~w\nMax_temporary:~w\n",[Color0,Color1,Node_sets,Node_sets2,Max_temporary]),
 
75
  %% io:format("color0:~w\nColor1:~w\nNodes:~w\nNodes2:~w\nNo_temporaries:~w\n",[Color0,Color1,Node_sets,Node_sets2,No_temporaries]),
80
76
 
81
77
  ?debug_msg("Build mapping ~p\n",[Node_sets2]),
82
78
  Coloring = build_namelist(Node_sets2,SpillIndex,Alias0,Color1),
90
86
%% Parameters:
91
87
%%   IG          --  An interference graph
92
88
%%   Worklists   --  Worklists, that is simplify, spill and freeze
93
 
%%   Node_sets   --  Node sets, that is spilled, coalesced and so on.
94
89
%%   Moves       --  Moves sets, that is coalesced, constrained 
95
90
%%                   and so on.
96
91
%%   Alias       --  Tells if two temporaries can have their value
97
92
%%                   in the same register.
98
 
%%   SelStk      --  Stack where simplified nodes are pushed.
99
93
%%   K           --  Want to create a K coloring.
100
94
%%   SpillLimit  --  Try not to spill nodes that are above the spill limit.
101
95
%%
104
98
%%   Worklists   --  Updated Worklists structure
105
99
%%   Moves       --  Updated Moves structure 
106
100
%%   Alias       --  Updates Alias structure
107
 
%%   Node_sets   --  Updated Node_sets structure
108
 
%%   SelStk      --  Updated SelStk.
109
101
%%   
110
102
%%----------------------------------------------------------------------
111
103
 
112
 
do_coloring(IG, Worklists, Node_sets, Moves, Alias, SelStk, K, 
113
 
            SpillLimit, Target) ->
114
 
 
115
 
  Simplify = not(hipe_reg_worklists:is_empty(simplify, Worklists)),
116
 
  Coalesce = not(hipe_moves:is_empty(worklist, Moves)),
117
 
  Freeze   = not(hipe_reg_worklists:is_empty(freeze, Worklists)),
118
 
  Spill    = not(hipe_reg_worklists:is_empty(spill, Worklists)),
119
 
  if Simplify == true ->
120
 
      {IG0, Worklists0, Moves0, SelStk0} = 
 
104
do_coloring(IG, Worklists, Moves, Alias, K, SpillLimit, Target) ->
 
105
  Simplify = not(hipe_reg_worklists:is_empty_simplify(Worklists)),
 
106
  Coalesce = not(hipe_moves:is_empty_worklist(Moves)),
 
107
  Freeze   = not(hipe_reg_worklists:is_empty_freeze(Worklists)),
 
108
  Spill    = not(hipe_reg_worklists:is_empty_spill(Worklists)),
 
109
  if Simplify =:= true ->
 
110
      {IG0, Worklists0, Moves0} = 
121
111
        simplify(hipe_reg_worklists:simplify(Worklists),
122
112
                 IG, 
123
 
                 Node_sets,
124
113
                 Worklists, 
125
114
                 Moves, 
126
 
                 SelStk, 
127
115
                 K),
128
 
      do_coloring(IG0, Worklists0, Node_sets, Moves0, Alias,
129
 
                  SelStk0, K, SpillLimit,Target);
130
 
     Coalesce == true ->
131
 
      {Moves0, IG0, Worklists0, Node_sets0, Alias0} = 
132
 
        coalesce(Moves, IG, Worklists, Node_sets, Alias, 
133
 
                 SelStk, K, Target),
134
 
      do_coloring(IG0, Worklists0, Node_sets0, Moves0, Alias0, 
135
 
                  SelStk, K, SpillLimit,Target);
136
 
     Freeze == true ->
 
116
      do_coloring(IG0, Worklists0, Moves0, Alias,
 
117
                  K, SpillLimit, Target);
 
118
     Coalesce =:= true ->
 
119
      {Moves0, IG0, Worklists0, Alias0} =
 
120
        coalesce(Moves, IG, Worklists, Alias, K, Target),
 
121
      do_coloring(IG0, Worklists0, Moves0, Alias0, 
 
122
                  K, SpillLimit, Target);
 
123
     Freeze =:= true ->
137
124
      {Worklists0,Moves0} = 
138
 
        freeze(K, Worklists, Moves, hipe_ig:degree(IG), Node_sets, Alias),
139
 
      do_coloring(IG, Worklists0, Node_sets, Moves0, Alias, 
140
 
                  SelStk, K, SpillLimit, Target);
141
 
     Spill == true ->
 
125
        freeze(K, Worklists, Moves, IG, Alias),
 
126
      do_coloring(IG, Worklists0, Moves0, Alias, 
 
127
                  K, SpillLimit, Target);
 
128
     Spill =:= true ->
142
129
      {Worklists0, Moves0} = 
143
 
        selectSpill(Worklists, Moves, IG, K, Node_sets, Alias, SpillLimit),
144
 
      do_coloring(IG, Worklists0, Node_sets, Moves0, Alias, 
145
 
                  SelStk, K, SpillLimit,Target);
 
130
        selectSpill(Worklists, Moves, IG, K, Alias, SpillLimit),
 
131
      do_coloring(IG, Worklists0, Moves0, Alias, 
 
132
                  K, SpillLimit, Target);
146
133
     true -> % Catchall case
147
 
      {IG, Worklists, Moves, Alias, Node_sets, SelStk}
 
134
      {IG, Worklists, Moves, Alias}
148
135
    end.
149
136
 
150
137
%%----------------------------------------------------------------------
151
138
%% Function:    adjacent
152
139
%%
153
140
%% Description: Adjacent nodes that's not coalesced, on the stack or
154
 
%%               precolored.
 
141
%%               precoloured.
155
142
%% Parameters:
156
143
%%   Node        --  Node that you want to adjacents of
157
 
%%   Adj_list    --  An adjacent nodes list (created in IG)
158
 
%%   Coalesced   --  Nodes that are ready for coalesced
159
 
%%   SelStk      --  Nodes that we think will get a coloring
 
144
%%   IG          --  The interference graph
160
145
%%
161
146
%%   Returns: 
162
147
%%     A set with nodes/temporaries that are not coalesced, on the 
163
 
%%      stack or precolored.
 
148
%%      stack or precoloured.
164
149
%%----------------------------------------------------------------------
165
150
 
166
 
adjacent(Node, Adj_list, Coalesced, SelStk) ->
167
 
  Adjacent_edges = hipe_adj_list:edges(Node, Adj_list),
168
 
  adjacent_edges(Adjacent_edges, Coalesced, SelStk).
169
 
 
170
 
adjacent_edges(Adjacent_edges, Coalesced, SelStk) ->
171
 
  Removed_coalesced = ordsets:subtract(Adjacent_edges, Coalesced),
172
 
  remove_stacked(Removed_coalesced, SelStk).
173
 
 
 
151
adjacent(Node, IG, Worklists) ->
 
152
  Adjacent_edges = hipe_ig:node_adj_list(Node, IG),
 
153
  hipe_reg_worklists:non_stacked_or_coalesced_nodes(Adjacent_edges, Worklists).
174
154
 
175
155
%%----------------------------------------------------------------------
176
156
%% Function:    simplify
180
160
%% Parameters:
181
161
%%   [Node|Nodes]  --  The simplify worklist
182
162
%%   IG            --  The interference graph
183
 
%%   Node_sets     --  The node_sets data-structure
184
163
%%   Worklists     --  The worklists data-structure
185
164
%%   Moves         --  The moves data-structure
186
 
%%   SelStk        --  The stack data-structure
187
165
%%   K             --  Produce a K coloring
188
166
%%
189
167
%%   Returns: 
190
168
%%     IG          --  An updated interference graph
191
169
%%     Worklists   --  An updated worklists data-structure
192
170
%%     Moves       --  An updated moves data-structure
193
 
%%     SelStk      --  An updated stack data-structure
194
171
%%----------------------------------------------------------------------
195
172
 
196
 
simplify([], IG, _Node_sets, Worklists, Moves, SelStk, _K) -> 
197
 
  {IG, Worklists, Moves, SelStk};
198
 
simplify([Node|Nodes], IG, Node_sets, Worklists, Moves, SelStk, K) ->
199
 
  Worklists0 = hipe_reg_worklists:remove(simplify, Node, Worklists),
200
 
  Adj_nodes = hipe_adj_list:edges(Node, hipe_ig:adj_list(IG)),
 
173
simplify([], IG, Worklists, Moves, _K) -> 
 
174
  {IG, Worklists, Moves};
 
175
simplify([Node|Nodes], IG, Worklists, Moves, K) ->
 
176
  Worklists0 = hipe_reg_worklists:remove_simplify(Node, Worklists),
201
177
  ?debug_msg("putting ~w on stack~n",[Node]),
202
 
  SelStk0 = push(Node, Adj_nodes,SelStk),
203
 
  Adjacent = adjacent_edges(Adj_nodes, 
204
 
                      hipe_node_sets:coalesced(Node_sets), SelStk0),
 
178
  Adjacent = adjacent(Node, IG, Worklists0),
 
179
  Worklists01 = hipe_reg_worklists:push_stack(Node, Adjacent, Worklists0),
205
180
  {New_ig, Worklists1, New_moves} =
206
 
    decrement_degree(Adjacent, IG, Node_sets, Worklists0, 
207
 
                     Moves, SelStk0, K),
208
 
  simplify(Nodes, New_ig, Node_sets, Worklists1, New_moves, SelStk0, K).
 
181
    decrement_degree(Adjacent, IG, Worklists01, Moves, K),
 
182
  simplify(Nodes, New_ig, Worklists1, New_moves, K).
209
183
 
210
184
%%----------------------------------------------------------------------
211
185
%% Function:    decrement_degree
214
188
%% Parameters:
215
189
%%   [Node|Nodes]  --  Decrement degree on these nodes
216
190
%%   IG            --  The interference graph
217
 
%%   Node_sets     --  The Node_sets data structure
218
191
%%   Worklists     --  The Worklists data structure
219
192
%%   Moves         --  The Moves data structure.
220
 
%%   SelStk        --  Nodes that we think will get a coloring
221
193
%%   K             --  We want to create a coloring with K colors
222
194
%%
223
195
%%   Returns: 
228
200
%%                     gets degree K.
229
201
%%----------------------------------------------------------------------
230
202
 
231
 
decrement_degree([], IG, _Node_sets, Worklists, Moves, _SelStk, _K) -> 
 
203
decrement_degree([], IG, Worklists, Moves, _K) -> 
232
204
  {IG, Worklists, Moves};
233
 
decrement_degree([Node|Nodes], IG, Node_sets, Worklists, Moves, SelStk, K) ->
234
 
  Degree0 = hipe_ig:degree(IG),
235
 
  Degree1 = hipe_degree:dec(Node, Degree0),
236
 
  IG0 = hipe_ig:set_degree(Degree1, IG),
237
 
  %% case (hipe_degree:degree(Node, Degree0) == K) of
238
 
  %% The degree has to drop *below* K before it is colorable.
239
 
  case (hipe_degree:degree(Node, Degree0) < K) of
240
 
    true ->
241
 
      Adjacent = adjacent(Node, 
242
 
                          hipe_ig:adj_list(IG0), 
243
 
                          hipe_node_sets:coalesced(Node_sets),
244
 
                          SelStk),
245
 
      Moves0 = enable_moves(ordsets:add_element(Node, Adjacent), Moves),
246
 
      Worklists0 = hipe_reg_worklists:remove(spill, Node, Worklists),
 
205
decrement_degree([Node|Nodes], IG, Worklists, Moves, K) ->
 
206
  PrevDegree = hipe_ig:get_node_degree(Node, IG),
 
207
  IG0 = hipe_ig:dec_node_degree(Node, IG),
 
208
  if PrevDegree =:= K ->
 
209
      AdjList = hipe_ig:node_adj_list(Node, IG0),
 
210
      %% Ok since Node (a) is still in IG, and (b) cannot be adjacent to itself.
 
211
      Moves00 = enable_moves_active_to_worklist(hipe_moves:node_movelist(Node, Moves),
 
212
                                                Moves),
 
213
      Moves0 = enable_moves(AdjList, Worklists, Moves00),
 
214
      Worklists0 = hipe_reg_worklists:remove_spill(Node, Worklists),
247
215
      case hipe_moves:move_related(Node, Moves0) of
248
216
        true ->
249
 
          Worklists1 = hipe_reg_worklists:add(freeze, Node, Worklists0),
250
 
          decrement_degree(Nodes, IG0, Node_sets, Worklists1, Moves0, 
251
 
                           SelStk, K);
 
217
          Worklists1 = hipe_reg_worklists:add_freeze(Node, Worklists0),
 
218
          decrement_degree(Nodes, IG0, Worklists1, Moves0, K);
252
219
        _ ->
253
 
          Worklists1 = hipe_reg_worklists:add(simplify, Node, Worklists0),
254
 
          decrement_degree(Nodes, IG0, Node_sets, Worklists1, Moves0, 
255
 
                           SelStk, K)
 
220
          Worklists1 = hipe_reg_worklists:add_simplify(Node, Worklists0),
 
221
          decrement_degree(Nodes, IG0, Worklists1, Moves0, K)
256
222
      end;
257
 
    _ ->
258
 
      decrement_degree(Nodes, IG0, Node_sets, Worklists, Moves, SelStk,K)
 
223
     true ->
 
224
      decrement_degree(Nodes, IG0, Worklists, Moves, K)
259
225
  end.
260
226
            
261
227
%%----------------------------------------------------------------------
272
238
%%     An updated moves data-structure
273
239
%%----------------------------------------------------------------------
274
240
 
275
 
enable_moves([], Moves) -> Moves;
276
 
enable_moves([Node|Nodes], Moves) ->
277
 
  Node_moves = hipe_moves:node_moves(Node, Moves),
278
 
  New_moves = enable_moves_active_to_worklist(Node_moves, Moves),
279
 
  enable_moves(Nodes, New_moves).
 
241
enable_moves([], _Worklists, Moves) -> Moves;
 
242
enable_moves([Node|Nodes], Worklists, Moves) ->
 
243
  case hipe_reg_worklists:member_stack_or_coalesced(Node, Worklists) of
 
244
    true -> enable_moves(Nodes, Worklists, Moves);
 
245
    _ ->
 
246
      %% moveList[n] suffices since we're checking for activeMoves membership
 
247
      Node_moves = hipe_moves:node_movelist(Node, Moves),
 
248
      New_moves = enable_moves_active_to_worklist(Node_moves, Moves),
 
249
      enable_moves(Nodes, Worklists, New_moves)
 
250
  end.
280
251
 
281
252
%%----------------------------------------------------------------------
282
253
%% Function:    enable_moves_active_to_worklist
294
265
 
295
266
enable_moves_active_to_worklist([], Moves) -> Moves;
296
267
enable_moves_active_to_worklist([Node|Nodes], Moves) ->
297
 
  case hipe_moves:member(active,Node,Moves) of
 
268
  case hipe_moves:member_active(Node, Moves) of
298
269
    true ->
299
 
      New_moves = hipe_moves:add(worklist, Node,
300
 
                                 hipe_moves:remove(active, Node, Moves)),
 
270
      New_moves = hipe_moves:add_worklist(Node,
 
271
                                 hipe_moves:remove_active(Node, Moves)),
301
272
      enable_moves_active_to_worklist(Nodes, New_moves);
302
273
    _ ->
303
274
      enable_moves_active_to_worklist(Nodes, Moves)
308
279
 
309
280
build_namelist(NodeSets,Index,Alias,Color) ->
310
281
  ?debug_msg("Building mapping\n",[]),
311
 
  {alias,AliasVector} = Alias,
312
282
  ?debug_msg("Vector to list\n",[]),
313
283
  AliasList = 
314
 
    build_alias_list(hipe_vectors_wrapper:vector_to_list(AliasVector),
 
284
    build_alias_list(aliasToList(Alias),
315
285
                     0, %% The first temporary has index 0
316
286
                     []), %% Accumulator
317
287
  ?debug_msg("Alias list:~p\n",[AliasList]),
318
288
  ?debug_msg("Coalesced\n",[]),
319
 
  NL1 = build_coalescedlist(AliasList,NodeSets,Color,Alias,[]),
 
289
  NL1 = build_coalescedlist(AliasList,Color,Alias,[]),
320
290
  ?debug_msg("Coalesced list:~p\n",[NL1]),
321
291
  ?debug_msg("Regs\n",[]),
322
292
  NL2 = build_reglist(hipe_node_sets:colored(NodeSets),Color,NL1),
330
300
  ?debug_msg("[~p]: Spill ~p to ~p\n", [?MODULE,Node,Index]),
331
301
  build_spillist(Nodes,Index+1,[{Node,{spill,Index}}|List]).
332
302
 
333
 
build_coalescedlist([],_NodeSets,_Color,_Alias,List) ->
 
303
build_coalescedlist([],_Color,_Alias,List) ->
334
304
  List;
335
 
build_coalescedlist([Node|Ns],NodeSets,Color,Alias,List)
 
305
build_coalescedlist([Node|Ns],Color,Alias,List)
336
306
when is_integer(Node) ->
337
 
  ?debug_msg("Alias of ~p is ~p~n",[Node,getAlias(Node,NodeSets,Alias)]),
338
 
  AC = getColor(getAlias(Node,NodeSets,Alias),Color),
339
 
  build_coalescedlist(Ns,NodeSets,Color,Alias,[{Node,{reg,AC}}|List]);
340
 
build_coalescedlist([_Node|Ns],NodeSets,Color,Alias,List) ->
341
 
  build_coalescedlist(Ns,NodeSets,Color,Alias,List).
 
307
  ?debug_msg("Alias of ~p is ~p~n",[Node,getAlias(Node,Alias)]),
 
308
  AC = getColor(getAlias(Node,Alias),Color),
 
309
  build_coalescedlist(Ns,Color,Alias,[{Node,{reg,AC}}|List]);
 
310
build_coalescedlist([_Node|Ns],Color,Alias,List) ->
 
311
  build_coalescedlist(Ns,Color,Alias,List).
342
312
 
343
313
build_reglist([],_Color,List) -> 
344
314
  List;
352
322
build_alias_list([_Alias|Aliases],I,List) ->
353
323
  build_alias_list(Aliases,I+1,List).
354
324
 
355
 
 
356
325
%%----------------------------------------------------------------------
357
326
%% Function:    assignColors
358
327
%%
382
351
      {Color,NodeSets};
383
352
    [{Node,Edges}|Stack1] ->
384
353
      ?debug_msg("Coloring Node: ~p~n",[Node]),
385
 
      lists:foreach(fun (E) ->
386
 
                        ?debug_msg("  Edge ~w-><~w>->~w~n",
387
 
                                   begin A = getAlias(E,NodeSets,Alias),
388
 
                                         [E,A,getColor(A,Color)]
389
 
                                   end)
390
 
                    end, Edges),
391
 
      case hipe_node_sets:member(precolored,Node, NodeSets) of
392
 
        true ->                                 % Already colored
393
 
          ?debug_msg("Node ~p is already colored~n",[Node]),
394
 
          assignColors(Stack1,NodeSets,Color,Alias,AllColors,Target);
395
 
        false ->                                % Try to find color
396
 
          OkColors = findOkColors(Edges,AllColors,Color,NodeSets,Alias),
397
 
          case OkColors of
398
 
            [] ->                           % Spill case
399
 
              NodeSets1 = hipe_node_sets:add(spilled,Node,NodeSets),
400
 
              
401
 
              assignColors(Stack1,NodeSets1,Color,
402
 
                           Alias,AllColors,Target);
403
 
            [Col|_Cols] ->                   % Colorize case
404
 
              NodeSets1 = hipe_node_sets:add(colored,Node,NodeSets),
405
 
              Color1 = 
406
 
                setColor(Node, Target:physical_name(Col), Color),
407
 
              
408
 
              assignColors(Stack1,NodeSets1,Color1,Alias,AllColors,Target)
409
 
          end
 
354
      ?IF_DEBUG(lists:foreach(fun (_E) ->
 
355
                                  ?msg("  Edge ~w-><~w>->~w~n",
 
356
                                       begin A = getAlias(_E,Alias),
 
357
                                             [_E,A,getColor(A,Color)]
 
358
                                       end)
 
359
                              end, Edges),
 
360
                []),
 
361
      %% When debugging, check that Node isn't precoloured.
 
362
      OkColors = findOkColors(Edges, AllColors, Color, Alias),
 
363
      case colset_is_empty(OkColors) of
 
364
        true -> % Spill case
 
365
          NodeSets1 = hipe_node_sets:add_spilled(Node, NodeSets),
 
366
          assignColors(Stack1, NodeSets1, Color, Alias, AllColors, Target);
 
367
        false -> % Colour case
 
368
          Col = colset_smallest(OkColors),
 
369
          NodeSets1 = hipe_node_sets:add_colored(Node, NodeSets),
 
370
          Color1 = setColor(Node, Target:physical_name(Col), Color),
 
371
          assignColors(Stack1, NodeSets1, Color1, Alias, AllColors, Target)
410
372
      end
411
373
  end.
412
374
 
429
391
  {Color,NodeSets};
430
392
defaultColoring([Reg|Regs],Color,NodeSets,Target) ->
431
393
  Color1 = setColor(Reg,Target:physical_name(Reg),Color),
432
 
  NodeSets1 = hipe_node_sets:add(colored,Reg,NodeSets),
 
394
  NodeSets1 = hipe_node_sets:add_colored(Reg, NodeSets),
433
395
  defaultColoring(Regs,Color1,NodeSets1,Target).
434
396
 
435
397
%% Find the colors that are OK for a node with certain edges.
436
398
 
437
 
findOkColors(Edges,AllColors,Color,NodeSets,Alias) ->
438
 
  Edges2 = [getAlias(Node,NodeSets,Alias) || Node <- Edges],
439
 
  find(Edges2,AllColors,Color,NodeSets,Alias).
 
399
findOkColors(Edges,AllColors,Color,Alias) ->
 
400
  find(Edges, AllColors, Color, Alias).
440
401
 
441
402
%% Find all the colors of the nodes in the list [Node|Nodes] and remove them 
442
403
%% from the set OkColors, when the list is empty, return OkColors.
443
404
 
444
 
find([],OkColors,_Color,_NodeSets,_Alias) ->
445
 
  ordsets:to_list(OkColors); 
446
 
find([Node|Nodes],OkColors,Color,NodeSets,Alias) ->
447
 
  case (hipe_node_sets:member(colored,Node,NodeSets) or 
448
 
        hipe_node_sets:member(precolored,Node,NodeSets)) of
449
 
    true ->  
450
 
      Col = getColor(Node,Color),
451
 
      OkColors1 = ordsets:del_element(Col,OkColors),
452
 
      find(Nodes,OkColors1,Color,NodeSets,Alias);
453
 
    false ->
454
 
      find(Nodes,OkColors,Color,NodeSets,Alias)
455
 
  end.
456
 
 
457
 
%%----------------------------------------------------------------------
458
 
%% Function: initColor
459
 
%%
460
 
%% Description:  Initialize a color mapping with NrOfNodes slots.
461
 
%% Parameters:
462
 
%%   NrOfNodes      -- The maximum number of the nodes that shall be colored.
463
 
%%
464
 
%% Returns:
465
 
%%   Color          -- The brand new color mapping.
466
 
%%----------------------------------------------------------------------
467
 
 
468
 
initColor(NrOfNodes) ->
469
 
  {color, hipe_vectors_wrapper:empty(NrOfNodes,undef)}.
470
 
 
471
 
%%----------------------------------------------------------------------
472
 
%% Function: getColor
473
 
%%
474
 
%% Description:  Get the color of a node in a certain color mapping
475
 
%% Parameters:
476
 
%%   Node          -- The node whose color shall be found
477
 
%%   Color         -- The color mapping we shall find the color in
478
 
%%
479
 
%% Returns:
480
 
%%   Col           -- The color of the node
481
 
%%----------------------------------------------------------------------
482
 
 
483
 
getColor(Node, {color,Color}) when is_integer(Node) ->
484
 
  hipe_vectors_wrapper:get(Color,Node);
485
 
getColor(Node, {color,_Color}) ->
486
 
  ?error_msg("ERROR: ~p: Node is not an integer ~p",
487
 
             [{?MODULE,getColor,2},Node]).
488
 
 
489
 
%%----------------------------------------------------------------------
490
 
%% Function: setColor
491
 
%%
492
 
%% Description: Set the color of a node in a certain color mapping.
493
 
%% Parameters: 
494
 
%%   Node          -- The node to color
495
 
%%   NodeColor     -- The color the node shall have
496
 
%%   Color         -- The colormapping the info shall be stored in
497
 
%% Returns:
498
 
%%   NewColor      -- The new mapping.
499
 
%%----------------------------------------------------------------------
500
 
 
501
 
setColor(Node, NodeColor, {color,Color}) when is_integer(Node) ->
502
 
  {color, hipe_vectors_wrapper:set(Color,Node,NodeColor)};
503
 
setColor(Node, _NodeColor, {color,_Color}) ->
504
 
  ?error_msg("ERROR: ~p: Node is not an integer ~p",
505
 
             [{?MODULE,setColor,3},Node]).
506
 
 
 
405
find([],OkColors,_Color,_Alias) ->
 
406
  OkColors;
 
407
find([Node0|Nodes],OkColors,Color,Alias) ->
 
408
  Node = getAlias(Node0, Alias),
 
409
  case getColor(Node, Color) of
 
410
    [] ->
 
411
      find(Nodes,OkColors,Color,Alias);
 
412
    Col ->
 
413
      OkColors1 = colset_del_element(Col, OkColors),
 
414
      find(Nodes,OkColors1,Color,Alias)
 
415
  end.
 
416
 
 
417
%%%
 
418
%%% ColSet -- ADT for the set of available colours while
 
419
%%% assigning colours.
 
420
%%%
 
421
-ifdef(notdef). % old ordsets-based implementation
 
422
colset_from_list(Allocatable) ->
 
423
  ordsets:from_list(Allocatable).
 
424
 
 
425
colset_del_element(Colour, ColSet) ->
 
426
  ordsets:del_element(Colour, ColSet).
 
427
 
 
428
colset_is_empty(ColSet) ->
 
429
  case ColSet of
 
430
    [] -> true;
 
431
    [_|_] -> false
 
432
  end.
 
433
 
 
434
colset_smallest([Colour|_]) ->
 
435
  Colour.
 
436
-endif.
 
437
 
 
438
-ifdef(notdef). % new gb_sets-based implementation
 
439
colset_from_list(Allocatable) ->
 
440
  gb_sets:from_list(Allocatable).
 
441
 
 
442
colset_del_element(Colour, ColSet) ->
 
443
  %% Must use gb_sets:delete_any/2 since gb_sets:del_element/2
 
444
  %% fails if the element isn't present. Bummer.
 
445
  gb_sets:delete_any(Colour, ColSet).
 
446
 
 
447
colset_is_empty(ColSet) ->
 
448
  gb_sets:is_empty(ColSet).
 
449
 
 
450
colset_smallest(ColSet) ->
 
451
  gb_sets:smallest(ColSet).
 
452
-endif.
 
453
 
 
454
%%-ifdef(notdef). % new bitmask-based implementation
 
455
colset_from_list(Allocatable) ->
 
456
  colset_from_list(Allocatable, 0).
 
457
colset_from_list([], ColSet) ->
 
458
  ColSet;
 
459
colset_from_list([Colour|Allocatable], ColSet) ->
 
460
  colset_from_list(Allocatable, ColSet bor (1 bsl Colour)).
 
461
 
 
462
colset_del_element(Colour, ColSet) ->
 
463
  ColSet band bnot(1 bsl Colour).
 
464
 
 
465
colset_is_empty(0) -> true;
 
466
colset_is_empty(_) -> false.
 
467
 
 
468
colset_smallest(ColSet) ->
 
469
  bitN_log2(ColSet band -ColSet, 0).
 
470
 
 
471
bitN_log2(BitN, ShiftN) ->
 
472
  if BitN > 16#ffff ->
 
473
      bitN_log2(BitN bsr 16, ShiftN + 16);
 
474
     true ->
 
475
      ShiftN + hweight16(BitN - 1)
 
476
  end.
 
477
 
 
478
hweight16(W) ->
 
479
  Res1 = (   W band 16#5555) + ((   W bsr 1) band 16#5555),
 
480
  Res2 = (Res1 band 16#3333) + ((Res1 bsr 2) band 16#3333),
 
481
  Res3 = (Res2 band 16#0F0F) + ((Res2 bsr 4) band 16#0F0F),
 
482
         (Res3 band 16#00FF) + ((Res3 bsr 8) band 16#00FF).
 
483
%%-endif.
 
484
 
 
485
%%%
 
486
%%% Colour ADT providing a partial mapping from nodes to colours.
 
487
%%%
 
488
 
 
489
initColor(NrNodes) ->
 
490
  {colmap, hipe_bifs:array(NrNodes, [])}.
 
491
 
 
492
getColor(Node, {colmap,ColMap}) ->
 
493
  hipe_bifs:array_sub(ColMap, Node).
 
494
 
 
495
setColor(Node, Colour, {colmap,ColMap}) ->
 
496
  hipe_bifs:array_update(ColMap, Node, Colour),  
 
497
  {colmap,ColMap}.
 
498
 
 
499
%%%
 
500
%%% Alias ADT providing a partial mapping from nodes to nodes.
 
501
%%%
 
502
 
 
503
initAlias(NrNodes) ->
 
504
  {alias, hipe_bifs:array(NrNodes, [])}.
 
505
 
 
506
getAlias(Node, {alias,AliasMap}) ->
 
507
  case hipe_bifs:array_sub(AliasMap, Node) of
 
508
    [] ->
 
509
      Node;
 
510
    AliasNode ->
 
511
      getAlias(AliasNode, {alias,AliasMap})
 
512
  end.
 
513
 
 
514
setAlias(Node, AliasNode, {alias,AliasMap}) ->
 
515
  hipe_bifs:array_update(AliasMap, Node, AliasNode),
 
516
  {alias,AliasMap}.
 
517
 
 
518
aliasToList({alias,AliasMap}) ->
 
519
  aliasToList(AliasMap, hipe_bifs:array_length(AliasMap), []).
 
520
aliasToList(AliasMap, I1, Tail) ->
 
521
  I0 = I1 - 1,
 
522
  if I0 >= 0 ->
 
523
      aliasToList(AliasMap, I0, [hipe_bifs:array_sub(AliasMap, I0)|Tail]);
 
524
     true ->
 
525
      Tail
 
526
  end.
507
527
 
508
528
%%----------------------------------------------------------------------
509
529
%% Function:    coalesce
513
533
%%   Moves       -- Current move information
514
534
%%   IG          -- Interference graph
515
535
%%   Worklists   -- Current worklists
516
 
%%   Node_sets   -- Current node information
517
536
%%   Alias       -- Current aliases for temporaries
518
 
%%   SelStk      -- Nodes selected for coloring
519
537
%%   K           -- Number of registers
520
538
%%   
521
539
%% Returns:
522
 
%%   {Moves, IG, Worklists, Node_sets, Alias}
 
540
%%   {Moves, IG, Worklists, Alias}
523
541
%%         (Updated versions of above structures, after coalescing)
524
542
%%----------------------------------------------------------------------
525
543
 
526
 
coalesce(Moves, IG, Worklists, Node_sets, Alias, SelStk, K, Target) ->
527
 
  case hipe_moves:worklist(Moves) of
528
 
    [] ->
529
 
      ?error_msg("ERROR: ~p: No moves in worklist", [?MODULE]);
530
 
    [Move|_Rest] ->
531
 
      {move, Dest, Source} = Move,
532
 
      
 
544
coalesce(Moves, IG, Worklists, Alias, K, Target) ->
 
545
  case hipe_moves:worklist_get_and_remove(Moves) of
 
546
    {[],Moves0} ->
 
547
      %% Moves marked for removal from worklistMoves by FreezeMoves()
 
548
      %% are removed by worklist_get_and_remove(). This case is unlikely,
 
549
      %% but can occur if only stale moves remain in worklistMoves.
 
550
      {Moves0,IG,Worklists,Alias};
 
551
    {Move,Moves0} ->
 
552
      {Dest,Source} = hipe_moves:get_move(Move, Moves0),
533
553
      ?debug_msg("Testing nodes ~p and ~p for coalescing~n",[Dest,Source]),
534
 
      
535
 
      Alias_src = getAlias(Source, Node_sets, Alias),
536
 
      Alias_dst = getAlias(Dest, Node_sets, Alias),
537
 
      {U, V} = case Target:is_precolored(Alias_dst) of
538
 
                 true -> {Alias_dst, Alias_src};
539
 
                 false -> {Alias_src, Alias_dst}
540
 
               end,
541
 
 
542
 
      Moves0 = hipe_moves:remove(worklist, Move, Moves),
543
 
      Degree0 = hipe_ig:degree(IG),
544
 
 
545
 
      %% XXX: (Happi) This is probably not the right fix -- but it
546
 
      %%                       works better... 
547
 
      %% FIX: If an aliased dst already is on the stack it should not colaesced.
548
 
      case on_stack(V,SelStk) orelse 
549
 
           on_stack(U,SelStk) of
550
 
        true -> 
551
 
          Moves1 = 
552
 
            hipe_moves:add(constrained, Move, Moves0),
553
 
          Worklists1 = 
554
 
            add_worklist(add_worklist(Worklists,
555
 
                                      U,
556
 
                                      K,
557
 
                                      Moves1,
558
 
                                      Degree0,
559
 
                                      Target),
560
 
                         V,
561
 
                         K,
562
 
                         Moves1,
563
 
                         Degree0,
564
 
                         Target),
565
 
          {Moves1,
566
 
           IG,
567
 
           Worklists1,
568
 
           Node_sets,
569
 
           Alias};
570
 
        _ -> %% U and V not on the stack.
571
 
          if U == V ->
572
 
              Moves1 = hipe_moves:add(coalesced, Move, Moves0),
573
 
              Worklists0 = add_worklist(Worklists, U, K, Moves1, Degree0, Target),
574
 
              {Moves1,
575
 
               IG,
576
 
               Worklists0,
577
 
               Node_sets,
578
 
               Alias};
579
 
             true ->
580
 
              case Target:is_precolored(V) or 
581
 
                hipe_adj_set:adjacent(U, V, hipe_ig:adj_set(IG)) of 
 
554
      Alias_src = getAlias(Source, Alias),
 
555
      Alias_dst = getAlias(Dest, Alias),
 
556
      {U,V} = case Target:is_precoloured(Alias_dst) of
 
557
                true -> {Alias_dst, Alias_src};
 
558
                false -> {Alias_src, Alias_dst}
 
559
              end,
 
560
      %% When debugging, check that neither V nor U is on the stack.
 
561
      if U =:= V ->
 
562
          Moves1 = Moves0, % drop coalesced move Move
 
563
          Worklists1 = add_worklist(Worklists, U, K, Moves1, IG, Target),
 
564
          {Moves1, IG, Worklists1, Alias};
 
565
         true ->
 
566
          case (Target:is_precoloured(V) orelse
 
567
                hipe_ig:nodes_are_adjacent(U, V, IG)) of 
 
568
            true ->
 
569
              Moves1 = Moves0, % drop constrained move Move
 
570
              Worklists1 = add_worklist(Worklists, U, K, Moves1, IG, Target),
 
571
              Worklists2 = add_worklist(Worklists1, V, K, Moves1, IG, Target),
 
572
              {Moves1, IG, Worklists2, Alias};
 
573
            false ->
 
574
              case (case Target:is_precoloured(U) of
 
575
                      true ->
 
576
                        AdjV = hipe_ig:node_adj_list(V, IG),
 
577
                        all_adjacent_ok(AdjV, U, Worklists, IG, K, Target);
 
578
                      false ->
 
579
                        AdjV = hipe_ig:node_adj_list(V, IG),
 
580
                        AdjU = hipe_ig:node_adj_list(U, IG),
 
581
                        conservative(AdjU, AdjV, U, Worklists, IG, K)
 
582
                    end) of
582
583
                true ->
583
 
                  Moves1 = 
584
 
                    hipe_moves:add(constrained, Move, Moves0),
585
 
                  Worklists1 = 
586
 
                    add_worklist(add_worklist(Worklists,
587
 
                                              U,
588
 
                                              K,
589
 
                                              Moves1,
590
 
                                              Degree0,
591
 
                                              Target),
592
 
                                 V,
593
 
                                 K,
594
 
                                 Moves1,
595
 
                                 Degree0,
596
 
                                 Target),
597
 
                  {Moves1,
598
 
                   IG,
599
 
                   Worklists1,
600
 
                   Node_sets,
601
 
                   Alias};
 
584
                  Moves1 = Moves0, % drop coalesced move Move
 
585
                  {IG1,Worklists1,Moves2,Alias1} =
 
586
                    combine(U, V, IG, Worklists, Moves1, Alias, K, Target),
 
587
                  Worklists2 = add_worklist(Worklists1, U, K, Moves2, IG1, Target),
 
588
                  {Moves2, IG1, Worklists2, Alias1};
602
589
                false ->
603
 
                  Adj_list = hipe_ig:adj_list(IG),
604
 
                  Coalesced_nodes = hipe_node_sets:coalesced(Node_sets),
605
 
                  AdjU = adjacent(U, Adj_list, Coalesced_nodes, SelStk),
606
 
                  AdjV = adjacent(V, Adj_list, Coalesced_nodes, SelStk),
607
 
              
608
 
                  case (Target:is_precolored(U)
609
 
                        and all_adjacent_ok(AdjV, U, IG, K, Target))
610
 
                    or (not(Target:is_precolored(U))
611
 
                        and (conservative(ordsets:union(AdjU, AdjV),
612
 
                                          IG,
613
 
                                          K))) of
614
 
                    true ->
615
 
                      Moves1 = hipe_moves:add(coalesced, Move, Moves0),
616
 
                      {IG0,
617
 
                       Node_sets0,
618
 
                       Worklists1,
619
 
                       Moves2,
620
 
                       Alias0} = combine(U,
621
 
                                         V,
622
 
                                         IG,
623
 
                                         Node_sets,
624
 
                                         Worklists,
625
 
                                         Moves1,
626
 
                                         Alias,
627
 
                                         SelStk,
628
 
                                         K,
629
 
                                         Target),
630
 
                      
631
 
                      Degree1 = hipe_ig:degree(IG0),
632
 
                      Worklists2 = add_worklist(Worklists1,
633
 
                                                U,
634
 
                                                K,
635
 
                                                Moves2,
636
 
                                                Degree1,
637
 
                                                Target),
638
 
                      {Moves2,
639
 
                       IG0,
640
 
                       Worklists2,
641
 
                       Node_sets0,
642
 
                       Alias0};
643
 
                    false ->
644
 
                      {hipe_moves:add(active, Move, Moves0),
645
 
                       IG,
646
 
                       Worklists,
647
 
                       Node_sets,
648
 
                       Alias}
649
 
                  end
 
590
                  Moves1 = hipe_moves:add_active(Move, Moves0),
 
591
                  {Moves1, IG, Worklists, Alias}
650
592
              end
651
593
          end
652
594
      end
663
605
%%   U             -- Node to operate on
664
606
%%   K             -- Number of registers
665
607
%%   Moves         -- Current move information
666
 
%%   Degree        -- Degree information from interference graph
 
608
%%   IG            -- Interference graph
667
609
%%   Target        -- The containing the target-specific functions
668
610
%%   
669
611
%% Returns:
670
612
%%   Worklists (updated)
671
613
%%----------------------------------------------------------------------
672
614
 
673
 
add_worklist(Worklists, U, K, Moves, Degree, Target) ->
674
 
  case (not(Target:is_precolored(U))
675
 
        and not(hipe_moves:move_related(U, Moves))
676
 
        and (hipe_degree:is_simple(U, K, Degree))) of
 
615
add_worklist(Worklists, U, K, Moves, IG, Target) ->
 
616
  case (not(Target:is_precoloured(U))
 
617
        andalso not(hipe_moves:move_related(U, Moves))
 
618
        andalso (hipe_ig:is_trivially_colourable(U, K, IG))) of
677
619
    true ->
678
 
      hipe_reg_worklists:transfer(freeze, simplify, U, Worklists);
 
620
      hipe_reg_worklists:transfer_freeze_simplify(U, Worklists);
679
621
    false ->
680
622
      Worklists
681
623
  end.
689
631
%%   U          -- First node to operate on
690
632
%%   V          -- Second node to operate on
691
633
%%   IG         -- Interference graph
692
 
%%   Node_sets  -- Current node information
693
634
%%   Worklists  -- Current worklists
694
635
%%   Moves      -- Current move information
695
636
%%   Alias      -- Current aliases for temporaries
696
 
%%   SelStk     -- Nodes selected for coloring
697
637
%%   K          -- Number of registers
698
638
%%
699
639
%% Returns:
700
 
%%   {IG, Node_sets, Worklists, Moves, Alias} (updated)
 
640
%%   {IG, Worklists, Moves, Alias} (updated)
701
641
%%----------------------------------------------------------------------
702
642
       
703
 
combine(U, V, IG, Node_sets, Worklists, Moves, Alias, SelStk, K, Target) ->
704
 
  Worklists1 = case hipe_reg_worklists:member(freeze, V, Worklists) of
705
 
                 true -> hipe_reg_worklists:remove(freeze, V, Worklists);
706
 
                 false -> hipe_reg_worklists:remove(spill, V, Worklists)
 
643
combine(U, V, IG, Worklists, Moves, Alias, K, Target) ->
 
644
  Worklists1 = case hipe_reg_worklists:member_freeze(V, Worklists) of
 
645
                 true -> hipe_reg_worklists:remove_freeze(V, Worklists);
 
646
                 false -> hipe_reg_worklists:remove_spill(V, Worklists)
707
647
               end,
708
 
  Node_sets1 = hipe_node_sets:add(coalesced, V, Node_sets),
 
648
  Worklists11 = hipe_reg_worklists:add_coalesced(V, Worklists1),
709
649
  
710
650
  ?debug_msg("Coalescing ~p and ~p to ~p~n",[V,U,U]),
711
651
  
712
652
  Alias1 = setAlias(V, U, Alias),
713
653
  
714
 
  %% NOTE: Here there is an error in the pseudocode for the algorithm!
715
 
  Moves1 = hipe_moves:set_movelist(hipe_vectors_wrapper:set(hipe_moves:movelist(Moves),
716
 
                                                            U,
717
 
                                                            ordsets:union(hipe_moves:node_moves(U, Moves),
718
 
                                                                          hipe_moves:node_moves(V, Moves))),
719
 
                                   Moves),
720
 
  
721
 
  Adj_list = hipe_ig:adj_list(IG),
722
 
  Adjacent =
723
 
    adjacent(V, Adj_list, hipe_node_sets:coalesced(Node_sets1), SelStk),
724
 
  
725
 
  {IG1, Worklists2, Moves2} =
726
 
    combine_edges(Adjacent, U, IG, Node_sets1, Worklists1,
727
 
                  Moves1, SelStk, K, Target),
 
654
  %% Typo in published algorithm: s/nodeMoves/moveList/g to fix.
 
655
  %% XXX: moveList[u] \union moveList[v] OR NodeMoves(u) \union NodeMoves(v) ???
 
656
  %% XXX: NodeMoves() is correct, but unnecessarily strict. The ordsets:union
 
657
  %% constrains NodeMoves() to return an ordset.
 
658
  Moves1 = hipe_moves:update_movelist(U,
 
659
                                      ordsets:union(hipe_moves:node_moves(U, Moves),
 
660
                                                    hipe_moves:node_moves(V, Moves)),
 
661
                                      Moves),
 
662
  %% Missing in published algorithm. From Tiger book Errata.
 
663
  Moves2 = enable_moves_active_to_worklist(hipe_moves:node_movelist(V, Moves1), Moves1),
 
664
  AdjV = hipe_ig:node_adj_list(V, IG),
 
665
  
 
666
  {IG1, Worklists2, Moves3} =
 
667
    combine_edges(AdjV, U, IG, Worklists11, Moves2, K, Target),
728
668
 
729
 
  New_worklists = case (not(hipe_degree:is_simple(U, K, hipe_ig:degree(IG1)))
730
 
                        and hipe_reg_worklists:member(freeze, U, Worklists2)) of
731
 
                    true -> hipe_reg_worklists:transfer(freeze, spill, U, 
732
 
                                                        Worklists2);
 
669
  New_worklists = case (not(hipe_ig:is_trivially_colourable(U, K, IG1))
 
670
                        andalso hipe_reg_worklists:member_freeze(U, Worklists2)) of
 
671
                    true -> hipe_reg_worklists:transfer_freeze_spill(U, Worklists2);
733
672
                    false -> Worklists2
734
673
                  end,
735
 
  {IG1, Node_sets1, New_worklists, Moves2, Alias1}.
 
674
  {IG1, New_worklists, Moves3, Alias1}.
736
675
 
737
676
%%----------------------------------------------------------------------
738
677
%% Function:    combine_edges
746
685
%%   [T|Ts]      -- List of nodes to make edges to
747
686
%%   U           -- Node to make edges from
748
687
%%   IG          -- Interference graph
749
 
%%   Node_sets   -- Current node information
750
688
%%   Worklists   -- Current worklists
751
689
%%   Moves       -- Current move information
752
 
%%   SelStk      -- Stack of nodes selected for coloring
753
690
%%   K           -- Number of registers
754
691
%%
755
692
%% Returns:
756
693
%%   {IG, Worklists, Moves} (updated)
757
694
%%----------------------------------------------------------------------
758
695
 
759
 
combine_edges([], _U, IG, _Node_sets, Worklists, Moves, _SelStk, _K, _Target) ->
 
696
combine_edges([], _U, IG, Worklists, Moves, _K, _Target) ->
760
697
  {IG, Worklists, Moves};
761
 
combine_edges([T|Ts], U, IG, Node_sets, Worklists, Moves, SelStk, K, Target) ->
762
 
  IG1 = hipe_ig:add_edge(T, U, IG, Target),
763
 
  {IG2, Worklists1, Moves1} =
764
 
    decrement_degree([T], IG1, Node_sets, Worklists, Moves, SelStk, K),
765
 
  combine_edges(Ts, U, IG2, Node_sets, Worklists1, Moves1, SelStk, K, Target).
 
698
combine_edges([T|Ts], U, IG, Worklists, Moves, K, Target) ->
 
699
  case hipe_reg_worklists:member_stack_or_coalesced(T, Worklists) of
 
700
    true -> combine_edges(Ts, U, IG, Worklists, Moves, K, Target);
 
701
    _ ->
 
702
      %% XXX: The issue below occurs because the T->V edge isn't removed.
 
703
      %% This causes adjList[T] to contain stale entries, to possibly grow
 
704
      %% (if T isn't already adjacent to U), and degree[T] to possibly
 
705
      %% increase (again, if T isn't already adjacent to U).
 
706
      %% The decrement_degree() call repairs degree[T] but not adjList[T].
 
707
      %% It would be better to physically replace T->V with T->U, and only
 
708
      %% decrement_degree(T) if T->U already existed.
 
709
      %%
 
710
      %% add_edge() may change a low-degree move-related node to be of
 
711
      %% significant degree. In this case the node belongs in the spill
 
712
      %% worklist, and that's where decrement_degree() expects to find it.
 
713
      %% This issue is not covered in the published algorithm.
 
714
      OldDegree = hipe_ig:get_node_degree(T, IG),
 
715
      IG1 = hipe_ig:add_edge(T, U, IG, Target),
 
716
      NewDegree = hipe_ig:get_node_degree(T, IG1),
 
717
      Worklists0 =
 
718
        if NewDegree =:= K, OldDegree =:= K-1 ->
 
719
            %% io:format("~w:combine_edges(): repairing worklist membership for node ~w\n", [?MODULE,T]),
 
720
            %% The node T must be on the freeze worklist:
 
721
            %% 1. Since we're coalescing, the simplify worklist must have been
 
722
            %%    empty when combine_edges() started.
 
723
            %% 2. decrement_degree() may put the node T back on the simplify
 
724
            %%    worklist, but that occurs after the worklists repair step.
 
725
            %% 3. There are no duplicates among the edges.
 
726
            Worklists00 = hipe_reg_worklists:remove_freeze(T, Worklists),
 
727
            hipe_reg_worklists:add_spill(T, Worklists00);
 
728
           true ->
 
729
            Worklists
 
730
        end,
 
731
      {IG2, Worklists1, Moves1} =
 
732
        decrement_degree([T], IG1, Worklists0, Moves, K),
 
733
      combine_edges(Ts, U, IG2, Worklists1, Moves1, K, Target)
 
734
  end.
766
735
 
767
736
%%----------------------------------------------------------------------
768
737
%% Function:    ok
781
750
%%----------------------------------------------------------------------
782
751
 
783
752
ok(T, R, IG, K, Target) ->
784
 
    ((hipe_degree:is_simple(T, K, hipe_ig:degree(IG)))
785
 
     or Target:is_precolored(T)
786
 
     or hipe_adj_set:adjacent(T, R, hipe_ig:adj_set(IG))).
 
753
  ((hipe_ig:is_trivially_colourable(T, K, IG))
 
754
   orelse Target:is_precoloured(T)
 
755
   orelse hipe_ig:nodes_are_adjacent(T, R, IG)).
787
756
 
788
757
%%----------------------------------------------------------------------
789
758
%% Function:    all_ok
801
770
%%   true iff coalescing is OK for all nodes in the list
802
771
%%----------------------------------------------------------------------
803
772
 
804
 
all_adjacent_ok([], _U, _IG, _K, _Target) -> false;
805
 
all_adjacent_ok([T|Ts], U, IG, K, Target) ->
806
 
    ok(T, U, IG, K, Target) andalso all_adjacent_ok(Ts, U, IG, K, Target).
 
773
all_adjacent_ok([], _U, _Worklists, _IG, _K, _Target) -> true;
 
774
all_adjacent_ok([T|Ts], U, Worklists, IG, K, Target) ->
 
775
  case hipe_reg_worklists:member_stack_or_coalesced(T, Worklists) of
 
776
    true -> all_adjacent_ok(Ts, U, Worklists, IG, K, Target);
 
777
    _ ->
 
778
      %% 'andalso' does not preserve tail-recursion
 
779
      case ok(T, U, IG, K, Target) of
 
780
        true -> all_adjacent_ok(Ts, U, Worklists, IG, K, Target);
 
781
        false -> false
 
782
      end
 
783
  end.
807
784
 
808
785
%%----------------------------------------------------------------------
809
786
%% Function:    conservative
820
797
%%   true iff coalescing is safe
821
798
%%----------------------------------------------------------------------
822
799
 
823
 
conservative(Nodes, IG, K) ->
824
 
    conservative_count(Nodes, hipe_ig:degree(IG), K, 0) < K.
 
800
conservative(AdjU, AdjV, U, Worklists, IG, K) ->
 
801
  conservative_countU(AdjU, AdjV, U, Worklists, IG, K, 0).
825
802
 
826
803
%%----------------------------------------------------------------------
827
804
%% Function:    conservative_count
830
807
%%
831
808
%% Parameters:
832
809
%%   Nodes         -- (Remaining) adjacent nodes
833
 
%%   Degree        -- Degree information from interference graph
 
810
%%   IG            -- Interference graph
834
811
%%   K             -- Number of registers
835
812
%%   Cnt           -- Accumulator for counting
836
813
%%   
838
815
%%   Final value of accumulator
839
816
%%----------------------------------------------------------------------
840
817
 
841
 
conservative_count([], _Degree, _K, Cnt) -> Cnt;
842
 
conservative_count([Node|Nodes], Degree, K, Cnt) ->
843
 
  case hipe_degree:is_simple(Node, K, Degree) of
844
 
    true -> conservative_count(Nodes, Degree, K, Cnt);
845
 
    false -> conservative_count(Nodes, Degree, K, Cnt+1)
 
818
conservative_countU([], AdjV, U, Worklists, IG, K, Cnt) ->
 
819
  conservative_countV(AdjV, U, Worklists, IG, K, Cnt);
 
820
conservative_countU([Node|AdjU], AdjV, U, Worklists, IG, K, Cnt) ->
 
821
  case hipe_reg_worklists:member_stack_or_coalesced(Node, Worklists) of
 
822
    true -> conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt);
 
823
    _ ->
 
824
      case hipe_ig:is_trivially_colourable(Node, K, IG) of
 
825
        true -> conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt);
 
826
        _ ->
 
827
          Cnt1 = Cnt + 1,
 
828
          if Cnt1 < K -> conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt1);
 
829
             true -> false
 
830
          end
 
831
      end
846
832
  end.
847
833
 
 
834
conservative_countV([], _U, _Worklists, _IG, _K, _Cnt) -> true;
 
835
conservative_countV([Node|AdjV], U, Worklists, IG, K, Cnt) ->
 
836
  case hipe_reg_worklists:member_stack_or_coalesced(Node, Worklists) of
 
837
    true -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt);
 
838
    _ ->
 
839
      case hipe_ig:nodes_are_adjacent(Node, U, IG) of
 
840
        true -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt);
 
841
        _ ->
 
842
          case hipe_ig:is_trivially_colourable(Node, K, IG) of
 
843
            true -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt);
 
844
            _ ->
 
845
              Cnt1 = Cnt + 1,
 
846
              if Cnt1 < K -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt1);
 
847
                 true -> false
 
848
              end
 
849
          end
 
850
      end
 
851
  end.
848
852
 
849
853
%%---------------------------------------------------------------------
850
854
%% Function:    selectSpill
855
859
%%   Moves          -- A datatype containing the move sets
856
860
%%   IG             -- The interference graph
857
861
%%   K              -- The number of available registers
858
 
%%   NodeSets       -- A datatype containing the node sets
859
862
%%   Alias          -- The alias mapping
860
863
%%   SpillLimit     -- Try not to spill any nodes above the spill limit
861
864
%%
864
867
%%   Moves          -- The updated moves
865
868
%%---------------------------------------------------------------------
866
869
 
867
 
selectSpill(WorkLists, Moves, IG, K, NodeSets, Alias, SpillLimit) ->
 
870
selectSpill(WorkLists, Moves, IG, K, Alias, SpillLimit) ->
868
871
  [CAR|CDR] = hipe_reg_worklists:spill(WorkLists),
869
872
  
870
873
  SpillCost = getCost(CAR, IG,SpillLimit),
871
874
  M = findCheapest(CDR,IG,SpillCost,CAR, SpillLimit),
872
875
  
873
 
  WorkLists1 = hipe_reg_worklists:remove(spill,M,WorkLists),
874
 
  WorkLists2 = hipe_reg_worklists:add(simplify,M,WorkLists1),
875
 
  freezeMoves(M, K, WorkLists2, Moves, hipe_ig:degree(IG), NodeSets, Alias).
 
876
  WorkLists1 = hipe_reg_worklists:remove_spill(M, WorkLists),
 
877
  %% The published algorithm adds M to the simplify worklist
 
878
  %% before the freezeMoves() call. That breaks the worklist
 
879
  %% invariants, which is why the order is switched here.
 
880
  {WorkLists2,Moves1} = freezeMoves(M, K, WorkLists1, Moves, IG, Alias),
 
881
  WorkLists3 = hipe_reg_worklists:add_simplify(M, WorkLists2),
 
882
  {WorkLists3,Moves1}.
876
883
 
877
884
%% Find the node that is cheapest to spill
878
885
 
893
900
getCost(Node, IG, SpillLimit) ->
894
901
  case Node > SpillLimit of
895
902
    true ->  inf;
896
 
    false -> hipe_spillcost:spill_cost(Node, IG)
 
903
    false -> hipe_ig:node_spill_cost(Node, IG)
897
904
  end.
898
905
 
899
 
 
900
906
%%----------------------------------------------------------------------
901
907
%% Function:    freeze
902
908
%%
909
915
%%   K              -- The number of available registers
910
916
%%   WorkLists      -- A datatype containing the different worklists
911
917
%%   Moves          -- A datatype containing the different movelists
912
 
%%   Degrees        -- A Datatype containing the degrees of the nodes
913
 
%%   NodeSets       -- A Datatype containing the different NodeSets
 
918
%%   IG             -- Interference graph
914
919
%%   Alias          -- An alias mapping, shows the alias of all coalesced 
915
920
%%                      nodes  
916
921
%%
919
924
%%   Moves          -- The updated movelists
920
925
%%----------------------------------------------------------------------
921
926
 
922
 
freeze(K,WorkLists,Moves,Degrees,NodeSets,Alias) ->
 
927
freeze(K,WorkLists,Moves,IG,Alias) ->
923
928
  [U|_] = hipe_reg_worklists:freeze(WorkLists),         % Smarter routine?
924
929
  ?debug_msg("freezing node ~p~n",[U]),
925
 
  WorkLists0 = hipe_reg_worklists:transfer(freeze, simplify, U, WorkLists),
926
 
  freezeMoves(U,K,WorkLists0,Moves,Degrees,NodeSets,Alias).
 
930
  WorkLists0 = hipe_reg_worklists:remove_freeze(U, WorkLists),
 
931
  %% The published algorithm adds U to the simplify worklist
 
932
  %% before the freezeMoves() call. That breaks the worklist
 
933
  %% invariants, which is why the order is switched here.
 
934
  {WorkLists1,Moves1} = freezeMoves(U,K,WorkLists0,Moves,IG,Alias),
 
935
  WorkLists2 = hipe_reg_worklists:add_simplify(U, WorkLists1),
 
936
  {WorkLists2,Moves1}.
927
937
 
928
938
%%----------------------------------------------------------------------
929
939
%% Function:    freezeMoves
936
946
%%   K              -- The number of available registers
937
947
%%   WorkLists      -- A datatype containing the different worklists
938
948
%%   Moves          -- A datatype containing the different movelists
939
 
%%   Degrees        -- A Datatype containing the degrees of the nodes
940
 
%%   NodeSets       -- A Datatype containing the different NodeSets
 
949
%%   IG             -- Interference graph
941
950
%%   Alias          -- An alias mapping, shows the alias of all coalesced 
942
951
%%                     nodes  
943
952
%%
946
955
%%   Moves          -- The updated movelists
947
956
%%----------------------------------------------------------------------
948
957
 
949
 
freezeMoves(U,K,WorkLists,Moves,Degrees,NodeSets,Alias) ->
 
958
freezeMoves(U,K,WorkLists,Moves,IG,Alias) ->
950
959
  Nodes = hipe_moves:node_moves(U, Moves),
951
 
  freezeEm(U,Nodes,K,WorkLists,Moves,Degrees,NodeSets,Alias).
 
960
  freezeEm(U,Nodes,K,WorkLists,Moves,IG,Alias).
952
961
 
953
962
%% Find what the other value in a copy instruction is, return false if 
954
963
%% the instruction isn't a move with the first argument in it.
955
964
 
956
 
moves (U,{move,U,V}) ->
957
 
  V;
958
 
moves(U,{move,V,U}) ->
959
 
  V;
960
 
moves(_U,_Node) ->
961
 
  false.
 
965
moves(U, Move, Alias, Moves) ->
 
966
  {X,Y} = hipe_moves:get_move(Move, Moves),
 
967
  %% The old code (which followed the published algorithm) did
 
968
  %% not follow aliases before looking for "the other" node.
 
969
  %% This caused moves() to skip some moves, making some nodes
 
970
  %% still move-related after freezeMoves(). These move-related
 
971
  %% nodes were then added to the simplify worklist (by freeze()
 
972
  %% or selectSpill()), breaking the worklist invariants. Nodes
 
973
  %% already simplified appeared in coalesce(), were re-added to
 
974
  %% the simplify worklist by add_worklist(), simplified again,
 
975
  %% and coloured multiple times by assignColors(). Ouch!
 
976
  X1 = getAlias(X, Alias),
 
977
  Y1 = getAlias(Y, Alias),
 
978
  if U =:= X1 -> Y1;
 
979
     U =:= Y1 -> X1;
 
980
     true -> exit({?MODULE,moves}) % XXX: shouldn't happen
 
981
  end.
962
982
 
963
 
freezeEm(_U,[],_K,WorkLists,Moves,_Degrees,_NodeSets,_Alias) -> 
 
983
freezeEm(_U,[],_K,WorkLists,Moves,_IG,_Alias) -> 
964
984
  {WorkLists,Moves};
965
 
freezeEm(U,[M|Ms],K,WorkLists,Moves,Degrees,NodeSets,Alias) ->
966
 
  case moves(U,M) of
967
 
    false ->
968
 
      freezeEm(U,Ms,K,WorkLists,Moves,Degrees,NodeSets,Alias);
969
 
    V ->
970
 
      {WorkLists2,Moves2} = freezeEm2(U,V,M,K,WorkLists,
971
 
                                      Moves,Degrees,NodeSets,Alias),
972
 
      freezeEm(U,Ms,K,WorkLists2,Moves2,Degrees,NodeSets,Alias)
973
 
  end.
 
985
freezeEm(U,[M|Ms],K,WorkLists,Moves,IG,Alias) ->
 
986
  V = moves(U, M, Alias, Moves),
 
987
  {WorkLists2,Moves2} = freezeEm2(U,V,M,K,WorkLists,
 
988
                                  Moves,IG,Alias),
 
989
  freezeEm(U,Ms,K,WorkLists2,Moves2,IG,Alias).
974
990
 
975
 
freezeEm2(U,V,M,K,WorkLists,Moves,Degrees,NodeSets,Alias) ->
976
 
  case hipe_moves:member(active, M, Moves) of
 
991
freezeEm2(U,V,M,K,WorkLists,Moves,IG,Alias) ->
 
992
  case hipe_moves:member_active(M, Moves) of
977
993
    true ->
978
 
      Moves1 = hipe_moves:remove(active, M, Moves),
979
 
      freezeEm3(U,V,M,K,WorkLists,Moves1,Degrees,NodeSets,Alias);       
 
994
      Moves1 = hipe_moves:remove_active(M, Moves),
 
995
      freezeEm3(U,V,M,K,WorkLists,Moves1,IG,Alias);     
980
996
    false ->
981
 
      Moves1 = hipe_moves:remove(worklist, M, Moves),
982
 
      freezeEm3(U,V,M,K,WorkLists,Moves1,Degrees,NodeSets,Alias)
 
997
      Moves1 = hipe_moves:remove_worklist(M, Moves),
 
998
      freezeEm3(U,V,M,K,WorkLists,Moves1,IG,Alias)
983
999
  end.
984
1000
 
985
 
freezeEm3(_U,V,M,K,WorkLists,Moves,Degrees,NodeSets,Alias) ->
986
 
  Moves1 = hipe_moves:add(frozen,M,Moves),
987
 
  V1 = getAlias(V,NodeSets,Alias),
988
 
  %% We know that hipe_moves:node_moves/2 returns an ordset (a list).
989
 
  case (hipe_moves:node_moves(V1,Moves1) == []) and 
990
 
    hipe_degree:is_simple(V1,K,Degrees) of
 
1001
freezeEm3(_U,V,_M,K,WorkLists,Moves,IG,_Alias) ->
 
1002
  Moves1 = Moves, % drop frozen move M
 
1003
  V1 = V, % getAlias(V,Alias),
 
1004
  %% "not MoveRelated(v)" is cheaper than "NodeMoves(v) = {}"
 
1005
  case ((not hipe_moves:move_related(V1,Moves1)) andalso
 
1006
        hipe_ig:is_trivially_colourable(V1,K,IG)) of
991
1007
    true ->
992
1008
      ?debug_msg("freezing move to ~p~n", [V]),
993
 
      Worklists1 = hipe_reg_worklists:transfer(freeze, simplify, V1, WorkLists),
994
 
      {Worklists1, Moves1};
 
1009
      Worklists1 = hipe_reg_worklists:transfer_freeze_simplify(V1, WorkLists),
 
1010
      {Worklists1,Moves1};
995
1011
    false ->
996
1012
      {WorkLists,Moves1}
997
1013
  end.
998
 
 
999
 
 
1000
 
%%----------------------------------------------------------------------
1001
 
%% Function:     initAlias
1002
 
%%
1003
 
%% Description:  Initialize an alias mapping with NrOfNodes slots.
1004
 
%% Parameters:
1005
 
%%   NrOfNodes      -- The number of registers that might need an alias.
1006
 
%%
1007
 
%% Returns:
1008
 
%%  Alias           -- The initial alias mapping.
1009
 
%%----------------------------------------------------------------------
1010
 
 
1011
 
initAlias(NrOfNodes) ->
1012
 
  {alias, hipe_vectors_wrapper:init(NrOfNodes)}.
1013
 
 
1014
 
%%----------------------------------------------------------------------
1015
 
%% Function getAlias
1016
 
%%
1017
 
%% Description: Get the alias of a node.
1018
 
%% Parameters:
1019
 
%%   Node           -- The node, whose alias shall be found 
1020
 
%%   NodeSets       -- A structure containing the different NodeSets
1021
 
%%   Alias          -- The alias mapping
1022
 
%%
1023
 
%% Returns:
1024
 
%%   Name           -- The requested alias
1025
 
%%----------------------------------------------------------------------
1026
 
 
1027
 
getAlias(Node, NodeSets, {alias,Alias}) when is_integer(Node) ->
1028
 
  case hipe_node_sets:member(coalesced,Node,NodeSets) of 
1029
 
    true ->
1030
 
      getAlias(hipe_vectors_wrapper:get(Alias,Node),NodeSets,{alias, Alias});
1031
 
    false ->
1032
 
      Node
1033
 
  end;
1034
 
getAlias(Node, _NodeSets, {alias,_Alias}) ->
1035
 
  ?error_msg("ERROR: ~p: Node not integer: ~p", [{?MODULE,getAlias,3},Node]).
1036
 
 
1037
 
%%----------------------------------------------------------------------
1038
 
%% Function: setAlias
1039
 
%%
1040
 
%% Description: Set the alias of a node.
1041
 
%% 
1042
 
%% Parameters:
1043
 
%%   Node           -- The node that shall get an alias
1044
 
%%   ToNode         -- The new name for the node
1045
 
%%   Alias          -- The alias mapping the info shall be stored in
1046
 
%%
1047
 
%% Returns:
1048
 
%%   Alias          -- The new alias mapping
1049
 
%%----------------------------------------------------------------------
1050
 
 
1051
 
setAlias(Node, ToNode, {alias,Alias})
1052
 
when is_integer(Node), is_integer(ToNode) ->
1053
 
  {alias, hipe_vectors_wrapper:set(Alias,Node,ToNode)};
1054
 
setAlias(Node, ToNode, {alias,_Alias}) ->
1055
 
  ?error_msg("ERROR: ~p: Node not integer: ~p or ~p",
1056
 
             [{?MODULE,setAlias,3},Node,ToNode]).
1057
 
 
1058
 
 
1059
 
%%----------------------------------------------------------------------
1060
 
%% SelStack
1061
 
%%
1062
 
%%
1063
 
stack_new() -> {[],gb_sets:new()}.
1064
 
 
1065
 
push(Node,Adj,{Stack,OnStack}) ->
1066
 
  {[{Node,Adj}|Stack], gb_sets:add_element(Node,OnStack)}.
1067
 
 
1068
 
remove_stacked(List,{_Stack,OnStack}) ->
1069
 
  [Node || Node <- List,
1070
 
           not gb_sets:is_member(Node,OnStack)].
1071
 
           
1072
 
on_stack(Node, {_Stack,OnStack}) ->
1073
 
  gb_sets:is_member(Node,OnStack).
1074
 
 
1075
 
stack({Stack,_}) -> Stack.