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

« back to all changes in this revision

Viewing changes to lib/hipe/opt/hipe_reach.erl

  • 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
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2
 
%
3
 
%                        REACHING DEFINITIONS
4
 
%
5
 
% Compute reaching definitions for a CFG.
6
 
%
7
 
 
8
 
-module(hipe_reach).
9
 
-export([cfg/1,cfg_annot/1]).
10
 
-compile(export_all).
11
 
 
12
 
-define(cfg,hipe_icode_cfg).
13
 
-define(code,hipe_icode).
14
 
-define(debug(Str,Xs),io:format(Str,Xs)).
15
 
 
16
 
% Returns {Deftab,N,InVals}
17
 
%   where Deftab is a definition table (see below)
18
 
%         N is
19
 
%         InVals is a hash table (Label -> DefSet)
20
 
 
21
 
cfg(CFG) ->
22
 
    {Deftab,N} = name_defs(CFG),
23
 
    Transf = hash:init(rd_transf(?cfg:labels(CFG),CFG,Deftab)),
24
 
    Succ = ?cfg:succ_map(CFG),
25
 
    {Start,In} = start_invals(CFG),
26
 
    {Deftab,N,fix_all(Start,Succ,Transf,In)}.
27
 
 
28
 
% Annotate each use with its reaching definitions
29
 
 
30
 
cfg_annot(CFG) ->
31
 
    ?debug('reach defs~n',[]),
32
 
    {Deftab,_,In} = cfg(CFG),
33
 
    ?debug('annotation~n',[]),
34
 
    [ {L, annot_block(hipe_bb:code(?cfg:bb(CFG,L)),
35
 
                      inval(L,In),
36
 
                      Deftab,L,start_pos(),CFG)}
37
 
     || L <- ?cfg:labels(CFG) ].
38
 
 
39
 
annot_block([],In,Deftab,L,Pos,CFG) -> [];
40
 
annot_block([I|Is],In,Deftab,L,N,CFG) ->
41
 
    NewI = annot_instr(I,In,Deftab,L,N,CFG),
42
 
    Out = apply_transf(gen_kill_instr(L,N,I,Deftab),In),
43
 
    [NewI|annot_block(Is,Out,Deftab,L,N+1,CFG)].
44
 
 
45
 
annot_instr(Instr,In,Deftab,L,N,CFG) ->
46
 
    {N, Instr, [ {U, reaching_defs(U,In,Deftab,CFG)} 
47
 
                || U <- ?code:uses(Instr) ]}.
48
 
 
49
 
reaching_defs(U,In,Deftab,CFG) ->
50
 
    Refs = killed_by_var(U,Deftab),
51
 
    Relevant = set:list(set:intersect(Refs,In)),
52
 
    [ reaching_instr(CFG,Deftab,R) || R <- Relevant ].
53
 
 
54
 
reaching_instr(CFG,Deftab,R) ->
55
 
    {L,Pos} = def_of(R,Deftab),
56
 
    instr_of(L,Pos,CFG).
57
 
 
58
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
59
 
%
60
 
% name_defs(CFG)
61
 
%   returns {DefTable, N}
62
 
%    where DefTable is a def table (see below)
63
 
%          N is the number of definitions allocated (poss +1?)
64
 
 
65
 
name_defs(CFG) ->
66
 
    Ps = ?cfg:params(CFG),
67
 
    Deftab = empty_def_table(Ps),
68
 
    name_defs(?cfg:labels(CFG),CFG,first_eqv(Ps),Deftab).
69
 
 
70
 
first_eqv(Ps) -> start_def() + length(Ps).
71
 
 
72
 
name_defs([],CFG,Ix,Deftab) -> {Deftab,Ix};
73
 
name_defs([L|Ls],CFG,Ix,Deftab) ->
74
 
    { NewDeftab, NewIx } = name_defs_block(hipe_bb:code(?cfg:bb(CFG,L)),L,Ix,Deftab),
75
 
    name_defs(Ls,CFG,NewIx,NewDeftab).
76
 
 
77
 
name_defs_block(Xs,L,Ix,Deftab) ->
78
 
    name_defs_block(Xs,L,start_pos(),Ix,Deftab).
79
 
 
80
 
name_defs_block([],L,Pos,Ix,Deftab) -> {Deftab,Ix};
81
 
name_defs_block([I|Is],L,Pos,Ix,Deftab) ->
82
 
    {NewDeftab, NewIx} = add_defs(I,Deftab,L,Pos,Ix),
83
 
    name_defs_block(Is,L,Pos+1,NewIx,NewDeftab).
