~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
55
55
 
56
56
regalloc(CFG, SpillIndex, SpillLimit, Target, _Options) ->
57
57
  %% Build interference graph
58
 
  ?debug_msg("Build IG\n",[]),
 
58
  ?debug_msg("Build IG\n", []),
59
59
  IG = hipe_ig:build(CFG, Target),
60
 
  %% io:format("IG: ~p\n",[IG]),
 
60
  %% io:format("IG: ~p\n", [IG]),
61
61
 
62
 
  ?debug_msg("Init\n",[]),
 
62
  ?debug_msg("Init\n", []),
63
63
  Num_Temps = Target:number_of_temporaries(CFG),
64
64
  ?debug_msg("Coalescing RA: num_temps = ~p~n", [Num_Temps]),
65
65
  Allocatable = Target:allocatable(),
67
67
  All_colors = colset_from_list(Allocatable),
68
68
 
69
69
  %% Add registers with their own coloring
70
 
  ?debug_msg("Moves\n",[]),
 
70
  ?debug_msg("Moves\n", []),
71
71
  Move_sets = hipe_moves:new(IG),
72
72
 
73
 
  ?debug_msg("Build Worklist\n",[]),
 
73
  ?debug_msg("Build Worklist\n", []),
74
74
  Worklists = hipe_reg_worklists:new(IG, Target, CFG, Move_sets, K, Num_Temps),
75
75
  Alias = initAlias(Num_Temps),
76
76
 
77
 
  ?debug_msg("Do coloring\n~p~n",[Worklists]),
 
77
  ?debug_msg("Do coloring\n~p~n", [Worklists]),
78
78
  {_IG0, Worklists0, _Moves0, Alias0} = 
79
79
    do_coloring(IG, Worklists, Move_sets, Alias, K, SpillLimit, Target),
80
80
  %% io:format("SelStk0 ~w\n",[SelStk0]),
81
 
  ?debug_msg("Init node sets\n",[]),
 
81
  ?debug_msg("Init node sets\n", []),
82
82
  Node_sets = hipe_node_sets:new(),
83
83
  %% io:format("NodeSet: ~w\n NonAlloc ~w\n",[Node_sets,Target:non_alloc(CFG)]),
84
 
  ?debug_msg("Default coloring\n",[]),
 
84
  ?debug_msg("Default coloring\n", []),
85
85
  {Color0,Node_sets1} = 
86
86
    defaultColoring(Target:all_precoloured(),
87
87
                    initColor(Num_Temps), Node_sets, Target),
88
88
 
89
 
  ?debug_msg("Assign colors\n",[]),
 
89
  ?debug_msg("Assign colors\n", []),
90
90
  {Color1,Node_sets2} =
91
91
    assignColors(hipe_reg_worklists:stack(Worklists0), Node_sets1, Color0, 
92
92
                 Alias0, All_colors, Target),
93
93
  %% io:format("color0:~w\nColor1:~w\nNodes:~w\nNodes2:~w\nNum_Temps:~w\n",[Color0,Color1,Node_sets,Node_sets2,Num_Temps]),
94
94
 
95
 
  ?debug_msg("Build mapping ~p\n",[Node_sets2]),
 
95
  ?debug_msg("Build mapping ~p\n", [Node_sets2]),
96
96
  Coloring = build_namelist(Node_sets2, SpillIndex, Alias0, Color1),
97
 
  ?debug_msg("Coloring ~p\n",[Coloring]),
 
97
  ?debug_msg("Coloring ~p\n", [Coloring]),
98
98
  Coloring.
99
99
 
100
100
%%----------------------------------------------------------------------
131
131
                 Worklists, 
132
132
                 Moves, 
133
133
                 K),
134
 
      do_coloring(IG0, Worklists0, Moves0, Alias,
135
 
                  K, SpillLimit, Target);
 
134
      do_coloring(IG0, Worklists0, Moves0, Alias, K, SpillLimit, Target);
136
135
     Coalesce =:= true ->
137
136
      {Moves0, IG0, Worklists0, Alias0} =
138
137
        coalesce(Moves, IG, Worklists, Alias, K, Target),
139
 
      do_coloring(IG0, Worklists0, Moves0, Alias0, 
140
 
                  K, SpillLimit, Target);
 
