~ubuntu-branches/ubuntu/lucid/erlang/lucid-updates

« back to all changes in this revision

Viewing changes to lib/compiler/src/sys_expand_pmod.erl

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
Tags: 1:13.b.3-dfsg-2ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
109
109
string_to_conses([E|Rest], Line, Tail) ->
110
110
    {cons, Line, {integer, Line, E}, string_to_conses(Rest, Line, Tail)}.
111
111
 
112
 
pattern({var,Line,V},_St) -> {var,Line,V};
 
112
pattern({var,_Line,_V}=Var,_St) -> Var;
113
113
pattern({match,Line,L0,R0},St) ->
114
114
    L1 = pattern(L0,St),
115
115
    R1 = pattern(R0,St),
116
116
    {match,Line,L1,R1};
117
 
pattern({integer,Line,I},_St) -> {integer,Line,I};
118
 
pattern({char,Line,C},_St) -> {char,Line,C};
119
 
pattern({float,Line,F},_St) -> {float,Line,F};
120
 
pattern({atom,Line,A},_St) -> {atom,Line,A};
121
 
pattern({string,Line,S},_St) -> {string,Line,S};
122
 
pattern({nil,Line},_St) -> {nil,Line};
 
117
pattern({integer,_Line,_I}=Integer,_St) -> Integer;
 
118
pattern({char,_Line,_C}=Char,_St) -> Char;
 
119
pattern({float,_Line,_F}=Float,_St) -> Float;
 
120
pattern({atom,_Line,_A}=Atom,_St) -> Atom;
 
121
pattern({string,_Line,_S}=String,_St) -> String;
 
122
pattern({nil,_Line}=Nil,_St) -> Nil;
123
123
pattern({cons,Line,H0,T0},St) ->
124
124
    H1 = pattern(H0,St),
125
125
    T1 = pattern(T0,St),
132
132
    {bin,Line,Fs2};
133
133
pattern({op,_Line,'++',{nil,_},R},St) ->
134
134
    pattern(R,St);
135
 
pattern({op,_Line,'++',{cons,Li,{char,C2,I},T},R},St) ->
136
 
    pattern({cons,Li,{char,C2,I},{op,Li,'++',T,R}},St);
137
 
pattern({op,_Line,'++',{cons,Li,{integer,L2,I},T},R},St) ->
138
 
    pattern({cons,Li,{integer,L2,I},{op,Li,'++',T,R}},St);
 
135
pattern({op,_Line,'++',{cons,Li,{char,_C2,_I}=Char,T},R},St) ->
 
136
    pattern({cons,Li,Char,{op,Li,'++',T,R}},St);
 
137
pattern({op,_Line,'++',{cons,Li,{integer,_L2,_I}=Integer,T},R},St) ->
 
138
    pattern({cons,Li,Integer,{op,Li,'++',T,R}},St);
139
139
pattern({op,_Line,'++',{string,Li,L},R},St) ->
140
140
    pattern(string_to_conses(L, Li, R),St);
141
 
pattern({op,Line,Op,A},_St) ->
142
 
    {op,Line,Op,A};
143
 
pattern({op,Line,Op,L,R},_St) ->
144
 
    {op,Line,Op,L,R}.
 
141
pattern({op,_Line,_Op,_A}=Op4,_St) -> Op4;
 
142
pattern({op,_Line,_Op,_L,_R}=Op5,_St) -> Op5.
145
143
 
146
144
pattern_grp([{bin_element,L1,E1,S1,T1} | Fs],St) ->
147
145
    S2 = case S1 of
193
191
guard_test(Any,St) ->
194
192
    gexpr(Any,St).
195
193
 
196
 
gexpr({var,L,V},_St) ->
197
 
    {var,L,V};
 
194
gexpr({var,_L,_V}=Var,_St) -> Var;
198
195
% %% alternative implementation of accessing module parameters
199
196
%     case index(V,St#pmod.parameters) of
200
197
%       N when N > 0 ->
201
198
%           {call,L,{remote,L,{atom,L,erlang},{atom,L,element}},
202
199
%            [{integer,L,N+1},{var,L,'THIS'}]};
203
200
%       _ ->
204
 
%           {var,L,V}
 
201
%           Var
205
202
%     end;
206
 
gexpr({integer,Line,I},_St) -> {integer,Line,I};
207
 
gexpr({char,Line,C},_St) -> {char,Line,C};
208
 
gexpr({float,Line,F},_St) -> {float,Line,F};
209
 
gexpr({atom,Line,A},_St) -> {atom,Line,A};
210
 
gexpr({string,Line,S},_St) -> {string,Line,S};
211
 
gexpr({nil,Line},_St) -> {nil,Line};
 
203
gexpr({integer,_Line,_I}=Integer,_St) -> Integer;
 
204
gexpr({char,_Line,_C}=Char,_St) -> Char;
 
205
gexpr({float,_Line,_F}=Float,_St) -> Float;
 
206
gexpr({atom,_Line,_A}=Atom,_St) -> Atom;
 
207
gexpr({string,_Line,_S}=String,_St) -> String;
 
208
gexpr({nil,_Line}=Nil,_St) -> Nil;
212
209
gexpr({cons,Line,H0,T0},St) ->
213
210
    H1 = gexpr(H0,St),
214
211
    T1 = gexpr(T0,St),
216
213
gexpr({tuple,Line,Es0},St) ->
217
214
    Es1 = gexpr_list(Es0,St),
218
215
    {tuple,Line,Es1};
219
 
gexpr({call,Line,{atom,La,F},As0},St) ->
220
 
    case erl_internal:guard_bif(F, length(As0)) of
221
 
        true -> As1 = gexpr_list(As0,St),
222
 
                {call,Line,{atom,La,F},As1}
223
 
    end;
224
 
% Pre-expansion generated calls to erlang:is_record/3 must also be handled
225
 
gexpr({call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,is_record}},As0},St)
226
 
  when length(As0) =:= 3 ->
 
