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

« back to all changes in this revision

Viewing changes to lib/hipe/ssa/hipe_ssa_copy_prop.inc

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%% -*- Erlang -*-
2
2
%%% -*- erlang-indent-level: 2 -*-
3
3
%%%-------------------------------------------------------------------
4
 
%%% File    : hipe_ssa_copy_prop.inc
5
 
%%% Author  : Tobias Lindahl <tobiasl@fan.it.uu.se>
6
 
%%% Description : Copy propagation on ssa form.
 
4
%%% File        : hipe_ssa_copy_prop.inc
 
5
%%% Author      : Tobias Lindahl <tobiasl@it.uu.se>
 
6
%%% Description : Copy propagation on SSA form.
7
7
%%%
8
 
%%% Created :  4 Apr 2003 by Tobias Lindahl <tobiasl@fan.it.uu.se>
 
8
%%% Created     :  4 Apr 2003 by Tobias Lindahl <tobiasl@it.uu.se>
9
9
%%%-------------------------------------------------------------------
10
10
 
11
11
-export([cfg/1]).
12
12
 
13
13
%%--------------------------------------------------------------------
14
 
%% Two passes through the code choosing the blocks in reverse
 
14
%% Two passes through the code visiting the blocks in reverse
15
15
%% postorder. The first pass binds all destinations of copying moves
16
 
%% to the sources and propagates the copies, the second propagates the
17
 
%% copies and removes the copying moves. 
18
 
%%
19
 
%% Copies must not be propagated across the point of redefinition of
20
 
%% the source variable. If the original value is used after the
21
 
%% redefinition we must use this value and cannot remove the copying
22
 
%% move.
23
 
%% %%--------------------------------------------------------------------
 
16
%% to the sources, and the second propagates the copies and removes 
 
17
%% the copying moves. 
 
18
%%
 
19
%% Problem:
 
20
%% Since phi-nodes are implemented as instructions they are not
 
21
%% atomic. If we are not careful we can get the situation (after propagation):
 
22
%%
 
23
%% v0 = phi(v0, v2)
 
24
%% v1 = phi(v0, v3)
 
25
%%          ^^
 
26
%% where the underlined v0 really corresponds to the v0 before the first 
 
27
%% phi-instruction.
 
28
%%
 
29
%% Solution: 
 
30
%% * Find all dependencies between the uses of a
 
31
%%   phi-instruction to the destination of any earlier phi-instruction
 
32
%%   in the same phi-node; 
 
33
%% * Keep the copying move/fmove that defines the variable used in the 
 
34
%%   latter phi-instruction; and 
 
35
%% * Do not propagate the copy into the phi-instruction
 
36
%%
 
37
%%--------------------------------------------------------------------
24
38
 
25
 
cfg(Cfg)->
 
39
cfg(Cfg) ->
26
40
  Labels = ?cfg:reverse_postorder(Cfg),
27
 
  {Info, NewCfg1} = propagate(Labels, Cfg, gb_trees:empty(), fun first_pass/3),
28
 
  {_, NewCfg2} = propagate(Labels, NewCfg1, Info, fun second_pass/3),
29
 
  NewCfg2.
 
41
  {Info,PhiDep} = analyse(Labels, Cfg, gb_trees:empty(), gb_sets:empty()),
 
42
  rewrite(Labels, Cfg, Info, PhiDep).
30
43
 
31
 
propagate([Label|Left], Cfg, Info, Fun)->
 
44
analyse([Label|Left], Cfg, Info, PhiDep) ->
32
45
  BB = ?cfg:bb(Cfg, Label),
33
46
  Code = hipe_bb:code(BB),
34
 
  {NewInfo, NewCode} = Fun(Code, Info, []),
35
 
  NewBB = hipe_bb:code_update(BB, NewCode),
36
 
  propagate(Left, ?cfg:bb_update(Cfg, Label, NewBB), NewInfo, Fun);
37
 
propagate([], Cfg, Info, _Fun) ->
38
 
  {Info, Cfg}.
39
 
 
40
 
first_pass([I|Left], Info, Acc)->
41
 
  case ?code:type(I) of
42
 
    mov ->
43
 
      NewInfo = get_info_mov_or_fmov(I, Info),
44
 
      first_pass(Left, NewInfo, [I|Acc]);
45
 
    fmov ->
46
 
      NewInfo = get_info_mov_or_fmov(I, Info),
47
 
      first_pass(Left, NewInfo, [I|Acc]);
48
 
    _ ->
49
 
      {_, NewI} = propagate_instr(I, Info),
50
 
      first_pass(Left, Info, [NewI|Acc])
51
 
  end;
52
 