138
      do_coloring(IG0, Worklists0, Moves0, Alias0, K, SpillLimit, Target);
141
139
     Freeze =:= true ->
142
140
      {Worklists0,Moves0} = 
143
141
        freeze(K, Worklists, Moves, IG, Alias),
146
144
     Spill =:= true ->
147
145
      {Worklists0, Moves0} = 
148
146
        selectSpill(Worklists, Moves, IG, K, Alias, SpillLimit),
149
 
      do_coloring(IG, Worklists0, Moves0, Alias, 
150
 
                  K, SpillLimit, Target);
 
147
      do_coloring(IG, Worklists0, Moves0, Alias, K, SpillLimit, Target);
151
148
     true -> % Catchall case
152
149
      {IG, Worklists, Moves, Alias}
153
150
    end.
324
321
  AC = getColor(getAlias(Node, Alias), Color),
325
322
  build_coalescedlist(Ns, Color, Alias, [{Node,{reg,AC}}|List]).
326
323
 
327
 
build_reglist([],_Color,List) -> 
 
324
build_reglist([], _Color, List) -> 
328
325
  List;
329
 
build_reglist([Node|Ns],Color,List) ->
330
 
  build_reglist(Ns,Color,[{Node,{reg,getColor(Node,Color)}}|List]).
 
326
build_reglist([Node|Ns], Color, List) ->
 
327
  build_reglist(Ns, Color, [{Node,{reg,getColor(Node,Color)}}|List]).
331
328
 
332
 
build_alias_list([],_I,List) ->
 
329
build_alias_list([], _I, List) ->
333
330
  List;
334
 
build_alias_list([Alias|Aliases],I,List) when is_integer(Alias) ->
335
 
  build_alias_list(Aliases,I+1,[I|List]);
336
 
build_alias_list([_Alias|Aliases],I,List) ->
337
 
  build_alias_list(Aliases,I+1,List).
 
331
build_alias_list([Alias|Aliases], I, List) when is_integer(Alias) ->
 
332
  build_alias_list(Aliases, I+1, [I|List]);
 
333
build_alias_list([_Alias|Aliases], I, List) ->
 
334
  build_alias_list(Aliases, I+1, List).
338
335
 
339
336
%%----------------------------------------------------------------------
340
337
%% Function:    assignColors
359
356
%%   NodeSets       --  The updated node sets.
360
357
%%----------------------------------------------------------------------
361
358
 
362
 
assignColors(Stack,NodeSets,Color,Alias,AllColors,Target) ->
 
359
assignColors(Stack, NodeSets, Color, Alias, AllColors, Target) ->
363
360
  case Stack of
364
361
    [] ->
365
362
      {Color,NodeSets};
401
398
%%   NewNodeSets    -- The updated node sets
402
399
%%---------------------------------------------------------------------
403
400
 
404
 
defaultColoring([],Color,NodeSets,_Target) ->
 
401
defaultColoring([], Color, NodeSets, _Target) ->
405
402
  {Color,NodeSets};
406
 
defaultColoring([Reg|Regs],Color,NodeSets,Target) ->
407
 
  Color1 = setColor(Reg,Target:physical_name(Reg),Color),
 
403
defaultColoring([Reg|Regs], Color, NodeSets, Target) ->
 
404
  Color1 = setColor(Reg,Target:physical_name(Reg), Color),
408
405
  NodeSets1 = hipe_node_sets:add_colored(Reg, NodeSets),
409
 
  defaultColoring(Regs,Color1,NodeSets1,Target).
 
406
  defaultColoring(Regs, Color1, NodeSets1, Target).
410
407
 
411
408
%% Find the colors that are OK for a node with certain edges.
412
409
 
413
 
findOkColors(Edges,AllColors,Color,Alias) ->
 
410
findOkColors(Edges, AllColors, Color, Alias) ->
414
411
  find(Edges, AllColors, Color, Alias).
415
412
 
416
413
%% Find all the colors of the nodes in the list [Node|Nodes] and remove them 
417
414
%% from the set OkColors, when the list is empty, return OkColors.
418
415
 
419
 
find([],OkColors,_Color,_Alias) ->
 
416
find([], OkColors, _Color, _Alias) ->
420
417
  OkColors;
421
 
find([Node0|Nodes],OkColors,Color,Alias) ->
 