216
gexpr({call,Line,{atom,_La,F}=Atom,As0},St) ->
 
217
    true = erl_internal:guard_bif(F, length(As0)),
 
218
    As1 = gexpr_list(As0,St),
 
219
    {call,Line,Atom,As1};
 
220
%% Pre-expansion generated calls to erlang:is_record/3 must also be handled
 
221
gexpr({call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,is_record}},[_,_,_]=As0},St) ->
227
222
    As1 = gexpr_list(As0,St),
228
223
    {call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,is_record}},As1};
229
 
% Guard bif's can be remote, but only in the module erlang...
 
224
%% Guard BIFs can be remote, but only in the module erlang...
230
225
gexpr({call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,F}},As0},St) ->
231
 
    case erl_internal:guard_bif(F, length(As0)) or
232
 
         erl_internal:arith_op(F, length(As0)) or 
233
 
         erl_internal:comp_op(F, length(As0)) or
234
 
         erl_internal:bool_op(F, length(As0)) of
235
 
        true -> As1 = gexpr_list(As0,St),
236
 
                {call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,F}},As1}
237
 
    end;
238
 
% Unfortunately, writing calls as {M,F}(...) is also allowed.
 
226
    A = length(As0),
 
227
    true =
 
228
        erl_internal:guard_bif(F, A) orelse erl_internal:arith_op(F, A) orelse
 
229
        erl_internal:comp_op(F, A) orelse erl_internal:bool_op(F, A),
 
230
    As1 = gexpr_list(As0,St),
 
231
    {call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,F}},As1};
 
232
%% Unfortunately, writing calls as {M,F}(...) is also allowed.
239
233
gexpr({call,Line,{tuple,La,[{atom,Lb,erlang},{atom,Lc,F}]},As0},St) ->
240
 
    case erl_internal:guard_bif(F, length(As0)) or
241
 
         erl_internal:arith_op(F, length(As0)) or 
242
 
         erl_internal:comp_op(F, length(As0)) or
243
 
         erl_internal:bool_op(F, length(As0)) of
244
 
        true -> As1 = gexpr_list(As0,St),
245
 
                {call,Line,{tuple,La,[{atom,Lb,erlang},{atom,Lc,F}]},As1}
246
 
    end;
 
234
    A = length(As0),
 
235
    true =
 
236
        erl_internal:guard_bif(F, A) orelse erl_internal:arith_op(F, A) orelse 
 
237
        erl_internal:comp_op(F, A) orelse erl_internal:bool_op(F, A),
 
238
    As1 = gexpr_list(As0,St),
 
239
    {call,Line,{tuple,La,[{atom,Lb,erlang},{atom,Lc,F}]},As1};
247
240
gexpr({bin,Line,Fs},St) ->
248
241
    Fs2 = pattern_grp(Fs,St),
249
242
    {bin,Line,Fs2};
250
243
gexpr({op,Line,Op,A0},St) ->
251
 
    case erl_internal:arith_op(Op, 1) orelse
252
 
        erl_internal:bool_op(Op, 1) of
253
 
        true -> A1 = gexpr(A0,St),
254
 
                {op,Line,Op,A1}
255
 
    end;
 
244
    true = erl_internal:arith_op(Op, 1) orelse erl_internal:bool_op(Op, 1),
 
245
    A1 = gexpr(A0,St),
 
246
    {op,Line,Op,A1};
256
247
gexpr({op,Line,Op,L0,R0},St) ->
257
 
    case Op =:= 'andalso' orelse Op =:= 'orelse' orelse
 
248
    true =
 
249
        Op =:= 'andalso' orelse Op =:= 'orelse' orelse
258
250
        erl_internal:arith_op(Op, 2) orelse
259
 
        erl_internal:bool_op(Op, 2) orelse
260
 
        erl_internal:comp_op(Op, 2) of
261
 
        true ->
262
 
            L1 = gexpr(L0,St),
263
 
            R1 = gexpr(R0,St),
264
 
            {op,Line,Op,L1,R1}
265
 
    end.
 
