~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/hipe/regalloc/hipe_graph_coloring_regalloc.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
10
10
%% - select colors
11
11
%%
12
12
%% Emits a coloring: a list of {TempName,Location}
13
 
%%  where Location is {reg,N} or {spill,M}.
 
13
%%  where Location is {reg,N} or {spill,M}
14
14
%%   and {reg,N} denotes some register N
15
15
%%   and {spill,M} denotes the Mth spilled node
16
16
%% You have to figure out how to rewrite the code yourself.
58
58
%% that the coloring agrees with the interference graph (that is, that
59
59
%% no neighbors have the same register or spill location).
60
60
 
 
61
%% @spec regalloc(#cfg{}, non_neg_fixnum(), non_neg_fixnum(), atom(), list()) -> {, non_neg_fixnum()}
 
62
 
61
63
regalloc(CFG, SpillIndex, SpillLimit, Target, _Options) ->
62
64
  PhysRegs = Target:allocatable(),
63
65
  ?report2("building IG~n", []),
64
66
  {IG, Spill} = build_ig(CFG, Target),
65
67
 
66
68
  %% check_ig(IG),
67
 
  ?report3("graph: ~p~nphysical regs: ~p~n",[list_ig(IG), PhysRegs]),
 
69
  ?report3("graph: ~p~nphysical regs: ~p~n", [list_ig(IG), PhysRegs]),
68
70
 
69
71
  %% These nodes *can't* be allocated to registers. 
70
72
  NotAllocatable = [Target:reg_nr(X) || X <- Target:non_alloc(CFG)],
72
74
  ?report2("Nonalloc ~w~n", [NotAllocatable]),
73
75
 
74
76
  {Cols, NewSpillIndex} = 
75
 
    color(IG, Spill, 
 
77
    color(IG, Spill,
76
78
          ordsets:from_list(PhysRegs), 
77
79
          SpillIndex,
78
 
          SpillLimit, 
 
80
          SpillLimit,
79
81
          Target:number_of_temporaries(CFG),
80
82
          Target, NotAllocatable),
81
83
  Coloring = [{X, {reg, X}} || X <- NotAllocatable] ++ Cols,
94
96
build_ig(CFG, Target) ->
95
97
  case catch build_ig0(CFG, Target) of
96
98
    {'EXIT',Rsn} ->
97
 
      exit({regalloc, build_ig, Rsn});
 
99
      exit({?MODULE, build_ig, Rsn});
98
100
    Else ->
99
101
      Else
100
102
  end.
114
116
  {IG, Spill};
115
117
build_ig_bbs([L|Ls], CFG, Live, IG, Spill, Target) ->
116
118
  Xs = bb(CFG, L, Target),
117
 
  {_, NewIG, NewSpill} = 
118
 
    build_ig_bb(Xs, liveout(Live,L, Target), IG, Spill, Target),
 
119
  {_, NewIG, NewSpill} =
 
120
    build_ig_bb(Xs, liveout(Live, L, Target), IG, Spill, Target),
119
121
  build_ig_bbs(Ls, CFG, Live, NewIG, NewSpill, Target).
120
122
 
121
123
build_ig_bb([], LiveOut, IG, Spill, _Target) ->
132
134
 
133
135
build_ig_instr(X, Live, IG, Spill, Target) ->
134
136
  {Def, Use} = def_use(X, Target),
135
 
  ?report3("Live ~w\n~w : Def: ~w Use ~w\n",[Live, X, Def,Use]),
 
137
  ?report3("Live ~w\n~w : Def: ~w Use ~w\n", [Live, X, Def,Use]),
136
138
  DefList = ordsets:to_list(Def),
137
139
  NewSpill = inc_spill_costs(DefList, 
138
140
                             inc_spill_costs(ordsets:to_list(Use), Spill)),
143
145
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
144
146
 
145
147
interference_arcs([], _Live, IG) -> 
146
 
   IG;
147
 
interference_arcs([X|Xs],Live,IG) ->
148
 
   interference_arcs(Xs, Live, i_arcs(X, Live, IG)).
 
148
  IG;
 
149
interference_arcs([X|Xs], Live, IG) ->
 
150
  interference_arcs(Xs, Live, i_arcs(X, Live, IG)).
149
151
 
150
152
i_arcs(_X, [], IG) -> 
151
 
   IG;
 
153
  IG;
152
154
i_arcs(X, [Y|Ys], IG) ->
153
 
   i_arcs(X, Ys, add_edge(X,Y, IG)).
154
 
 
155
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
156
 
 
157
 
inc_spill_costs([],Spill) -> Spill;
158
 
inc_spill_costs([X|Xs],Spill) ->
159
 
   inc_spill_costs(Xs,inc_spill_cost(X,Spill)).
160
 
 
161
 
inc_spill_cost(X,Spill) ->
162
 
   set_spill_cost(X,get_spill_cost(X,Spill)+1,Spill).
163
 
 
164
 
get_spill_cost(X,Spill) ->
165
 
   spill_cost_lookup(X,Spill).
166
 
 
167
 
set_spill_cost(X,N,Spill) ->
168
 
   spill_cost_update(X,N,Spill).
169
 
 
170
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
171
 
 
 
155
  i_arcs(X, Ys, add_edge(X,Y, IG)).
 
156
 
 
157
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
158
 
 
159
inc_spill_costs([], Spill) -> Spill;
 
160
inc_spill_costs([X|Xs], Spill) ->
 
161
  inc_spill_costs(Xs, inc_spill_cost(X, Spill)).
 
162
 
 
163
inc_spill_cost(X, Spill) ->
 
164
  set_spill_cost(X, get_spill_cost(X, Spill)+1, Spill).
 
165
 
 
166
get_spill_cost(X, Spill) ->
 
167
  spill_cost_lookup(X, Spill).
 
168
 
 
169
set_spill_cost(X, N, Spill) ->
 
170
  spill_cost_update(X, N, Spill).
 
171
 
 
172
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
172
173
 
173
174
 
174
175
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
195
196
   case catch color_0(IG, Spill, PhysRegs, SpillIx, SpillLimit,
196
197
                      NumNodes, Target, NotAllocatable) of
197
198
      {'EXIT',Rsn} ->
198
 
         ?error_msg("Coloring failed with ~p~n",[Rsn]),
 
199
         ?error_msg("Coloring failed with ~p~n", [Rsn]),
199
200
         ?EXIT(Rsn);
200
201
      Else ->
201
202
         Else
203
204
 
204
205
color_0(IG, Spill, PhysRegs, SpillIx, SpillLimit, NumNodes, Target,
205
206
        NotAllocatable) -> 
206
 
  ?report("simplification of IG~n",[]),
 
207
  ?report("simplification of IG~n", []),
207
208
  K = ordsets:size(PhysRegs),
208
209
  Nodes = list_ig(IG),
209
210
 
211
212
 
212
213
  %% Any nodes above the spillimit must be colored first...
213
214
  MustNotSpill = 
214
 
    if NumNodes > SpillLimit +1 -> 
 
215
    if NumNodes > SpillLimit+1 ->
215
216
        sort_on_degree(lists:seq(SpillLimit+1,NumNodes-1) -- Low,IG);
216
217
       true -> []
217
218
    end,
230
231
sort_on_degree(Nodes, IG) ->
231
232
  [ Node3 || {_,Node3} <- 
232
233
               lists:sort([{degree(Info),Node2} || 
233
 
                            {Info,Node2} <- [{ hipe_vectors:get(IG, Node),
 
234
                            {Info,Node2} <- [{hipe_vectors:get(IG, Node),
234
235
                                              Node} || Node <-
235
236
                                                         Nodes]])].
236
237
 
275
276
  %% Make sure that the registers that must not be spilled
276
277
  %%  get a degree less than K by spilling other regs.
277
278
  {Stk2, Ix2, Vis2, Low2} =  
278
 
    handle_non_spill(MustNotSpill,  IG, Spill, K, Ix, Stk, Vis1, Low,
279
 
               SpillLimit, Target),
 
279
    handle_non_spill(MustNotSpill, IG, Spill, K, Ix, Stk, Vis1, Low,
 
280
                     SpillLimit, Target),
280
281
  simplify_ig(Low2, ActualNumNodes-length(Stk2), IG, Spill, K, Ix2, Stk2, Vis2,
281
282
              SpillLimit, Target).
282
283
 
307
308
  {Stk, Ix};
308
309
simplify_ig([], N, IG, Spill, K, Ix, Stk, Vis, SpillLimit, Target) 
309
310
  when N > 0 ->
310
 
  ?report3("N: ~w Stk: ~w N+Stk ~w\n",[N,length(Stk),N+length(Stk)]),
311
 
 
312
 
  ?report("  *** spill required (N<~w)***~n",[SpillLimit]),
 
311
  ?report3("N: ~w Stk: ~w N+Stk ~w\n", [N,length(Stk),N+length(Stk)]),
 
312
  ?report("  *** spill required (N<~w)***~n", [SpillLimit]),
313
313
  {X, Low, NewIG} = spill(IG, Vis, Spill, K, SpillLimit, Target),
314
314
  NewVis = visit(X,Vis),
315
315
  {NewStk, NewIx} = push_spill_node(X, Ix, Stk),
317
317
  simplify_ig(Low, N-1, NewIG, Spill, K, NewIx, NewStk, NewVis,
318
318
              SpillLimit, Target);
319
319
simplify_ig([X|Xs], N, IG, Spill, K, Ix, Stk, Vis, SpillLimit, Target) ->
320
 
  ?report3("N: ~w Stk: ~w N+Stk ~w\n",[N,length(Stk),N+length(Stk)]),
321
 
 
 
320
  ?report3("N: ~w Stk: ~w N+Stk ~w\n", [N,length(Stk),N+length(Stk)]),
322
321
  case is_visited(X,Vis) of
323
322
    true ->
324
323
      ?report("  node ~p already visited~n",[X]),
326
325
    false ->
327
326
      ?report("Stack ~w\n", [Stk]),
328
327
      {NewLow, NewIG} = decrement_neighbors(X, Xs, IG, Vis, K),
329
 
      ?report("  node ~w pushed\n(~w now ready)~n",[X,NewLow]),
 
328
      ?report("  node ~w pushed\n(~w now ready)~n", [X,NewLow]),
330
329
      NewStk = push_colored(X, Stk),
331
330
      simplify_ig(NewLow, N-1, NewIG, Spill, K, Ix, NewStk, visit(X,Vis),
332
331
                  SpillLimit, Target)
337
336
decrement_neighbors(X, Xs, IG, Vis, K) ->
338
337
  Ns = unvisited_neighbors(X, Vis, IG),
339
338
  ?report("  node ~p has neighbors ~w\n(unvisited ~p)~n",
340
 
          [X, neighbors(X,IG),Ns]),
341
 
  decrement_each(Ns,Xs,IG,Vis,K).
 
339
          [X, neighbors(X, IG), Ns]),
 
340
  decrement_each(Ns, Xs, IG, Vis, K).
342
341
 
343
342
%% For each node, decrement its degree and check if it is now
344
343
%% a low-degree node. In that case, add it to the 'low list'.
349
348
  {Low, CurrIG} = decrement_each(Ns, OldLow, IG, Vis, K),
350
349
  case is_visited(N, Vis) of
351
350
    true ->
352
 
         {Low, CurrIG};
 
351
      {Low, CurrIG};
353
352
    false ->
354
 
         {D, NewIG} = decrement_degree(N, CurrIG),
355
 
         if
356
 
            D =:= K-1 ->
357
 
               {[N|Low], NewIG};
358
 
            true ->
359
 
               {Low, NewIG}
360
 
         end
 
353
      {D, NewIG} = decrement_degree(N, CurrIG),
 
354
      if
 
355
        D =:= K-1 ->
 
356
          {[N|Low], NewIG};
 
357
        true ->
 
358
          {Low, NewIG}
 
359
      end
361
360
  end.
362
361
 
363
362
%%%%%%%%%%%%%%%%%%%%
471
470
 
472
471
%%%%%%%%%%%%%%%%%%%%
473
472
 
474
 
get_colors([],_Cols) -> [];
475
 
get_colors([X|Xs],Cols) ->
476
 
  case color_of(X,Cols) of
 
473
get_colors([], _Cols) -> [];
 
474
get_colors([X|Xs], Cols) ->
 
475
  case color_of(X, Cols) of
477
476
    uncolored ->
478
 
      get_colors(Xs,Cols);
 
477
      get_colors(Xs, Cols);
479
478
    {color,R} ->
480
 
      [R|get_colors(Xs,Cols)]
 
479
      [R|get_colors(Xs, Cols)]
481
480
  end.
482
481
 
483
482
select_unused_color(UsedColors, PhysRegs) ->
494
493
%%   order (some may be occupied).
495
494
%% - When a color has been selected, put it at the end of the LRU.
496
495
 
497
 
% select_avail_reg(Regs) ->
498
 
%     case get(seeded) of
499
 
%       undefined ->
500
 
%           random:seed(),
501
 
%           put(seeded,true);
502
 
%       true ->
503
 
%           ok
504
 
%     end,
505
 
%     NReg = length(Regs),
506
 
%     RegNo = random:uniform(NReg),
507
 
%     nth(RegNo, Regs).
508
 
 
509
 
%Nth(1,[R|_]) -> R;
510
 
%nth(N,[_|Rs]) when N > 1 ->
511
 
%    nth(N-1,Rs).
 
496
%% select_avail_reg(Regs) ->
 
497
%%   case get(seeded) of
 
498
%%     undefined ->
 
499
%%       random:seed(),
 
500
%%       put(seeded,true);
 
501
%%     true ->
 
502
%%       ok
 
503
%%   end,
 
504
%%   NReg = length(Regs),
 
505
%%   RegNo = random:uniform(NReg),
 
506
%%   lists:nth(RegNo, Regs).
512
507
 
513
508
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
514
509
 
515
 
push_spill_node(X,M,Stk) ->
516
 
   {[{X,{spill,M}}|Stk], M+1}.
 
510
push_spill_node(X, M, Stk) ->
 
511
  {[{X,{spill,M}}|Stk], M+1}.
517
512
 
518
 
push_colored(X,Stk) ->
519
 
    [{X, colorable} | Stk].
 
513
push_colored(X, Stk) ->
 
514
  [{X, colorable} | Stk].
520
515
 
521
516
%%%%%%%%%%%%%%%%%%%%
522
517
 
530
525
      Deg = degree(Info),
531
526
      if
532
527
        Deg < K ->
533
 
          [N|low_degree_nodes(Xs,K, NotAllocatable)];
 
528
          [N|low_degree_nodes(Xs, K, NotAllocatable)];
534
529
        true ->
535
 
          low_degree_nodes(Xs,K, NotAllocatable)
 
530
          low_degree_nodes(Xs, K, NotAllocatable)
536
531
      end
537
532
  end.
538
533
 
539
534
%%%%%%%%%%%%%%%%%%%%
540
535
 
541
 
unvisited_neighbors(X,Vis,IG) ->
542
 
    ordsets:from_list(unvisited(neighbors(X,IG),Vis)).
543
 
 
544
 
unvisited([],_Vis) -> [];
545
 
unvisited([X|Xs],Vis) ->
546
 
   case is_visited(X,Vis) of
547
 
      true ->
548
 
         unvisited(Xs,Vis);
549
 
      false ->
550
 
         [X|unvisited(Xs,Vis)]
551
 
   end.
552
 
 
 
536
unvisited_neighbors(X, Vis, IG) ->
 
537
  ordsets:from_list(unvisited(neighbors(X,IG), Vis)).
 
538
 
 
539
unvisited([], _Vis) -> [];
 
540
unvisited([X|Xs], Vis) ->
 
541
  case is_visited(X, Vis) of
 
542
    true ->
 
543
      unvisited(Xs, Vis);
 
544
    false ->
 
545
      [X|unvisited(Xs, Vis)]
 
546
  end.
553
547
 
554
548
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
555
549
%%
566
560
%%
567
561
%% Note: later on, we may wish to add 'move-related' support.
568
562
 
569
 
-record(ig_info,{neighbors=[],degree=0}).
 
563
-record(ig_info, {neighbors=[], degree=0 :: integer()}).
570
564
 
571
565
empty_ig(NumNodes) ->
572
 
  hipe_vectors:new(NumNodes,#ig_info{neighbors=[],degree=0}).
 
566
  hipe_vectors:new(NumNodes, #ig_info{neighbors=[], degree=0}).
573
567
 
574
568
degree(Info) ->
575
569
  Info#ig_info.degree.
577
571
neighbors(Info) ->
578
572
  Info#ig_info.neighbors.
579
573
 
580
 
add_edge(X,X,IG) -> IG;
581
 
add_edge(X,Y,IG) ->
582
 
  add_arc(X,Y,add_arc(Y,X,IG)).
 
574
add_edge(X, X, IG) -> IG;
 
575
add_edge(X, Y, IG) ->
 
576
  add_arc(X, Y, add_arc(Y, X, IG)).
583
577
 
584
578
add_arc(X, Y, IG) ->
585
579
  Info = hipe_vectors:get(IG, X),
586
580
  Old = neighbors(Info),
587
581
  New = Info#ig_info{neighbors=[Y|Old]},
588
 
  hipe_vectors:set(IG,X,New).
589
 
 
 
582
  hipe_vectors:set(IG, X, New).
590
583
 
591
584
normalize_ig(IG) ->
592
585
  Size = hipe_vectors:size(IG),
613
606
  Degree = degree(Info),
614
607
  NewDegree = Degree-1,
615
608
  NewInfo = Info#ig_info{degree=NewDegree},
616
 
  {NewDegree,hipe_vectors:set(IG,X,NewInfo)}.
 
609
  {NewDegree, hipe_vectors:set(IG,X,NewInfo)}.
617
610
 
618
611
list_ig(IG) ->
619
612
  hipe_vectors:list(IG).
638
631
  hipe_vectors:set(Spill, X, N).
639
632
 
640
633
%%list_spill_costs(Spill) ->
641
 
%%   hipe_vectors:list(Spill).
 
634
%%  hipe_vectors:list(Spill).
642
635
 
643
636
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
644
637
%%
661
654
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
662
655
%%
663
656
%% Note: there might be a slight gain in separating the two versions
664
 
%% of visit/2 and visited/2. (So that {var,X} selects X and calls
665
 
%% the integer version.
 
657
%% of visit/2 and visited/2. (So that {var,X} selects X and calls the
 
658
%% integer version.
666
659
 
667
660
none_visited(NumNodes) ->
668
 
  hipe_vectors:new(NumNodes,false).
 
661
  hipe_vectors:new(NumNodes, false).
669
662
 
670
663
visit(X,Vis) ->
671
 
  hipe_vectors:set(Vis,X,true).
 
664
  hipe_vectors:set(Vis, X, true).
672
665
 
673
666
is_visited(X,Vis) ->
674
 
  hipe_vectors:get(Vis,X).
 
667
  hipe_vectors:get(Vis, X).
675
668
 
676
 
visit_all([],Vis) -> Vis;
677
 
visit_all([X|Xs],Vis) ->
678
 
  visit_all(Xs,visit(X,Vis)).
 
669
visit_all([], Vis) -> Vis;
 
670
visit_all([X|Xs], Vis) ->
 
671
  visit_all(Xs, visit(X, Vis)).
679
672
 
680
673
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
681
674
%% Check that all arcs in IG are bidirectional + degree is correct
682
675
 
683
 
% check_ig(IG) ->
684
 
%    check_ig(list_ig(IG),IG).
685
 
 
686
 
% check_ig([],IG) -> 
687
 
%    ok;
688
 
% check_ig([{N,Info}|Xs],IG) ->
689
 
%    Ns = neighbors(Info),
690
 
%    NumNs = length(Ns),
691
 
%    D = degree(Info),
692
 
%    if
693
 
%       D =:= NumNs ->
694
 
%        ok;
695
 
%       true ->
696
 
%        ?WARNING_MSG('node ~p has degree ~p but ~p neighbors~n',[N,D,NumNs])
697
 
%    end,
698
 
%    check_neighbors(N,Ns,IG),
699
 
%    check_ig(Xs,IG).
700
 
 
701
 
% check_neighbors(N,[],IG) -> 
702
 
%    ok;
703
 
% check_neighbors(N,[M|Ms],IG) ->
704
 
%    Ns = neighbors(M,IG),
705
 
%    case member(N,Ns) of
706
 
%       true ->
707
 
%        ok;
708
 
%       true ->
709
 
%        ?WARNING_MSG('node ~p should have ~p as neighbor (has ~p)~n',[M,N,Ns])
710
 
%    end,
711
 
%    check_neighbors(N,Ms,IG).
 
676
%% check_ig(IG) ->
 
677
%%   check_ig(list_ig(IG),IG).
 
678
 
 
679
%% check_ig([],IG) -> 
 
680
%%   ok;
 
681
%% check_ig([{N,Info}|Xs],IG) ->
 
682
%%   Ns = neighbors(Info),
 
683
%%   NumNs = length(Ns),
 
684
%%   D = degree(Info),
 
685
%%   if
 
686
%%      D =:= NumNs ->
 
687
%%        ok;
 
688
%%      true ->
 
689
%%       ?WARNING_MSG('node ~p has degree ~p but ~p neighbors~n',[N,D,NumNs])
 
690
%%   end,
 
691
%%   check_neighbors(N,Ns,IG),
 
692
%%   check_ig(Xs,IG).
 
693
 
 
694
%% check_neighbors(N,[],IG) -> 
 
695
%%   ok;
 
696
%% check_neighbors(N,[M|Ms],IG) ->
 
697
%%   Ns = neighbors(M,IG),
 
698
%%   case member(N,Ns) of
 
699
%%     true ->
 
700
%%       ok;
 
701
%%     true ->
 
702
%%       ?WARNING_MSG('node ~p should have ~p as neighbor (has ~p)~n',[M,N,Ns])
 
703
%%   end,
 
704
%%   check_neighbors(N,Ms,IG).
712
705
 
713
706
-ifdef(DO_ASSERT).
714
707
%%%%%%%%%%%%%%%%%%%%
715
708
%% Check that the coloring is correct (if the IG is correct):
716
709
%%
717
710
 
718
 
check_coloring(Coloring,IG, Target) ->
719
 
   ?report0("checking coloring ~p~n",[Coloring]),
720
 
   check_cols(list_ig(IG),init_coloring(Coloring, Target)).
 
711
check_coloring(Coloring, IG, Target) ->
 
712
  ?report0("checking coloring ~p~n",[Coloring]),
 
713
  check_cols(list_ig(IG),init_coloring(Coloring, Target)).
721
714
 
722
715
init_coloring(Xs, Target) ->
723
716
  hipe_temp_map:cols2tuple(Xs, Target).
724
717
 
725
 
check_color_of(X,Cols) ->
 
718
check_color_of(X, Cols) ->
726
719
%%    if
727
720
%%      is_precoloured(X) ->
728
721
%%          phys_reg_color(X,Cols);
729
722
%%      true ->
730
 
   case hipe_temp_map:find(X,Cols) of
731
 
     unknown ->
732
 
         ?WARNING_MSG("node ~p: color not found~n",[X]),
733
 
         uncolored;
734
 
     C ->
735
 
         C
736
 
   end.
737
 
 
738
 
check_cols([],Cols) ->
739
 
    ?report("coloring valid~n",[]),
740
 
    true;
741
 
check_cols([{X,Info}|Xs],Cols) ->
742
 
    Cs = [ {N,check_color_of(N,Cols)} || N <- neighbors(Info) ],
743
 
    C = check_color_of(X,Cols),
744
 
    case valid_coloring(X,C,Cs) of
745
 
       yes ->
746
 
         check_cols(Xs,Cols);
747
 
       {no,Invalids} ->
748
 
         ?WARNING_MSG("node ~p has same color (~p) as ~p~n",
749
 
                 [X,C,Invalids]),
750
 
         check_cols(Xs,Cols)
751
 
    end.
752
 
 
753
 
 valid_coloring(X,C,[]) ->
754
 
    yes;
755
 
 valid_coloring(X,C,[{Y,C}|Ys]) ->
756
 
    case valid_coloring(X,C,Ys) of
757
 
       yes -> {no,[Y]};
758
 
       {no,Zs} -> {no,[Y|Zs]}
759
 
 
760
 
    end;
761
 
 valid_coloring(X,C,[_|Ys]) ->
762
 
    valid_coloring(X,C,Ys).
 
723
  case hipe_temp_map:find(X, Cols) of
 
724
    unknown ->
 
725
      ?WARNING_MSG("node ~p: color not found~n", [X]),
 
726
      uncolored;
 
727
    C ->
 
728
      C
 
729
  end.
 
730
 
 
731
check_cols([], Cols) ->
 
732
  ?report("coloring valid~n",[]),
 
733
  true;
 
734
check_cols([{X,Info}|Xs], Cols) ->
 
735
  Cs = [{N, check_color_of(N, Cols)} || N <- neighbors(Info)],
 
736
  C = check_color_of(X, Cols),
 
737
  case valid_coloring(X, C, Cs) of
 
738
    yes ->
 
739
      check_cols(Xs, Cols);
 
740
    {no,Invalids} ->
 
741
      ?WARNING_MSG("node ~p has same color (~p) as ~p~n", [X,C,Invalids]),
 
742
      check_cols(Xs, Cols)
 
743
  end.
 
744
 
 
745
valid_coloring(X, C, []) ->
 
746
  yes;
 
747
valid_coloring(X, C, [{Y,C}|Ys]) ->
 
748
  case valid_coloring(X, C, Ys) of
 
749
    yes -> {no, [Y]};
 
750
    {no,Zs} -> {no, [Y|Zs]}
 
751
  end;
 
752
valid_coloring(X, C, [_|Ys]) ->
 
753
  valid_coloring(X, C, Ys).
763
754
-endif.
764
755
 
765
756
 
768
759
%% *** INTERFACES TO OTHER MODULES ***
769
760
%%
770
761
 
771
 
liveout(CFG,L, Target) ->
772
 
  ordsets:from_list(reg_names(Target:liveout(CFG,L), Target)).
 
762
liveout(CFG, L, Target) ->
 
763
  ordsets:from_list(reg_names(Target:liveout(CFG, L), Target)).
773
764
 
774
 
bb(CFG,L,Target) ->
775
 
   hipe_bb:code(Target:bb(CFG,L)).
 
765
bb(CFG, L, Target) ->
 
766
  hipe_bb:code(Target:bb(CFG, L)).
776
767
 
777
768
def_use(X, Target) ->
778
 
   {ordsets:from_list(reg_names(Target:defines(X), Target)), 
779
 
    ordsets:from_list(reg_names(Target:uses(X), Target))}.
 
769
  {ordsets:from_list(reg_names(Target:defines(X), Target)), 
 
770
   ordsets:from_list(reg_names(Target:uses(X), Target))}.
780
771
 
781
772
reg_names(Rs, Target) ->
782
 
   Regs = 
 
773
  Regs = 
783
774
    case Target of
784
775
      hipe_sparc_specific ->
785
776
        hipe_sparc:keep_registers(Rs);
794
785
%%
795
786
 
796
787
precolor(Xs, Cols, Target) ->
797
 
   ?report("precoloring ~p~n",[Xs]),
798
 
   {Cs,NewCol} = precolor0(Xs, Cols, Target),
799
 
   ?report("    yielded ~p~n", [Cs]),
800
 
   {Cs,NewCol}.
 
788
  ?report("precoloring ~p~n", [Xs]),
 
789
  {Cs,NewCol} = precolor0(Xs, Cols, Target),
 
790
  ?report("    yielded ~p~n", [Cs]),
 
791
  {Cs,NewCol}.
801
792
 
802
793
precolor0([], Cols, _Target) ->
803
 
   {[], Cols};
 
794
  {[], Cols};
804
795
precolor0([R|Rs], Cols, Target) ->
805
 
   {Cs, Cols1} = precolor0(Rs, Cols, Target),
806
 
   {[{R,{reg,physical_name(R, Target)}}|Cs], 
807
 
    set_color(R,physical_name(R, Target),Cols1)}.
 
796
  {Cs, Cols1} = precolor0(Rs, Cols, Target),
 
797
  {[{R, {reg, physical_name(R, Target)}}|Cs], 
 
798
   set_color(R, physical_name(R, Target), Cols1)}.
808
799
 
809
800
physical_name(X, Target) ->
810
 
   Target:physical_name(X).
811
 
 
 
801
  Target:physical_name(X).