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

« back to all changes in this revision

Viewing changes to lib/compiler/src/beam_receive.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
-module(beam_receive).
 
21
-export([module/2]).
 
22
-import(lists, [foldl/3,reverse/1,reverse/2]).
 
23
 
 
24
%%%
 
25
%%% In code such as:
 
26
%%%
 
27
%%%    Ref = make_ref(),        %Or erlang:monitor(process, Pid)
 
28
%%%      .
 
29
%%%      .
 
30
%%%      .
 
31
%%%    receive
 
32
%%%       {Ref,Reply} -> Reply
 
33
%%%    end.
 
34
%%%
 
35
%%% we know that none of the messages that exist in the message queue
 
36
%%% before the call to make_ref/0 can be matched out in the receive
 
37
%%% statement. Therefore we can avoid going through the entire message
 
38
%%% queue if we introduce two new instructions (here written as
 
39
%%% BIFs in pseudo-Erlang):
 
40
%%%
 
41
%%%    recv_mark(SomeUniqInteger),
 
42
%%%    Ref = make_ref(),
 
43
%%%      .
 
44
%%%      .
 
45
%%%      .
 
46
%%%    recv_set(SomeUniqInteger),
 
47
%%%    receive
 
48
%%%       {Ref,Reply} -> Reply
 
49
%%%    end.
 
50
%%%
 
51
%%% The recv_mark/1 instruction will save the current position and
 
52
%%% SomeUniqInteger in the process context. The recv_set
 
53
%%% instruction will verify that SomeUniqInteger is still stored
 
54
%%% in the process context. If it is, it will set the current pointer
 
55
%%% for the message queue (the next message to be read out) to the
 
56
%%% position that was saved by recv_mark/1.
 
57
%%%
 
58
%%% The remove_message instruction must be modified to invalidate
 
59
%%% the information stored by the previous recv_mark/1, in case there
 
60
%%% is another receive executed between the calls to recv_mark/1 and
 
61
%%% recv_set/1.
 
62
%%%
 
63
%%% We use a reference to a label (i.e. a position in the loaded code)
 
64
%%% as the SomeUniqInteger.
 
65
%%%
 
66
 
 
67
module({Mod,Exp,Attr,Fs0,Lc}, _Opts) ->
 
68
    Fs = [function(F) || F <- Fs0],
 
69
    Code = {Mod,Exp,Attr,Fs,Lc},
 
70
    {ok,Code}.
 
71
 
 
72
%%%
 
73
%%% Local functions.
 
74
%%%
 
75
 
 
76
function({function,Name,Arity,Entry,Is}) ->
 
77
    try
 
78
        D = beam_utils:index_labels(Is),
 
79
        {function,Name,Arity,Entry,opt(Is, D, [])}
 
80
    catch
 
81
        Class:Error ->
 
82
            Stack = erlang:get_stacktrace(),
 
83
            io:fwrite("Function: ~w/~w\n", [Name,Arity]),
 
84
            erlang:raise(Class, Error, Stack)
 
85
    end.
 
86
 
 
87
opt([{call_ext,Arity,{extfunc,erlang,Name,Arity}}=I|Is0], D, Acc) ->
 
88
    case creates_new_ref(Name, Arity) of
 
89
        true ->
 
90
            %% The call creates a brand new reference. Now
 
91
            %% search for a receive statement in the same
 
92
            %% function that will match against the reference.
 
93
            case opt_recv(Is0, D) of
 
94
                no ->
 
95
                    opt(Is0, D, [I|Acc]);
 
96
                {yes,Is,Lbl} ->
 
97
                    opt(Is, D, [I,{recv_mark,{f,Lbl}}|Acc])
 
98
            end;
 
99
        false ->
 
100
            opt(Is0, D, [I|Acc])
 
101
    end;
 
102
opt([I|Is], D, Acc) ->
 
103
    opt(Is, D, [I|Acc]);
 
104
opt([], _, Acc) ->
 
105
    reverse(Acc).
 