251
        erl_internal:bool_op(Op, 2) orelse erl_internal:comp_op(Op, 2),
 
252
    L1 = gexpr(L0,St),
 
253
    R1 = gexpr(R0,St),
 
254
    {op,Line,Op,L1,R1}.
266
255
 
267
256
gexpr_list([E0|Es],St) ->
268
257
    E1 = gexpr(E0,St),
274
263
    [E1|exprs(Es,St)];
275
264
exprs([],_St) -> [].
276
265
 
277
 
expr({var,L,V},_St) ->
278
 
    {var,L,V};
 
266
expr({var,_L,_V}=Var,_St) ->
 
267
    Var;
279
268
%     case index(V,St#pmod.parameters) of
280
269
%       N when N > 0 ->
281
270
%           {call,L,{remote,L,{atom,L,erlang},{atom,L,element}},
282
271
%            [{integer,L,N+1},{var,L,'THIS'}]};
283
272
%       _ ->
284
 
%           {var,L,V}
 
273
%           Var
285
274
%     end;
286
 
expr({integer,Line,I},_St) -> {integer,Line,I};
287
 
expr({float,Line,F},_St) -> {float,Line,F};
288
 
expr({atom,Line,A},_St) -> {atom,Line,A};
289
 
expr({string,Line,S},_St) -> {string,Line,S};
290
 
expr({char,Line,C},_St) -> {char,Line,C};
291
 
expr({nil,Line},_St) -> {nil,Line};
 
275
expr({integer,_Line,_I}=Integer,_St) -> Integer;
 
276
expr({float,_Line,_F}=Float,_St) -> Float;
 
277
expr({atom,_Line,_A}=Atom,_St) -> Atom;
 
278
expr({string,_Line,_S}=String,_St) -> String;
 
279
expr({char,_Line,_C}=Char,_St) -> Char;
 
280
expr({nil,_Line}=Nil,_St) -> Nil;
292
281
expr({cons,Line,H0,T0},St) ->
293
282
    H1 = expr(H0,St),
294
283
    T1 = expr(T0,St),
329
318
        {clauses,Cs0} ->
330
319
            Cs1 = fun_clauses(Cs0,St),
331
320
            {'fun',Line,{clauses,Cs1},Info};
332
 
        {function,F,A} ->
 
321
        {function,F,A} = Function ->
333
322
            {F1,A1} = update_function_name({F,A},St),
334
 
            if A1 == A ->
335
 
                    {'fun',Line,{function,F,A},Info};
 
323
            if A1 =:= A ->
 
324
                    {'fun',Line,Function,Info};
336
325
               true ->
337
326
                    %% Must rewrite local fun-name to a fun that does a
338
327
                    %% call with the extra THIS parameter.
342
331
                    Cs = [{clause,Line,As,[],[Call]}],
343
332
                    {'fun',Line,{clauses,Cs},Info}
344
333
            end;
345
 
        {function,M,F,A} ->                     %This is an error in lint!
346
 
            {'fun',Line,{function,M,F,A},Info}
 
334
        {function,_M,_F,_A} = Fun4 ->           %This is an error in lint!
 
335
            {'fun',Line,Fun4,Info}
347
336
    end;
348
337
expr({call,Lc,{atom,_,instance}=Name,As0},St) ->
349
338
    %% All local functions 'instance(...)' are static by definition,
360
349
    %% The module_info/0 and module_info/1 functions are also static.
361
350
    As1 = expr_list(As0,St),
362
351
    {call,Lc,Name,As1};
363
 
expr({call,Lc,{atom,Lf,F},As0},St) ->
 
352
expr({call,Lc,{atom,_Lf,_F}=Atom,As0},St) ->
364
353
    %% Local function call - needs THIS parameter.
365
354
    As1 = expr_list(As0,St),
366
 
    {call,Lc,{atom,Lf,F},As1 ++ [{var,0,'THIS'}]};
 
355
    {call,Lc,Atom,As1 ++ [{var,0,'THIS'}]};
367
356
expr({call,Line,F0,As0},St) ->
368
357
    %% Other function call
369
358
    F1 = expr(F0,St),
416
405
    [C1|fun_clauses(Cs,St)];
417
406
fun_clauses([],_St) -> [].
418
407
 
419
 
% %% Return index from 1 upwards, or 0 if not in the list.
420
 
%
421
 
% index(X,Ys) -> index(X,Ys,1).
422
 
%
423
 
% index(X,[X|Ys],A) -> A;
424
 
% index(X,[Y|Ys],A) -> index(X,Ys,A+1);
425
 
% index(X,[],A) -> 0.
 
408
%% %% Return index from 1 upwards, or 0 if not in the list.
 
409
%%
 
410
%% index(X,Ys) -> index(X,Ys,1).
 
411
%%
 
412
%% index(X,[X|Ys],A) -> A;
 
413
%% index(X,[Y|Ys],A) -> index(X,Ys,A+1);
 
414
%% index(X,[],A) -> 0.
426
415
 
427
416
make_vars(N, L) ->
428
417
    make_vars(1, N, L).