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

« back to all changes in this revision

Viewing changes to lib/hipe/ssa/hipe_ssa_phi.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
 
%%%----------------------------------------------------------------------
2
 
%%% File    : addphi.erl
3
 
%%% Author  : 
4
 
%%% Purpose : 
5
 
%%% Created : 5 Mar 2002 by Christoffer Vikstrom <chvi3471@rama.it.uu.se>
6
 
%%%----------------------------------------------------------------------
7
 
-export([place/2]).
8
 
 
9
 
%%>----------< Auxiliry Functions >----------<%%
10
 
 
11
 
%%----------------------------------------------------------------------
12
 
% Procedure : lookup/3 
13
 
% Purpose   : Wrapper for diffrent hashtables using lookup.
14
 
% Arguments : Key   - the hashtable key
15
 
%             Table - the hashtable
16
 
%             Type  - the type of hashtable. Can be: work, hasAlready or assMap
17
 
% Return    : The value at key place or for Type=work/hasAlready -> 0 and
18
 
%              for Type=assMap -> [].
19
 
% Notes     : 
20
 
%%----------------------------------------------------------------------
21
 
lookup(Key, Table, Type) -> 
22
 
    case Type of
23
 
        work ->
24
 
            case ?hash:lookup(Key, Table) of
25
 
                not_found -> 0;
26
 
                {found, Other} -> Other
27
 
            end;
28
 
        hasAlready ->
29
 
            case ?hash:lookup(Key, Table) of
30
 
                not_found -> 0;
31
 
                {found, Other} -> Other
32
 
            end;
33
 
        assMap -> 
34
 
            case ?hash:lookup(Key, Table) of
35
 
                not_found -> [];
36
 
                {found, Other} -> Other
37
 
            end;
38
 
        _Other ->
39
 
            {error, {addphi, lookup, 3}}
40
 
    end.
41
 
    
42
 
 
43
 
%%----------------------------------------------------------------------
44
 
% Procedure : lookup/3 
45
 
% Purpose   : Wrapper for ?hash:lookup().
46
 
% Arguments : Key   - the hashtable key
47
 
%             Table - the hashtable
48
 
%             Value - the value
49
 
% Return    : Table
50
 
% Notes     : 
51
 
%%----------------------------------------------------------------------      
52
 
update(Key, Value, Table) -> ?hash:update(Key, Value, Table).
53
 
 
54
 
 
55
 
 
56
 
%%>----------< PlacePhi Algorithm >----------<%%
57
 
 
58
 
%%----------------------------------------------------------------------
59
 
% Procedure : place/2 
60
 
% Purpose   : Places phi at appropriate places in the CFG.
61
 
% Arguments : CFG - Control Flow Graph.
62
 
%             DF  - Dominance Frontier.
63
 
% Return    : CFG with phi functions.
64
 
% Notes     : 
65
 
%%----------------------------------------------------------------------
66
 
place(CFG, DF) ->
67
 
    PredMap = ?cfg:pred_map(CFG),
68
 
    AssMap = insertParams(CFG),
69
 
    AssMap2 = preProcessing(CFG, AssMap),
70
 
    VarList = ?hash:list(AssMap2),
71
 
    variableTraverse(CFG, DF, ?hash:empty(), ?hash:empty(), 
72
 
                     0, AssMap2, VarList, PredMap).
73
 
    
74
 
 
75
 
%%----------------------------------------------------------------------
76
 
% Procedure : insertParams/1 
77
 
% Purpose   : Inserts the parameters of the CFG into the AssMap.
78
 
% Arguments : CFG - Control Flow Graph
79
 
% Return    : AssMap - Assignment map.
80
 
% Notes     : 
81
 
%%----------------------------------------------------------------------
82
 
insertParams(CFG) ->
83
 
    StartLabel = ?cfg:start_label(CFG),
84
 
    Params = ?cfg:params(CFG),
85
 
    insertParams(Params, StartLabel, ?hash:empty()).
86
 
 
87
 
insertParams([Param | T], StartLabel, AssMap) ->
88
 
    insertParams(T, StartLabel, update(Param, [StartLabel], AssMap));
89
 
 
90
 
insertParams([], _, AssMap) -> AssMap.
91
 
 
92
 
 
93
 
%%----------------------------------------------------------------------
94
 
% Procedure : preProcessing/2
95
 
% Purpose   : Creates the assignment map.
96
 
% Arguments : CFG     - Control Flow Graph
97
 
%             AssMap  - Assignment map
98
 
% Return    : AssMap.
99
 
% Notes     : 
100
 
%%----------------------------------------------------------------------
101
 
preProcessing(CFG, AssMap) -> 
102
 
    traverseLabels(CFG, ?cfg:labels(CFG), AssMap).
103
 
 
104
 
 
105
 
%%----------------------------------------------------------------------
106
 
% Procedure : traverseLabels/3
107
 
% Purpose   : Traverses all labels and adds all assignments in the basic
108
 