106
 
 
107
%% creates_new_ref(Name, Arity) -> true|false.
 
108
%%  Return 'true' if the BIF Name/Arity will create a new reference.
 
109
creates_new_ref(monitor, 2) -> true;
 
110
creates_new_ref(make_ref, 0) -> true;
 
111
creates_new_ref(_, _) -> false.
 
112
 
 
113
%% opt_recv([Instruction], LabelIndex) -> no|{yes,[Instruction]}
 
114
%%  Search for a receive statement that will only retrieve messages
 
115
%%  that contain the newly created reference (which is currently in {x,0}).
 
116
opt_recv(Is, D) ->
 
117
    R = regs_init_x0(),
 
118
    L = gb_sets:empty(),
 
119
    opt_recv(Is, D, R, L, []).
 
120
 
 
121
opt_recv([{label,L}=Lbl,{loop_rec,{f,Fail},_}=Loop|Is], D, R0, _, Acc) ->
 
122
    R = regs_kill_not_live(0, R0),
 
123
    case regs_to_list(R) of
 
124
        [{y,_}=RefReg] ->
 
125
            %% We now have the new reference in the Y register RefReg
 
126
            %% and the current instruction is the beginning of a
 
127
            %% receive statement. We must now verify that only messages
 
128
            %% that contain the reference will be matched.
 
129
            case opt_ref_used(Is, RefReg, Fail, D) of
 
130
                false ->
 
131
                    no;
 
132
                true ->
 
133
                    RecvSet = {recv_set,{f,L}},
 
134
                    {yes,reverse(Acc, [RecvSet,Lbl,Loop|Is]),L}
 
135
            end;
 
136
        [] ->
 
137
            no
 
138
    end;
 
139
opt_recv([I|Is], D, R0, L0, Acc) ->
 
140
    {R,L} = opt_update_regs(I, R0, L0),
 
141
    case regs_empty(R) of
 
142
        true ->
 
143
            %% The reference is no longer alive. There is no
 
144
            %% point in continuing the search.
 
145
            no;
 
146
        false ->
 
147
            opt_recv(Is, D, R, L, [I|Acc])
 
148
    end.
 
149
 
 
150
opt_update_regs({block,Bl}, R, L) ->
 
151
    {opt_update_regs_bl(Bl, R),L};
 
152
opt_update_regs({call,_,_}, R, L) ->
 
153
    {regs_kill_not_live(0, R),L};
 
154
opt_update_regs({call_ext,_,_}, R, L) ->
 
155
    {regs_kill_not_live(0, R),L};
 
156
opt_update_regs({call_fun,_}, R, L) ->
 
157
    {regs_kill_not_live(0, R),L};
 
158
opt_update_regs({kill,Y}, R, L) ->
 
159
    {regs_kill([Y], R),L};
 
160
opt_update_regs(send, R, L) ->
 
161
    {regs_kill_not_live(0, R),L};
 
162
opt_update_regs({'catch',_,{f,Lbl}}, R, L) ->
 
163
    {R,gb_sets:add(Lbl, L)};
 
164
opt_update_regs({catch_end,_}, R, L) ->
 
165
    {R,L};
 
166
opt_update_regs({label,Lbl}, R, L) ->
 
167
    case gb_sets:is_member(Lbl, L) of
 
168
        false ->
 
169
            %% We can't allow arbitrary labels (since the receive
 
170
            %% could be entered without first creating the reference).
 
171
            {regs_init(),L};
 
172
        true ->
 
173
            %% A catch label for a previously seen catch instruction is OK.
 
174
            {R,L}
 
175
    end;
 
176
opt_update_regs({try_end,_}, R, L) ->
 
177
    {R,L};
 
178
opt_update_regs(_I, _R, L) ->
 
179
    %% Unrecognized instruction. Abort the search.
 
180
    {regs_init(),L}.
 
181
 
 
182
opt_update_regs_bl([{set,Ds,_,{alloc,Live,_}}|Is], Regs0) ->
 
