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

« back to all changes in this revision

Viewing changes to lib/hipe/ssa/hipe_ssa_liveness.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
%% -*- Erlang -*-
 
2
%% -*- erlang-indent-level: 2 -*-
 
3
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
4
%%
 
5
%% GENERIC MODULE TO PERFORM LIVENESS ANALYSIS ON SSA FORM
 
6
%%
 
7
%% Exports:
 
8
%% ~~~~~~~
 
9
%% analyze(CFG) - returns a liveness analysis of CFG.
 
10
%% liveout(Liveness, Label) - returns the list of variables that are
 
11
%%      live at exit from basic block named Label.
 
12
%% livein(Liveness, Label) - returns the list of variables that are
 
13
%%      live on entry to the basic block named Label.
 
14
%%
 
15
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
16
 
 
17
%% Uncomment the following if this is ever needed as an independent module
 
18
%%
 
19
-ifdef(LIVENESS_NEEDED).
 
20
-export([ssa_liveness__analyze/1,
 
21
         ssa_liveness__livein/3]).
 
22
%%       ssa_liveness__liveout/2]).
 
23
-endif.
 
24
%% -ifdef(DEBUG_LIVENESS).
 
25
%% -export([pp_liveness/1]).
 
26
%% -endif.
 
27
 
 
28
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
29
%%
 
30
%% Interface functions that MUST be implemented in the supporting files
 
31
%%
 
32
%% In the CFG file:
 
33
%% ----------------
 
34
%%  - bb(CFG, L) -> BasicBlock, extract a basic block from a cfg.
 
35
%%  - postorder(CFG) -> [Labels], the labels of the cfg in postorder
 
36
%%  - succ_map(CFG) -> SuccMap, a successor mapping.
 
37
%%  - succ(SuccMap, L) -> [Labels], 
 
38
%%  - function(CFG) -> {M,F,A}
 
39
%%
 
40
%% In the CODE file:
 
41
%% ----------------- 
 
42
%%  - uses(Instr) ->
 
43
%%  - defines(Instr) ->
 
44
%%  - is_phi(Instr) -> Boolean
 
45
%%  - phi_arglist(Instr) -> [{Pred, Var}]
 
46
 
 
47
 
 
48
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
49
%%
 
50
%% The generic liveness analysis on SSA form
 
51
%%
 
52
ssa_liveness__analyze(CFG) ->
 
53
  PO = ?CFG:postorder(CFG),
 
54
  InitLiveness = liveness_init(init(PO, CFG)),
 
55
  merry_go_around(PO, InitLiveness).
 
56
 
 
57
%%
 
58
%% The fixpoint iteration
 
59
%%
 
60
 
 
61
merry_go_around(Labels, Liveness) ->
 
62
  case doit_once(Labels, Liveness) of
 
63
    {fixpoint, NewLiveness} -> 
 
64
      NewLiveness;
 
65
    {value, NewLiveness} -> 
 
66
      merry_go_around(Labels, NewLiveness)
 
67
  end.
 
68
 
 
69
%%
 
70
%% One iteration
 
71
%%
 
72
 
 
73
doit_once(Labels, Liveness) ->
 
74
  doit_once(Labels, Liveness, true).
 
75
 
 
76
doit_once([], Liveness, FixPoint) ->
 
77
  if FixPoint -> {fixpoint, Liveness};
 
78
     true -> {value, Liveness}
 
79
  end;
 
80
doit_once([L|Ls], Liveness, FixPoint) ->
 
81
  LiveOut = join_livein(Liveness, L),
 
82
  NewLiveness = update_liveout(L, LiveOut, Liveness),
 
83
  Kill = set_subtract(LiveOut, kill(L, NewLiveness)),
 
84
  LiveIn = set_union(Kill, gen(L,NewLiveness)),
 
85
  case update_livein(L, LiveIn, NewLiveness) of
 
86
    fixpoint -> doit_once(Ls, NewLiveness, FixPoint);
 
87
    {value, NewLiveness1} -> doit_once(Ls, NewLiveness1, false)
 
88
  end.
 
89
      
 
90
%%
 
91
%% updates liveness for a basic block
 
92
%%
 
93
 
 
94
update_livein(Label, NewLiveIn, Liveness) ->
 
95
  {GKD, LiveIn, LiveOut, Succ} = liveness_lookup(Label, Liveness),
 
96
  case LiveIn of
 
97
    NewLiveIn -> 
 
98
      fixpoint;
 
99
    _ -> 
 
