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

« back to all changes in this revision

Viewing changes to lib/hipe/flow/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
1
%% -*- Erlang -*-
2
2
%% -*- erlang-indent-level: 2 -*-
3
 
 
4
3
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
5
4
%%
6
5
%% LIVENESS ANALYSIS
7
6
%%
8
7
%% Exports:
9
8
%% ~~~~~~~
10
 
%% analyze(CFG) - returns a livenes analyzis of CFG.
11
 
%% liveout(Liveness, Label) - returns a set of variables that are alive at
 
9
%% analyze(CFG) - returns a liveness analysis of CFG.
 
10
%% liveout(Liveness, Label) - returns a set of variables that are live at
12
11
%%      exit from basic block named Label.
13
 
%% livein(Liveness, Label) - returns a set of variables that are alive at
 
12
%% livein(Liveness, Label) - returns a set of variables that are live at
14
13
%%      entry to the basic block named Label.
15
 
%% list(Instructions, LiveOut) - Given a list of instructions and a 
16
 
%%      liveout-set, returns a set of variables live at the first instruction.
 
14
%% livein_from_liveout(Instructions, LiveOut) - Given a list of instructions 
 
15
%%      and a liveout-set, returns a set of variables live at the 
 
16
%%      first instruction.
17
17
%%
18
18
 
19
19
-export([analyze/1,
20
 
         liveout/2,
21
 
         livein/2,
22
 
         list/2,
23
 
         annotate/2,
24
 
         update_livein/3]).
25
 
 
 
20
         livein/2]).
 
21
-ifdef(LIVEOUT_NEEDED).
 
22
-export([liveout/2]).
 
23
-endif.
 
24
-ifdef(PRETTY_PRINT).
 
25
-export([pp/1]).
 
26
-endif.
 
27
%%-export([livein_from_liveout/2]).
 
28
-ifdef(DEBUG_LIVENESS).
 
29
-export([annotate_liveness/2]).
 
30
-endif.
26
31
 
27
32
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
28
33
%%
29
34
%% Interface functions that MUST be implemented in the including file
30
35
%%
31
 
%%
32
36
%% cfg_bb(CFG, L) -> BasicBlock, extract a basic block from a cfg.
33
37
%% cfg_postorder(CFG) -> [Labels], the labels of the cfg in postorder
34
38
%% cfg_succ_map(CFG) -> SuccMap, a successor mapping.
35
39
%% cfg_succ(CFG, L) -> [Labels], 
36
 
%% cfg_bb_update(CFG, L, NewBB) ->
37
 
%% cfg_labels(CFG) ->
38
40
%% uses(Instr) ->
39
41
%% defines(Instr) ->
 
42
%%
 
43
%% Plus the following, if basic block annotations are needed
 
44
%%
 
45
%% cfg_labels(CFG) ->
 
46
%% cfg_bb_add(CFG, L, NewBB) ->
40
47
%% mk_comment(Text) ->
41
 
%%
42
48
 
43
49
 
44
50
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
49
55
analyze(CFG) ->
50
56
  PO = cfg_postorder(CFG),
51
57
  InitLiveness = liveness_init(init(cfg_labels(CFG), CFG)),
52
 
 
53
58
  _Max = case get(hipe_largest_liveset) of
54
59
           undefined ->
55
60
             put(hipe_largest_liveset,0),
77
82
%%
78
83
 
79
84
merry_go_around(Labels, Liveness, Count) ->
80
 
   case doit_once(Labels, Liveness, 0) of
81
 
      {NewLiveness, 0} -> 
82
 
         %% io:format("Iterations ~w~n",[Count]),
83
 
         NewLiveness;
84
 
      {NewLiveness, _Changed} ->
85
 
         merry_go_around(Labels, NewLiveness,Count+1)
86
 
   end.
 
85
  case doit_once(Labels, Liveness, 0) of
 
86
    {NewLiveness, 0} -> 
 
87
       %% io:format("Iterations ~w~n",[Count]),
 
88
       NewLiveness;
 
89
    {NewLiveness, _Changed} ->
 
90
       merry_go_around(Labels, NewLiveness,Count+1)
 
91
  end.
87
92
 
88
93
 
89
94
%%
103
108
  if Le > Max -> put(hipe_largest_liveset,Le);
104
109
     true -> true
105
110
  end,
106
 
   doit_once(Ls, NewLiveness, Changed+ChangedP).
 
111
  doit_once(Ls, NewLiveness, Changed+ChangedP).
107
112
 
108
113
-else.
 
114
 
109
115
doit_once([], Liveness, Changed) ->
110
116
  {Liveness, Changed};
111
117
doit_once([L|Ls], Liveness, Changed) ->
113
119
  Kill = ordsets:subtract(LiveOut, kill(L, Liveness)),
114
120
  LiveIn = ordsets:union(Kill, gen(L,Liveness)),
