~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/options1_tests_SUITE_data/src/compiler/beam_jump.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: beam_jump.erl,v 1.1 2008/12/17 09:53:41 mikpe Exp $
 
17
%%
 
18
%%% Purpose : Optimise jumps and remove unreachable code.
 
19
 
 
20
-module(beam_jump).
 
21
 
 
22
-export([module/2,module_labels/1,
 
23
         is_unreachable_after/1,remove_unused_labels/1]).
 
24
 
 
25
%%% The following optimisations are done:
 
26
%%%
 
27
%%% (1) This code with two identical instruction sequences
 
28
%%% 
 
29
%%%     L1: <Instruction sequence>
 
30
%%%     L2:
 
31
%%%          . . .
 
32
%%%     L3: <Instruction sequence>
 
33
%%%     L4:
 
34
%%%
 
35
%%%     can be replaced with
 
36
%%% 
 
37
%%%     L1: jump L3
 
38
%%%     L2:
 
39
%%%          . . .
 
40
%%%     L3: <Instruction sequence>
 
41
%%%     L4
 
42
%%%     
 
43
%%%     Note: The instruction sequence must end with an instruction
 
44
%%%     such as a jump that never transfers control to the instruction
 
45
%%%     following it.
 
46
%%%
 
47
%%% (2) case_end, if_end, and badmatch, and function calls that cause an
 
48
%%%     exit (such as calls to exit/1) are moved to the end of the function.
 
49
%%%     The purpose is to allow further optimizations at the place from
 
50
%%%     which the code was moved.
 
51
%%%
 
52
%%% (3) Any unreachable code is removed.  Unreachable code is code after
 
53
%%%     jump, call_last and other instructions which never transfer control
 
54
%%%     to the following instruction.  Code is unreachable up to the next
 
55
%%%     *referenced* label.  Note that the optimisations below might
 
56
%%%     generate more possibilities for removing unreachable code.
 
57
%%%
 
58
%%% (4) This code:
 
59
%%%     L1:     jump L2
 
60
%%%          . . .
 
61
%%%     L2: ...
 
62
%%%
 
63
%%%    will be changed to
 
64
%%%
 
65
%%%    jump L2
 
66
%%%          . . .
 
67
%%%    L1:
 
68
%%%    L2: ...
 
69
%%%
 
70
%%%    If the jump is unreachable, it will be removed according to (1).
 
71
%%%
 
72
%%% (5) In
 
73
%%%
 
74
%%%      jump L1
 
75
%%%      L1:
 
76
%%%
 
77
%%%      the jump will be removed.
 
78
%%%
 
79
%%% (6) If test instructions are used to skip a single jump instruction,
 
80
%%%      the test is inverted and the jump is eliminated (provided that
 
81
%%%      the test can be inverted).  Example:
 
82
%%%
 
83
%%%      is_eq L1 {x,1} {x,2}
 
84
%%%      jump L2
 
85
%%%      L1:
 
86
%%%
 
87
%%%      will be changed to
 
88
%%%
 
89
%%%      is_ne L2 {x,1} {x,2}
 
90
%%%
 
91
%%%      (The label L1 will be retained if there were previous references to it.)
 
92
%%%
 
93
%%% (7) Some redundant uses of is_boolean/1 is optimized away.
 
94
%%%
 
95
%%% Terminology note: The optimisation done here is called unreachable-code
 
96
%%% elimination, NOT dead-code elimination.  Dead code elimination
 
97
%%% means the removal of instructions that are executed, but have no visible
 
98
%%% effect on the program state.
 
99
%%% 
 
100
 
 
101
-import(lists, [reverse/1,reverse/2,map/2,mapfoldl/3,foldl/3,
 
102
                last/1,foreach/2,member/2]).
 
103
 
 
104
module({Mod,Exp,Attr,Fs0,Lc}, _Opt) ->
 
105
    Fs = map(fun function/1, Fs0),
 
106
    {ok,{Mod,Exp,Attr,Fs,Lc}}.
 
107
 
 
108
module_labels({Mod,Exp,Attr,Fs,Lc}) ->
 
109
    {Mod,Exp,Attr,map(fun function_labels/1, Fs),Lc}.
 
110
 
 
111
function_labels({function,Name,Arity,CLabel,Asm0}) ->
 
112
    Asm = remove_unused_labels(Asm0),
 
