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

« back to all changes in this revision

Viewing changes to lib/tools/src/xref_reader.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(xref_reader).
22
22
 
23
23
-import(lists, [keysearch/3, member/2, reverse/1]).
24
24
 
25
 
-record(xrefr, 
 
25
-record(xrefr,
26
26
        {module=[],
27
27
         function=[],
28
28
         def_at=[],
59
59
module(Module, Forms, CollectBuiltins, X, DF) ->
60
60
    Attrs = [{Attr,V} || {attribute,_Line,Attr,V} <- Forms],
61
61
    IsAbstract = xref_utils:is_abstract_module(Attrs),
62
 
    S = #xrefr{module = Module, builtins_too = CollectBuiltins, 
 
62
    S = #xrefr{module = Module, builtins_too = CollectBuiltins,
63
63
               is_abstr = IsAbstract, x = X, df = DF},
64
64
    forms(Forms, S).
65
65
 
66
66
forms([F | Fs], S) ->
67
67
    S1 = form(F, S),
68
68
    forms(Fs, S1);
69
 
forms([], S) -> 
70
 
    #xrefr{module = M, def_at = DefAt, 
 
69
forms([], S) ->
 
70
    #xrefr{module = M, def_at = DefAt,
71
71
           l_call_at = LCallAt, x_call_at = XCallAt,
72
72
           el = LC, ex = XC, x = X, df = Depr,
73
73
           lattrs = AL, xattrs = AX, battrs = B, unresolved = U} = S,
75
75
    {ok, M, {DefAt, LCallAt, XCallAt, LC, XC, X, Attrs, Depr}, U}.
76
76
 
77
77
form({attribute, Line, xref, Calls}, S) -> % experimental
78
 
    #xrefr{module = M, function = Fun, 
 
78
    #xrefr{module = M, function = Fun,
79
79
           lattrs = L, xattrs = X, battrs = B} = S,
80
80
    attr(Calls, Line, M, Fun, L, X, B, S);
81
81
form({attribute, _Line, _Attr, _Val}, S) ->
110
110
    S2 = expr(B, S1),
111
111
    S3 = S2#xrefr{funvars = FunVars, matches = Matches},
112
112
    clauses(Cs, S3);
113
 
clauses([], _FunVars, _Matches, S) -> 
 
113
clauses([], _FunVars, _Matches, S) ->
114
114
    S.
115
115
 
116
116
attr([E={From, To} | As], Ln, M, Fun, AL, AX, B, S) ->
117
117
    case mfa(From, M) of
118
 
        {_, _, MFA} when MFA =:= Fun; [] =:= Fun -> 
 
118
        {_, _, MFA} when MFA =:= Fun; [] =:= Fun ->
119
119
            attr(From, To, Ln, M, Fun, AL, AX, B, S, As, E);
120
120
        {_, _, _} ->
121
121
            attr(As, Ln, M, Fun, AL, AX, [E | B], S);
164
164
    %% Added in R10B-6. M:F/A.
165
165
    expr({'fun', Line, {function, Mod, Fun, Arity}}, S);
166
166
expr({'fun', Line, {function, Mod, Name, Arity}}, S) ->
167
 
    %% Added in R10B-6. M:F/A. 
 
167
    %% Added in R10B-6. M:F/A.
168
168
    As = lists:duplicate(Arity, {atom, Line, foo}),
169
169
    external_call(Mod, Name, As, Line, false, S);
170
170
expr({'fun', Line, {function, Name, Arity}, _Extra}, S) ->
183
183
expr({call, Line, F, As}, S) ->
184
184
    external_call(erlang, apply, [F, list2term(As)], Line, true, S);
185
185
expr({match, _Line, {var,_,Var}, {'fun', _, {clauses, Cs}, _Extra}}, S) ->
186
 
    %% This is what is needed in R7 to avoid warnings for the functions 
 
186
    %% This is what is needed in R7 to avoid warnings for the functions
187
187
    %% that are passed around by the "expansion" of list comprehension.
188
188
    S1 = S#xrefr{funvars = [Var | S#xrefr.funvars]},
189
189
    clauses(Cs, S1);
192
192
    %%     Args = [A,B], apply(m, f, Args)
193
193
    S1 = S#xrefr{matches = [{Var, E} | S#xrefr.matches]},
194
194
    expr(E, S1);
 
195
expr({op, _Line, 'orelse', Op1, Op2}, S) ->
 
196
    expr([Op1, Op2], S);
 
197
expr({op, _Line, 'andalso', Op1, Op2}, S) ->
 
198
    expr([Op1, Op2], S);
 
199
expr({op, Line, Op, Operand1, Operand2}, S) ->
 
200
    external_call(erlang, Op, [Operand1, Operand2], Line, false, S);
 
201
expr({op, Line, Op, Operand}, S) ->
 
202
    external_call(erlang, Op, [Operand], Line, false, S);
195
203
expr(T, S) when is_tuple(T) ->
196
204
    expr(tuple_to_list(T), S);
197
205
expr([E | Es], S) ->
241
249
        _Else -> % apply2, 1 or 2
242
250
            check_funarg(W, ArgsList, Line, S1)
243
251
    end.
244
 
            
 
252
 
245
253
eval_args(Mod, Fun, ArgsTerm, Line, S, ArgsList, Extra) ->
246
254
    {IsSimpleCall, M, F} = mod_fun(Mod, Fun),
247
255
    case term2list(ArgsTerm, [], S) of
248
256
        undefined ->
249
257
            S1 = unresolved(M, F, -1, Line, S),
250
 
            expr(ArgsList, S1);     
 
258
            expr(ArgsList, S1);
251
259
        ArgsList2 when not IsSimpleCall ->
252
260
            S1 = unresolved(M, F, length(ArgsList2), Line, S),
253
261
            expr(ArgsList, S1);
288
296
fun_args(1, [FunArg | Args]) -> {FunArg, Args};
289
297
fun_args(2, [_Node, FunArg | Args]) -> {FunArg, Args}.
290
298
 
291
 
list2term([A | As]) -> 
 
299
list2term([A | As]) ->
292
300
    {cons, 0, A, list2term(As)};
293
 
list2term([]) -> 
 
301
list2term([]) ->
294
302
    {nil, 0}.
295
303
 
296
304
term2list({cons, _Line, H, T}, L, S) ->
297
305
    term2list(T, [H | L], S);
298
 
term2list({nil, _Line}, L, _S) -> 
 
306
term2list({nil, _Line}, L, _S) ->
299
307
    reverse(L);
300
308
term2list({var, _, Var}, L, S) ->
301
309
    case keysearch(Var, 1, S#xrefr.matches) of
332
340
             true ->
333
341
                 S
334
342
         end,
335
 
    case Locality of 
336
 
        local -> 
 
343
    case Locality of
 
344
        local ->
337
345
            S1#xrefr{el = [Call | S1#xrefr.el],
338
346
                     l_call_at = [CallAt | S1#xrefr.l_call_at]};
339
 
        external -> 
 
347
        external ->
340
348
            S1#xrefr{ex = [Call | S1#xrefr.ex],
341
349
                     x_call_at = [CallAt | S1#xrefr.x_call_at]}
342
350
    end.