183
    Regs1 = regs_kill_not_live(Live, Regs0),
 
184
    Regs = regs_kill(Ds, Regs1),
 
185
    opt_update_regs_bl(Is, Regs);
 
186
opt_update_regs_bl([{set,[Dst]=Ds,[Src],move}|Is], Regs0) ->
 
187
    Regs1 = regs_kill(Ds, Regs0),
 
188
    Regs = case regs_is_member(Src, Regs1) of
 
189
               false -> Regs1;
 
190
               true -> regs_add(Dst, Regs1)
 
191
           end,
 
192
    opt_update_regs_bl(Is, Regs);
 
193
opt_update_regs_bl([{set,Ds,_,_}|Is], Regs0) ->
 
194
    Regs = regs_kill(Ds, Regs0),
 
195
    opt_update_regs_bl(Is, Regs);
 
196
opt_update_regs_bl([], Regs) -> Regs.
 
197
 
 
198
%% opt_ref_used([Instruction], RefRegister, FailLabel, LabelIndex) -> true|false
 
199
%%  Return 'true' if it is certain that only messages that contain the same
 
200
%%  reference as in RefRegister can be matched out. Otherwise return 'false'.
 
201
%%
 
202
%%  Basically, we follow all possible paths through the receive statement.
 
203
%%  If all paths are safe, we return 'true'.
 
204
%%
 
205
%%  A branch to FailLabel is safe, because it exits the receive statement
 
206
%%  and no further message may be matched out.
 
207
%%
 
208
%%  If a path hits an comparision between RefRegister and part of the message,
 
209
%%  that path is safe (any messages that may be matched further down the
 
210
%%  path is guaranteed to contain the reference).
 
211
%%
 
212
%%  Otherwise, if we hit a 'remove_message' instruction, we give up
 
213
%%  and return 'false' (the optimization is definitely unsafe). If
 
214
%%  we hit an unrecognized instruction, we also give up and return
 
215
%%  'false' (the optimization may be unsafe).
 
216
 
 
217
opt_ref_used(Is, RefReg, Fail, D) ->
 
218
    Done = gb_sets:singleton(Fail),
 
219
    Regs = regs_init_x0(),
 
220
    try
 
221
        opt_ref_used_1(Is, RefReg, D, Done, Regs),
 
222
        true
 
223
    catch
 
224
        throw:not_used ->
 
225
            false
 
226
    end.
 
227
 
 
228
%% This functions only returns if all paths through the receive
 
229
%% statement are safe, and throws an 'not_used' term otherwise.
 
230
opt_ref_used_1([{block,Bl}|Is], RefReg, D, Done, Regs0) ->
 
231
    Regs = opt_ref_used_bl(Bl, Regs0),
 
232
    opt_ref_used_1(Is, RefReg, D, Done, Regs);
 
233
opt_ref_used_1([{test,is_eq_exact,{f,Fail},Args}|Is], RefReg, D, Done0, Regs) ->
 
234
    Done = opt_ref_used_at(Fail, RefReg, D, Done0, Regs),
 
235
    case is_ref_msg_comparison(Args, RefReg, Regs) of
 
236
        false ->
 
237
            opt_ref_used_1(Is, RefReg, D, Done, Regs);
 
238
        true ->
 
239
            %% The instructions that follow (Is) can only be executed
 
240
            %% if the message contains the same reference as in RefReg.
 
241
            Done
 
242
    end;
 
243
opt_ref_used_1([{test,is_ne_exact,{f,Fail},Args}|Is], RefReg, D, Done0, Regs) ->
 
244
    Done = opt_ref_used_1(Is, RefReg, D, Done0, Regs),
 
245
    case is_ref_msg_comparison(Args, RefReg, Regs) of
 
246
        false ->
 
247
            opt_ref_used_at(Fail, RefReg, D, Done, Regs);
 
248
        true ->
 
249
            Done
 
250
    end;
 