%             block to the assignment map.
109
 
% Arguments : CFG    - Control Flow Graph
110
 
%             AssMap - Assignment Map
111
 
%             Label  - A label for a node
112
 
% Return    : AssMap. 
113
 
% Notes     : 
114
 
%%----------------------------------------------------------------------
115
 
traverseLabels(CFG, [Label|T], AssMap) ->
116
 
    Code = hipe_bb:code(?cfg:bb(CFG, Label)),
117
 
    NewVarList = getAssignments(Code),
118
 
    traverseLabels(CFG, T, updateAssMap(NewVarList, Label, AssMap)); 
119
 
traverseLabels(_, [], AssMap) -> AssMap. 
120
 
 
121
 
 
122
 
%%----------------------------------------------------------------------
123
 
% Procedure : getAssignments/1
124
 
% Purpose   : Retrieves all assigned variables in a basic block.
125
 
% Arguments : InstrLst - A list of instructions from a basic block.
126
 
%             VarList  - A list of variables.
127
 
% Return    : VarList.
128
 
% Notes     : This function may return a list containing duplicated elements
129
 
%%----------------------------------------------------------------------
130
 
getAssignments(InstrLst) -> getAssignments(InstrLst, []).
131
 
getAssignments([Instr | T], VarList) ->
132
 
    getAssignments(T, ?code:defines(Instr) ++ VarList);
133
 
 
134
 
getAssignments([], VarList) -> VarList.
135
 
 
136
 
 
137
 
%%----------------------------------------------------------------------
138
 
% Procedure : updateAssMap/3
139
 
% Purpose   : Updates the assignment map with. Each variable in the AssVar
140
 
%             list is inserted with the value Label.
141
 
% Arguments : Label  - a label of a node
142
 
%             AssVar - a variable that is assigned at Label
143
 
%             AssMap - Assignment map.
144
 
% Return    : AssMap.
145
 
% Notes     : 
146
 
%%----------------------------------------------------------------------
147
 
updateAssMap([AssVar|T], Label, AssMap) ->
148
 
    Lst = lookup(AssVar, AssMap, assMap),
149
 
    updateAssMap(T, Label, update(AssVar, [Label|Lst], AssMap));
150
 
 
151
 
updateAssMap([], _, AssMap) -> AssMap.    
152
 
 
153
 
 
154
 
%%----------------------------------------------------------------------
155
 
% Procedure : variableTraverse/4
156
 
% Purpose   : This function traverses all variables and adds phi functions 
157
 
%             at appropriate nodes.
158
 
% Arguments : CFG        - Control Flow Graph
159
 
%             DFMap      - Dominance Frontier Map
160
 
%             HasAlready - A map of which nodes that already has phi functions
161
 
%             Work       - 
162
 
%             IterCount  - Counter of how many itterations that has been done
163
 
%             AssMap     - Assignment map
164
 
%             VarLst     - Variable list that is traversed
165
 
%             PredMap    - A map of predecessors in the CFG
166
 
% Return    : CFG.
167
 
% Notes     : 
168
 
%%----------------------------------------------------------------------
169
 
variableTraverse(CFG, DFMap, HasAlready, Work, 
170
 
                 IterCount, AssMap, [{Var,_}|VarLst], PredMap) ->
171
 
    IterCount2 = IterCount + 1, 
172
 
    DefLst = lookup(Var, AssMap, assMap),
173
 
    {Work2, WorkLst2} = workListBuilder(DefLst, Work, [], IterCount2),
174
 
    {CFG2, HasAlready2, Work3} =  doWork(CFG, DFMap, HasAlready, 
175
 
                                         Work2, IterCount2, WorkLst2,
176
 
                                         Var, PredMap),   
177
 
    variableTraverse(CFG2, DFMap, HasAlready2, Work3, 
178
 
                     IterCount2, AssMap, VarLst, PredMap);
179
 
 
180
 
variableTraverse(CFG,_,_,_,_,_,[],_) -> CFG.
181
 
 
182
 
 
183
 
%%----------------------------------------------------------------------
184
 
% Procedure : workListBuilder/4
185
 
% Purpose   : Builds the worklist that the algorithm is working on.
186
 
% Arguments : Work       - 
187
 
%             WorkLst    - The worklist that is worked through
188
 
%             IterCount  - Counter of how many itterations that has been done
189
 
%             Node       - A node in the CFG
190
 
% Return    : 
191
 
% Notes     : 
192
 
%%----------------------------------------------------------------------
193
 
workListBuilder([Node|T], Work, WorkLst, IterCount) ->
194
 
    case lookup(Node, Work, work) of
195
 
        0 ->
196
 
            Work2 = update(Node, IterCount, Work),
197
 
            workListBuilder(T, Work2, [Node|WorkLst], IterCount);
198
 
        _ ->
199
 
            Work2 = update(Node, IterCount, Work),
200
 
            workListBuilder(T, Work2, [Node|WorkLst], IterCount)
