1%% -*- erlang-indent-level: 2 -*-
2%%
3%% Licensed under the Apache License, Version 2.0 (the "License");
4%% you may not use this file except in compliance with the License.
5%% You may obtain a copy of the License at
6%%
7%%     http://www.apache.org/licenses/LICENSE-2.0
8%%
9%% Unless required by applicable law or agreed to in writing, software
10%% distributed under the License is distributed on an "AS IS" BASIS,
11%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
12%% See the License for the specific language governing permissions and
13%% limitations under the License.
14%%
15%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
16%%@doc
17%%		  GRAPH COLORING REGISTER ALLOCATOR
18%%
19%% A simple graph coloring register allocator:
20%%
21%% - build interference graph + estimate spill costs
22%% - simplify graph (push on stack + spill)
23%% - select colors
24%%
25%% Emits a coloring: a list of {TempName,Location}
26%%  where Location is {reg,N} or {spill,M}
27%%   and {reg,N} denotes some register N
28%%   and {spill,M} denotes the Mth spilled node
29%% You have to figure out how to rewrite the code yourself.
30%%
31%% This version uses vectors rather than hash tables, and uses
32%% faster algorithms since all vars are known at the start.
33%% The result should be considerably quicker than earlier versions.
34%%
35%% Deficiencies:
36%% - no renaming                 (to reduce unnecessary register pressure)
37%% - spill costs are naive       (should use better; e.g., exec.estimates)
38%% - no biased coloring          (which coalesces moves)
39%% - no live range splitting     (possibly not critical)
40%%
41%% *** NOTE ***
42%% Uses apply for target specific functions, takes the module name as
43%% argument. This target specific module should implement all target
44%% specific functions, see the end of the file.
45%%
46
47-module(hipe_graph_coloring_regalloc).
48-export([regalloc/7]).
49
50%%-ifndef(DO_ASSERT).
51%%-define(DO_ASSERT, true).
52%%-endif.
53
54%%-ifndef(DEBUG).
55%%-define(DEBUG,0).
56%%-endif.
57-include("../main/hipe.hrl").
58
59%% Define these as 'ok' or 'report(X,Y)' depending on how much output you want.
60-define(report0(X,Y), ?IF_DEBUG_LEVEL(0,?msg(X, Y),ok)).
61-define(report(X,Y),  ?IF_DEBUG_LEVEL(1,?msg(X, Y),ok)).
62-define(report2(X,Y), ?IF_DEBUG_LEVEL(2,?msg(X, Y),ok)).
63-define(report3(X,Y), ?IF_DEBUG_LEVEL(3,?msg(X, Y),ok)).
64
65%% Given CFG and number of colors K, produce a coloring list
66%% of items {reg,N} (0 =< N =< K) and {spill,M}, where M is
67%% an index denoting 'a location'.
68%% (You might use it as a stack index, perhaps.)
69%%
70%% You can in principle delete check_coloring/2; it merely checks
71%% that the coloring agrees with the interference graph (that is, that
72%% no neighbors have the same register or spill location).
73
74%% @spec regalloc(#cfg{}, liveness(), non_neg_fixnum(), non_neg_fixnum(),
75%%                module(), tgt_ctx(), list()) -> {, non_neg_fixnum()}
76
77regalloc(CFG, Live, SpillIndex, SpillLimit, TargetMod, TargetContext,
78	 _Options) ->
79  Target = {TargetMod, TargetContext},
80  PhysRegs = allocatable(Target),
81  ?report2("building IG~n", []),
82  {IG, Spill} = build_ig(CFG, Live, Target),
83
84  %% check_ig(IG),
85  ?report3("graph: ~p~nphysical regs: ~p~n", [list_ig(IG), PhysRegs]),
86
87  %% These nodes *can't* be allocated to registers.
88  NotAllocatable = non_alloc(CFG, Target),
89  %% i.e. Arguments on x86
90  ?report2("Nonalloc ~w~n", [NotAllocatable]),
91
92  {Cols, NewSpillIndex} =
93    color(IG, Spill,
94	  ordsets:from_list(PhysRegs),
95	  SpillIndex,
96	  SpillLimit,
97	  number_of_temporaries(CFG, Target),
98	  Target, NotAllocatable),
99  Coloring = [{X, {reg, X}} || X <- NotAllocatable] ++ Cols,
100  ?ASSERT(check_coloring(Coloring, IG, Target)),
101
102  {Coloring, NewSpillIndex}.
103
104
105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
106%%
107%% *** BUILD THE INTERFERENCE GRAPH ***
108%%
109%% Returns {Interference_graph, Spill_cost_dictionary}
110%%
111
112build_ig(CFG, Live, Target) ->
113  NumN = number_of_temporaries(CFG, Target),  % poss. N-1?
114  {IG, Spill} = build_ig_bbs(labels(CFG, Target),
115			     CFG,
116			     Live,
117			     empty_ig(NumN),
118			     empty_spill(NumN),
119			     Target),
120  {normalize_ig(IG), Spill}.
121
122build_ig_bbs([], _CFG, _Live, IG, Spill, _Target) ->
123  {IG, Spill};
124build_ig_bbs([L|Ls], CFG, Live, IG, Spill, Target) ->
125  Xs = bb(CFG, L, Target),
126  {_, NewIG, NewSpill} =
127    build_ig_bb(Xs, liveout(Live, L, Target), IG, Spill, Target),
128  build_ig_bbs(Ls, CFG, Live, NewIG, NewSpill, Target).
129
130build_ig_bb([], LiveOut, IG, Spill, _Target) ->
131  {LiveOut, IG, Spill};
132build_ig_bb([X|Xs], LiveOut, IG, Spill, Target) ->
133  {Live,NewIG,NewSpill} = build_ig_bb(Xs, LiveOut, IG, Spill, Target),
134  build_ig_instr(X, Live, NewIG, NewSpill, Target).
135
136%% Note: We could add move-related arcs here as well.
137%%
138%% Note: Ideally, we would like to add all registers to the IG
139%% at once rather than doing 'add_nodes' for each instruction.
140%% (This is costly, since nodes that already are present are checked!)
141
142build_ig_instr(X, Live, IG, Spill, Target) ->
143  {Def, Use} = def_use(X, Target),
144  ?report3("Live ~w\n~w : Def: ~w Use ~w\n", [Live, X, Def,Use]),
145  DefList = ordsets:to_list(Def),
146  NewSpill = inc_spill_costs(DefList,
147			     inc_spill_costs(ordsets:to_list(Use), Spill)),
148  NewIG = interference_arcs(DefList, ordsets:to_list(Live), IG),
149  NewLive = ordsets:union(Use, ordsets:subtract(Live, Def)),
150  {NewLive, NewIG, NewSpill}.
151
152%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
153
154interference_arcs([], _Live, IG) ->
155  IG;
156interference_arcs([X|Xs], Live, IG) ->
157  interference_arcs(Xs, Live, i_arcs(X, Live, IG)).
158
159i_arcs(_X, [], IG) ->
160  IG;
161i_arcs(X, [Y|Ys], IG) ->
162  i_arcs(X, Ys, add_edge(X,Y, IG)).
163
164%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
165
166inc_spill_costs([], Spill) -> Spill;
167inc_spill_costs([X|Xs], Spill) ->
168  inc_spill_costs(Xs, inc_spill_cost(X, Spill)).
169
170inc_spill_cost(X, Spill) ->
171  set_spill_cost(X, get_spill_cost(X, Spill)+1, Spill).
172
173get_spill_cost(X, Spill) ->
174  spill_cost_lookup(X, Spill).
175
176set_spill_cost(X, N, Spill) ->
177  spill_cost_update(X, N, Spill).
178
179%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
180
181
182%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
183%%
184%% *** COLORING ***
185%%
186%% Coloring is done straightforwardly:
187%% - find the low-degree nodes, put them in low
188%% - while low non-empty:
189%%   * remove x from low
190%%   * push x on stack
191%%   * decrement degree of neighbors of x
192%%   * for each neighbor y of low degree, put y on low
193%% - when low empty:
194%%   - if graph empty, return stack
195%%   - otherwise
196%%     * select a node z to spill
197%%     * push z on stack
198%%     * decrement degree of neighbors of z
199%%     * add low-degree neighbors of z to low
200%%     * restart the while-loop above
201
202color(IG, Spill, PhysRegs, SpillIx, SpillLimit, NumNodes, Target,
203      NotAllocatable) ->
204  ?report("simplification of IG~n", []),
205  K = ordsets:size(PhysRegs),
206  Nodes = list_ig(IG),
207
208  Low = low_degree_nodes(Nodes, K, NotAllocatable),
209
210  %% Any nodes above the spillimit must be colored first...
211  MustNotSpill =
212    if NumNodes > SpillLimit ->
213	sort_on_degree(lists:seq(SpillLimit,NumNodes-1) -- Low,IG);
214       true -> []
215    end,
216
217  ?report(" starting with low degree nodes ~p~n",[Low]),
218  EmptyStk = [],
219  Precolored = all_precoloured(Target),
220  {Stk, NewSpillIx} =
221    simplify(Low, NumNodes, Precolored,
222	     IG, Spill, K, SpillIx, EmptyStk,
223	     SpillLimit, Target, NotAllocatable, MustNotSpill),
224  ?report("selecting colors~n",[]),
225  {select(Stk, Precolored, IG, K, PhysRegs, NumNodes, Target),
226   NewSpillIx}.
227
228sort_on_degree(Nodes, IG) ->
229  [ Node3 || {_,Node3} <-
230	       lists:sort([{degree(Info),Node2} ||
231			    {Info,Node2} <- [{hipe_vectors:get(IG, Node),
232					      Node} || Node <-
233							 Nodes]])].
234
235%%%%%%%%%%%%%%%%%%%%
236%%
237%% Simplification: push all easily colored nodes on a stack;
238%%  when the list of easy nodes becomes empty, see if graph is
239%%  empty as well. If it is not, spill a node and continue.
240%%  If it is empty, return the stack.
241%%
242%% Notes:
243%% - We keep the set of visited nodes around for spill purposes
244%%   (visited nodes are not considered for spilling)
245%%
246%% - At present, nodes can be pushed onto the stack even if they
247%%   already are on the stack. This can be fixed by another 'Vis'
248%%   dictionary that keeps track of what is on the stack.
249%%   Currently, we just skip already colored nodes.
250%%
251%% - Arguments:
252%%   Low: low-degree nodes (ready to color)
253%%   NumNodes: number of remaining nodes in graph
254%%   IG: interference graph
255%%   Spill: spill costs of nodes
256%%   K: number of colors
257%%   Ix: next spill index
258%%   Stk: stack of already simplified nodes
259%%
260%% Physical registers are marked as 'visited' prior to simplify.
261%% This has the following effect:
262%% - they are not considered for spilling
263%% - they are not pushed on the stack
264%% - since we do NOT decrement degrees of surrounding vars, the
265%%   non-physreg variables must still take them into account.
266
267simplify(Low, NumNodes, PreC, IG, Spill, K, Ix, Stk, SpillLimit,
268	 Target, NotAllocatable, MustNotSpill) ->
269  Vis = visit_all(PreC, none_visited(NumNodes)),
270  Vis1 = visit_all(NotAllocatable, Vis),
271  ActualNumNodes = (NumNodes-length(PreC))-length(NotAllocatable),
272  %% Make sure that the registers that must not be spilled
273  %%  get a degree less than K by spilling other regs.
274  {Stk2, Ix2, Vis2, Low2} =
275    handle_non_spill(MustNotSpill, IG, Spill, K, Ix, Stk, Vis1, Low,
276		     SpillLimit, Target),
277  simplify_ig(Low2, ActualNumNodes-length(Stk2), IG, Spill, K, Ix2, Stk2, Vis2,
278	      SpillLimit, Target).
279
280handle_non_spill([], _IG, _Spill, _K, Ix, Stk, Vis, Low, _SpillLimit, _Target) ->
281  {Stk, Ix, Vis, Low};
282handle_non_spill([X|Xs] = L, IG, Spill, K, Ix, Stk, Vis, Low, SpillLimit, Target) ->
283  Info = hipe_vectors:get(IG, X),
284  Degree = degree(Info),
285  ?report("Can't Spill ~w with degree ~w\n", [X,Degree]),
286  if Degree > K ->
287      ?report("  *** spill required (N<~w)***~n", [SpillLimit]),
288      {Y, NewLow, NewIG} = spill(IG, Vis, Spill, K, SpillLimit, Target),
289      NewVis = visit(Y,Vis),
290      {NewStk, NewIx} = push_spill_node(Y, Ix, Stk),
291      ?report("  node ~w spilled~n", [Y]),
292      handle_non_spill(L, NewIG, Spill, K, NewIx, NewStk, NewVis,
293		       Low ++ NewLow, SpillLimit, Target);
294     true ->
295      {NewLow, NewIG} = decrement_neighbors(X, Low, IG, Vis, K),
296      ?report("  node ~w pushed\n(~w now ready)~n", [X,NewLow]),
297      NewStk = push_colored(X, Stk),
298      handle_non_spill(Xs, NewIG, Spill, K, Ix, NewStk, visit(X,Vis),
299		       NewLow, SpillLimit, Target)
300  end.
301
302simplify_ig([], 0, _IG, _Spill, _K, Ix, Stk, _Vis, _SpillLimit, _Target) ->
303  {Stk, Ix};
304simplify_ig([], N, IG, Spill, K, Ix, Stk, Vis, SpillLimit, Target)
305  when N > 0 ->
306  ?report3("N: ~w Stk: ~w N+Stk ~w\n", [N,length(Stk),N+length(Stk)]),
307  ?report("  *** spill required (N<~w)***~n", [SpillLimit]),
308  {X, Low, NewIG} = spill(IG, Vis, Spill, K, SpillLimit, Target),
309  NewVis = visit(X,Vis),
310  {NewStk, NewIx} = push_spill_node(X, Ix, Stk),
311  ?report("  node ~w spilled\n(~w now ready)~n", [X, Low]),
312  simplify_ig(Low, N-1, NewIG, Spill, K, NewIx, NewStk, NewVis,
313	      SpillLimit, Target);
314simplify_ig([X|Xs], N, IG, Spill, K, Ix, Stk, Vis, SpillLimit, Target) ->
315  ?report3("N: ~w Stk: ~w N+Stk ~w\n", [N,length(Stk),N+length(Stk)]),
316  case is_visited(X,Vis) of
317    true ->
318      ?report("  node ~p already visited~n",[X]),
319      simplify_ig(Xs, N, IG, Spill, K, Ix, Stk, Vis, SpillLimit, Target);
320    false ->
321      ?report("Stack ~w\n", [Stk]),
322      {NewLow, NewIG} = decrement_neighbors(X, Xs, IG, Vis, K),
323      ?report("  node ~w pushed\n(~w now ready)~n", [X,NewLow]),
324      NewStk = push_colored(X, Stk),
325      simplify_ig(NewLow, N-1, NewIG, Spill, K, Ix, NewStk, visit(X,Vis),
326		  SpillLimit, Target)
327  end.
328
329%% Returns { NowLowDegreeNeighbors, NewIG }
330
331decrement_neighbors(X, Xs, IG, Vis, K) ->
332  Ns = unvisited_neighbors(X, Vis, IG),
333  ?report("  node ~p has neighbors ~w\n(unvisited ~p)~n",
334	  [X, neighbors(X, IG), Ns]),
335  decrement_each(Ns, Xs, IG, Vis, K).
336
337%% For each node, decrement its degree and check if it is now
338%% a low-degree node. In that case, add it to the 'low list'.
339
340decrement_each([], Low, IG, _Vis, _K) ->
341  {Low, IG};
342decrement_each([N|Ns], OldLow, IG, Vis, K) ->
343  {Low, CurrIG} = Res = decrement_each(Ns, OldLow, IG, Vis, K),
344  case is_visited(N, Vis) of
345    true ->
346      Res;
347    false ->
348      {D, NewIG} = decrement_degree(N, CurrIG),
349      if
350	D =:= K-1 ->
351	  {[N|Low], NewIG};
352	true ->
353	  {Low, NewIG}
354      end
355  end.
356
357%%%%%%%%%%%%%%%%%%%%
358%%
359%% The spill cost of a node is:
360%%    est_spill_cost / current_degree
361%%
362%% For all unvisited nodes, compute spill cost and select the minimum.
363%% This node is chosen to be spilled. Then decrement the degree of its
364%% neighbors, and return those of low degree.
365%%
366%% Notes:
367%% - A better method for computing spill costs is to just keep the
368%%   minimum cost node. But for debugging purposes, we compute a list
369%%   of {node,spillcost} pairs and select the minimum.
370%%
371%% Returns:
372%%  {Spilled_node, Low_degree_neighbors, New_interference_graph}
373
374spill(IG, Vis, Spill, K, SpillLimit, Target) ->
375  Ns = list_ig(IG),
376  Costs = spill_costs(Ns, IG, Vis, Spill, SpillLimit, Target),
377  ?report3("spill costs are ~p~n", [Costs]),
378  ActualCosts = lists:sort(Costs),
379  ?report3("actual costs are ~p~n", [ActualCosts]),
380  case ActualCosts of
381    [] ->
382      ?error_msg("There is no node to spill", []),
383      ?EXIT('no node to spill');
384    [{_Cost,N}|_] ->
385      {Low, NewIG} = decrement_neighbors(N, [], IG, Vis, K),
386      %% ?report("spilled node ~p at cost ~p (~p now ready)~n", [N,Cost,Low]),
387      {N, Low, NewIG}
388  end.
389
390spill_costs([], _IG, _Vis, _Spill, _SpillLimit, _Target) ->
391  [];
392spill_costs([{N,Info}|Ns], IG, Vis, Spill, SpillLimit, Target) ->
393  case degree(Info) of
394    0 -> spill_costs(Ns,IG,Vis,Spill, SpillLimit, Target);
395    Deg ->
396      case is_visited(N,Vis) of
397	true ->
398	  spill_costs(Ns,IG,Vis,Spill, SpillLimit, Target);
399	_ ->
400	  case is_fixed(N, Target) of
401	    true ->
402	      spill_costs(Ns, IG, Vis, Spill, SpillLimit, Target);
403	    false ->
404	      if N >= SpillLimit ->
405		  spill_costs(Ns, IG, Vis, Spill, SpillLimit, Target);
406		 true ->
407		  [{spill_cost_of(N,Spill)/Deg,N} |
408		   spill_costs(Ns,IG, Vis, Spill, SpillLimit, Target)]
409	      end
410	  end
411      end
412  end.
413
414%%%%%%%%%%%%%%%%%%%%
415%%
416%% Returns a list of {Name,Location}, where Location is
417%%   either {spill,M} or {reg,R}
418%%
419%% Note: we use pessimistic coloring here.
420%% - we could use optimistic coloring: for spilled node, check if there is
421%%   an unused color among the neighbors and choose that.
422
423select(Stk, PreC, IG, K, PhysRegs, NumNodes, Target) ->
424  %% NumNodes = length(Stk)+length(PreC),
425  {PhysColors, Cols} = precolor(PreC, none_colored(NumNodes), Target),
426  ?report("precoloring has yielded ~p~n",[list_coloring(Cols)]),
427  PhysColors ++ select_colors(Stk, IG, Cols, PhysRegs, K).
428
429select_colors([], _IG, _Cols, _PhysRegs, _K) ->
430  ?report("all nodes colored~n",[]),
431  [];
432select_colors([{X,colorable}|Xs], IG, Cols, PhysRegs, K) ->
433  ?report("color of ~p\n",[X]),
434  {Reg,NewCols} = select_color(X, IG, Cols, PhysRegs),
435  ?report("~p~n",[Reg]),
436  [{X,{reg,Reg}} | select_colors(Xs, IG, NewCols, PhysRegs, K)];
437%%select_colors([{X,{spill,M}}|Xs], IG, Cols, PhysRegs, K) ->
438%%  ?report('spilled: ~p~n',[X]),
439%%  %% Check if optimistic coloring could have found a color
440%%  case catch select_color(X,IG,Cols,K) of
441%%    {'EXIT',_} ->   % no color possible
442%%	?report('(no optimistic color)~n',[]),
443%%	[{X,{spill,M}}|select_colors(Xs, IG, Cols, PhysRegs, K)];
444%%    {Reg,NewCols} ->
445%%	?report('(optimistic color: ~p)~n',[Reg]),
446%%	[{X,{reg,Reg}}|select_colors(Xs, IG, Cols, PhysRegs, K)]
447%%  end.
448
449%% Old code / pessimistic coloring:
450select_colors([{X,{spill,M}}|Xs], IG, Cols, PhysRegs, K) ->
451  ?report("spilled: ~p~n",[X]),
452  %% Check if optimistic coloring could have found a color
453%%    case catch select_color(X,IG,Cols,K) of
454%%	{'EXIT',_} ->   % no color possible
455%%	    ?report('(no optimistic color)~n',[]);
456%%	{Reg,NewCols} ->
457%%	    ?report('(optimistic color: ~p)~n',[Reg])
458%%    end,
459  [{X,{spill,M}} | select_colors(Xs, IG, Cols, PhysRegs, K)].
460
461select_color(X, IG, Cols, PhysRegs) ->
462  UsedColors = get_colors(neighbors(X, IG), Cols),
463  Reg = select_unused_color(UsedColors, PhysRegs),
464  {Reg, set_color(X, Reg, Cols)}.
465
466%%%%%%%%%%%%%%%%%%%%
467
468get_colors([], _Cols) -> [];
469get_colors([X|Xs], Cols) ->
470  case color_of(X, Cols) of
471    uncolored ->
472      get_colors(Xs, Cols);
473    {color,R} ->
474      [R|get_colors(Xs, Cols)]
475  end.
476
477select_unused_color(UsedColors, PhysRegs) ->
478  Summary = ordsets:from_list(UsedColors),
479  AvailRegs = ordsets:to_list(ordsets:subtract(PhysRegs, Summary)),
480  hd(AvailRegs).
481  %% select_avail_reg(AvailRegs).
482
483%% We choose the register to use randomly from the set of available
484%% registers.
485%%
486%% Note: Another way of doing it is LRU-order:
487%% - Have an LRU-queue of register names; when coloring, try the colors in that
488%%   order (some may be occupied).
489%% - When a color has been selected, put it at the end of the LRU.
490
491%% select_avail_reg(Regs) ->
492%%   case get(seeded) of
493%%     undefined ->
494%% 	 random:seed(),
495%% 	 put(seeded,true);
496%%     true ->
497%% 	 ok
498%%   end,
499%%   NReg = length(Regs),
500%%   RegNo = random:uniform(NReg),
501%%   lists:nth(RegNo, Regs).
502
503%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
504
505push_spill_node(X, M, Stk) ->
506  {[{X,{spill,M}}|Stk], M+1}.
507
508push_colored(X, Stk) ->
509  [{X, colorable} | Stk].
510
511%%%%%%%%%%%%%%%%%%%%
512
513low_degree_nodes([], _K, _NotAllocatable) -> [];
514low_degree_nodes([{N,Info}|Xs], K, NotAllocatable) ->
515  case lists:member(N, NotAllocatable) of
516    true ->
517      low_degree_nodes(Xs,K, NotAllocatable);
518    false ->
519      ?report0("node ~p has degree ~p: ~w~n",[N,degree(Info),neighbors(Info)]),
520      Deg = degree(Info),
521      if
522	Deg < K ->
523	  [N|low_degree_nodes(Xs, K, NotAllocatable)];
524	true ->
525	  low_degree_nodes(Xs, K, NotAllocatable)
526      end
527  end.
528
529%%%%%%%%%%%%%%%%%%%%
530
531unvisited_neighbors(X, Vis, IG) ->
532  ordsets:from_list(unvisited(neighbors(X,IG), Vis)).
533
534unvisited([], _Vis) -> [];
535unvisited([X|Xs], Vis) ->
536  case is_visited(X, Vis) of
537    true ->
538      unvisited(Xs, Vis);
539    false ->
540      [X|unvisited(Xs, Vis)]
541  end.
542
543%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
544%%
545%% *** ABSTRACT DATATYPES ***
546
547
548
549%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
550%%
551%% The ig datatype:
552%%
553%% Note: if we know the number of temps used, we can use a VECTOR
554%% instead, which will speed up things.
555%%
556%% Note: later on, we may wish to add 'move-related' support.
557
558-record(ig_info, {neighbors=[], degree=0 :: integer()}).
559
560empty_ig(NumNodes) ->
561  hipe_vectors:new(NumNodes, #ig_info{neighbors=[], degree=0}).
562
563degree(Info) ->
564  Info#ig_info.degree.
565
566neighbors(Info) ->
567  Info#ig_info.neighbors.
568
569add_edge(X, X, IG) -> IG;
570add_edge(X, Y, IG) ->
571  add_arc(X, Y, add_arc(Y, X, IG)).
572
573add_arc(X, Y, IG) ->
574  Info = hipe_vectors:get(IG, X),
575  Old = neighbors(Info),
576  New = Info#ig_info{neighbors=[Y|Old]},
577  hipe_vectors:set(IG, X, New).
578
579normalize_ig(IG) ->
580  Size = hipe_vectors:size(IG),
581  normalize_ig(Size-1, IG).
582
583normalize_ig(-1, IG) ->
584  IG;
585normalize_ig(I, IG) ->
586  Info = hipe_vectors:get(IG, I),
587  N = ordsets:from_list(neighbors(Info)),
588  NewIG = hipe_vectors:set(IG, I, Info#ig_info{neighbors=N, degree=length(N)}),
589  normalize_ig(I-1, NewIG).
590
591%%degree(X, IG) ->
592%%  Info = hipe_vectors:get(IG, X),
593%%  Info#ig_info.degree.
594
595neighbors(X, IG) ->
596  Info = hipe_vectors:get(IG, X),
597  Info#ig_info.neighbors.
598
599decrement_degree(X, IG) ->
600  Info = hipe_vectors:get(IG, X),
601  Degree = degree(Info),
602  NewDegree = Degree-1,
603  NewInfo = Info#ig_info{degree=NewDegree},
604  {NewDegree, hipe_vectors:set(IG,X,NewInfo)}.
605
606list_ig(IG) ->
607  hipe_vectors:list(IG).
608
609%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
610%%
611%% The spill cost datatype:
612%%
613%% Note: if we know the number of temps used, we can use a VECTOR
614%% instead, which will speed up things.
615
616empty_spill(NumNodes) ->
617  hipe_vectors:new(NumNodes, 0).
618
619spill_cost_of(X, Spill) ->
620  hipe_vectors:get(Spill, X).
621
622spill_cost_lookup(X, Spill) ->
623  spill_cost_of(X, Spill).
624
625spill_cost_update(X, N, Spill) ->
626  hipe_vectors:set(Spill, X, N).
627
628%%list_spill_costs(Spill) ->
629%%  hipe_vectors:list(Spill).
630
631%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
632%%
633%% The coloring datatype:
634
635none_colored(NumNodes) ->
636  hipe_vectors:new(NumNodes,uncolored).
637
638color_of(X,Cols) ->
639  hipe_vectors:get(Cols,X).
640
641set_color(X,R,Cols) ->
642  hipe_vectors:set(Cols,X,{color,R}).
643
644-ifdef(DEBUG).
645list_coloring(Cols) ->
646  hipe_vectors:list(Cols).
647-endif.
648
649%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
650%%
651%% Note: there might be a slight gain in separating the two versions
652%% of visit/2 and visited/2. (So that {var,X} selects X and calls the
653%% integer version.
654
655none_visited(NumNodes) ->
656  hipe_vectors:new(NumNodes, false).
657
658visit(X,Vis) ->
659  hipe_vectors:set(Vis, X, true).
660
661is_visited(X,Vis) ->
662  hipe_vectors:get(Vis, X).
663
664visit_all([], Vis) -> Vis;
665visit_all([X|Xs], Vis) ->
666  visit_all(Xs, visit(X, Vis)).
667
668%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
669%% Check that all arcs in IG are bidirectional + degree is correct
670
671%% check_ig(IG) ->
672%%   check_ig(list_ig(IG),IG).
673
674%% check_ig([],IG) ->
675%%   ok;
676%% check_ig([{N,Info}|Xs],IG) ->
677%%   Ns = neighbors(Info),
678%%   NumNs = length(Ns),
679%%   D = degree(Info),
680%%   if
681%%      D =:= NumNs ->
682%%        ok;
683%%      true ->
684%% 	 ?WARNING_MSG('node ~p has degree ~p but ~p neighbors~n',[N,D,NumNs])
685%%   end,
686%%   check_neighbors(N,Ns,IG),
687%%   check_ig(Xs,IG).
688
689%% check_neighbors(N,[],IG) ->
690%%   ok;
691%% check_neighbors(N,[M|Ms],IG) ->
692%%   Ns = neighbors(M,IG),
693%%   case member(N,Ns) of
694%%     true ->
695%% 	 ok;
696%%     true ->
697%% 	 ?WARNING_MSG('node ~p should have ~p as neighbor (has ~p)~n',[M,N,Ns])
698%%   end,
699%%   check_neighbors(N,Ms,IG).
700
701-ifdef(DO_ASSERT).
702%%%%%%%%%%%%%%%%%%%%
703%% Check that the coloring is correct (if the IG is correct):
704%%
705
706check_coloring(Coloring, IG, Target) ->
707  ?report0("checking coloring ~p~n",[Coloring]),
708  check_cols(list_ig(IG),init_coloring(Coloring, Target)).
709
710init_coloring(Xs, Target) ->
711  hipe_temp_map:cols2tuple(Xs, Target).
712
713check_color_of(X, Cols) ->
714%%    if
715%%	is_precoloured(X) ->
716%%	    phys_reg_color(X,Cols);
717%%	true ->
718  case hipe_temp_map:find(X, Cols) of
719    unknown ->
720      ?WARNING_MSG("node ~p: color not found~n", [X]),
721      uncolored;
722    C ->
723      C
724  end.
725
726check_cols([], Cols) ->
727  ?report("coloring valid~n",[]),
728  true;
729check_cols([{X,Info}|Xs], Cols) ->
730  Cs = [{N, check_color_of(N, Cols)} || N <- neighbors(Info)],
731  C = check_color_of(X, Cols),
732  case valid_coloring(X, C, Cs) of
733    yes ->
734      check_cols(Xs, Cols);
735    {no,Invalids} ->
736      ?WARNING_MSG("node ~p has same color (~p) as ~p~n", [X,C,Invalids]),
737      check_cols(Xs, Cols)
738  end.
739
740valid_coloring(X, C, []) ->
741  yes;
742valid_coloring(X, C, [{Y,C}|Ys]) ->
743  case valid_coloring(X, C, Ys) of
744    yes -> {no, [Y]};
745    {no,Zs} -> {no, [Y|Zs]}
746  end;
747valid_coloring(X, C, [_|Ys]) ->
748  valid_coloring(X, C, Ys).
749-endif.
750
751
752%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
753%%
754%% *** INTERFACES TO OTHER MODULES ***
755%%
756
757all_precoloured({TgtMod,TgtCtx}) ->
758  TgtMod:all_precoloured(TgtCtx).
759
760allocatable({TgtMod,TgtCtx}) ->
761  TgtMod:allocatable(TgtCtx).
762
763is_fixed(Reg, {TgtMod,TgtCtx}) ->
764  TgtMod:is_fixed(Reg, TgtCtx).
765
766labels(CFG, {TgtMod,TgtCtx}) ->
767  TgtMod:labels(CFG, TgtCtx).
768
769liveout(CFG, L, Target={TgtMod,TgtCtx}) ->
770  ordsets:from_list(reg_names(TgtMod:liveout(CFG, L, TgtCtx), Target)).
771
772bb(CFG, L, {TgtMod,TgtCtx}) ->
773  hipe_bb:code(TgtMod:bb(CFG, L, TgtCtx)).
774
775def_use(X, Target={TgtMod,TgtCtx}) ->
776  {ordsets:from_list(reg_names(TgtMod:defines(X,TgtCtx), Target)),
777   ordsets:from_list(reg_names(TgtMod:uses(X,TgtCtx), Target))}.
778
779non_alloc(CFG, Target={TgtMod,TgtCtx}) ->
780  reg_names(TgtMod:non_alloc(CFG, TgtCtx), Target).
781
782number_of_temporaries(CFG, {TgtMod,TgtCtx}) ->
783  TgtMod:number_of_temporaries(CFG, TgtCtx).
784
785reg_names(Regs, {TgtMod,TgtCtx}) ->
786  [TgtMod:reg_nr(X,TgtCtx) || X <- Regs].
787
788%%
789%% Precoloring: use this version when a proper implementation of
790%%  physical_name(X) is available!
791%%
792
793precolor(Xs, Cols, Target) ->
794  ?report("precoloring ~p~n", [Xs]),
795  {_Cs, _NewCol} = Res = precolor0(Xs, Cols, Target),
796  ?report("    yielded ~p~n", [_Cs]),
797  Res.
798
799precolor0([], Cols, _Target) ->
800  {[], Cols};
801precolor0([R|Rs], Cols, Target) ->
802  {Cs, Cols1} = precolor0(Rs, Cols, Target),
803  {[{R, {reg, physical_name(R, Target)}}|Cs],
804   set_color(R, physical_name(R, Target), Cols1)}.
805
806physical_name(X, {TgtMod,TgtCtx}) ->
807  TgtMod:physical_name(X, TgtCtx).
808