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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_binary_pass.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_binary_pass.erl
3
 
%%% Author  : Per Gustafsson <pergu@fan.it.uu.se>
4
 
%%% Description : 
5
 
%%%
6
 
%%% Created : 13 Mar 2003 by Per Gustafsson <pergu@fan.it.uu.se>
7
 
%%%-------------------------------------------------------------------
8
1
%% -*- erlang-indent-level: 2 -*-
9
 
 
 
2
%%--------------------------------------------------------------------
 
3
%% File    : hipe_icode_binary_pass.erl
 
4
%% Author  : Per Gustafsson <pergu@it.uu.se>
 
5
%% Description : 
 
6
%%
 
7
%% Created : 13 Mar 2003 by Per Gustafsson <pergu@it.uu.se>
 
8
%%--------------------------------------------------------------------
10
9
 
11
10
-module(hipe_icode_binary_pass).
12
11
 
14
13
 
15
14
-include("../rtl/hipe_literals.hrl").
16
15
 
17
 
 
18
 
%% make_pass starts a pass over an icodecfg. The purpose of the pass
19
 
%% It creates a list of basic blocks that are members of a binary match
20
 
%% Then it calculates the maximal heap need of this binary match. Finally
21
 
%% it creates a new bit syntax operation create space that makes 
22
 
%% sure that there is enough space on the heap for each binary match
23
 
%%
24
 
%% The lists of basic blocks that are members of binary matches are also used 
25
 
%% to give all bit syntax operations the state parameters as arguments and destinations. 
26
 
make_pass(CFG0) ->
27
 
  CFG=make_bs_ops_end_basic_blocks(CFG0),
28
 
  StartLabel = hipe_icode_cfg:start(CFG),
29
 
  Vis0 = hipe_icode_cfg:none_visited(CFG),   
 
16
%%--------------------------------------------------------------------
 
17
 
 
18
%% @spec make_pass(IcodeCFG::icode_cfg()) -> icode_cfg()
 
19
%%
 
20
%% @type icode_cfg() = term()
 
21
%%
 
22
%% @doc Makes a pass over an IcodeCFG so as to create a list of basic
 
23
%% blocks that are members of a binary match. Then it calculates the
 
24
%% maximal heap need of this binary match. Finally, it creates a new
 
25
%% bit syntax operation which makes sure that there is enough space on
 
26
%% the heap for each binary match.
 
27
%%
 
28
%% <p> The lists of basic blocks which are members of binary matches
 
29
%% are also used to give all bit syntax operations the state
 
30
%% parameters as arguments and destinations. </p>
 
31
%%
 
32
 
 
33
make_pass(IcodeCFG0) ->
 
34
  CFG = make_bs_ops_end_basic_blocks(IcodeCFG0),
 
35
  StartLabel = hipe_icode_cfg:start_label(CFG),
 
36
  Vis0 = hipe_icode_cfg:none_visited(),
30
37
  EmptyBinChunks = [],
31
38
  FinalBinChunks = make_pass(CFG, [StartLabel], Vis0, EmptyBinChunks),
32
 
  CFG1=add_code(FinalBinChunks,CFG),
33
 
  copy_state(FinalBinChunks,CFG1).
 
39
  CFG1 = add_code(FinalBinChunks, CFG),
 
40
  copy_state(FinalBinChunks, CFG1).
34
41
 
35
42
make_bs_ops_end_basic_blocks(CFG) ->
36
 
  LinIcode = hipe_icode_cfg:linearize(CFG),
 
43
  LinIcode = hipe_icode_cfg:cfg_to_linear(CFG),
37
44
  Code = hipe_icode:icode_code(LinIcode),
38
 
  NewCode=lists:foldr(fun break_block/2, [], Code),
 
45
  NewCode = lists:foldr(fun break_block/2, [], Code),
39
46
  NewLinIcode = hipe_icode:icode_code_update(LinIcode, NewCode),
40
 
  hipe_icode_cfg:init(NewLinIcode).
 
47
  hipe_icode_cfg:linear_to_cfg(NewLinIcode).
41
48
 
42
49
break_block(Instr, Acc) ->
43
50
  case hipe_icode:is_call(Instr) of 
44
51
    true ->
45
52
      case hipe_icode:call_fun(Instr) of
46
 
        {hipe_bs_primop,_} ->
 
53
        {hipe_bs_primop, _} ->
47
54
          case hipe_icode:call_continuation(Instr) of
48
55
            [] ->
49
56
              ContLbl = hipe_icode:mk_new_label(),
58
65
    false ->
59
66
      [Instr|Acc]
60
67
  end.
 
68
 
61
69
make_pass(CFG, [Label | Labels], Visited, BinChunks) ->
62
 
  case hipe_icode_cfg:visited(Label, Visited) of 
 
70
  case hipe_icode_cfg:is_visited(Label, Visited) of 
63
71
    true ->
64
72
      make_pass(CFG, Labels, Visited, BinChunks); 
65
73
    false ->
66
74
      NewVisited = hipe_icode_cfg:visit(Label, Visited),
67
75
      CurrentBB = hipe_icode_cfg:bb(CFG, Label),
68
76
      Instr = hipe_bb:last(CurrentBB),
