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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_split_arith.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
%%% File    : hipe_icode_split_arith.erl
 
3
%%% Author  : Tobias Lindahl <tobiasl@csd.uu.se>
 
4
%%% Description : 
 
5
%%%
 
6
%%% Created : 12 Nov 2003 by Tobias Lindahl <tobiasl@csd.uu.se>
 
7
%%%-------------------------------------------------------------------
 
8
-module(hipe_icode_split_arith).
 
9
 
 
10
-export([cfg/2]).
 
11
 
 
12
-include("hipe_icode.hrl").
 
13
 
 
14
-define(MIN_RATIO, 0.005).
 
15
 
 
16
%%-define(UNSAFE, true).
 
17
-define(UNSAFE, false).
 
18
 
 
19
cfg(Cfg, _Fun)->
 
20
  case preprocess(Cfg) of
 
21
    {do_not_split, _Ratio} -> 
 
22
      %%io:format("split(Cfg): NOT Reasonable to split ~w.Ratio: ~.3f\n", 
 
23
      %%                [_Fun, _Ratio]),
 
24
      Cfg;
 
25
    {split, _Ratio, NewCfg} ->
 
26
      %%hipe_icode_cfg:pp(Cfg),
 
27
      %%io:format("split(Cfg):Reasonable to split ~w. Ratio: ~.2f\n", 
 
28
      %%                [_Fun, _Ratio]),
 
29
      NewCfg0 = split(NewCfg),
 
30
      NewCfg1 = cleanup(NewCfg0),
 
31
      %%hipe_icode_cfg:pp(NewCfg1),
 
32
      NewCfg1
 
33
  end.
 
34
 
 
35
cleanup(Cfg) ->
 
36
  Icode=hipe_icode_cfg:cfg_to_linear(Cfg),
 
37
  LinearCode = hipe_icode:icode_code(Icode),
 
38
  NewLinearCode=cleanup_code(LinearCode),
 
39
  NewIcode = hipe_icode:icode_code_update(Icode, NewLinearCode),
 
40
  hipe_icode_cfg:linear_to_cfg(NewIcode).
 
41
 
 
42
cleanup_code([I|Is]) ->
 
43
  case I of
 
44
    #call{} ->
 
45
      case hipe_icode:call_fail_label(I) of
 
46
        [] ->
 
47
          [I|cleanup_code(Is)];
 
48
        _ ->
 
49
          case hipe_icode:call_continuation(I) of
 
50
            [] ->
 
51
              NewLabel = hipe_icode:mk_new_label(),
 
52
              NewLabelName = hipe_icode:label_name(NewLabel),
 
53
              NewI=hipe_icode:call_set_continuation(I, NewLabelName),
 
54
              [NewI, NewLabel|cleanup_code(Is)];
 
55
            _ ->
 
56
              [I|cleanup_code(Is)]
 
57
          end
 
58
      end;
 
59
    _ ->
 
60
      [I|cleanup_code(Is)]
 
61
  end;
 
62
cleanup_code([]) -> [].
 
63
 
 
64
preprocess(Cfg)->
 
65
  Icode = hipe_icode_cfg:cfg_to_linear(Cfg),
 
66
  LinearCode = hipe_icode:icode_code(Icode),
 
67
  {NofArith, NofIns, NewLinearCode} = preprocess_code(LinearCode),
 
68
  case NofArith / NofIns of
 
69
    X when X >= ?MIN_RATIO ->
 
70
      NewIcode = hipe_icode:icode_code_update(Icode, NewLinearCode),
 
71
      {split, X, hipe_icode_cfg:linear_to_cfg(NewIcode)};
 
72
    Y ->
 
73
      {do_not_split, Y}
 
74
  end.
 
75
 
 
76
preprocess_code([H|Code])->
 
77
  preprocess_code(Code, 0, 0, [H]).
 
78
 
 
79
preprocess_code([I|Left], NofArith, NofIns,CodeAcc = [HdCode|TlCodeAcc])->
 
80
  case I of
 
81
    #call{} ->
 
82
      case is_arith(I) of
 
83
        true ->
 
84
          case hipe_icode:is_label(HdCode) of
 
85
            true ->
 
86
              preprocess_code(Left, NofArith + 1, NofIns + 1,[I|CodeAcc]);
 
87
            false ->
 
88
              NewLabel = hipe_icode:mk_new_label(),
 
89
              NewLabelName = hipe_icode:label_name(NewLabel),
 
90
              NewCodeAcc = 
 