418
find([Node0|Nodes], OkColors, Color, Alias) ->
422
419
  Node = getAlias(Node0, Alias),
423
420
  case getColor(Node, Color) of
424
421
    [] ->
425
 
      find(Nodes,OkColors,Color,Alias);
 
422
      find(Nodes, OkColors, Color, Alias);
426
423
    Col ->
427
424
      OkColors1 = colset_del_element(Col, OkColors),
428
 
      find(Nodes,OkColors1,Color,Alias)
 
425
      find(Nodes, OkColors1, Color, Alias)
429
426
  end.
430
427
 
431
428
%%%
504
501
initColor(NrNodes) ->
505
502
  {colmap, hipe_bifs:array(NrNodes, [])}.
506
503
 
507
 
getColor(Node, {colmap,ColMap}) ->
 
504
getColor(Node, {colmap, ColMap}) ->
508
505
  hipe_bifs:array_sub(ColMap, Node).
509
506
 
510
 
setColor(Node, Colour, {colmap,ColMap}) ->
 
507
setColor(Node, Colour, {colmap, ColMap} = Col) ->
511
508
  hipe_bifs:array_update(ColMap, Node, Colour),  
512
 
  {colmap, ColMap}.
 
509
  Col.
513
510
 
514
511
%%%
515
512
%%% Alias ADT providing a partial mapping from nodes to nodes.
526
523
      getAlias(AliasNode, {alias,AliasMap})
527
524
  end.
528
525
 
529
 
setAlias(Node, AliasNode, {alias,AliasMap}) ->
 
526
setAlias(Node, AliasNode, {alias, AliasMap} = Alias) ->
530
527
  hipe_bifs:array_update(AliasMap, Node, AliasNode),
531
 
  {alias, AliasMap}.
 
528
  Alias.
532
529
 
533
530
aliasToList({alias,AliasMap}) ->
534
531
  aliasToList(AliasMap, hipe_bifs:array_length(AliasMap), []).
843
840
        true -> conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt);
844
841
        _ ->
845
842
          Cnt1 = Cnt + 1,
846
 
          if Cnt1 < K -> conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt1);
 
843
          if Cnt1 < K ->
 
844
              conservative_countU(AdjU, AdjV, U, Worklists, IG, K, Cnt1);
847
845
             true -> false
848
846
          end
849
847
      end
861
859
            true -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt);
862
860
            _ ->
863
861
              Cnt1 = Cnt + 1,
864
 
              if Cnt1 < K -> conservative_countV(AdjV, U, Worklists, IG, K, Cnt1);
 
862
              if Cnt1 < K ->
 
863
                  conservative_countV(AdjV, U, Worklists, IG, K, Cnt1);
865
864
                 true -> false
866
865
              end
867
866
          end
888
887
selectSpill(WorkLists, Moves, IG, K, Alias, SpillLimit) ->
889
888
  [CAR|CDR] = hipe_reg_worklists:spill(WorkLists),
890
889
  
891
 
  SpillCost = getCost(CAR, IG,SpillLimit),
892
 
  M = findCheapest(CDR,IG,SpillCost,CAR, SpillLimit),
 
890
  SpillCost = getCost(CAR, IG, SpillLimit),
 
891
  M = findCheapest(CDR, IG, SpillCost, CAR, SpillLimit),
893
892
  
894
893
  WorkLists1 = hipe_reg_worklists:remove_spill(M, WorkLists),
895
894
  %% The published algorithm adds M to the simplify worklist
917
916
 
918
917
getCost(Node, IG, SpillLimit) ->
919
918
  case Node > SpillLimit of
920
 
    true ->  inf;
 
919
    true -> inf;
921
920
    false -> hipe_ig:node_spill_cost(Node, IG)
922
921
  end.
923
922
 
942
941
%%   Moves          -- The updated movelists
943
942
%%----------------------------------------------------------------------
944
943
 
945
 
freeze(K,WorkLists,Moves,IG,Alias) ->
 
944
freeze(K, WorkLists, Moves, IG, Alias) ->
946
945
  [U|_] = hipe_reg_worklists:freeze(WorkLists),         % Smarter routine?
947
 
  ?debug_msg("freezing node ~p~n",[U]),
 
946
  ?debug_msg("freezing node ~p~n", [U]),