251
opt_ref_used_1([{test,_,{f,Fail},_}|Is], RefReg, D, Done0, Regs) ->
 
252
    Done = opt_ref_used_at(Fail, RefReg, D, Done0, Regs),
 
253
    opt_ref_used_1(Is, RefReg, D, Done, Regs);
 
254
opt_ref_used_1([{select_tuple_arity,_,{f,Fail},{list,List}}|_], RefReg, D, Done, Regs) ->
 
255
    Lbls = [F || {f,F} <- List] ++ [Fail],
 
256
    opt_ref_used_in_all(Lbls, RefReg, D, Done, Regs);
 
257
opt_ref_used_1([{select_val,_,{f,Fail},{list,List}}|_], RefReg, D, Done, Regs) ->
 
258
    Lbls = [F || {f,F} <- List] ++ [Fail],
 
259
    opt_ref_used_in_all(Lbls, RefReg, D, Done, Regs);
 
260
opt_ref_used_1([{label,Lbl}|Is], RefReg, D, Done, Regs) ->
 
261
    case gb_sets:is_member(Lbl, Done) of
 
262
        true -> Done;
 
263
        false -> opt_ref_used_1(Is, RefReg, D, Done, Regs)
 
264
    end;
 
265
opt_ref_used_1([{loop_rec_end,_}|_], _, _, Done, _) ->
 
266
    Done;
 
267
opt_ref_used_1([_I|_], _RefReg, _D, _Done, _Regs) ->
 
268
    %% The optimization may be unsafe.
 
269
    throw(not_used).
 
270
 
 
271
%% is_ref_msg_comparison(Args, RefReg, RegisterSet) -> true|false.
 
272
%%  Return 'true' if Args denotes a comparison between the
 
273
%%  reference and message or part of the message.
 
274
is_ref_msg_comparison([R,RefReg], RefReg, Regs) ->
 
275
    regs_is_member(R, Regs);
 
276
is_ref_msg_comparison([RefReg,R], RefReg, Regs) ->
 
277
    regs_is_member(R, Regs);
 
278
is_ref_msg_comparison([_,_], _, _) -> false.
 
279
 
 
280
opt_ref_used_in_all([L|Ls], RefReg, D, Done0, Regs) ->
 
281
    Done = opt_ref_used_at(L, RefReg, D, Done0, Regs),
 
282
    opt_ref_used_in_all(Ls, RefReg, D, Done, Regs);
 
283
opt_ref_used_in_all([], _, _, Done, _) -> Done.
 
284
 
 
285
opt_ref_used_at(Fail, RefReg, D, Done0, Regs) ->
 
286
    case gb_sets:is_member(Fail, Done0) of
 
287
        true ->
 
288
            Done0;
 
289
        false ->
 
290
            Is = beam_utils:code_at(Fail, D),
 
291
            Done = opt_ref_used_1(Is, RefReg, D, Done0, Regs),
 
292
            gb_sets:add(Fail, Done)
 
293
    end.
 
294
 
 
295
opt_ref_used_bl([{set,[],[],remove_message}|_], _) ->
 
296
    %% We have proved that a message that does not depend on the
 
297
    %% reference can be matched out.
 
298
    throw(not_used);
 
299
opt_ref_used_bl([{set,Ds,Ss,_}|Is], Regs0) ->
 
300
    case regs_all_members(Ss, Regs0) of
 
301
        false ->
 
302
            %% The destination registers may be assigned values that
 
303
            %% are not dependent on the message being matched.
 
304
            Regs = regs_kill(Ds, Regs0),
 
305
            opt_ref_used_bl(Is, Regs);
 
306
        true ->
 
307
            %% All the sources depend on the message directly or
 
308
            %% indirectly.
 
309
            Regs = regs_add_list(Ds, Regs0),
 
310
            opt_ref_used_bl(Is, Regs)
 
311
    end;
 
312
opt_ref_used_bl([], Regs) -> Regs.
 
313
 
 
314
%%%
 