69
 
      NewBinChunks=test_instr(Instr, CFG, Label, BinChunks), 
 
77
      NewBinChunks = test_instr(Instr, CFG, Label, BinChunks), 
70
78
      NewLabels = Labels ++ hipe_icode_cfg:succ(CFG, Label),
71
79
      make_pass(CFG, NewLabels, NewVisited, NewBinChunks)
72
80
  end;
73
 
 
74
81
make_pass(_CFG, [], _Visited, BinChunks) ->
75
82
  BinChunks.
76
83
 
92
99
extract_binary_creation(CFG, Label) ->
93
100
  CurrentBB = hipe_icode_cfg:bb(CFG, Label),
94
101
  LastInstr = hipe_bb:last(CurrentBB),
95
 
  FailLbl = hipe_icode:call_fail(LastInstr),
96
 
  Next=hipe_icode:call_continuation(LastInstr),
97
 
  extract_binary_creation(CFG, Next, Label,[],[],FailLbl).
 
102
  FailLbl = hipe_icode:call_fail_label(LastInstr),
 
103
  Next = hipe_icode:call_continuation(LastInstr),
 
104
  extract_binary_creation(CFG, Next, Label, [], [], gb_trees:empty(), FailLbl).
98
105
 
99
 
extract_binary_creation(CFG, Label, Start, Labels,Sizes,FailLbl) ->
 
106
extract_binary_creation(CFG, Label, Start, Labels, Sizes, VarMap, FailLbl) ->
100
107
  CurrentBB = hipe_icode_cfg:bb(CFG, Label),
101
108
  LastInstr = hipe_bb:last(CurrentBB),
 
109
  OtherCode = hipe_bb:butlast(CurrentBB),
 
110
  NewVarMap = update_varmap(OtherCode, VarMap),
102
111
  case hipe_icode:is_call(LastInstr) of
103
112
    true ->
104
113
      case hipe_icode:call_fun(LastInstr) of
115
124
            {bs_put_integer, Size, _, _} ->
116
125
              [];
117
126
            {bs_put_string, _, SizeInBytes} ->
118
 
              Size = SizeInBytes * 8  
 
127
              Size = SizeInBytes bsl 3;  % SizeInBytes * 8
 
128
            {bs_put_string, _, SizeInBytes, _} ->
 
129
              Size = SizeInBytes bsl 3   % SizeInBytes * 8
119
130
          end,
120
 
          Next=hipe_icode:call_continuation(LastInstr),
 
131
          Next = hipe_icode:call_continuation(LastInstr),
121
132
          case {hipe_icode:call_args(LastInstr), Size} of
122
 
            {[Arg], all} -> 
123
 
              NewFailLbl=hipe_icode:call_fail(LastInstr),
 
133
            {[Arg],all} -> 
 
134
              NewFailLbl = hipe_icode:call_fail_label(LastInstr),
124
135
              case acceptable(CurrentBB, Arg) of
125
 
                true ->
126
 
                  extract_binary_creation(CFG, Next, Start, [Label|Labels], [{all, Arg}|Sizes], NewFailLbl);
 
136
                {true, Arg1} ->
 
137
                  extract_binary_creation(CFG, Next, Start,
 
138
                                          [Label|Labels], [{all, Arg1}|Sizes],
 
139
                                          NewVarMap, NewFailLbl);
127
140
                false ->
128
 
                  extract_binary_creation(CFG, Next, Start, [Label|Labels], [fail|Sizes], FailLbl)
 
141
                  extract_binary_creation(CFG, Next, Start, 
 
142
                                          [Label|Labels], [fail|Sizes],
 
143
                                          NewVarMap, FailLbl)
129
144
              end;
130
 
            {[_], _} ->
131
 
              extract_binary_creation(CFG, Next, Start, [Label|Labels], [{const, Size}|Sizes], FailLbl);
 
145
            {[_],_} ->
 
146
              extract_binary_creation(CFG, Next, Start,
 
147
                                      [Label|Labels], [{const, Size}|Sizes],
 
148
                                      NewVarMap, FailLbl);
132
149
            {[],_} ->
133
 
              extract_binary_creation(CFG, Next, Start, [Label|Labels], [{const, Size}|Sizes], FailLbl);
134
 
            {[_, SizeVar], _} ->
135
 
              NewFailLbl=hipe_icode:call_fail(LastInstr),
136
 
              extract_binary_creation(CFG, Next, Start, [Label|Labels], [{Size, SizeVar}|Sizes], NewFailLbl)
 
150
              extract_binary_creation(CFG, Next, Start,
 
151
                                      [Label|Labels], [{const, Size}|Sizes],
 
152
                                      NewVarMap, FailLbl);
 
153
            {[_,SizeVar],_} ->
 
154
              RealSizeVar = translate_sizevar(SizeVar, NewVarMap),
 
155
              NewFailLbl = hipe_icode:call_fail_label(LastInstr),
 
156
              extract_binary_creation(CFG, Next, Start, [Label|Labels],
 
157
                                      [{Size, RealSizeVar}|Sizes],
 
158
                                      NewVarMap, NewFailLbl)
137
159
          end
138
160
      end
139
161
  end.      
140
 