91
                case hipe_icode:is_call(HdCode) of
 
92
                  true -> 
 
93
                    [I,
 
94
                     NewLabel,
 
95
                     hipe_icode:call_set_continuation(HdCode, NewLabelName)|
 
96
                     TlCodeAcc];
 
97
                  false ->
 
98
                    [I,
 
99
                     NewLabel,
 
100
                     hipe_icode:mk_goto(hipe_icode:label_name(NewLabel))|
 
101
                     CodeAcc]
 
102
                end,
 
103
              preprocess_code(Left, NofArith + 1, NofIns + 1, NewCodeAcc)
 
104
          end;
 
105
        false ->
 
106
          case hipe_icode:is_label(I) of % Don't count labels as intructions.
 
107
            true ->
 
108
              preprocess_code(Left, NofArith, NofIns, [I|CodeAcc]);
 
109
            false ->
 
110
              preprocess_code(Left, NofArith, NofIns + 1, [I|CodeAcc])
 
111
          end
 
112
      end;
 
113
    _ ->
 
114
      preprocess_code(Left, NofArith, NofIns + 1, [I|CodeAcc])
 
115
  end;
 
116
preprocess_code([], NofArith, NofIns, CodeAcc) ->
 
117
  {NofArith, NofIns, lists:reverse(CodeAcc)}.
 
118
   
 
119
 
 
120
split(Cfg)->
 
121
  AllLabels = hipe_icode_cfg:reverse_postorder(Cfg),
 
122
  {OldToNewMap, NewToOldMap}  = new_label_maps(AllLabels),
 
123
  %%io:format("split(Cfg): Adding fixnum trace ...\n", []),
 
124
  NewCfg = add_fixnum_trace(AllLabels, OldToNewMap, Cfg),
 
125
  %%io:format("split(Cfg): Adding fixnum trace: Done\n", []),
 
126
  %%io:format("split(Cfg): Inserting tests\n", []),
 
127
  case ?UNSAFE of
 
128
    true ->
 
129
      Start = hipe_icode_cfg:start_label(NewCfg),
 
130
      NewStart = gb_trees:get(Start, OldToNewMap),
 
131
      hipe_icode_cfg:start_label_update(NewCfg, NewStart);
 
132
    false ->
 
133
      NewCfg2 = 
 
134
        insert_tests(NewCfg, [gb_trees:get(X, OldToNewMap)||X<-AllLabels], 
 
135
                     NewToOldMap, OldToNewMap),
 
136
      %%io:format("split(Cfg): Inserting testsL Done\n", []),
 
137
      NewCfg2
 
138
  end.
 
139
 
 
140
add_fixnum_trace([Lbl|Left], LabelMap, Cfg)->
 
141
  NewLbl = gb_trees:get(Lbl, LabelMap),
 
142
  Code = hipe_bb:code(hipe_icode_cfg:bb(Cfg, Lbl)),
 
143
  NewCode = map_code(Code, Lbl, LabelMap),
 
144
  NewBB = hipe_bb:mk_bb(NewCode),
 
145
  NewCfg = hipe_icode_cfg:bb_add(Cfg, NewLbl, NewBB),
 
146
  add_fixnum_trace(Left, LabelMap, NewCfg);
 
147
add_fixnum_trace([], _LabelMap, Cfg) ->
 
148
  Cfg.
 
149
 
 
150
map_code(Ins, ArithFail, LabelMap) ->
 
151
  map_code(Ins, ArithFail, LabelMap, []).
 
152
 
 
153
map_code([I|Left], ArithFail, LabelMap, Acc) ->
 
154
  case I of
 
155
    #call{} ->
 
156
      case is_arith(I) of
 
157
        true ->
 
158
          case hipe_icode:defines(I) of
 
159
            []-> 
 
160
              map_code(Left, ArithFail, LabelMap, [redirect(I, LabelMap)|Acc]);
 
161
            _ ->
 
162
              NewOp = arithop_to_unsafe(hipe_icode:call_fun(I)),
 
163
              NewI1 = hipe_icode:call_fun_update(I, NewOp),
 
164
              NewI2 = redirect(NewI1, LabelMap),
 
165
              NewI3 =
 
166
                case hipe_icode:call_fail_label(NewI2) of
 
167
                  [] ->
 
168
                    case ?UNSAFE of
 
169
                      true -> NewI2;
 
170
                      false -> hipe_icode:call_set_fail_label(NewI2, ArithFail)
 
171
                    end;
 
172
                  _ -> NewI2
 
173
                end,
 
