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

« back to all changes in this revision

Viewing changes to lib/compiler/src/sys_pre_expand.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 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-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
%% Purpose : Expand some source Erlang constructions. This is part of the
114
114
            St1 = St0#expand{exports=Xs, defined=Ds},
115
115
            {Fs2,St2} = add_instance(Ps, Fs1, St1),
116
116
            {Fs3,St3} = ensure_new(Base, Ps0, Fs2, St2),
117
 
            {Fs3,St3#expand{attributes = [{abstract, [true]}
 
117
            {Fs3,St3#expand{attributes = [{abstract, 0, [true]}
118
118
                                          | St3#expand.attributes]}}
119
119
    end.
120
120
 
173
173
    St#expand{defined=ordsets:from_list(Fs)}.
174
174
 
175
175
module_attrs(St) ->
176
 
    {[{attribute,0,Name,Val} || {Name,Val} <- St#expand.attributes],St}.
 
176
    {[{attribute,Line,Name,Val} || {Name,Line,Val} <- St#expand.attributes],St}.
177
177
 
178
178
module_predef_funcs(St) ->
179
179
    PreDef = [{module_info,0},{module_info,1}],
197
197
forms([{attribute,_,file,_File}=F|Fs0], St0) ->
198
198
    {Fs,St1} = forms(Fs0, St0),
199
199
    {[F|Fs],St1};
200
 
forms([{attribute,_,Name,Val}|Fs0], St0) ->
201
 
    St1 = attribute(Name, Val, St0),
 
200
forms([{attribute,Line,Name,Val}|Fs0], St0) ->
 
201
    St1 = attribute(Name, Val, Line, St0),
202
202
    forms(Fs0, St1);
203
203
forms([{function,L,N,A,Cs}|Fs0], St0) ->
204
204
    {Ff,St1} = function(L, N, A, Cs, St0),
207
207
forms([_|Fs], St) -> forms(Fs, St);
208
208
forms([], St) -> {[],St}.
209
209
 
210
 
%% attribute(Attribute, Value, State) -> State'.
 
210
%% attribute(Attribute, Value, Line, State) -> State'.
211
211
%%  Process an attribute, this just affects the state.
212
212
 
213
 
attribute(module, {Module, As}, St) ->
 
213
attribute(module, {Module, As}, _L, St) ->
214
214
    M = package_to_string(Module),
215
215
    St#expand{module=list_to_atom(M),
216
 
              package = packages:strip_last(M),
 
216
              package=packages:strip_last(M),
217
217
              parameters=As};
218
 
attribute(module, Module, St) ->
 
218
attribute(module, Module, _L, St) ->
219
219
    M = package_to_string(Module),
220
220
    St#expand{module=list_to_atom(M),
221
 
              package = packages:strip_last(M)};
222
 
attribute(export, Es, St) ->
 
221
              package=packages:strip_last(M)};
 
222
attribute(export, Es, _L, St) ->
223
223
    St#expand{exports=union(from_list(Es), St#expand.exports)};
224
 
attribute(import, Is, St) ->
 
224
attribute(import, Is, _L, St) ->
225
225
    import(Is, St);
226
 
attribute(compile, C, St) when is_list(C) ->
 
226
attribute(compile, C, _L, St) when is_list(C) ->
227
227
    St#expand{compile=St#expand.compile ++ C};
228
 
attribute(compile, C, St) ->
 
228
attribute(compile, C, _L, St) ->
229
229
    St#expand{compile=St#expand.compile ++ [C]};
230
 
attribute(Name, Val, St) when is_list(Val) ->
231
 
    St#expand{attributes=St#expand.attributes ++ [{Name,Val}]};
232
 
attribute(Name, Val, St) ->
233
 
    St#expand{attributes=St#expand.attributes ++ [{Name,[Val]}]}.
 
230
attribute(Name, Val, Line, St) when is_list(Val) ->
 
231
    St#expand{attributes=St#expand.attributes ++ [{Name,Line,Val}]};
 
232
attribute(Name, Val, Line, St) ->
 
233
    St#expand{attributes=St#expand.attributes ++ [{Name,Line,[Val]}]}.
234
234
 
235
235
function(L, N, A, Cs0, St0) ->
236
236
    {Cs,St} = clauses(Cs0, St0#expand{func=N,arity=A,fcount=0}),
299
299
    {TT,St2} = pattern(Pat1, St1),
300
300
    {{match,Line,TT,TH},St2};
301
301
%% Compile-time pattern expressions, including unary operators.
302
 
pattern({op,Line,Op,A}, St) ->
303
 
    {erl_eval:partial_eval({op,Line,Op,A}),St};
304
 
pattern({op,Line,Op,L,R}, St) ->
305
 
    {erl_eval:partial_eval({op,Line,Op,L,R}),St}.
 
302
pattern({op,_Line,_Op,_A}=Op, St) ->
 
303
    {erl_eval:partial_eval(Op),St};
 
304
pattern({op,_Line,_Op,_L,_R}=Op, St) ->
 
305
    {erl_eval:partial_eval(Op),St}.
306
306
 
307
307
pattern_list([P0|Ps0], St0) ->
308
308
    {P,St1} = pattern(P0, St0),
400
400
    {{'receive',Line,Cs,To,ToEs},St3};
401
401
expr({'fun',Line,Body}, St) ->
402
402
    fun_tq(Line, Body, St);
403
 
expr({call,Line,{atom,La,N},As0}, St0) ->
 
403
expr({call,Line,{atom,La,N}=Atom,As0}, St0) ->
404
404
    {As,St1} = expr_list(As0, St0),
405
405
    Ar = length(As),
406
 
    case erl_internal:bif(N, Ar) of
407
 
        true ->
408
 
            {{call,Line,{remote,La,{atom,La,erlang},{atom,La,N}},As},St1};
409
 
        false ->
410
 
            case imported(N, Ar, St1) of
411
 
                {yes,Mod} ->
412
 
                    {{call,Line,{remote,La,{atom,La,Mod},{atom,La,N}},As},St1};
413
 
                no ->
414
 
                    {{call,Line,{atom,La,N},As},St1}
415
 
            end
 
406
    case defined(N,Ar,St1) of
 
407
        true ->
 
408
            {{call,Line,Atom,As},St1};
 
409
        _ ->
 
410
            case imported(N, Ar, St1) of
 
411
                {yes,Mod} ->
 
412
                    {{call,Line,{remote,La,{atom,La,Mod},Atom},As},St1};
 
413
                no ->
 
414
                    case erl_internal:bif(N, Ar) of
 
415
                        true ->
 
416
                            {{call,Line,{remote,La,{atom,La,erlang},Atom},As},St1};
 
417
                        false -> %% This should have been handled by erl_lint
 
418
                            {{call,Line,Atom,As},St1}
 
419
                    end
 
420
            end
416
421
    end;
417
422
expr({call,Line,{record_field,_,_,_}=M,As0}, St0) ->
418
423
    expr({call,Line,expand_package(M, St0),As0}, St0);
685
690
        {ok,Mod} -> {yes,Mod};
686
691
        error -> no
687
692
    end.
 
693
 
 
694
defined(F, A, St) ->
 
695
    ordsets:is_element({F,A}, St#expand.defined).