%%Extract binaries creates the lists of basic blocks that belongs to each binary match
 
162
 
 
163
update_varmap([Instr|Rest], VarMap) ->
 
164
  case hipe_icode:is_move(Instr) of
 
165
    true ->
 
166
      Src = hipe_icode:move_src(Instr),
 
167
      Dst = hipe_icode:move_dst(Instr),
 
168
      case hipe_icode:is_var(Src) andalso hipe_icode:is_var(Dst) of
 
169
        true ->
 
170
          case gb_trees:lookup(Src, VarMap) of
 
171
            {value,Val} ->
 
172
              update_varmap(Rest, gb_trees:insert(Dst, Val, VarMap));
 
173
            none ->
 
174
              update_varmap(Rest, gb_trees:insert(Dst, Src, VarMap))
 
175
          end;
 
176
        false ->
 
177
          update_varmap(Rest, VarMap)
 
178
      end;
 
179
    false ->
 
180
      update_varmap(Rest, VarMap)
 
181
  end;
 
182
update_varmap([], VarMap) ->
 
183
  VarMap.
 
184
 
 
185
translate_sizevar(SizeVar, VarMap) ->
 
186
  case gb_trees:lookup(SizeVar, VarMap) of
 
187
    {value, Val} ->
 
188
      Val;
 
189
    none ->
 
190
      SizeVar
 
191
  end.
 
192
 
 
193
%% Extract binaries creates the lists of basic blocks that belong to
 
194
%% each binary match
141
195
 
142
196
acceptable(BB, Arg) ->
143
 
  Code=hipe_bb:butlast(BB),
144
 
  case get_last(Code) of
 
197
  Code = hipe_bb:butlast(BB),
 
198
  case Code of
145
199
    [] ->
146
 
      true;
147
 
    Instr ->
148
 
      case hipe_icode:is_mov(Instr) of
 
200
      {true, Arg};
 
201
    [_|_] ->
 
202
      Instr = lists:last(Code),
 
203
      case hipe_icode:is_move(Instr) of
149
204
        true ->
150
 
          case hipe_icode:mov_dst(Instr) of
 
205
          case hipe_icode:move_dst(Instr) of
151
206
            Arg ->
152
 
              false;
 
207
              Src = hipe_icode:move_src(Instr),
 
208
              case hipe_icode:is_var(Src) of
 
209
                true ->
 
210
                  {true, Src};
 
211
                false ->
 
212
                  false
 
213
              end;
153
214
            _ ->
154
 
              true
 
215
              {true, Arg}
155
216
          end;
156
217
        _ ->
157
 
          true
 
218
          {true, Arg}
158
219
      end
159
220
  end.
160
221
 
161
 
get_last([Last]) ->
162
 
  Last;
163
 
get_last([_|Rest]) ->
164
 
  get_last(Rest);
165
 
get_last([]) ->
166
 
  [].
167
222
extract_binary_matches(CFG, Label) ->
168
223
  CurrentBB = hipe_icode_cfg:bb(CFG, Label),
169
 
  Exit_set0 = hipe_icode_cfg:none_visited(CFG),
 
224
  Exit_set0 = hipe_icode_cfg:none_visited(),
170
225
  Bin_match_call = hipe_bb:last(CurrentBB),
171
 
  Exit_set = hipe_icode_cfg:visit(pass_by_restore_catch(hipe_icode:call_fail(Bin_match_call),CFG), Exit_set0),
172
 
  Chunk = [{Label, 0, Successors = [hipe_icode:call_continuation(Bin_match_call)] }],
 
226
  Exit_set = hipe_icode_cfg:visit(pass_by_begin_handler(hipe_icode:call_fail_label(Bin_match_call),CFG), Exit_set0),
 
227
  Successors = [hipe_icode:call_continuation(Bin_match_call)],
 
228
  Chunk = [{Label, 0, Successors}],
173
229
  {Label, extract_binary_matches(CFG, Successors, Exit_set, Chunk)}.
174
230
 
175
231
extract_binary_matches(CFG, [Label | Labels], Exit_set0, Chunk0) ->
185
241
            true ->
186
242
              case hipe_icode:call_fun(LastInstr) of
187
243
                {_, {bs_test_tail,_}} ->
188
 
                  hipe_icode_cfg:visit(hipe_icode:call_continuation(LastInstr), Exit_set0);
 
244
                  hipe_icode_cfg:visit(hipe_icode:call_continuation(LastInstr),
 
245
                                       Exit_set0);
189
246
                _ ->
190
247
                  Exit_set0
191
248
              end;
192
249
            false ->
193
250
              Exit_set0
194
251
          end,
195
 
        PossibleLabels = pass_by_restore_catch(hipe_icode_cfg:succ(CFG, Label), CFG, []), 
 
252
        PossibleLabels = pass_by_begin_handler(hipe_icode_cfg:succ(CFG, Label), CFG, []), 
196
253
        AcceptableLabels = remove_members(PossibleLabels, Exit_set1),
197
254
        Chunk1 = [{Label, Size, AcceptableLabels} | Chunk0],
198
255
        extract_binary_matches(CFG, AcceptableLabels, Exit_set1, Chunk1)
199
256
    end,