174
              map_code(Left, ArithFail, LabelMap, [NewI3|Acc])
 
175
          end;
 
176
        false ->
 
177
          map_code(Left, ArithFail, LabelMap, [redirect(I, LabelMap)|Acc])
 
178
      end;
 
179
    _ -> 
 
180
      map_code(Left, ArithFail, LabelMap, [redirect(I, LabelMap)|Acc])
 
181
  end;
 
182
map_code([], _ArithFail, _LabelMap, Acc) ->
 
183
  lists:reverse(Acc).
 
184
 
 
185
insert_tests(Cfg, Labels,NewToOldMap, OldToNewMap) ->
 
186
  InfoMap = infomap_init(Labels),
 
187
  %%io:format("insert_tests/3: Finding testpoints ...\n", []),
 
188
  NewInfoMap = find_testpoints(Cfg, Labels, InfoMap),
 
189
  %%io:format("insert_tests/3: Finding testpoints: Done\n", []),
 
190
  %%io:format("insert_tests/3: Infomap: ~w\n", [gb_trees:to_list(NewInfoMap)]),
 
191
  make_tests(Cfg, NewInfoMap, NewToOldMap, OldToNewMap).
 
192
 
 
193
find_testpoints(Cfg, Labels, InfoMap) ->
 
194
  case find_testpoints(Labels, InfoMap, Cfg, false) of
 
195
    {dirty, NewInfoMap} -> 
 
196
      %%io:format("find_testpoints/3: Looping\n", []),
 
197
      find_testpoints(Cfg, Labels, NewInfoMap);
 
198
    fixpoint ->
 
199
      InfoMap 
 
200
  end.
 
201
 
 
202
find_testpoints([Lbl|Left], InfoMap, Cfg, Dirty)->
 
203
  Code = hipe_bb:code(hipe_icode_cfg:bb(Cfg, Lbl)),
 
204
  InfoOut = join_info(hipe_icode_cfg:succ(Cfg, Lbl), InfoMap),  
 
205
  OldInfoIn = infomap_get_all(Lbl, InfoMap),
 
206
  NewInfoIn = traverse_code(lists:reverse(Code), InfoOut),
 
207
  case (gb_sets:is_subset(OldInfoIn, NewInfoIn) andalso 
 
208
        gb_sets:is_subset(NewInfoIn, OldInfoIn)) of
 
209
    true ->
 
210
      find_testpoints(Left, InfoMap, Cfg, Dirty);
 
211
    false ->
 
212
      %%io:format("find_testpoints/4: Label: ~w: OldMap ~w\nNewMap: ~w\n", 
 
213
      %%         [Lbl, gb_sets:to_list(OldInfoIn), gb_sets:to_list(NewInfoIn)]),
 
214
      NewInfoMap = gb_trees:update(Lbl, NewInfoIn, InfoMap),
 
215
      find_testpoints(Left, NewInfoMap, Cfg, true)
 
216
  end;
 
217
find_testpoints([], InfoMap, _Cfg, Dirty) ->
 
218
  if Dirty -> {dirty, InfoMap};
 
219
     true -> fixpoint
 
220
  end.
 
221
      
 
222
traverse_code([I|Left], Info)->
 
223
  NewInfo = kill_defines(I, Info),
 
224
  case I of
 
225
    #call{} ->
 
226
      case is_unsafe_arith(I) of
 
227
        true ->
 
228
          %% The dst is sure to be a fixnum. Remove the 'killed' mark.
 
229
          Dst = hd(hipe_icode:call_dstlist(I)),
 
230
          NewInfo1 = gb_sets:delete_any({killed, Dst}, NewInfo),
 
231
          NewInfo2 = 
 
232
            gb_sets:union(NewInfo1, gb_sets:from_list(hipe_icode:uses(I))),
 
233
          traverse_code(Left, NewInfo2);
 
234
        false ->
 
235
          traverse_code(Left, NewInfo)
 
236
      end;
 
237
    #move{} ->
 
238
      Dst = hipe_icode:move_dst(I),
 
239
      case gb_sets:is_member(Dst, Info) of 
 
240
        true -> 
 
241
          %% The dst is an argument to an arith op. Transfer the test
 
242
          %% to the src and remove the 'killed' mark from the dst.
 
243
          NewInfo1 = gb_sets:delete({killed, Dst}, NewInfo),
 
244
          Src = hipe_icode:move_src(I),
 
245
          case hipe_icode:is_const(Src) of
 
246
            true ->
 