115
121
  {NewLiveness, ChangedP} = update_livein(L, LiveIn, Liveness),
116
 
 
117
 
   doit_once(Ls, NewLiveness, Changed+ChangedP).
118
 
-endif.
119
 
 
120
 
%%
121
 
%% Given a list of instructions and liveout, calculates livein
122
 
%%
123
 
-ifdef(HIPE_LIVENESS_CALC_LARGEST_LIVESET).
124
 
list([], LiveOut) ->
125
 
  LiveOut;
126
 
list([I|Is], LiveOut) ->
127
 
  LiveIn = list(Is, LiveOut),
128
 
  InstrGen = ordsets:from_list(uses(I)),
129
 
  InstrKill = ordsets:from_list(defines(I)),
130
 
  Live = ordsets:union(InstrGen, ordsets:subtract(LiveIn, InstrKill)),
131
 
  Le = size(Live),
132
 
  Max = get(hipe_largest_liveset),
133
 
  if Le > Max -> put(hipe_largest_liveset,Le);
134
 
     true -> true
135
 
  end,
136
 
  Live.
137
 
-else.
138
 
 
139
 
list([], LiveOut) ->
140
 
  LiveOut;
141
 
list([I|Is], LiveOut) ->
142
 
  LiveIn = list(Is, LiveOut),
143
 
  InstrGen = ordsets:from_list(uses(I)),
144
 
  InstrKill = ordsets:from_list(defines(I)),
145
 
  Live = ordsets:union(InstrGen, ordsets:subtract(LiveIn, InstrKill)),
146
 
  Live.
147
 
 
148
 
-endif.
 
122
  doit_once(Ls, NewLiveness, Changed+ChangedP).
 
123
-endif.
 
124
 
 
125
%% %%
 
126
%% %% Given a list of instructions and liveout, calculates livein
 
127
%% %%
 
128
%% livein_from_liveout(List, LiveOut) when is_list(List)->
 
129
%%   livein_from_liveout_1(lists:reverse(List), gb_sets:from_list(LiveOut));
 
130
%% livein_from_liveout(Instr, LiveOut) ->
 
131
%%   livein_from_liveout_1([Instr], gb_sets:from_list(LiveOut)).
 
132
%% 
 
133
%% livein_from_liveout_1([], LiveOut) ->
 
134
%%   gb_sets:to_list(LiveOut);
 
135
%% livein_from_liveout_1([I|Is], LiveOut) ->
 
136
%%   Def = defines(I),
 
137
%%   Use = uses(I),
 
138
%%   DefSet = gb_sets:from_list(Def),
 
139
%%   UseSet = gb_sets:from_list(Use),
 
140
%%   LiveIn = gb_sets:union(gb_sets:difference(LiveOut, DefSet), UseSet),
 
141
%%   Le = gb_sets:size(LiveIn),
 
142
%%   Max = get(hipe_largest_liveset),
 
143
%%   if Le > Max -> put(hipe_largest_liveset,Le);
 
144
%%      true -> true
 
145
%%   end,
 
146
%%   livein_from_liveout_1(Is, LiveIn).
149
147
 
150
148
%%
151
149
%% updates liveness for a basic block
156
154
 
157
155
update_livein(Label, NewLiveIn, Liveness) ->
158
156
  {GK, LiveIn, Successors} = liveness_lookup(Label, Liveness),
159
 
 
160
 
   NewLiveness = liveness_update(Label, {GK, NewLiveIn, Successors}, Liveness),
161
 
   if LiveIn =:= NewLiveIn ->
 
157
  NewLiveness = liveness_update(Label, {GK, NewLiveIn, Successors}, Liveness),
 
158
  if LiveIn =:= NewLiveIn ->
162
159
         {NewLiveness, 0};
163
 
      true ->
 
160
  true ->
164
161
         {NewLiveness, 1}
165
 
   end.
 
162
  end.
166
163
 
167
164
 
168
165
%%
170
167
%%
171
168
 
172
169
liveout(Liveness, L) ->
173
 
   Succ = successors(L, Liveness),
174
 
   case Succ of
175
 
      [] ->    % special case if no successors
176
 
         liveout_no_succ();
177
 
      _ ->
178
 
         liveout1(Succ, Liveness)
179
 
   end.
 
170
  Succ = successors(L, Liveness),
 
171
  case Succ of
 
172
    [] ->    % special case if no successors
 
173
      liveout_no_succ();
 
174
    _ ->
 
175
      liveout1(Succ, Liveness)
 
176
  end.
180
177
 
181
178
liveout1(Labels, Liveness) ->
182
179
  liveout1(Labels, Liveness, ordsets:new()).
183
 
liveout1([], Liveness, Live) ->
184
 
   Live;
 
180
 
 
181
liveout1([], _Liveness, Live) ->
 