84
 
 
85
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
86
 
% Computing transfer functions per block
87
 
% - yields a list {Label, {Gen, Kill}}
88
 
 
89
 
rd_transf0(Ls,CFG,Deftab) ->
90
 
    [ {L,gen_kill_block_catch(hipe_bb:code(?cfg:bb(CFG,L)),L,Deftab)} 
91
 
     || L <- Ls ].
92
 
 
93
 
gen_kill_block_catch(Instrs,L,Deftab) ->
94
 
    case catch gen_kill_block(Instrs,L,Deftab) of
95
 
        {'EXIT',_} -> exit;
96
 
        Res -> {ok,Res}
97
 
    end.
98
 
 
99
 
rd_transf(Ls,CFG,Deftab) ->
100
 
    [ {L,gen_kill_block(hipe_bb:code(?cfg:bb(CFG,L)),L,Deftab)} 
101
 
     || L <- Ls ].
102
 
 
103
 
gen_kill_block(Instrs,L,Deftab) ->
104
 
    Start_gen = set:empty(),
105
 
    Start_kill = set:empty(),
106
 
    gen_kill_block(Instrs,L,start_pos(),Deftab,Start_gen,Start_kill).
107
 
 
108
 
% L label, N position in block, Deftab deftable, Gen = set, Kill = set
109
 
 
110
 
gen_kill_block([],L,N,Deftab,Gen,Kill) -> {Gen,Kill};
111
 
gen_kill_block([I|Is],L,N,Deftab,Gen0,Kill0) ->
112
 
    {Gen,Kill} = gen_kill_instr(L,N,I,Deftab),
113
 
    Kill1 = set:union(Kill0,Kill),
114
 
    Gen1 = set:union(Gen, set:diff(Gen0, Kill)),
115
 
    gen_kill_block(Is, L, N+1, Deftab, Gen1, Kill1).
116
 
 
117
 
gen_kill_instr(L, Pos, Instr, Deftab) ->
118
 
    Defs = ?code:defines(Instr),
119
 
    Gen = indices_of_defs(L,Pos,Defs,Deftab),
120
 
    Kill = killed_by_defs(Defs,Deftab),
121
 
    { Gen, Kill }.
122
 
 
123
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
124
 
%
125
 
% Reaching definitions by fixpoint iteration
126
 
% - note: uses chaotic iteration, since I'm feeling lazy :-)
127
 
%
128
 
% Returns a hash table (Label -> InVal)
129
 
 
130
 
% testing function:
131
 
fix(CFG) ->
132
 
    {Deftab,_} = name_defs(CFG),
133
 
    Transf = hash:init(rd_transf(?cfg:labels(CFG),CFG,Deftab)),
134
 
    Succ = ?cfg:succ_map(CFG),
135
 
    {Start,In} = start_invals(CFG),
136
 
    fix_all(Start,Succ,Transf,In).
137
 
 
138
 
fix_all([],Succ,Transf,In) -> In;
139
 
fix_all([L|Ls],Succ,Transf,In) ->
140
 
    fix_block(L,Ls,Succ,Transf,In).
141
 
 
142
 
fix_block(L,Ls,Succ,Transf,In) ->
143
 
    Out = apply_transf(transf_of(L,Transf),inval(L,In)),
144
 
    { NewLs, NewIn } = prop_succ(?cfg:succ(Succ,L), Ls, Out, In),
145
 
    fix_all(NewLs,Succ,Transf,NewIn).
146
 
 
147
 
prop_succ([],Ls,Out,In) -> {Ls,In};
148
 
prop_succ([L|Ls],Rest,Out,In) ->
149
 
    case changed(L,Out,In) of
150
 
        {yes,NewIn} ->
151
 
            prop_succ(Ls,[L|Rest],Out,NewIn);
152
 
        no ->
153
 
            prop_succ(Ls,Rest,Out,In)
154
 
    end.
155
 
 
156
 
apply_transf({Gen,Kill},Inval) ->
157
 
    set:union(Gen,set:diff(Inval,Kill)).
158
 
 
159
 
transf_of(L,Transf) ->
160
 
    {found,Trfun} = hash:lookup(L,Transf),
161
 
    Trfun.
162
 
 
163
 
% *** UNFINISHED ***
164
 
% - start_invals should make defs of all input params available
165
 
%   to start node
166
 
% - either should defines/1 be redefined to only return rtl_vars
167
 
%   or we must provide which rtl_regs are defined everywhere
168
 
 
169
 
start_invals(CFG) ->
170
 
    Entry = ?cfg:start(CFG),
171
 
    Start = [Entry],