315
%%% Functions for keeping track of a set of registers.
 
316
%%%
 
317
 
 
318
%% regs_init() -> RegisterSet
 
319
%%  Return an empty set of registers.
 
320
 
 
321
regs_init() ->
 
322
    {0,0}.
 
323
 
 
324
%% regs_init_x0() -> RegisterSet
 
325
%%  Return a set that only contains the {x,0} register.
 
326
 
 
327
regs_init_x0() ->
 
328
    {1 bsl 0,0}.
 
329
 
 
330
%% regs_empty(Register) -> true|false
 
331
%%  Test whether the register set is empty.
 
332
 
 
333
regs_empty(R) ->
 
334
    R =:= {0,0}.
 
335
 
 
336
%% regs_kill_not_live(Live, RegisterSet) -> RegisterSet'
 
337
%%  Kill all registers indicated not live by Live.
 
338
 
 
339
regs_kill_not_live(Live, {Xregs,Yregs}) ->
 
340
    {Xregs band ((1 bsl Live)-1),Yregs}.
 
341
 
 
342
%% regs_kill([Register], RegisterSet) -> RegisterSet'
 
343
%%  Kill all registers mentioned in the list of registers.
 
344
 
 
345
regs_kill([{x,N}|Rs], {Xregs,Yregs}) ->
 
346
    regs_kill(Rs, {Xregs band (bnot (1 bsl N)),Yregs});
 
347
regs_kill([{y,N}|Rs], {Xregs,Yregs}) ->
 
348
    regs_kill(Rs, {Xregs,Yregs band (bnot (1 bsl N))});
 
349
regs_kill([{fr,_}|Rs], Regs) ->
 
350
    regs_kill(Rs, Regs);
 
351
regs_kill([], Regs) -> Regs.
 
352
 
 
353
regs_add_list(List, Regs) ->
 
354
    foldl(fun(R, A) -> regs_add(R, A) end, Regs, List).
 
355
 
 
356
%% regs_add(Register, RegisterSet) -> RegisterSet'
 
357
%%  Add a new register to the set of registers.
 
358
 
 
359
regs_add({x,N}, {Xregs,Yregs}) ->
 
360
    {Xregs bor (1 bsl N),Yregs};
 
361
regs_add({y,N}, {Xregs,Yregs}) ->
 
362
    {Xregs,Yregs bor (1 bsl N)}.
 
363
 
 
364
%% regs_all_members([Register], RegisterSet) -> true|false
 
365
%%  Test whether all of the registers are part of the register set.
 
366
 
 
367
regs_all_members([R|Rs], Regs) ->
 
368
    regs_is_member(R, Regs) andalso regs_all_members(Rs, Regs);
 
369
regs_all_members([], _) -> true.
 
370
 
 
371
%% regs_is_member(Register, RegisterSet) -> true|false
 
372
%%  Test whether Register is part of the register set.
 
373
 
 
374
regs_is_member({x,N}, {Regs,_}) -> Regs band (1 bsl N) =/= 0;
 
375
regs_is_member({y,N}, {_,Regs}) -> Regs band (1 bsl N) =/= 0;
 
376
regs_is_member(_, _) -> false.
 
377
 
 
378
%% regs_to_list(RegisterSet) -> [Register]
 
379
%%  Convert the register set to an explicit list of registers.
 
380
regs_to_list({Xregs,Yregs}) ->
 
381
    regs_to_list_1(Xregs, 0, x, regs_to_list_1(Yregs, 0, y, [])).
 
382
 
 
383
regs_to_list_1(0, _, _, Acc) ->
 
384
    Acc;
 
385
regs_to_list_1(Regs, N, Tag, Acc) when (Regs band 1) =:= 1 ->
 
386
    regs_to_list_1(Regs bsr 1, N+1, Tag, [{Tag,N}|Acc]);
 
387
regs_to_list_1(Regs, N, Tag, Acc) ->
 
388
    regs_to_list_1(Regs bsr 1, N+1, Tag, Acc).