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

« back to all changes in this revision

Viewing changes to lib/compiler/src/core_lint.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
3
%% 
4
 
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
5
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
65
65
                  | {'return_mismatch', fa()} | {'undefined_function', fa()}
66
66
                  | {'duplicate_var', cerl:var_name(), fa()}
67
67
                  | {'unbound_var', cerl:var_name(), fa()}
68
 
                  | {'undefined_function', fa(), fa()}.
 
68
                  | {'undefined_function', fa(), fa()}
 
69
                  | {'tail_segment_not_at_end', fa()}.
69
70
 
70
71
-type error()    :: {module(), err_desc()}.
71
72
-type warning()  :: {module(), term()}.
116
117
format_error({unbound_var,N,{F,A}}) ->
117
118
    io_lib:format("unbound variable ~s in ~w/~w", [N,F,A]);
118
119
format_error({undefined_function,{F1,A1},{F2,A2}}) ->
119
 
    io_lib:format("undefined function ~w/~w in ~w/~w", [F1,A1,F2,A2]).
 
120
    io_lib:format("undefined function ~w/~w in ~w/~w", [F1,A1,F2,A2]);
 
121
format_error({tail_segment_not_at_end,{F,A}}) ->
 
122
    io_lib:format("binary tail segment not at end in ~w/~w", [F,A]).
120
123
 
121
124
-type ret() :: {'ok', [{module(), [warning(),...]}]}
122
125
             | {'error', [{module(), [error(),...]}],
450
453
    pattern_list([H,T], Def, Ps, St);
451
454
pattern(#c_tuple{es=Es}, Def, Ps, St) ->
452
455
    pattern_list(Es, Def, Ps, St);
453
 
pattern(#c_binary{segments=Ss}, Def, Ps, St) ->
 
456
pattern(#c_binary{segments=Ss}, Def, Ps, St0) ->
 
457
    St = pat_bin_tail_check(Ss, St0),
454
458
    pat_bin(Ss, Def, Ps, St);
455
459
pattern(#c_alias{var=V,pat=P}, Def, Ps, St0) ->
456
460
    {Vvs,St1} = variable(V, Ps, St0),
482
486
pat_segment(_, Def, Ps, St) ->
483
487
    {Ps,Def,add_error({not_bs_pattern,St#lint.func}, St)}.
484
488
 
 
489
%% pat_bin_tail_check([Elem], State) -> State.
 
490
%%  There must be at most one tail segment (a size-less segment of
 
491
%%  type binary) and it must occur at the end.
 
492
 
 
493
pat_bin_tail_check([#c_bitstr{size=#c_literal{val=all}}], St) ->
 
494
    %% Size-less field is OK at the end of the list of segments.
 
495
    St;
 
496
pat_bin_tail_check([#c_bitstr{size=#c_literal{val=all}}|_], St) ->
 
497
    add_error({tail_segment_not_at_end,St#lint.func}, St);
 
498
pat_bin_tail_check([_|Ss], St) ->
 
499
    pat_bin_tail_check(Ss, St);
 
500
pat_bin_tail_check([], St) -> St.
 
501
 
485
502
%% pat_bit_expr(SizePat, Type, Defined, State) -> State.
486
503
%%  Check the Size pattern, this is an input!  Because of optimizations,
487
504
%%  we must allow any kind of constant and literal here.