247
              traverse_code(Left, NewInfo1);
 
248
            false ->
 
249
              NewInfo2 = gb_sets:add(Src, NewInfo1),
 
250
              traverse_code(Left, NewInfo2)
 
251
          end;
 
252
        false ->
 
253
          traverse_code(Left, NewInfo)
 
254
      end;
 
255
    _ ->
 
256
      traverse_code(Left, NewInfo)
 
257
  end;
 
258
traverse_code([], Info) ->
 
259
  Info.
 
260
 
 
261
kill_defines(I, Info)->  
 
262
  Defines = hipe_icode:defines(I),
 
263
  case [X||X<-Defines, gb_sets:is_member(X, Info)] of
 
264
    List when length(List)>0 ->
 
265
      TmpInfo = gb_sets:difference(Info, gb_sets:from_list(List)),
 
266
      gb_sets:union(gb_sets:from_list([{killed, X}||X<-List]), TmpInfo);
 
267
    [] ->
 
268
      Info
 
269
  end.
 
270
 
 
271
make_tests(Cfg, InfoMap, NewToOldMap, OldToNewMap)->
 
272
  %%io:format("make_tests 0:\n",[]),
 
273
  WorkList = make_worklist(gb_trees:keys(NewToOldMap), InfoMap, 
 
274
                           NewToOldMap, Cfg, []),
 
275
  %%io:format("make_tests 1:Worklist: ~w\n",[WorkList]),
 
276
  NewCfg = make_tests(WorkList, Cfg),
 
277
  %%io:format("make_tests 2\n",[]),
 
278
  %% If the arguments to this function are used in unsafe arith
 
279
  %% they should be marked as killed by a new start block.
 
280
  Args = hipe_icode_cfg:params(NewCfg),
 
281
  Start = hipe_icode_cfg:start_label(NewCfg),
 
282
  AltStart = gb_trees:get(Start, OldToNewMap),
 
283
  UnsafeIn = gb_sets:to_list(infomap_get(AltStart, InfoMap)),
 
284
  case [X || X<-UnsafeIn, Y<-Args, X=:=Y] of
 
285
    [] -> 
 
286
      hipe_icode_cfg:start_label_update(NewCfg, AltStart);
 
287
    KilledArgs ->
 
288
      NewStart = hipe_icode:label_name(hipe_icode:mk_new_label()),
 
289
      NewCfg1 = insert_test_block(NewStart, AltStart, 
 
290
                                  Start,
 
291
                                  KilledArgs, NewCfg),
 
292
      hipe_icode_cfg:start_label_update(NewCfg1, NewStart)
 
293
  end.
 
294
 
 
295
 
 
296
 
 
297
make_worklist([Lbl|Left], InfoMap, LabelMap, Cfg, Acc)->
 
298
  case infomap_get_killed(Lbl, InfoMap) of
 
299
    [] -> make_worklist(Left, InfoMap, LabelMap, Cfg, Acc);
 
300
    Vars ->
 
301
      %%io:format("make_worklist 1 ~w\n",[Vars]),      
 
302
      NewAcc = 
 
303
        [{Lbl, Succ, gb_trees:get(Succ, LabelMap), Vars}
 
304
         || Succ<-hipe_icode_cfg:succ(Cfg, Lbl)] ++ Acc,
 
305
      %%io:format("make_worklist 2\n",[]),
 
306
      make_worklist(Left, InfoMap, LabelMap, Cfg, NewAcc)
 
307
  end;
 
308
make_worklist([], _InfoMap, _LabelMap, _Cfg, Acc) ->
 
309
  Acc.
 
310
 
 
311
make_tests([{FromLbl, ToLbl, FailLbl, Vars}|Left], Cfg)->
 
312
  NewLbl = hipe_icode:label_name(hipe_icode:mk_new_label()),
 
313
  TmpCfg = insert_test_block(NewLbl, ToLbl, FailLbl, Vars, Cfg),  
 
314
  NewCfg = hipe_icode_cfg:redirect(TmpCfg, FromLbl, ToLbl, NewLbl),
 
315
  make_tests(Left, NewCfg);
 
316
make_tests([], Cfg) ->
 
317
  Cfg.
 
318
 
 
319
insert_test_block(NewLbl, Succ, FailLbl, Vars, Cfg)->
 
320
  Code = [hipe_icode:mk_type(Vars, fixnum, Succ, FailLbl, 0.99)],
 
321
  BB = hipe_bb:mk_bb(Code),
 
322
  hipe_icode_cfg:bb_add(Cfg, NewLbl, BB).
 