113
    {function,Name,Arity,CLabel,Asm}.    
 
114
 
 
115
function({function,Name,Arity,CLabel,Asm0}) ->
 
116
    Asm1 = share(Asm0),
 
117
    Asm2 = bopt(Asm1),
 
118
    Asm3 = move(Asm2),
 
119
    Asm4 = opt(Asm3, CLabel),
 
120
    Asm = remove_unused_labels(Asm4),
 
121
    {function,Name,Arity,CLabel,Asm}.
 
122
 
 
123
%%%
 
124
%%% (1) We try to share the code for identical code segments by replacing all
 
125
%%% occurrences except the last with jumps to the last occurrence.
 
126
%%%
 
127
 
 
128
share(Is) ->
 
129
    share_1(reverse(Is), gb_trees:empty(), [], []).
 
130
 
 
131
share_1([{label,_}=Lbl|Is], Dict, [], Acc) ->
 
132
    share_1(Is, Dict, [], [Lbl|Acc]);
 
133
share_1([{label,L}=Lbl|Is], Dict0, Seq, Acc) ->
 
134
    case is_unreachable_after(last(Seq)) of
 
135
        false ->
 
136
            share_1(Is, Dict0, [], [Lbl|Seq ++ Acc]);
 
137
        true ->
 
138
            case gb_trees:lookup(Seq, Dict0) of
 
139
                none ->
 
140
                    Dict = gb_trees:insert(Seq, L, Dict0),
 
141
                    share_1(Is, Dict, [], [Lbl|Seq ++ Acc]);
 
142
                {value,Label} ->
 
143
                    share_1(Is, Dict0, [], [Lbl,{jump,{f,Label}}|Acc])
 
144
            end
 
145
    end;
 
146
share_1([{func_info,_,_,_}=I|Is], _, [], Acc) ->
 
147
    Is++[I|Acc];
 
148
share_1([I|Is], Dict, Seq, Acc) ->
 
149
    case is_unreachable_after(I) of
 
150
        false ->
 
151
            share_1(Is, Dict, [I|Seq], Acc);
 
152
        true ->
 
153
            share_1(Is, Dict, [I], Acc)
 
154
    end.
 
155
 
 
156
%%%
 
157
%%% (2) Move short code sequences ending in an instruction that causes an exit
 
158
%%% to the end of the function.
 
159
%%%
 
160
 
 
161
move(Is) ->
 
162
    move_1(Is, [], []).
 
163
 
 
164
move_1([I|Is], End, Acc) ->
 
165
    case is_exit_instruction(I) of
 
166
        false -> move_1(Is, End, [I|Acc]);
 
167
        true -> move_2(I, Is, End, Acc)
 
168
    end;
 
169
move_1([], End, Acc) ->
 
170
    reverse(Acc, reverse(End)).
 
171
 
 
172
move_2(Exit, Is, End, [{block,_},{label,_},{func_info,_,_,_}|_]=Acc) ->
 
173
    move_1(Is, End, [Exit|Acc]);
 
174
move_2(Exit, Is, End, [{kill,_Y}|Acc]) ->
 
175
    move_2(Exit, Is, End, Acc);
 
176
move_2(Exit, Is, End, [{block,_}=Blk,{label,_}=Lbl,Dead|More]=Acc) ->
 
177
    case is_unreachable_after(Dead) of
 
178
        false ->
 
179
            move_1(Is, End, [Exit|Acc]);
 
180
        true ->
 
181
            move_1([Dead|Is], [Exit,Blk,Lbl|End], More)
 
182
    end;
 
183
move_2(Exit, Is, End, [{label,_}=Lbl,Dead|More]=Acc) ->
 
184
    case is_unreachable_after(Dead) of
 
185
        false ->
 
186
            move_1(Is, End, [Exit|Acc]);
 
187
        true ->
 
188
            move_1([Dead|Is], [Exit,Lbl|End], More)
 
189
    end;
 
190
move_2(Exit, Is, End, Acc) ->
 
191
    move_1(Is, End, [Exit|Acc]).
 
192
 
 
193
%%%
 
194
%%% (7) Remove redundant is_boolean tests.
 
195
%%%
 
196
 
 
197
bopt(Is) ->
 
198
    bopt_1(Is, []).
 
199
 
 
200
bopt_1([{test,is_boolean,_,_}=I|Is], Acc0) ->
 