first_pass([], Info, Acc) ->
53
 
  {Info, lists:reverse(Acc)}.
54
 
 
55
 
get_info_mov_or_fmov(I, Info)->
 
47
  NewPhiDep = get_phi_dep(Code, gb_sets:empty(), PhiDep),
 
48
  NewInfo = analyse_code(Code, Info),
 
49
  analyse(Left, Cfg, NewInfo, NewPhiDep);
 
50
analyse([], _Cfg, Info, PhiDep) ->
 
51
  {Info,PhiDep}.
 
52
 
 
53
get_phi_dep([I|Left], Defined, Dep) ->
 
54
  case I of
 
55
    #phi{} ->
 
56
      Use = ?code:uses(I),
 
57
      [Def] = ?code:defines(I),
 
58
      NewDep = add_dep(Use, Defined, Dep),
 
59
      get_phi_dep(Left, gb_sets:insert(Def, Defined), NewDep);
 
60
    _ ->
 
61
      Dep
 
62
  end;
 
63
get_phi_dep([], _Defined, Dep) ->
 
64
  Dep.
 
65
 
 
66
add_dep([Use|Left], Defined, Dep) ->
 
67
  case gb_trees:lookup(Use, Dep) of
 
68
    none ->
 
69
      add_dep(Left, Defined, gb_trees:insert(Use, Defined, Dep));
 
70
    {value, Set} ->
 
71
      NewSet = gb_sets:union(Defined, Set),
 
72
      add_dep(Left, Defined, gb_trees:enter(Use, NewSet, Dep))
 
73
  end;
 
74
add_dep([], _Defined, Dep) ->
 
75
  Dep.
 
76
 
 
77
has_dep(Use, Def, Dep) ->
 
78
  case gb_trees:lookup(Use, Dep) of
 
79
    none ->
 
80
      false;
 
81
    {value, Set} ->
 
82
      gb_sets:is_member(Def, Set)
 
83
  end.
 
84
 
 
85
analyse_code([I|Left], Info) ->
 
86
  case I of
 
87
    #move{} ->
 
88
      NewInfo = get_info_move_or_fmove(I, Info),
 
89
      analyse_code(Left, NewInfo);
 
90
    #fmove{} ->
 
91
      NewInfo = get_info_move_or_fmove(I, Info),
 
92
      analyse_code(Left, NewInfo);
 
93
    _ ->
 
94
      analyse_code(Left, Info)
 
95
  end;
 
96
analyse_code([], Info) ->
 
97
  Info.
 
98
 
 
99
get_info_move_or_fmove(I, Info) ->
56
100
  case ?code:uses(I) of
57
101
    [] -> %% Constant.
58
102
      Info;
60
104
      add_binding(?code:defines(I), Src, Info)
61
105
  end.
62
106
 
63
 
second_pass([I|Left], Info, Acc)->
64
 
  case ?code:type(I) of
65
 
    mov ->
66
 
      NewI = propagate_mov_or_fmov(I, Info),
67
 
      second_pass(Left, Info, NewI++Acc);
68
 
    fmov ->
69
 
      NewI = propagate_mov_or_fmov(I, Info),
70
 
      second_pass(Left, Info, NewI++Acc);
 
107
rewrite([Label|Left], Cfg, Info, PhiDep) ->
 
108
  BB = ?cfg:bb(Cfg, Label),
 
109
  Code = hipe_bb:code(BB),
 
110
  NewCode = rewrite_code(Code, Info, PhiDep, []),
 
111
  NewBB = hipe_bb:code_update(BB, NewCode),
 
112
  rewrite(Left, ?cfg:bb_add(Cfg, Label, NewBB), Info, PhiDep);
 
113
rewrite([], Cfg, _Info, _PhiDep) ->
 
114
  Cfg.
 
115
 
 
116
rewrite_code([I|Left], Info, PhiDep, Acc) ->
 
117
  case I of
 
118
    #move{} ->
 
119
      Fun = fun(X, Y) -> ?code:mk_move(X, Y)end,
 
120
      NewI = rewrite_move_or_fmove(I, Fun, Info, PhiDep),
 
121
      rewrite_code(Left, Info, PhiDep, NewI++Acc);
 
122
    #fmove{} ->
 
123
      Fun = fun(X, Y) -> ?code:mk_fmove(X, Y)end,
 
124
      NewI = rewrite_move_or_fmove(I, Fun, Info, PhiDep),
 
125
      rewrite_code(Left, Info, PhiDep, NewI++Acc);
71
126
    _ ->      
72
 
      {NewInfo1, NewI} = propagate_instr(I, Info),
73
 
      NewInfo2 = add_binding(?code:defines(I), 'redefined', NewInfo1),