201
 
        end;
202
 
 
203
 
workListBuilder([], Work, WorkLst, _IterCount) -> {Work, WorkLst}.
204
 
 
205
 
 
206
 
%%----------------------------------------------------------------------
207
 
% Procedure : doWork/8
208
 
% Purpose   : This procedure works itself through the worklist and checks
209
 
%             if a node needs a phi functions.
210
 
% Arguments : CFG        - Control Flow Graph
211
 
%             DFMap      - Dominance Frontier Map
212
 
%             HasAlready - A map of which nodes that already has phi functions
213
 
%             Work       - 
214
 
%             IterCount  - Counter of how many itterations that has been done
215
 
%             WorkLst    - The worklist that is worked through
216
 
%             Var        - Variable
217
 
%             PredMap    - A map of predecessors in the CFG
218
 
% Return    : (CFG, HasAlready, Work)
219
 
% Notes     : 
220
 
%%----------------------------------------------------------------------   
221
 
doWork(CFG, DFMap, HasAlready, Work, IterCount,
222
 
       [Node|WorkLst], Var, PredMap) ->
223
 
    DFofX = hipe_df:get(Node, DFMap),
224
 
    {CFG2, HasAlready2, Work2, WorkLst2} =
225
 
        checkPhiNeeds(CFG, DFofX, HasAlready, Work,
226
 
                      IterCount, WorkLst, Var, PredMap),
227
 
    doWork(CFG2, DFMap, HasAlready2, Work2,
228
 
           IterCount, WorkLst2, Var, PredMap);
229
 
 
230
 
doWork(CFG, _, HasAlready, Work, _, [], _, _) ->
231
 
    {CFG, HasAlready, Work}.    
232
 
 
233
 
 
234
 
%%----------------------------------------------------------------------
235
 
% Procedure : checkPhiNeeds/8
236
 
% Purpose   : This function checks if a node needs a phi function and adds
237
 
%             one if its needed.
238
 
% Arguments : CFG        - Control Flow Graph
239
 
%             DFofX      - Dominance Frontier of a node
240
 
%             HasAlready - A map of which nodes that already has phi functions
241
 
%             Work       - 
242
 
%             IterCount  - Counter of how many itterations that has been done
243
 
%             WorkLst    - The worklist that is worked through
244
 
%             Var        - Variable
245
 
%             PredMap    - A map of predecessors in the CFG
246
 
% Return    : (CFG, HasAlready, Work, WorkLst)
247
 
% Notes     : 
248
 
%%----------------------------------------------------------------------
249
 
checkPhiNeeds(CFG, [Node|DFofX], HasAlready, Work,
250
 
              IterCount, WorkLst, Var, PredMap) ->
251
 
    case lookup(Node, HasAlready, hasAlready) < IterCount of
252
 
        true ->
253
 
            CFG2 = insertPhiCode(CFG, Node, Var, PredMap),
254
 
            HasAlready2 = update(Node, IterCount, HasAlready),
255
 
            case  lookup(Node, Work, work) < IterCount of
256
 
                true ->
257
 
                    Work2 = update(Node, IterCount, Work),
258
 
                    WorkLst2 = [Node|WorkLst],
259
 
                    checkPhiNeeds(CFG2, DFofX, HasAlready2, Work2, IterCount,
260
 
                                  WorkLst2, Var, PredMap);
261
 
                false ->
262
 
                    checkPhiNeeds(CFG2, DFofX, HasAlready2, Work, 
263
 
                                  IterCount, WorkLst, Var, PredMap)
264
 
            end;
265
 
        false ->
266
 
            checkPhiNeeds(CFG, DFofX, HasAlready, Work, IterCount, 
267
 
                          WorkLst, Var, PredMap)
268
 
    end;
269
 
 
270
 
checkPhiNeeds(CFG, [], HasAlready, Work, _, WorkLst, _, _) ->
271
 
    {CFG, HasAlready, Work, WorkLst}.   
272
 
 
273
 
 
274
 
%%----------------------------------------------------------------------
275
 
% Procedure : insertPhiCode/4
276
 
% Purpose   : 
277
 
% Arguments : CFG     - Control Flow Graph
278
 
%             Node    - A node
279
 
%             Var     - A variable
280
 
%             PredMap - A map of predecessors in the CFG
281
 
% Return    : CFG
282
 
% Notes     : 
283
 
%%----------------------------------------------------------------------
284
 
insertPhiCode(CFG, Node, Var, PredMap) ->
285
 
   BB = ?cfg:bb(CFG, Node),
286
 
   PredList = ?cfg:pred(PredMap, Node),
287
 
   Phi = ?code:mk_phi(Var, PredList),
288
 
   Code = [Phi | hipe_bb:code(BB)],
289
 
   ?cfg:bb_update(CFG, Node, hipe_bb:code_update(BB, Code)).
290
 
 
291
 
 
292
 
 
293
 
 
294