200
257
  extract_binary_matches(CFG, Labels, Exit_set, Chunk); 
201
 
 
202
258
extract_binary_matches(_CFG, [], Exit_set0, Chunk0) ->    
203
259
  {Exit_set0, Chunk0}.
204
260
 
205
 
pass_by_restore_catch([Label| Labels], CFG, Acc) -> 
206
 
  pass_by_restore_catch(Labels, CFG, [pass_by_restore_catch(Label, CFG)|Acc]);
207
 
pass_by_restore_catch([],_CFG, Acc) ->
 
261
pass_by_begin_handler([Label| Labels], CFG, Acc) -> 
 
262
  pass_by_begin_handler(Labels, CFG, [pass_by_begin_handler(Label, CFG)|Acc]);
 
263
pass_by_begin_handler([], _CFG, Acc) ->
208
264
  Acc.
209
 
pass_by_restore_catch(Label, CFG) -> 
 
265
 
 
266
pass_by_begin_handler(Label, CFG) -> 
210
267
  CurrentBB = hipe_icode_cfg:bb(CFG, Label), 
211
 
  [First | _] = hipe_bb:code(CurrentBB),
212
 
  case hipe_icode:is_restore_catch(First) of 
213
 
    true ->  
214
 
      hipe_icode:goto_label(hipe_bb:last(CurrentBB)); 
 
268
  [First|_] = hipe_bb:code(CurrentBB),
 
269
  case hipe_icode:is_begin_handler(First) of 
 
270
    true ->  hipe_icode:goto_label(hipe_bb:last(CurrentBB)); 
215
271
    false -> Label 
216
272
  end.
217
273
 
218
274
heap_need(Instruction) ->
219
 
  case {hipe_icode:is_call(Instruction), hipe_icode:call_fun(Instruction)} of
220
 
    {true, {hipe_bs_primop, Name}} ->
221
 
      case Name of
222
 
        {bs_get_integer,Size,_} ->
223
 
          case hipe_icode:call_args(Instruction) of
224
 
            [] ->
225
 
              case Size < 28 of
226
 
                true ->
227
 
                  0;
228
 
                false ->
229
 
                  ((Size+31) div 32)+2
230
 
              end;
 
275
  case hipe_icode:is_call(Instruction) of
 
276
    true ->
 
277
      case hipe_icode:call_fun(Instruction) of
 
278
        {hipe_bs_primop, Name} ->
 
279
          case Name of
 
280
            {bs_get_integer,Size,_} ->
 
281
              case hipe_icode:call_args(Instruction) of
 
282
                [] ->
 
283
                  case Size < 28 of
 
284
                    true ->
 
285
                      0;
 
286
                    false ->
 
287
                      ((Size+31) div 32)+2
 
288
                  end;
 
289
                _ ->
 
290
                  0
 
291
              end;
 
292
            {bs_get_float,_,_} ->
 
293
              3;
 
294
            {bs_get_binary,_Size,Flag} ->
 
295
              case Flag band 1 of
 
296
                1 ->
 
297
                  4;
 
298
                0 ->
 
299
                  trunc(?MAX_HEAP_BIN_SIZE/4)+2
 
300
              end;
 
301
            {bs_get_binary_all, _} ->
 
302
              4;
231
303
            _ ->
232
304
              0
233
305
          end;
234
 
        {bs_get_float,_,_} ->
235
 
          3;
236
 
        {bs_get_binary,_Size,Flag} ->
237
 
          case Flag band 1 of
238
 
            1 ->
239
 
              4;
240
 
            0 ->
241
 
              trunc(?MAX_HEAP_BIN_SIZE/4) +2
242
 
          end;
243
 
        {bs_get_binary_all, _} ->
244
 
          4;
245
 
        _ ->
246
 
          0
247
 
 
 
306
        _ ->
 
307
          0
248
308
      end;
249
 
    _ ->
 
309
    false ->
250
310
      0
251
311
  end.
252
312
 
253
 
 
254
313
remove_members(Labels, Set) ->
255
314
  remove_members(Labels, Set, []).
256
315
 
257
316
remove_members([Label | Labels], Set, Ok) ->
258
 
  case hipe_icode_cfg:visited(Label, Set) of
 
317
  case hipe_icode_cfg:is_visited(Label, Set) of
259
318
    true ->
260
319
      remove_members(Labels, Set, Ok);
261
320
    false ->
262
 
      remove_members(Labels, Set, [Label |Ok])
 
321
      remove_members(Labels, Set, [Label|Ok])
263
322
  end;
264
 
 
265
 
remove_members([], _Set, Ok) ->             
 
323
remove_members([], _Set, Ok) ->
266
324
  Ok.
267
325
 
 
326
calculate_need({Chunk, Hash}, Start) ->
 
327
  case gb_trees:lookup(Start, Hash) of
 
328
    {value, Val} ->
 
329
      {Val, {Chunk, Hash}};
 
330
    none ->
 
331
      {value,{Start,Need,Succ}} = lists:keysearch(Start,1,Chunk),
 
332
      {NewValue, {Chunk, NewHash}} = calculate_need(Chunk, Succ, Need, Hash),
 
333
      NewerHash = gb_trees:enter(Start, NewValue, NewHash),
 