201
    case opt_is_bool(I, Acc0) of
 
202
        no -> bopt_1(Is, [I|Acc0]);
 
203
        yes -> bopt_1(Is, Acc0);
 
204
        {yes,Acc} -> bopt_1(Is, Acc)
 
205
    end;
 
206
bopt_1([I|Is], Acc) -> bopt_1(Is, [I|Acc]);
 
207
bopt_1([], Acc) -> reverse(Acc).
 
208
 
 
209
opt_is_bool({test,is_boolean,{f,Lbl},[Reg]}, Acc) ->
 
210
    opt_is_bool_1(Acc, Reg, Lbl).
 
211
 
 
212
opt_is_bool_1([{test,is_eq_exact,{f,Lbl},[Reg,{atom,true}]}|_], Reg, Lbl) ->
 
213
    %% Instruction not needed in this context.
 
214
    yes;
 
215
opt_is_bool_1([{test,is_ne_exact,{f,Lbl},[Reg,{atom,true}]}|Acc], Reg, Lbl) ->
 
216
    %% Rewrite to shorter test.
 
217
    {yes,[{test,is_eq_exact,{f,Lbl},[Reg,{atom,false}]}|Acc]};
 
218
opt_is_bool_1([{test,_,{f,Lbl},_}=Test|Acc0], Reg, Lbl) ->
 
219
    case opt_is_bool_1(Acc0, Reg, Lbl) of
 
220
        {yes,Acc} -> {yes,[Test|Acc]};
 
221
        Other -> Other
 
222
    end;
 
223
opt_is_bool_1(_, _, _) -> no.
 
224
 
 
225
%%%
 
226
%%% (3) (4) (5) (6) Jump and unreachable code optimizations.
 
227
%%%
 
228
 
 
229
-record(st, {fc,                                %Label for function class errors.
 
230
             entry,                             %Entry label (must not be moved).
 
231
             mlbl,                              %Moved labels.
 
232
             labels                             %Set of referenced labels.
 
233
            }).
 
234
 
 
235
opt([{label,Fc}|_]=Is, CLabel) ->
 
236
    Lbls = initial_labels(Is),
 
237
    St = #st{fc=Fc,entry=CLabel,mlbl=dict:new(),labels=Lbls},
 
238
    opt(Is, [], St).
 
239
 
 
240
opt([{test,Test0,{f,Lnum}=Lbl,Ops}=I|Is0], Acc, St) ->
 
241
    case Is0 of
 
242
        [{jump,To}|[{label,Lnum}|Is2]=Is1] ->
 
243
            case invert_test(Test0) of
 
244
                not_possible ->
 
245
                    opt(Is0, [I|Acc], label_used(Lbl, St));
 
246
                Test ->
 
247
                    Is = case is_label_used(Lnum, St) of
 
248
                             true -> Is1;
 
249
                             false -> Is2
 
250
                         end,
 
251
                    opt([{test,Test,To,Ops}|Is], Acc, label_used(To, St))
 
252
            end;
 
253
        _Other ->
 
254
            opt(Is0, [I|Acc], label_used(Lbl, St))
 
255
    end;
 
256
opt([{select_val,_R,Fail,{list,Vls}}=I|Is], Acc, St) ->
 
257
    skip_unreachable(Is, [I|Acc], label_used([Fail|Vls], St));
 
258
opt([{select_tuple_arity,_R,Fail,{list,Vls}}=I|Is], Acc, St) ->
 
259
    skip_unreachable(Is, [I|Acc], label_used([Fail|Vls], St));
 
260
opt([{'try',_R,Lbl}=I|Is], Acc, St) ->
 
261
    opt(Is, [I|Acc], label_used(Lbl, St));
 
262
opt([{'catch',_R,Lbl}=I|Is], Acc, St) ->
 
263
    opt(Is, [I|Acc], label_used(Lbl, St));
 