100
      {value, liveness_update(Label, {GKD,NewLiveIn,LiveOut,Succ}, Liveness)}
 
101
  end.
 
102
 
 
103
update_liveout(Label, NewLiveOut, Liveness) ->
 
104
  {GKD, LiveIn, _LiveOut, Succ} = liveness_lookup(Label, Liveness),
 
105
  liveness_update(Label, {GKD,LiveIn,NewLiveOut,Succ}, Liveness).
 
106
 
 
107
%%
 
108
%% Join Live in to get the new live out.
 
109
%%
 
110
 
 
111
join_livein(Liveness, L) ->
 
112
  Succ = successors(L, Liveness),
 
113
  case Succ of
 
114
    [] ->    % special case if no successors
 
115
      gb_sets:from_list(liveout_no_succ());
 
116
    _ ->
 
117
      join_livein1(L, Succ, Liveness)
 
118
  end.
 
119
 
 
120
join_livein1(Pred, Labels, Liveness) ->
 
121
  join_livein1(Pred, Labels, Liveness, new_set()).
 
122
 
 
123
join_livein1(_Pred, [], _Liveness, Live) ->
 
124
  Live;
 
125
join_livein1(Pred, [L|Ls], Liveness, Live) ->
 
126
  OldLivein = livein_set(Liveness, L, Pred),
 
127
  NewLive = set_union(OldLivein, Live),
 
128
  join_livein1(Pred, Ls, Liveness, NewLive).
 
129
 
 
130
 
 
131
ssa_liveness__liveout(Liveness, L) ->
 
132
  {_GKD, _LiveIn, LiveOut, Successors} = liveness_lookup(L, Liveness),
 
133
  case Successors of
 
134
    [] ->  % special case if no successors
 
135
      liveout_no_succ();
 
136
    _ ->
 
137
      set_to_list(LiveOut)
 
138
  end.  
 
139
 
 
140
-ifdef(LIVENESS_NEEDED).
 
141
ssa_liveness__livein(Liveness, L, Pred) ->
 
142
  set_to_list(livein_set(Liveness, L, Pred)).
 
143
-endif.
 
144
 
 
145
livein_set(Liveness, L, Pred) ->
 
146
  {{_Gen,_Kill,DirGen}, LiveIn, _LiveOut, _Successors} = 
 
147
    liveness_lookup(L, Liveness),
 
148
  case gb_trees:lookup(Pred, DirGen) of
 
149
    none ->
 
150
      LiveIn;
 
151
    {value, LiveInFromPred} ->
 
152
      set_union(LiveInFromPred, LiveIn)
 
153
  end.
 
154
 
 
155
successors(L, Liveness) ->
 
156
  {_GKD, _LiveIn, _LiveOut, Successors} = liveness_lookup(L, Liveness),
 
157
  Successors.
 
158
 
 
159
kill(L, Liveness) ->
 
160
  {{_Gen,Kill,_DirGen},_LiveIn,_LiveOut,_Successors} = 
 
161
    liveness_lookup(L, Liveness),
 
162
  Kill.
 
163
 
 
164
gen(L, Liveness) ->
 
165
  {{Gen,_Kill,_DirGen},_LiveIn,_LiveOut,_Successors} = 
 
166
    liveness_lookup(L, Liveness),
 
167
  Gen.
 
168
 
 
169
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
170
%%
 
171
%% init returns a list of: {Label, {{Gen, Kill}, LiveIn, Successors}}
 
172
%%    - Label is the name of the basic block.
 
173
%%    - Gen is the set of varables that are used by this block.
 
174
%%    - Kill is the set of varables that are defined by this block.
 
175
%%    - LiveIn is the set of variables that are alive at entry to the
 
176
%%      block (initially empty).
 
177
%%    - Successors is a list of the successors to the block.
 
178
 
 
179
init([], _) ->
 
180
  [];
 
181
init([L|Ls], CFG) ->
 
182
  BB = ?CFG:bb(CFG, L),
 
183
  Code = hipe_bb:code(BB),
 
184
  SuccMap = ?CFG:succ_map(CFG),
 
185
  Succ = ?CFG:succ(SuccMap, L),
 
186
  {Gen, Kill} = make_bb_transfer(Code, Succ),
 
187
  DirectedGen = get_directed_gen(Code),
 
188
  [{L, {{Gen, Kill, DirectedGen}, new_set(), new_set(), Succ}} 
 
189
   | init(Ls, CFG)].
 
190
 
 
191
make_bb_transfer([], _Succ) ->
 
192
  {new_set(), new_set()};   % {Gen, Kill}
 