948
947
  WorkLists0 = hipe_reg_worklists:remove_freeze(U, WorkLists),
949
948
  %% The published algorithm adds U to the simplify worklist
950
949
  %% before the freezeMoves() call. That breaks the worklist
973
972
%%   Moves          -- The updated movelists
974
973
%%----------------------------------------------------------------------
975
974
 
976
 
freezeMoves(U,K,WorkLists,Moves,IG,Alias) ->
 
975
freezeMoves(U, K, WorkLists, Moves, IG, Alias) ->
977
976
  Nodes = hipe_moves:node_moves(U, Moves),
978
 
  freezeEm(U,Nodes,K,WorkLists,Moves,IG,Alias).
 
977
  freezeEm(U, Nodes, K, WorkLists, Moves, IG, Alias).
979
978
 
980
979
%% Find what the other value in a copy instruction is, return false if 
981
980
%% the instruction isn't a move with the first argument in it.
998
997
     true -> exit({?MODULE,moves}) % XXX: shouldn't happen
999
998
  end.
1000
999
 
1001
 
freezeEm(_U,[],_K,WorkLists,Moves,_IG,_Alias) -> 
 
1000
freezeEm(_U, [], _K, WorkLists, Moves, _IG, _Alias) ->
1002
1001
  {WorkLists,Moves};
1003
 
freezeEm(U,[M|Ms],K,WorkLists,Moves,IG,Alias) ->
 
1002
freezeEm(U,[M|Ms], K, WorkLists, Moves, IG, Alias) ->
1004
1003
  V = moves(U, M, Alias, Moves),
1005
 
  {WorkLists2,Moves2} = freezeEm2(U,V,M,K,WorkLists,Moves,IG,Alias),
1006
 
  freezeEm(U,Ms,K,WorkLists2,Moves2,IG,Alias).
 
1004
  {WorkLists2,Moves2} = freezeEm2(U, V, M, K, WorkLists, Moves, IG, Alias),
 
1005
  freezeEm(U, Ms, K, WorkLists2, Moves2, IG, Alias).
1007
1006
 
1008
 
freezeEm2(U,V,M,K,WorkLists,Moves,IG,Alias) ->
 
1007
freezeEm2(U, V, M, K, WorkLists, Moves, IG, Alias) ->
1009
1008
  case hipe_moves:member_active(M, Moves) of
1010
1009
    true ->
1011
1010
      Moves1 = hipe_moves:remove_active(M, Moves),
1012
 
      freezeEm3(U,V,M,K,WorkLists,Moves1,IG,Alias);     
 
1011
      freezeEm3(U, V, M, K, WorkLists, Moves1, IG, Alias);      
1013
1012
    false ->
1014
1013
      Moves1 = hipe_moves:remove_worklist(M, Moves),
1015
 
      freezeEm3(U,V,M,K,WorkLists,Moves1,IG,Alias)
 
1014
      freezeEm3(U, V, M, K, WorkLists, Moves1, IG, Alias)
1016
1015
  end.
1017
1016
 
1018
 
freezeEm3(_U,V,_M,K,WorkLists,Moves,IG,_Alias) ->
 
1017
freezeEm3(_U, V, _M, K, WorkLists, Moves, IG, _Alias) ->
1019
1018
  Moves1 = Moves, % drop frozen move M
1020
1019
  V1 = V, % getAlias(V,Alias),
1021
1020
  %% "not MoveRelated(v)" is cheaper than "NodeMoves(v) = {}"
1022
 
  case ((not hipe_moves:move_related(V1,Moves1)) andalso
1023
 
        hipe_ig:is_trivially_colourable(V1,K,IG)) of
 
1021
  case ((not hipe_moves:move_related(V1, Moves1)) andalso
 
1022
        hipe_ig:is_trivially_colourable(V1, K, IG)) of
1024
1023
    true ->
1025
1024
      ?debug_msg("freezing move to ~p~n", [V]),
1026
1025
      Worklists1 = hipe_reg_worklists:transfer_freeze_simplify(V1, WorkLists),
1027
 
      {Worklists1,Moves1};
 
1026
      {Worklists1, Moves1};
1028
1027
    false ->
1029
 
      {WorkLists,Moves1}
 
1028
      {WorkLists, Moves1}
1030
1029
  end.