264
opt([{label,L}=I|Is], Acc, #st{entry=L}=St) ->
 
265
    %% NEVER move the entry label.
 
266
    opt(Is, [I|Acc], St);
 
267
opt([{label,L1},{jump,{f,L2}}=I|Is], [Prev|Acc], St0) ->
 
268
    St = St0#st{mlbl=dict:append(L2, L1, St0#st.mlbl)},
 
269
    opt([Prev,I|Is], Acc, label_used({f,L2}, St));
 
270
opt([{label,Lbl}=I|Is], Acc, #st{mlbl=Mlbl}=St0) ->
 
271
    case dict:find(Lbl, Mlbl) of
 
272
        {ok,Lbls} ->
 
273
            %% Essential to remove the list of labels from the dictionary,
 
274
            %% since we will rescan the inserted labels.  We MUST rescan.
 
275
            St = St0#st{mlbl=dict:erase(Lbl, Mlbl)},
 
276
            insert_labels([Lbl|Lbls], Is, Acc, St);
 
277
        error -> opt(Is, [I|Acc], St0)
 
278
    end;
 
279
opt([{jump,{f,Lbl}},{label,Lbl}=I|Is], Acc, St) ->
 
280
    opt([I|Is], Acc, St);
 
281
opt([{jump,Lbl}=I|Is], Acc, St) ->
 
282
    skip_unreachable(Is, [I|Acc], label_used(Lbl, St));
 
283
opt([{loop_rec,Lbl,_R}=I|Is], Acc, St) ->
 
284
    opt(Is, [I|Acc], label_used(Lbl, St));
 
285
opt([{bif,_Name,Lbl,_As,_R}=I|Is], Acc, St) ->
 
286
    opt(Is, [I|Acc], label_used(Lbl, St));
 
287
opt([{bs_put_integer,Lbl,_Bits,_Unit,_Fl,_Val}=I|Is], Acc, St) ->
 
288
    opt(Is, [I|Acc], label_used(Lbl, St));
 
289
opt([{bs_put_binary,Lbl,_Bits,_Unit,_Fl,_Val}=I|Is], Acc, St) ->
 
290
    opt(Is, [I|Acc], label_used(Lbl, St));
 
291
opt([{bs_put_float,Lbl,_Bits,_Unit,_Fl,_Val}=I|Is], Acc, St) ->
 
292
    opt(Is, [I|Acc], label_used(Lbl, St));
 
293
opt([{bs_final,Lbl,_R}=I|Is], Acc, St) ->
 
294
    opt(Is, [I|Acc], label_used(Lbl, St));
 
295
opt([{bs_init2,Lbl,_,_,_,_,_}=I|Is], Acc, St) ->
 
296
    opt(Is, [I|Acc], label_used(Lbl, St));
 
297
opt([{bs_add,Lbl,_,_}=I|Is], Acc, St) ->
 
298
    opt(Is, [I|Acc], label_used(Lbl, St));
 
299
opt([{bs_bits_to_bytes,Lbl,_,_}=I|Is], Acc, St) ->
 
300
    opt(Is, [I|Acc], label_used(Lbl, St));
 
301
opt([I|Is], Acc, St) ->
 
302
    case is_unreachable_after(I) of
 
303
        true  -> skip_unreachable(Is, [I|Acc], St);
 
304
        false -> opt(Is, [I|Acc], St)
 
305
    end;
 
306
opt([], Acc, #st{fc=Fc,mlbl=Mlbl}) ->
 
307
    Code = reverse(Acc),
 
308
    case dict:find(Fc, Mlbl) of
 
309
        {ok,Lbls} -> insert_fc_labels(Lbls, Mlbl, Code);
 
310
        error -> Code
 
311
    end.
 
312
 
 
313
insert_fc_labels([L|Ls], Mlbl, Acc0) ->
 
314
    Acc = [{label,L}|Acc0],
 
315
    case dict:find(L, Mlbl) of
 
316
        error ->
 
317
            insert_fc_labels(Ls, Mlbl, Acc);
 
318
        {ok,Lbls} ->
 
319
            insert_fc_labels(Lbls++Ls, Mlbl, Acc)
 
320
    end;
 
321
insert_fc_labels([], _, Acc) -> Acc.
 
322
 
 
323
%% invert_test(Test0) -> not_possible | Test
 
324
 
 
325
invert_test(is_ge) ->       is_lt;
 
326
invert_test(is_lt) ->       is_ge;
 
327
invert_test(is_eq) ->       is_ne;
 
328
invert_test(is_ne) ->       is_eq;
 
329
invert_test(is_eq_exact) -> is_ne_exact;
 
330
invert_test(is_ne_exact) -> is_eq_exact;
 
331
invert_test(_) ->           not_possible.
 
332
 
 
333
insert_labels([L|Ls], Is, [{jump,{f,L}}|Acc], St) ->
 
334
    insert_labels(Ls, [{label,L}|Is], Acc, St);
 
335
insert_labels([L|Ls], Is, Acc, St) ->
 
336
    insert_labels(Ls, [{label,L}|Is], Acc, St);
 
337
insert_labels([], Is, Acc, St) ->
 
338
    opt(Is, Acc, St).
 
339
 
 
340
%% Skip unreachable code up to the next referenced label.
 
341
 
 
342
skip_unreachable([{label,L}|Is], [{jump,{f,L}}|Acc], St) ->
 
343
    opt([{label,L}|Is], Acc, St);
 
344
skip_unreachable([{label,L}|Is], Acc, St) ->
 
345
    case is_label_used(L, St) of
 
346
        true  -> opt([{label,L}|Is], Acc, St);
 
347
        false -> skip_unreachable(Is, Acc, St)
 
348
    end;
 
349
skip_unreachable([_|Is], Acc, St) ->
 
350
    skip_unreachable(Is, Acc, St);
 
351
skip_unreachable([], Acc, St) ->
 
352
    opt([], Acc, St).
 
353
 
 
354
%% Add one or more label to the set of used labels.
 
355
 
 
356
label_used({f,0}, St) -> St;
 
357
label_used({f,L}, St) -> St#st{labels=gb_sets:add(L, St#st.labels)};
 
358
label_used([H|T], St0) -> label_used(T, label_used(H, St0));
 
359
label_used([], St) -> St;
 
360
label_used(_Other, St) -> St.
 
361
 
 
362
%% Test if label is used.
 
363
 
 
364
is_label_used(L, St) ->
 
365
    gb_sets:is_member(L, St#st.labels).
 
366
 
 
367
%% is_unreachable_after(Instruction) -> true|false
 
368
%%  Test whether the code after Instruction is unreachable.
 
369
 
 
370
is_unreachable_after({func_info,_M,_F,_A}) -> true;
 
371
is_unreachable_after(return) -> true;
 
372
is_unreachable_after({call_ext_last,_Ar,_ExtFunc,_D}) -> true;
 
373
is_unreachable_after({call_ext_only,_Ar,_ExtFunc}) -> true;
 
374
is_unreachable_after({call_last,_Ar,_Lbl,_D}) -> true;
 
375
is_unreachable_after({call_only,_Ar,_Lbl}) -> true;
 
376
is_unreachable_after({apply_last,_Ar,_N}) -> true;
 
377
is_unreachable_after({jump,_Lbl}) -> true;
 
378
is_unreachable_after({select_val,_R,_Lbl,_Cases}) -> true;
 
379
is_unreachable_after({select_tuple_arity,_R,_Lbl,_Cases}) -> true;
 
380
is_unreachable_after({loop_rec_end,_}) -> true;
 
381
is_unreachable_after({wait,_}) -> true;
 
382
is_unreachable_after(I) -> is_exit_instruction(I).
 
383
 
 
384
%% is_exit_instruction(Instruction) -> true|false
 
385
%%  Test whether the instruction Instruction always
 
386
%%  causes an exit/failure.
 
387
 
 
388
is_exit_instruction({call_ext,_,{extfunc,M,F,A}}) ->
 
389
    is_exit_instruction_1(M, F, A);
 
390
is_exit_instruction({call_ext_last,_,{extfunc,M,F,A},_}) ->
 
391
    is_exit_instruction_1(M, F, A);
 
392
is_exit_instruction({call_ext_only,_,{extfunc,M,F,A}}) ->
 
393
    is_exit_instruction_1(M, F, A);
 
394
is_exit_instruction(if_end) -> true;
 
395
is_exit_instruction({case_end,_}) -> true;
 
396
is_exit_instruction({try_case_end,_}) -> true;
 
397
is_exit_instruction({badmatch,_}) -> true;
 
398
is_exit_instruction(_) -> false.
 
399
 
 
400
is_exit_instruction_1(erlang, exit, 1) -> true;
 
401
is_exit_instruction_1(erlang, throw, 1) -> true;
 
402
is_exit_instruction_1(erlang, error, 1) -> true;
 
403
is_exit_instruction_1(erlang, error, 2) -> true;
 
404
is_exit_instruction_1(erlang, fault, 1) -> true;
 
405
is_exit_instruction_1(erlang, fault, 2) -> true;
 
406
is_exit_instruction_1(_, _, _) -> false.
 
407
 
 
408
%% remove_unused_labels(Instructions0) -> Instructions
 
409
%%  Remove all unused labels.
 
410
 
 
411
remove_unused_labels(Is) ->
 
412
    Used0 = initial_labels(Is),
 
413
    Used = foldl(fun ulbl/2, Used0, Is),
 
414
    rem_unused(Is, Used, []).
 
415
 
 
416
rem_unused([{label,Lbl}=I|Is], Used, Acc) ->
 
417
    case gb_sets:is_member(Lbl, Used) of
 
418
        false -> rem_unused(Is, Used, Acc);
 
419
        true -> rem_unused(Is, Used, [I|Acc])
 
420
    end;
 
421
rem_unused([I|Is], Used, Acc) ->
 
422
    rem_unused(Is, Used, [I|Acc]);
 
423
rem_unused([], _, Acc) -> reverse(Acc).
 
424
 
 
425
initial_labels(Is) ->
 
426
    initial_labels(Is, []).
 
427
 
 
428
initial_labels([{label,Lbl}|Is], Acc) ->
 
429
    initial_labels(Is, [Lbl|Acc]);
 
430
initial_labels([{func_info,_,_,_},{label,Lbl}|_], Acc) ->
 
431
    gb_sets:from_list([Lbl|Acc]).
 
432
 
 
433
ulbl({test,_,Fail,_}, Used) ->
 
434
    mark_used(Fail, Used);
 
435
ulbl({select_val,_,Fail,{list,Vls}}, Used) ->
 
436
    mark_used_list(Vls, mark_used(Fail, Used));
 
437
ulbl({select_tuple_arity,_,Fail,{list,Vls}}, Used) ->
 
438
    mark_used_list(Vls, mark_used(Fail, Used));
 
439
ulbl({'try',_,Lbl}, Used) ->
 
440
    mark_used(Lbl, Used);
 
441
ulbl({'catch',_,Lbl}, Used) ->
 
442
    mark_used(Lbl, Used);
 
443
ulbl({jump,Lbl}, Used) ->
 
444
    mark_used(Lbl, Used);
 
445
ulbl({loop_rec,Lbl,_}, Used) ->
 
446
    mark_used(Lbl, Used);
 
447
ulbl({loop_rec_end,Lbl}, Used) ->
 
448
    mark_used(Lbl, Used);
 
449
ulbl({wait,Lbl}, Used) ->
 
450
    mark_used(Lbl, Used);
 
451
ulbl({wait_timeout,Lbl,_To}, Used) ->
 
452
    mark_used(Lbl, Used);
 
453
ulbl({bif,_Name,Lbl,_As,_R}, Used) ->
 
454
    mark_used(Lbl, Used);
 
455
ulbl({bs_init2,Lbl,_,_,_,_,_}, Used) ->
 
456
    mark_used(Lbl, Used);
 
457
ulbl({bs_put_integer,Lbl,_Bits,_Unit,_Fl,_Val}, Used) ->
 
458
    mark_used(Lbl, Used);
 
459
ulbl({bs_put_float,Lbl,_Bits,_Unit,_Fl,_Val}, Used) ->
 
460
    mark_used(Lbl, Used);
 
461
ulbl({bs_put_binary,Lbl,_Bits,_Unit,_Fl,_Val}, Used) ->
 
462
    mark_used(Lbl, Used);
 
463
ulbl({bs_final,Lbl,_}, Used) ->
 
464
    mark_used(Lbl, Used);
 
465
ulbl({bs_add,Lbl,_,_}, Used) ->
 
466
    mark_used(Lbl, Used);
 
467
ulbl({bs_bits_to_bytes,Lbl,_,_}, Used) ->
 
468
    mark_used(Lbl, Used);
 
469
ulbl(_, Used) -> Used.
 
470
 
 
471
mark_used({f,0}, Used) -> Used;
 
472
mark_used({f,L}, Used) -> gb_sets:add(L, Used);
 
473
mark_used(_, Used) -> Used.
 
474
 
 
475
mark_used_list([H|T], Used) ->
 
476
    mark_used_list(T, mark_used(H, Used));
 
477
mark_used_list([], Used) -> Used.