334
      {NewValue, {Chunk, NewerHash}}
 
335
  end;
268
336
calculate_need(Chunk, Start) ->
269
 
  {value,{Start,Need,Succ}}=lists:keysearch(Start,1,Chunk),
270
 
  calculate_need(Chunk, Succ, Need).
271
 
 
272
 
calculate_need(_Chunk, [], Need) ->
273
 
  Need;
274
 
 
275
 
calculate_need(Chunk, Succ, Need) ->
276
 
  {Resultlist, _} =     lists:mapfoldl(fun(X, Ch)->{calculate_need(Ch,X), Ch} end, Chunk, Succ),
277
 
  lists:max(Resultlist)+Need.
278
 
 
279
 
 
280
 
add_code([{match,{Start,{_Exitset,Chunk}}}|Rest],CFG) ->
281
 
  Need=calculate_need(Chunk, Start),
282
 
  {Shifts, Args}= runtime_effects(Chunk, CFG),
283
 
  StartBlock=hipe_icode_cfg:bb(CFG,Start),
284
 
  ResultBB=hipe_bb:code_update(StartBlock, hipe_bb:butlast(StartBlock) ++ [hipe_icode:mk_primop([],{hipe_bs_primop,{bs_create_space, Need, Shifts}},Args), hipe_bb:last(StartBlock)]),
285
 
  CFG1=hipe_icode_cfg:bb_update(CFG, Start, ResultBB),
 
337
  {Need,_} = calculate_need({Chunk, gb_trees:empty()}, Start),
 
338
  Need.
 
339
 
 
340
calculate_need(Chunk, [], Need, Hash) ->
 
341
  {Need, {Chunk, Hash}};
 
342
 
 
343
calculate_need(Chunk, Succ, Need, Hash) ->
 
344
  {Resultlist,NewAccu} = lists:mapfoldl(fun(X, Ch)-> calculate_need(Ch, X) end,
 
345
                                        {Chunk,Hash}, Succ),
 
346
  {lists:max(Resultlist)+Need, NewAccu}.
 
347
 
 
348
add_code([{match,{Start,{_Exitset,Chunk}}}|Rest], CFG) ->
 
349
  Need = calculate_need(Chunk, Start),
 
350
  {Shifts,Args} = runtime_effects(Chunk, CFG),
 
351
  StartBlock = hipe_icode_cfg:bb(CFG,Start),
 
352
  ResultBB = hipe_bb:code_update(StartBlock, hipe_bb:butlast(StartBlock) ++ [hipe_icode:mk_primop([],{hipe_bs_primop,{bs_create_space, Need, Shifts}},Args), hipe_bb:last(StartBlock)]),
 
353
  CFG1 = hipe_icode_cfg:bb_add(CFG, Start, ResultBB),
286
354
  add_code(Rest,CFG1);
287
 
 
288
355
add_code([{create,{Start, Sizes, Labels, FailLbl}}|Rest], CFG) ->
289
 
  StartBlock=hipe_icode_cfg:bb(CFG,Start),
290
 
  Init=hipe_bb:last(StartBlock),
291
 
  {NewBlock, State} = update_init(Init, StartBlock, Sizes, FailLbl),
292
 
  CFG1= hipe_icode_cfg:bb_update(CFG, Start, NewBlock),
293
 
  CFG2= add_state(Labels, State, CFG1),
 
356
  StartBlock = hipe_icode_cfg:bb(CFG,Start),
 
357
  Init = hipe_bb:last(StartBlock),
 
358
  {NewBlock,State} = update_init(Init, StartBlock, Sizes, FailLbl),
 
359
  CFG1 = hipe_icode_cfg:bb_add(CFG, Start, NewBlock),
 
360
  CFG2 = add_state(Labels, State, CFG1),
294
361
  add_code(Rest, CFG2);
295
 
 
296
 
add_code([],CFG) ->
 
362
add_code([], CFG) ->
297
363
  CFG.
298
364
 
299
365
update_init(Init, StartBlock, Sizes, FailLbl) ->                       
300
 
  Base=hipe_icode:mk_new_reg(),
301
 
  Offset=hipe_icode:mk_new_reg(),
 
366
  Base = hipe_icode:mk_new_reg(),
 
367
  Offset = hipe_icode:mk_new_reg(),
302
368
  NewInit = 
303
369
    case condense_sizes(Sizes) of
304
370
      {Const, Units, SizeArgs} ->
305
 
        Init1=hipe_icode:call_fun_update(Init, {hipe_bs_primop,{bs_init,{Const, Units}}}),
306
 
        Init2=hipe_icode:call_dst_update(Init1, [Base, Offset]),
307
 
        Init3=hipe_icode:call_args_update(Init2, SizeArgs),
308
 
        hipe_icode:call_set_fail(Init3, FailLbl);
 
371
        Init1 = hipe_icode:call_fun_update(Init, {hipe_bs_primop,{bs_init,{Const, Units}}}),
 
372
        Init2 = hipe_icode:call_dstlist_update(Init1, [Base, Offset]),
 
373
        Init3 = hipe_icode:call_args_update(Init2, SizeArgs),
 
374
        hipe_icode:call_set_fail_label(Init3, FailLbl);