172
 
    EntryInval = mk_def_set(?cfg:params(CFG),start_def(),set:empty()),
173
 
    { Start, hash:update(Entry,EntryInval,hash:empty()) }.
174
 
 
175
 
mk_def_set([],N,Set) -> Set;
176
 
mk_def_set([_|Xs],N,Set) ->
177
 
    mk_def_set(Xs,N+1,set:add_singleton(N,Set)).
178
 
 
179
 
inval(L,In) ->
180
 
    case hash:lookup(L,In) of
181
 
        {found,Inval} -> Inval;
182
 
        not_found -> set:empty()
183
 
    end.
184
 
 
185
 
changed(L,New,In) ->
186
 
    Old = inval(L,In),
187
 
    case set:included_by(New,Old) of
188
 
        true ->
189
 
            no;
190
 
        false ->
191
 
            {yes, hash:update(L,set:union(New,Old),In)}
192
 
    end.
193
 
 
194
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
195
 
%
196
 
% A Def_table is a tuple of hash tables,
197
 
%  { (Def -> Index), (Index -> Def), (Var -> set(Index)) }
198
 
% where
199
 
%  Def is a tuple {Block_label, Block_position, Var }
200
 
%  Index is an integer (unique to this def)
201
 
%  Var is a variable name, which maps to the set of indices killed
202
 
%    when Var is defined.
203
 
%
204
 
% Interface:
205
 
%
206
 
%  When def-table has been constructed:
207
 
%
208
 
%  - gen_kill_instr( Label, Pos, Instr, Deftable ) => {set(Index), set(Index)}
209
 
%  - index_of( Label, Pos, Var, Deftable) => index
210
 
%  - def_of(Index, Deftable) => { Label, Pos }
211
 
%  - defvar_of(Index, Deftable) => { Label, Pos, Var }
212
 
%  - instr_of( {Label, Pos}, Deftable ) => Instr
213
 
%  - instr_of( Label, Pos, Deftable ) => Instr
214
 
%
215
 
%  Constructing the def table:
216
 
%  - empty_def_table()
217
 
%  - add_defs( Instr, Deftab, Label, Pos )
218
 
%
219
 
 
220
 
%%%%%%%%%%%%%%%%%%%%
221
 
% Def table initially contains only the N parameters, numbered from 1..N
222
 
%
223
 
% The Deftable has the following data structures:
224
 
% - a mapping ({Label,Pos,Var} -> Index), yielding the index of a definition
225
 
% - a mapping (Index -> {Label,Pos,Var}), yielding the def of an index
226
 
% - a mapping (Var -> set(Index)), yielding the indices killed if Var is
227
 
%   defined.
228
 
 
229
 
empty_def_table(Ps) ->
230
 
    {Deftab,_} = add_ds(Ps,
231
 
                        param_pos(),
232
 
                        empty_def_table(),
233
 
                        param_label(),
234
 
                        start_def()),
235
 
    Deftab.
236
 
 
237
 
empty_def_table() -> { hash:empty(), hash:empty(), hash:empty() }.
238
 
 
239
 
param_pos() -> start.
240
 
 
241
 
param_label() -> start.
242
 
 
243
 
start_def() -> 1.
244
 
 
245
 
%%%%%%%%%%%%%%%%%%%%
246
 
 
247
 
% Given an instruction, a Deftab, a full position (L,Pos) and a starting
248
 
% index N, add the new definitions to the deftab.
249
 
% * for each variable x defined by Instr,
250
 
%   add a new definition N and increment index counter to N+1
251
 
%
252
 
% Returns {NewDeftab, NewIndex}
253
 
 
254
 
add_defs(Instr,Deftab,L,Pos,N) ->
255
 
    Def_lst = ?code:defines(Instr),
256
 
    case Def_lst of
257
 
        [] ->
258
 
            {Deftab,N};
259
 
        _ ->
260
 
            add_ds(Def_lst,Pos,Deftab,L,N)
261
 
    end.
262
 
 
263
 
start_pos() -> 0.
264
 
 
265
 
add_ds([],Pos,Deftab,L,N) -> {Deftab,N};
266
 
add_ds([X|Xs],Pos,Deftab,L,N) ->
267
 
    NewDeftab = map_def(X,L,Pos,N,Deftab),
268
 
    add_ds(Xs,Pos,NewDeftab,L,N+1).
269
 
 
270
 
% Given a variable X, label L, position Pos and index N, (and a Deftab)
271
 
% - map {L,Pos,X} to N.
272
 
% - map N to {L,Pos,X}
273
 
% - add N to the set of indices killed by defining X
274
 
 
275
 