182
  Live;
185
183
liveout1([L|Ls], Liveness,Live) ->
186
 
   liveout1(Ls, Liveness, ordsets:union(livein(Liveness, L),Live)).
187
 
 
 
184
  liveout1(Ls, Liveness, ordsets:union(livein(Liveness, L),Live)).
188
185
 
189
186
 
190
187
successors(L, Liveness) ->
191
 
   {_GK,_LiveIn, Successors} = liveness_lookup(L, Liveness),
192
 
   Successors.
 
188
  {_GK,_LiveIn, Successors} = liveness_lookup(L, Liveness),
 
189
  Successors.
193
190
 
194
191
livein(Liveness, L) ->
195
 
   {_GK, LiveIn,_Successors} = liveness_lookup(L, Liveness),
196
 
   LiveIn.
 
192
  {_GK, LiveIn,_Successors} = liveness_lookup(L, Liveness),
 
193
  LiveIn.
197
194
 
198
195
kill(L, Liveness) ->
199
 
   {{_Gen,Kill},_LiveIn,_Successors} = liveness_lookup(L, Liveness),
200
 
   Kill.
 
196
  {{_Gen,Kill},_LiveIn,_Successors} = liveness_lookup(L, Liveness),
 
197
  Kill.
201
198
 
202
199
gen(L, Liveness) ->
203
 
   {{Gen,_Kill},_LiveIn,_Successors} = liveness_lookup(L, Liveness),
204
 
   Gen.
 
200
  {{Gen,_Kill},_LiveIn,_Successors} = liveness_lookup(L, Liveness),
 
201
  Gen.
205
202
 
206
203
 
207
204
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
215
212
%%    - Successors is a list of the successors to the block.
216
213
 
217
214
init([], _) ->
218
 
   [];
 
215
  [];
219
216
init([L|Ls], CFG) ->
220
 
   BB = cfg_bb(CFG, L),
221
 
   Code = hipe_bb:code(BB),
222
 
   SuccMap = cfg_succ_map(CFG),
223
 
   Succ = cfg_succ(SuccMap, L),
224
 
   Transfer = make_bb_transfer(Code, Succ),
225
 
   [{L, {Transfer, ordsets:new(), Succ}} | init(Ls, CFG)].
 
217
  BB = cfg_bb(CFG, L),
 
218
  Code = hipe_bb:code(BB),
 
219
  SuccMap = cfg_succ_map(CFG),
 
220
  Succ = cfg_succ(SuccMap, L),
 
221
  Transfer = make_bb_transfer(Code, Succ),
 
222
  [{L, {Transfer, ordsets:new(), Succ}} | init(Ls, CFG)].
226
223
 
227
224
 
228
225
make_bb_transfer([], _Succ) ->
229
 
   {ordsets:new(), ordsets:new()};   % {Gen, Kill}
 
226
  {ordsets:new(), ordsets:new()};   % {Gen, Kill}
230
227
make_bb_transfer([I|Is], Succ) ->
231
 
   {Gen, Kill} = make_bb_transfer(Is, Succ),
232
 
   InstrGen = ordsets:from_list(uses(I)),
233
 
   InstrKill = ordsets:from_list(defines(I)),
234
 
   Gen1 = ordsets:subtract(Gen, InstrKill),
235
 
   Gen2 = ordsets:union(Gen1, InstrGen),
236
 
   Kill1 = ordsets:union(Kill, InstrKill),
237
 
   Kill2 = ordsets:subtract(Kill1, InstrGen),
238
 
   {Gen2, Kill2}.
 
228
  {Gen, Kill} = make_bb_transfer(Is, Succ),
 
229
  InstrGen = ordsets:from_list(uses(I)),
 
230
  InstrKill = ordsets:from_list(defines(I)),
 
231
  Gen1 = ordsets:subtract(Gen, InstrKill),
 
232
  Gen2 = ordsets:union(Gen1, InstrGen),
 
233
  Kill1 = ordsets:union(Kill, InstrKill),
 
234
  Kill2 = ordsets:subtract(Kill1, InstrGen),
 
235
  {Gen2, Kill2}.
 
236
 
 
237
 
 
238
 
 
239
 
239
240
 
240
241
 
241
242
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
243
244
%% Annotate each basic block with liveness info
244
245
%%
245
246
 
246
 
annotate(CFG, Liveness) ->
247
 
   Labels = cfg_labels(CFG),
248
 
   annotate_bb(Labels, CFG, Liveness).
249
 
 
250
 
annotate_bb([], CFG, _Liveness) ->
251
 
   CFG;
252
 
annotate_bb([L|Ls], CFG, Liveness) ->
253
 
   BB = cfg_bb(CFG, L),
254
 
   Code0 = hipe_bb:code(BB),
255
 
   LiveIn = strip(livein(Liveness, L)),