309
375
      fail ->
310
 
        Init1=hipe_icode:call_fun_update(Init, {hipe_bs_primop,{bs_init,fail}}),
311
 
        hipe_icode:call_dst_update(Init1, [Base, Offset])
 
376
        Init1 = hipe_icode:call_fun_update(Init, {hipe_bs_primop,{bs_init,fail}}),
 
377
        hipe_icode:call_dstlist_update(Init1, [Base, Offset])
312
378
    end,
313
 
  NewBlock=hipe_bb:code_update(StartBlock, hipe_bb:butlast(StartBlock) ++ [NewInit]),
314
 
  {NewBlock, [Base, Offset]}.
 
379
  NewBlock = hipe_bb:code_update(StartBlock, hipe_bb:butlast(StartBlock) ++ [NewInit]),
 
380
  {NewBlock,[Base,Offset]}.
315
381
 
316
382
add_state([Label|Rest], State, CFG) ->
317
383
  Block = hipe_icode_cfg:bb(CFG, Label),
318
384
  Instr = hipe_bb:last(Block),
319
385
  Instr1 = add_state_to_instr(Instr, State),
320
386
  NewBB = hipe_bb:code_update(Block, hipe_bb:butlast(Block)++[Instr1]),
321
 
  CFG1 = hipe_icode_cfg:bb_update(CFG, Label, NewBB),
 
387
  CFG1 = hipe_icode_cfg:bb_add(CFG, Label, NewBB),
322
388
  add_state(Rest, State, CFG1);
323
389
add_state([], _State, CFG) ->
324
390
  CFG.
 
391
 
325
392
add_state_to_instr(Instruction, State=[_Base, Offset]) ->
326
393
  case hipe_icode:is_call(Instruction) of
327
394
    true ->
328
395
      case hipe_icode:call_fun(Instruction) of
329
 
        
330
396
        {hipe_bs_primop, Name} ->
331
397
          OldArgs = hipe_icode:call_args(Instruction),
332
 
          OldDsts = hipe_icode:call_dst(Instruction),
 
398
          OldDsts = hipe_icode:call_dstlist(Instruction),
333
399
          {NewArgs, NewDsts} =
334
400
            case Name of
335
401
              bs_init ->
336
402
                {OldArgs, State};
337
403
              {bs_put_string, _, _} ->
338
404
                {OldArgs++State, [Offset]};
 
405
              {bs_put_string, _, _, _} ->
 
406
                {OldArgs++State, [Offset]};
339
407
              {bs_put_integer, _, _, _} ->
340
408
                {OldArgs++State, [Offset]};
341
409
              {bs_put_float, _, _, _} ->
348
416
                {OldArgs++State, OldDsts}
349
417
            end,
350
418
          Instruction1 = hipe_icode:call_args_update(Instruction, NewArgs),
351
 
          hipe_icode:call_dst_update(Instruction1, NewDsts);
 
419
          hipe_icode:call_dstlist_update(Instruction1, NewDsts);
352
420
        _ ->
353
421
          Instruction
354
422
      end;
355
423
    _ ->
356
424
      Instruction
357
425
  end.
358
 
copy_state([{match,{_Start,{_Exitset,Chunk}}}|Rest],CFG) ->
 
426
 
 
427
copy_state([{match,{_Start,{_Exitset,Chunk}}}|Rest], CFG) ->
359
428
  State = [hipe_icode:mk_new_reg(),
360
429
           hipe_icode:mk_new_reg(),
361
430
           hipe_icode:mk_new_reg(),
363
432
           hipe_icode:mk_new_reg()],
364
433
  NewCFG = add_state_to_bs_primops(Chunk, CFG, State),
365
434
  copy_state(Rest, NewCFG); 
366
 
 
367
435
copy_state([_|Rest], CFG) ->
368
436
  copy_state(Rest, CFG);
369
 
 
370
 
copy_state([],CFG) ->
 
437
copy_state([], CFG) ->
371
438
  CFG.
372
439
 
373
 
add_state_to_bs_primops([{Label,_,_}|Rest], CFG, State=[BinSize, Base, Offset, Orig, OrigOffset]) ->
374
 
  OldBB=hipe_icode_cfg:bb(CFG, Label),
375
 
  Instruction=hipe_bb:last(OldBB),
376
 
  CFG1= 
 
440
add_state_to_bs_primops([{Label,_,_}|Rest], CFG,
 
441
                        State=[BinSize,Base,Offset,Orig,OrigOffset]) ->
 
442
  OldBB = hipe_icode_cfg:bb(CFG, Label),
 
443
  Instruction = hipe_bb:last(OldBB),
 
444
  CFG1 =
377
445
    case hipe_icode:is_call(Instruction) of
378
446
      true ->
379
447
        case hipe_icode:call_fun(Instruction) of
380
 
 
381
448
          {hipe_bs_primop, Name} ->
382
449
            OldArgs = hipe_icode:call_args(Instruction),
383
 
            OldDsts = hipe_icode:call_dst(Instruction),
 
450
            OldDsts = hipe_icode:call_dstlist(Instruction),
384
451
            NewName = skip_bits(Name, OldDsts),
385
452
            {NewArgs, NewDsts} =