323
 
 
324
 
 
325
 
 
326
infomap_init(Labels)->
 
327
  infomap_init(Labels, gb_trees:empty()).
 
328
 
 
329
infomap_init([Lbl|Left], Map)->
 
330
  infomap_init(Left, gb_trees:insert(Lbl, gb_sets:empty(), Map));
 
331
infomap_init([], Map) ->
 
332
  Map.
 
333
 
 
334
join_info(Labels, Map)->
 
335
  join_info(Labels, Map, gb_sets:empty()).
 
336
 
 
337
join_info([Lbl|Left], Map, Set) ->  
 
338
  join_info(Left, Map, gb_sets:union(Set, infomap_get(Lbl, Map)));
 
339
join_info([], _Map, Set) ->
 
340
  Set.
 
341
 
 
342
 
 
343
infomap_get(Lbl, Map)->
 
344
  case gb_trees:lookup(Lbl, Map) of
 
345
    none -> gb_sets:empty();
 
346
    {value, Val} -> 
 
347
      gb_sets:filter(fun(X)->case X of 
 
348
                               {killed, _}->false;
 
349
                               _->true
 
350
                             end
 
351
                     end, 
 
352
                     Val)
 
353
  end.
 
354
 
 
355
infomap_get_all(Lbl, Map)->
 
356
  case gb_trees:lookup(Lbl, Map) of
 
357
    none -> gb_sets:empty();
 
358
    {value, Val} -> Val
 
359
  end.
 
360
 
 
361
infomap_get_killed(Lbl, Map)->
 
362
  case gb_trees:lookup(Lbl, Map) of
 
363
    none -> [];
 
364
    {value, Val} -> 
 
365
      Fun = fun(X, Acc) ->
 
366
                case X of
 
367
                  {killed, Var} -> [Var|Acc];
 
368
                  _ -> Acc
 
369
                end
 
370
            end,
 
371
      lists:foldl(Fun, [], gb_sets:to_list(Val))
 
372
  end.
 
373
 
 
374
is_arith(I)->
 
375
  case hipe_icode:call_fun(I) of
 
376
    '+' -> true;
 
377
    '-' -> true;
 
378
    'band' -> true;
 
379
    'bor' -> true;
 
380
    'bxor' -> true;
 
381
    'bnot' -> true;
 
382
    _ -> false
 
383
  end.
 
384
 
 
385
is_unsafe_arith(I)->
 
386
  case hipe_icode:call_fun(I) of
 
387
    unsafe_add -> true;
 
388
    unsafe_sub -> true;
 
389
    unsafe_band -> true;
 
390
    unsafe_bor -> true;
 
391
    unsafe_bxor -> true;
 
392
    unsafe_bnot -> true;
 
393
    _ -> false
 
394
  end.
 
395
 
 
396
arithop_to_unsafe(Op)->
 
397
  case Op of
 
398
    '+' -> unsafe_add;
 
399
    '-' -> unsafe_sub;
 
400
    'band' -> unsafe_band;
 
401
    'bor' -> unsafe_bor;
 
402
    'bxor' -> unsafe_bxor;
 
403
    'bnot' -> unsafe_bnot  
 
404
  end.
 
405
 
 
406
redirect(I, LabelMap)->
 
407
  case hipe_icode:successors(I) of
 
408
    [] -> I;
 
409
    [[]] -> I;
 
410
    Succ ->
 
411
      RedirectMap = [{X, gb_trees:get(X, LabelMap)}||X<-Succ],
 
412
      redirect_1(RedirectMap, I)
 
413
  end.
 
414
          
 
415
redirect_1([{From, To}|Left], I)->
 
416
  redirect_1(Left, hipe_icode:redirect_jmp(I, From, To));
 
417
redirect_1([], I) ->
 
418
  I.
 
419
 
 
420
new_label_maps(Labels)->
 
421
  new_label_maps(Labels, gb_trees:empty(), gb_trees:empty()).
 
422
 
 
423
new_label_maps([Lbl|Left], Map1, Map2)->
 
424
  NewLabel = hipe_icode:label_name(hipe_icode:mk_new_label()),
 
425
  NewMap1 = gb_trees:insert(Lbl, NewLabel, Map1),
 
426
  NewMap2 = gb_trees:insert(NewLabel, Lbl, Map2),
 
427
  new_label_maps(Left, NewMap1, NewMap2);
 
428
new_label_maps([], Map1, Map2) ->
 
429
  {Map1, Map2}.