map_def(X,L,Pos,N,{ Def_to_ix, Ix_to_def, Kill_map }) ->
276
 
    Def_name = {L,Pos,X},
277
 
    { hash:insert(Def_name, N, Def_to_ix), 
278
 
      hash:insert(N, Def_name, Ix_to_def),
279
 
      add_kill(X,N,Kill_map)
280
 
    }.
281
 
 
282
 
% Given label L, position Pos and a list of defined variables Defs
283
 
% and a Deftab, find the set(Index) of these definitions.
284
 
 
285
 
indices_of_defs(L, Pos, Defs, Deftab) -> 
286
 
    indices_of_defs(Defs, L, Pos, Deftab, set:empty()).
287
 
 
288
 
indices_of_defs([], L, Pos, Deftab, Set) -> Set;
289
 
indices_of_defs([X|Xs], L, Pos, Deftab, Set) ->
290
 
    N = index_of(L,Pos,X,Deftab),
291
 
    indices_of_defs(Xs, L, Pos, Deftab, set:add_singleton(N,Set)).
292
 
 
293
 
% Given a position {L,Pos,Var}, return the associated index.
294
 
 
295
 
index_of(L,Pos,X, { Def_to_ix, Ix_to_def, Kill_map }) ->
296
 
    {found,N} = hash:lookup({L,Pos,X},Def_to_ix),
297
 
    N.
298
 
 
299
 
% Given an index, return the {Label,Position} of the index
300
 
 
301
 
def_of(N, { Def_to_ix, Ix_to_def, Kill_map }) ->
302
 
    {found,{L,Pos,X}} = hash:lookup(N,Ix_to_def),
303
 
    {L,Pos}.
304
 
 
305
 
% Given an index, return the {Label,Position,Variable} of the index.
306
 
 
307
 
defvar_of(N, { Def_to_ix, Ix_to_def, Kill_map }) ->
308
 
    {found,{L,Pos,X}} = hash:lookup(N,Ix_to_def),
309
 
    {L,Pos,X}.
310
 
 
311
 
% Given a variable, return the set(Index) killed by the variable
312
 
%
313
 
% Note: this is simply the set of definitions of the variable,
314
 
%   so it is useful for other purposes as well. Thus, referring_defs/2.
315
 
 
316
 
killed_by_var(X, { Def_to_ix, Ix_to_def, Kill_map }) ->
317
 
    case hash:lookup(X,Kill_map) of
318
 
        not_found ->
319
 
            set:empty();
320
 
        {found,Set} ->
321
 
            Set
322
 
    end.
323
 
 
324
 
% Returns the set(Index) of definitions that define X.
325
 
 
326
 
referring_defs(X, Deftab) ->
327
 
    killed_by_var(X, Deftab).
328
 
 
329
 
% Given a list of defined variables, find the total set of defs killed
330
 
% by the vars. (Union of the individual kills.)
331
 
 
332
 
killed_by_defs(Xs,Deftab) -> kills_of_defs(Xs,Deftab,set:empty()).
333
 
 
334
 
kills_of_defs([],Deftab,Set) -> Set;
335
 
kills_of_defs([X|Xs],Deftab,Set) ->
336
 
    kills_of_defs(Xs,Deftab,set:union(killed_by_var(X,Deftab),Set)).
337
 
 
338
 
% Given variable X, an index N killed by X, and a Kill_map,
339
 
% return a new Kill_map where N is added to the kill set of X.
340
 
%
341
 
% (Note: internal function)
342
 
 
343
 
add_kill(X,N,Kill_map) ->
344
 
  N_set = set:add_singleton(N,set:empty()),
345
 
  NewSet = 
346
 
    case hash:lookup(X,Kill_map) of
347
 
      not_found ->
348
 
        N_set;
349
 
      {found,OldSet} ->
350
 
        set:union(N_set,OldSet)
351
 
    end,
352
 
  hash:update(X,NewSet,Kill_map).
353
 
 
354
 
% Given Label and Position and a CFG, 
355
 
% return the instruction at (Label,Pos) in CFG.
356
 
 
357
 
instr_of({L,Pos},CFG) -> instr_of(L,Pos,CFG).
358
 
 
359
 
instr_of(start,start,CFG) -> param;
360
 
instr_of(L,N,CFG) ->
361
 
    get_pos(N,hipe_bb:code(?cfg:bb(CFG,L))).
362
 
 
363
 
get_pos(0,[I|_]) -> I;
364
 
get_pos(N,[_|Is]) when N > 0 ->
365
 
    get_pos(N-1,Is).
366