74
 
      second_pass(Left, NewInfo2, [NewI|Acc])
 
127
      NewI = rewrite_instr(I, Info, PhiDep),
 
128
      rewrite_code(Left, Info, PhiDep, [NewI|Acc])
75
129
  end;
76
 
second_pass([], Info, Acc) ->
77
 
  {Info, lists:reverse(Acc)}.
 
130
rewrite_code([], _Info, _PhiDep, Acc) ->
 
131
  lists:reverse(Acc).
78
132
 
79
 
propagate_mov_or_fmov(I, Info)->
 
133
rewrite_move_or_fmove(I, Fun, Info, PhiDep) ->
80
134
  case ?code:uses(I) of
81
 
    [] ->%% Constant
 
135
    [] ->%% Constant move. Keep it!
82
136
      [I];
83
137
    _ ->
84
 
      case gb_trees:lookup(hd(?code:defines(I)), Info) of
85
 
        none -> %% We must keep this instruction.
86
 
          [I];
87
 
        _ ->
 
138
      Dst = hd(?code:defines(I)),
 
139
      case gb_trees:lookup(Dst, Info) of
 
140
        {value, Root} -> 
 
141
          case has_dep(Dst, Root, PhiDep) of
 
142
            true -> %% Must keep the copying move!
 
143
              [Fun(Dst, Root)];
 
144
            false -> 
 
145
              []
 
146
          end;
 
147
        none -> 
88
148
          []
89
149
      end
90
150
  end.
91
151
 
92
 
propagate_instr(I, Info)->
93
 
  propagate_instr0(I, ?code:uses(I), Info, []).
94
 
 
95
 
propagate_instr0(I, [Key|Left], Info, UpdateInfo)->
 
152
 
 
153
rewrite_instr(I, Info, PhiDep) ->
 
154
  rewrite_instr0(I, ?code:uses(I), Info, PhiDep, []).
 
155
 
 
156
rewrite_instr0(I, [Key|Left], Info, PhiDep, UpdateInfo) ->
96
157
  case gb_trees:lookup(Key, Info) of
97
 
    {value, 'redefined'} ->
98
 
      propagate_instr0(I, Left, Info, UpdateInfo);
99
 
    {value, Val} ->
100
 
      case  gb_trees:lookup(Val, Info) of
101
 
        {value, 'redefined'} ->
102
 
          %%Remove the binding to show that the copying move cannot be removed.
103
 
          propagate_instr0(I, Left, gb_trees:delete(Key, Info), UpdateInfo);
 
158
    none ->
 
159
      rewrite_instr0(I, Left, Info, PhiDep, UpdateInfo);
 
160
    {value, Root} -> 
 
161
      case gb_trees:lookup(Key, Info) of
 
162
        {value, Root} -> 
 
163
          case has_dep(Key, Root, PhiDep) of
 
164
            true -> %% Must keep Key!
 
165
              rewrite_instr0(I, Left, Info, PhiDep, UpdateInfo);
 
166
            false ->
 
167
              rewrite_instr0(I, Left, Info, PhiDep, [{Key, Root}|UpdateInfo])
 
168
          end;
104
169
        _ ->
105
 
          propagate_instr0(I, Left, Info, [{Key, Val}|UpdateInfo])
106
 
      end;
107
 
    _ ->
108
 
      propagate_instr0(I, Left, Info, UpdateInfo)
 
170
          rewrite_instr0(I, Left, Info, PhiDep, UpdateInfo)
 
171
      end
109
172
  end;
110
 
propagate_instr0(I, [], Info, UpdateInfo)->
111
 
  {Info, ?code:subst(UpdateInfo, I)}.
 
173
rewrite_instr0(I, [], _Info, _PhiDep, UpdateInfo) ->
 
174
  ?code:subst(UpdateInfo, I).
112
175
 
113
 
add_binding([Key|Left], Val, Info)->
 
176
add_binding([Key|Left], Val, Info) ->
114
177
  %% Make sure the key is bound to the end of any copy-chains.
115
178
  NewInfo = 
116
179
    case gb_trees:lookup(Val, Info) of
122
185
  add_binding(Left, Val, NewInfo);
123
186
add_binding([], _, Info) ->
124
187
  Info.
 
188
 
 
189
%% Returns the root of a 
 
190
%lookup_binding(Key, Info)->
 
191
%  case gb_trees:lookup(Key, Info) of
 
192
%    {value, Val} ->
 
193
%      case  gb_trees:lookup(Val, Info) of
 
194
%       {value, Root} ->
 
195
%         {value, Root};
 
196
%       none ->
 
197
%         {value, Val}
 
198
%      end;
 
199
%    none ->
 
200
%      none
 
201
%  end.