386
453
              case NewName of
393
460
                {bs_get_binary, _, _} ->
394
461
                  {OldArgs++State, OldDsts++[Offset]};
395
462
                {bs_get_binary_all, _} ->
396
 
                  {OldArgs++[BinSize, Offset, Orig, OrigOffset],  OldDsts++[Offset]};
 
463
                  {OldArgs++[BinSize, Offset, Orig, OrigOffset], OldDsts++[Offset]};
397
464
                {bs_skip_bits, _} ->
398
465
                  {OldArgs++[BinSize, Offset], [Offset]};
399
466
                {bs_skip_bits_all, _} ->
406
473
                  {OldArgs, OldDsts++State}
407
474
              end,
408
475
            Instruction1 = hipe_icode:call_args_update(Instruction, NewArgs),
409
 
            Instruction2 = hipe_icode:call_dst_update(Instruction1, NewDsts),
 
476
            Instruction2 = hipe_icode:call_dstlist_update(Instruction1, NewDsts),
410
477
            NewInstruction = hipe_icode:call_fun_update(Instruction2, {hipe_bs_primop, NewName}),
411
478
            NewBB = hipe_bb:code_update(OldBB, hipe_bb:butlast(OldBB)++[NewInstruction]),
412
 
            hipe_icode_cfg:bb_update(CFG, Label, NewBB);        
 
479
            hipe_icode_cfg:bb_add(CFG, Label, NewBB);   
413
480
          _ ->
414
481
            CFG
415
482
        end;
417
484
        CFG
418
485
    end,
419
486
  add_state_to_bs_primops(Rest, CFG1, State);
420
 
 
421
487
add_state_to_bs_primops([], CFG, _State) ->
422
488
  CFG.
423
489
 
 
490
get_local_mapping(Code) ->
 
491
  get_local_mapping(Code, gb_trees:empty()).
 
492
 
 
493
get_local_mapping([Instr|Instrs], Map) ->
 
494
  case hipe_icode:is_move(Instr) of
 
495
    true ->
 
496
      Dst = hipe_icode:move_dst(Instr), 
 
497
      Src = hipe_icode:move_src(Instr),
 
498
      get_local_mapping(Instrs, gb_trees:enter(Dst, Src, Map)); 
 
499
    false ->
 
500
      get_local_mapping(Instrs, Map)
 
501
  end;
 
502
get_local_mapping([], Map) ->
 
503
  Map.
 
504
 
 
505
get_alias(Arg, Map) ->
 
506
  case gb_trees:lookup(Arg, Map) of
 
507
    {value, Val} -> Val;
 
508
    none -> Arg
 
509
  end.
 
510
 
424
511
runtime_effects(Chunk, CFG) ->
425
512
  {Vars, Bin}=find_results(Chunk, CFG),
426
513
  runtime_effects(Chunk, CFG, [], [], Vars, Bin).
427
514
 
428
515
runtime_effects([{Label,_,_}|Rest], CFG, Shifts, Args, Vars, Bin) ->
429
 
  Instruction=hipe_bb:last(hipe_icode_cfg:bb(CFG, Label)),
 
516
  BB = hipe_icode_cfg:bb(CFG, Label),
 
517
  LocalMapping = get_local_mapping(hipe_bb:code(BB)),
 
518
  Instruction = hipe_bb:last(BB),
430
519
  case hipe_icode:is_call(Instruction) of
431
520
    true ->
432
521
      case hipe_icode:call_fun(Instruction) of
433
522
        {hipe_bs_primop, {bs_get_integer, Size,_}} ->
434
523
          {Shifts1, Args1} =
435
 
              case hipe_icode:call_args(Instruction) of
436
 
                [Arg] ->
437
 
                  case lists:member(Arg, Vars) of
438
 
                    true ->
439
 
                      {[size|Shifts], [Bin|Args]};
440
 
                    false ->
441
 
                      {[rooflog2(Size)|Shifts], [Arg|Args]}
442
 
                  end;
443
 
                _ ->
444
 
                  {Shifts,Args}
445
 
              end,
 
524
            case hipe_icode:call_args(Instruction) of
 
525
              [Arg] ->
 
526
                RealArg  = get_alias(Arg, LocalMapping),
 
527
                case lists:member(RealArg, Vars) of
 
528
                  true ->
 
529
                    {[size|Shifts], [Bin|Args]};
 
530
                  false ->
 
531
                    {[rooflog2(Size)|Shifts], [RealArg|Args]}
 
532
                end;
 
533
              _ ->
 
534
                {Shifts,Args}
 
535
            end,
446
536
          runtime_effects(Rest, CFG, Shifts1, Args1, Vars, Bin);
447
537
        _ ->
448
538
          runtime_effects(Rest, CFG, Shifts, Args, Vars, Bin)
450
540
    _ ->
451
541
      runtime_effects(Rest, CFG, Shifts, Args, Vars, Bin)
452
542
  end;
453
 
 
454
543
runtime_effects([], _CFG, Shifts, Args, _Vars, _Bin) ->
455
544
  {Shifts, Args}.
456
545
 
458
547
  find_results(Chunk, CFG, [], []).
459
548
 