193
make_bb_transfer([I|Is], Succ) ->
 
194
  {Gen, Kill} = make_bb_transfer(Is, Succ),
 
195
  case ?CODE:is_phi(I) of
 
196
    true ->
 
197
      InstrKill = set_from_list(?CODE:defines(I)),
 
198
      Gen1 = set_subtract(Gen, InstrKill),
 
199
      Kill1 = set_union(Kill, InstrKill),
 
200
      {Gen1, Kill1};
 
201
    false ->
 
202
      InstrGen = set_from_list(?CODE:uses(I)),
 
203
      InstrKill = set_from_list(?CODE:defines(I)),
 
204
      Gen1 = set_subtract(Gen, InstrKill),
 
205
      Gen2 = set_union(Gen1, InstrGen),
 
206
      Kill1 = set_union(Kill, InstrKill),
 
207
      Kill2 = set_subtract(Kill1, InstrGen),
 
208
      {Gen2, Kill2}
 
209
  end.
 
210
 
 
211
get_directed_gen([I|Left])->
 
212
  case ?CODE:is_phi(I) of
 
213
    false -> 
 
214
      gb_trees:empty();
 
215
    true -> 
 
216
      Map = get_directed_gen(Left),
 
217
      ArgList = ?CODE:phi_arglist(I),
 
218
      lists:foldl(fun update_directed_gen/2, Map, ArgList)
 
219
  end.
 
220
 
 
221
update_directed_gen({Pred, Var}, Map)->      
 
222
  case gb_trees:lookup(Pred, Map) of
 
223
    none -> gb_trees:insert(Pred, set_from_list([Var]), Map);
 
224
    {value, Set} -> gb_trees:update(Pred, set_add(Var, Set), Map)
 
225
  end.
 
226
       
 
227
 
 
228
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
229
%%
 
230
%% liveness
 
231
%%
 
232
 
 
233
liveness_init(List) ->
 
234
  liveness_init1(List, gb_trees:empty()).
 
235
 
 
236
liveness_init1([{Label, Info}|Left], Map) ->
 
237
  liveness_init1(Left, gb_trees:insert(Label, Info, Map));
 
238
liveness_init1([], Map) ->
 
239
  Map.
 
240
 
 
241
liveness_lookup(Label, Map) ->
 
242
  {value, Info} = gb_trees:lookup(Label, Map),
 
243
  Info.
 
244
 
 
245
liveness_update(Label, NewInfo, Map) ->
 
246
  gb_trees:update(Label, NewInfo, Map).
 
247
 
 
248
 
 
249
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
250
%%
 
251
%% Sets
 
252
%%
 
253
 
 
254
new_set() ->
 
255
  gb_sets:empty().
 
256
 
 
257
set_union(S1, S2) ->
 
258
  gb_sets:union(S1, S2).
 
259
 
 
260
set_subtract(S1, S2) ->
 
261
  gb_sets:subtract(S1, S2).
 
262
 
 
263
set_from_list(List) ->
 
264
  gb_sets:from_list(List).
 
265
 
 
266
set_to_list(Set) ->
 
267
  gb_sets:to_list(Set).
 
268
 
 
269
set_add(Var, Set) ->
 
270
  gb_sets:add(Var, Set).
 
271
 
 
272
 
 
273
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
274
%%
 
275
%% Pretty printer
 
276
%%
 
277
 
 
278
-ifdef(DEBUG_LIVENESS).
 
279
 
 
280
pp_liveness(Cfg) ->
 
281
  io:format("Liveness for ~p:\n", [?CFG:function(Cfg)]),
 
282
  Liveness = analyze(Cfg),
 
283
  RevPostorder = lists:reverse(?CFG:postorder(Cfg)),
 
284
  SuccMap = ?CFG:succ_map(Cfg),
 
285
  Edges = [{X, Y} || X <- RevPostorder, Y <- ?CFG:succ(SuccMap, X)],
 
286
  pp_liveness_edges(Edges, Liveness).
 
287
 
 
288
pp_liveness_edges([{From, To}|Left], Liveness)->
 
289
  LiveIn = livein(Liveness, To, From),
 
290
  io:format("Label ~w -> Label ~w: ~p\n", [From, To, LiveIn]),
 
291
  LiveOut = liveout(Liveness, From),
 
292
  io:format("Total live out from Label ~w: ~p\n", [From, LiveOut]),
 
293
  pp_liveness_edges(Left, Liveness);
 
294
pp_liveness_edges([], _Liveness) ->
 
295
  ok.
 
296
 
 
297
-endif.