256
 
   LiveOut = strip(liveout(Liveness, L)),
257
 
   Code = [mk_comment({live_in, LiveIn}),
258
 
           mk_comment({live_out, LiveOut})
259
 
           | Code0],
260
 
   NewBB = hipe_bb:code_update(BB, Code),
261
 
   NewCFG = cfg_bb_update(CFG, L, NewBB),
262
 
   annotate_bb(Ls, NewCFG, Liveness).
263
 
 
 
247
-ifdef(DEBUG_LIVENESS).
 
248
 
 
249
annotate_liveness(CFG, Liveness) ->
 
250
  Labels = cfg_labels(CFG),
 
251
  annotate_liveness_bb(Labels, CFG, Liveness).
 
252
 
 
253
annotate_liveness_bb([], CFG, _Liveness) ->
 
254
  CFG;
 
255
annotate_liveness_bb([L|Ls], CFG, Liveness) ->
 
256
  BB = cfg_bb(CFG, L),
 
257
  Code0 = hipe_bb:code(BB), 
 
258
  LiveIn = strip(livein(Liveness, L)),
 
259
  LiveOut = strip(liveout(Liveness, L)),
 
260
  Code = [mk_comment({live_in, LiveIn}),
 
261
          mk_comment({live_out, LiveOut})
 
262
          | Code0],
 
263
  NewBB = hipe_bb:code_update(BB, Code),
 
264
  NewCFG = cfg_bb_add(CFG, L, NewBB),
 
265
  annotate_liveness_bb(Ls, NewCFG, Liveness).
264
266
 
265
267
strip([]) ->
266
268
   [];
267
269
strip([{_,Y}|Xs]) ->
268
270
   [Y|strip(Xs)].
269
271
 
 
272
-endif. % DEBUG_LIVENESS
 
273
 
270
274
 
271
275
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
272
276
%%
273
277
liveness_init(List) ->
274
 
  ?vector_from_list(dense(0,lists:sort(List), [])).
275
 
% liveness_init(List) -> hipe_hash:init(List).
 
278
  liveness_init(List, gb_trees:empty()).
276
279
 
 
280
liveness_init([{Lbl, Data}|Left], Acc) ->
 
281
  liveness_init(Left, gb_trees:insert(Lbl, Data, Acc));
 
282
liveness_init([], Acc) ->
 
283
  Acc.
 
284
  
277
285
liveness_lookup(Label, Liveness) ->
278
 
   ?vector_get(Label+1, Liveness).
279
 
%% liveness_lookup(Label, Liveness) ->
280
 
%%  {found, {GK, LiveIn, Successors}} = hipe_hash:lookup(Label, Liveness),
281
 
%%  {GK, LiveIn, Successors}.
 
286
  gb_trees:get(Label, Liveness).
282
287
liveness_update(Label, Val, Liveness) ->
283
 
  ?vector_set(Label+1, Liveness, Val).
284
 
 
285
 
%% liveness_update(Label, Val, Liveness) ->
286
 
%%  hipe_hash:update(Label, Val, Liveness).
287
 
 
288
 
 
289
 
%% Build a dense mapping 
290
 
dense(_, [], Vs) ->
291
 
  %% Done reverse the list.
292
 
  lists:reverse(Vs);
293
 
dense(N, [{Pos, Data}|Ms], Vs) when N =:= Pos ->
294
 
  %% N makes sure the mapping is dense. N is he next key.
295
 
  dense(N+1, Ms, [Data|Vs]);
296
 
dense(N, Source, Vs) ->
297
 
  %% The source was sparce, make up some placeholders...
298
 
  dense(N+1, 
299
 
        Source, 
300
 
        [undef|Vs]).
 
288
  gb_trees:update(Label, Val, Liveness).
 
289
 
 
290
 
 
291
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
292
%%
 
293
%% pp/1 pretty prints liveness information for a CFG
 
294
%%
 
295
%%
 
296
-ifdef(PRETTY_PRINT).
 
297
pp(Cfg) ->
 
298
  Liveness=analyze(Cfg),
 
299
  Labels=cfg_labels(Cfg),
 
300
  ok=print_blocks(Labels, Liveness, Cfg).
 
301
 
 
302
print_blocks([Lbl|Rest], Liveness, Cfg) ->
 
303
  io:format("~nLivein:", []),
 
304
  pp_liveness_info(livein(Liveness, Lbl)),
 
305
  io:format("Label ~w:~n" , [Lbl]),
 
306
  pp_block(Lbl, Cfg),
 
307
  io:format("Liveout:", []),
 
308
  pp_liveness_info(liveout(Liveness, Lbl)),
 
309
  print_blocks(Rest, Liveness, Cfg);
 
310
print_blocks([], _Liveness, _Cfg) ->
 
311
  ok.
 
312
-endif. % PRETTY_PRINT