460
549
find_results([{Label,_,_}|Rest], CFG, Vars, Bin) ->
461
 
  Instruction=hipe_bb:last(hipe_icode_cfg:bb(CFG, Label)),
 
550
  Instruction = hipe_bb:last(hipe_icode_cfg:bb(CFG, Label)),
462
551
  {NewVars, NewBin} =
463
552
    case hipe_icode:is_call(Instruction) of
464
553
      true ->
466
555
          {hipe_bs_primop, bs_start_match} ->
467
556
            [Arg] = hipe_icode:call_args(Instruction),
468
557
            {Vars, Arg};
469
 
          {hipe_bs_primop, {bs_get_integer, _Size,_Flags}} ->
470
 
            [Dst]=hipe_icode:call_dst(Instruction),
 
558
          {hipe_bs_primop, {bs_get_integer, _Size, _Flags}} ->
 
559
            [Dst] = hipe_icode:call_dstlist(Instruction),
471
560
            {[Dst|Vars], Bin};
472
561
          _ ->
473
562
            {Vars,Bin}
478
567
  find_results(Rest, CFG, NewVars, NewBin);
479
568
find_results([], _CFG, NewVars, NewBin) ->
480
569
  {NewVars, NewBin}.
 
570
 
481
571
rooflog2(X) ->
482
572
  round(0.5+math:log(X)/math:log(2)).
483
573
 
495
585
condense_sizes([], Consts, {Units,Vars}, Alls) -> 
496
586
  {Consts, Units, Vars ++ Alls}.
497
587
 
498
 
remove_save_restore(CFG) ->
499
 
  Labels = hipe_icode_cfg:reverse_postorder(CFG),
500
 
  iterate_blocks(Labels, CFG, gb_trees:empty()).
 
588
%% @spec remove_save_restore(IcodeCFG::icode_cfg()) -> icode_cfg()
 
589
%%
 
590
%% @doc Given an IcodeCFG, returns a NewIcodeCFG where all the bs_save
 
591
%% and bs_restore primops are removed.
 
592
%%
 
593
remove_save_restore(IcodeCFG) ->
 
594
  Labels = hipe_icode_cfg:reverse_postorder(IcodeCFG),
 
595
  iterate_blocks(Labels, IcodeCFG, gb_trees:empty()).
501
596
 
502
597
iterate_blocks([Label|Rest], CFG, Info) ->
503
 
  CurrentBB=hipe_icode_cfg:bb(CFG, Label),
504
 
  Code=hipe_bb:code(CurrentBB),
505
 
  {NewCode, NewInfo} = iterate_instructions(Code, Info, []),
506
 
  NewBB=hipe_bb:code_update(CurrentBB, NewCode),
507
 
  NewCFG=hipe_icode_cfg:bb_update(CFG, Label, NewBB),
 
598
  CurrentBB = hipe_icode_cfg:bb(CFG, Label),
 
599
  Code = hipe_bb:code(CurrentBB),
 
600
  {NewCode,NewInfo} = iterate_instructions(Code, Info, []),
 
601
  NewBB = hipe_bb:code_update(CurrentBB, NewCode),
 
602
  NewCFG = hipe_icode_cfg:bb_add(CFG, Label, NewBB),
508
603
  iterate_blocks(Rest, NewCFG, NewInfo);
509
604
iterate_blocks([], CFG, _Info) ->
510
605
  CFG.
514
609
    true ->
515
610
      case hipe_icode:call_fun(Instruction) of
516
611
        {hipe_bs_primop, {bs_save, I}} ->
517
 
          Args=hipe_icode:call_args(Instruction),
 
612
          Args = hipe_icode:call_args(Instruction),
518
613
          NewInfo = gb_trees:enter(I, Args, Info),
519
614
          case hipe_icode:call_continuation(Instruction) of
520
615
            [] ->
521
616
              iterate_instructions(Rest, NewInfo, Acc);
522
617
            Lbl ->
523
 
              iterate_instructions(Rest, NewInfo, [hipe_icode:mk_goto(Lbl)|Acc])
 
618
              iterate_instructions(Rest, NewInfo, 
 
619
                                   [hipe_icode:mk_goto(Lbl)|Acc])
524
620
          end;
525
621
        {hipe_bs_primop, {bs_restore, I}} ->
526
622
          {value, Args} = gb_trees:lookup(I, Info),
527
 
          Dsts = hipe_icode:call_dst(Instruction),
528
 
          Moves = hipe_icode:mk_movs(Dsts, Args),
 
623
          Dsts = hipe_icode:call_dstlist(Instruction),
 
624
          Moves = hipe_icode:mk_moves(Dsts, Args),
529
625
          case hipe_icode:call_continuation(Instruction) of
530
626
            [] ->
531
627
              iterate_instructions(Rest, Info, Moves++Acc);
532
628
            Lbl ->
533
 
              iterate_instructions(Rest, Info, [hipe_icode:mk_goto(Lbl)|Moves] ++ Acc)
 
629
              iterate_instructions(Rest, Info,
 
630
                                   [hipe_icode:mk_goto(Lbl)|Moves] ++ Acc)
534
631
          end;
535
632
        _ ->
536
633
           iterate_instructions(Rest, Info, [Instruction|Acc])