~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_lint.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
2
2
%%
3
3
%% %CopyrightBegin%
4
4
%%
5
 
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
6
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
60
60
              (_Opt, Def) -> Def
61
61
          end, Default, Opts).
62
62
 
 
63
%% The maximum number of arguments allowed for a function.
 
64
 
 
65
-define(MAX_ARGUMENTS, 255).
 
66
 
63
67
%% The error and warning info structures, {Line,Module,Descriptor},
64
68
%% are kept in their seperate fields in the lint state record together
65
69
%% with the name of the file (when a new file is entered, marked by
119
123
               called= [] :: [{fa(),line()}],           %Called functions
120
124
               usage = #usage{}         :: #usage{},
121
125
               specs = dict:new()       :: dict(),      %Type specifications
 
126
               callbacks = dict:new()   :: dict(),      %Callback types
122
127
               types = dict:new()       :: dict(),      %Type definitions
123
128
               exp_types=gb_sets:empty():: gb_set()     %Exported types
124
129
              }).
125
130
 
126
131
-type lint_state() :: #lint{}.
 
132
-type error_description() :: term().
 
133
-type error_info() :: {erl_scan:line(), module(), error_description()}.
127
134
 
128
135
%% format_error(Error)
129
136
%%  Return a string describing the error.
130
137
 
 
138
-spec format_error(ErrorDescriptor) -> io_lib:chars() when
 
139
      ErrorDescriptor :: error_description().
 
140
 
131
141
format_error(undefined_module) ->
132
142
    "no module definition";
133
143
format_error({bad_module_name, M}) ->
226
236
    io_lib:format("~p/~p obsolete", [F, A]);
227
237
format_error({reserved_for_future,K}) ->
228
238
    io_lib:format("atom ~w: future reserved keyword - rename or quote", [K]);
 
239
format_error({too_many_arguments,Arity}) ->
 
240
    io_lib:format("too many arguments (~w) - "
 
241
                  "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
229
242
%% --- patterns and guards ---
230
243
format_error(illegal_pattern) -> "illegal pattern";
231
244
format_error(illegal_bin_pattern) ->
298
311
format_error({undefined_behaviour_func, {Func,Arity}, Behaviour}) ->
299
312
    io_lib:format("undefined callback function ~w/~w (behaviour '~w')",
300
313
                  [Func,Arity,Behaviour]);
301
 
format_error({undefined_behaviour_func, {Func,Arity,_Spec}, Behaviour}) ->
302
 
    format_error({undefined_behaviour_func, {Func,Arity}, Behaviour});
303
314
format_error({undefined_behaviour,Behaviour}) ->
304
315
    io_lib:format("behaviour ~w undefined", [Behaviour]);
305
316
format_error({undefined_behaviour_callbacks,Behaviour}) ->
308
319
format_error({ill_defined_behaviour_callbacks,Behaviour}) ->
309
320
    io_lib:format("behaviour ~w callback functions erroneously defined",
310
321
                  [Behaviour]);
 
322
format_error({behaviour_info, {_M,F,A}}) ->
 
323
    io_lib:format("cannot define callback attibute for ~w/~w when "
 
324
                  "behaviour_info is defined",[F,A]);
311
325
%% --- types and specs ---
312
326
format_error({singleton_typevar, Name}) ->
313
327
    io_lib:format("type variable ~w is only used once (is unbound)", [Name]);
336
350
    io_lib:format("bad ~w type", [Constr]);
337
351
format_error({redefine_spec, {M, F, A}}) ->
338
352
    io_lib:format("spec for ~w:~w/~w already defined", [M, F, A]);
 
353
format_error({redefine_callback, {M, F, A}}) ->
 
354
    io_lib:format("callback ~w:~w/~w already defined", [M, F, A]);
339
355
format_error({spec_fun_undefined, {M, F, A}}) ->
340
356
    io_lib:format("spec for undefined function ~w:~w/~w", [M, F, A]);
341
357
format_error({missing_spec, {F,A}}) ->
342
358
    io_lib:format("missing specification for function ~w/~w", [F, A]);
343
359
format_error(spec_wrong_arity) ->
344
360
    "spec has the wrong arity";
 
361
format_error(callback_wrong_arity) ->
 
362
    "callback has the wrong arity";
345
363
format_error({imported_predefined_type, Name}) ->
346
364
    io_lib:format("referring to built-in type ~w as a remote type; "
347
365
                  "please take out the module name", [Name]);
412
430
%%  apply_lambda/2 has been called to shut lint up. N.B. these lists are
413
431
%%  really all ordsets!
414
432
 
 
433
-spec(module(AbsForms) -> {ok, Warnings} | {error, Errors, Warnings} when
 
434
      AbsForms :: [erl_parse:abstract_form()],
 
435
      Warnings :: [{file:filename(),[ErrorInfo]}],
 
436
      Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],
 
437
      ErrorInfo :: error_info()).
 
438
 
415
439
module(Forms) ->
416
440
    Opts = compiler_options(Forms),
417
441
    St = forms(Forms, start("nofile", Opts)),
418
442
    return_status(St).
419
443
 
 
444
-spec(module(AbsForms, FileName) ->
 
445
             {ok, Warnings} | {error, Errors, Warnings} when
 
446
      AbsForms :: [erl_parse:abstract_form()],
 
447
      FileName :: atom() | string(),
 
448
      Warnings :: [{file:filename(),[ErrorInfo]}],
 
449
      Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],
 
450
      ErrorInfo :: error_info()).
 
451
 
420
452
module(Forms, FileName) ->
421
453
    Opts = compiler_options(Forms),
422
454
    St = forms(Forms, start(FileName, Opts)),
423
455
    return_status(St).
424
456
 
 
457
-spec(module(AbsForms, FileName, CompileOptions) ->
 
458
             {ok, Warnings} | {error, Errors, Warnings} when
 
459
      AbsForms :: [erl_parse:abstract_form()],
 
460
      FileName :: atom() | string(),
 
461
      CompileOptions :: [compile:option()],
 
462
      Warnings :: [{file:filename(),[ErrorInfo]}],
 
463
      Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],
 
464
      ErrorInfo :: error_info()).
 
465
 
425
466
module(Forms, FileName, Opts0) ->
426
467
    %% We want the options given on the command line to take
427
468
    %% precedence over options in the module.
712
753
    type_def(opaque, L, TypeName, TypeDef, Args, St);
713
754
attribute_state({attribute,L,spec,{Fun,Types}}, St) ->
714
755
    spec_decl(L, Fun, Types, St);
 
756
attribute_state({attribute,L,callback,{Fun,Types}}, St) ->
 
757
    callback_decl(L, Fun, Types, St);
715
758
attribute_state({attribute,L,on_load,Val}, St) ->
716
759
    on_load(L, Val, St);
717
760
attribute_state({attribute,_L,_Other,_Val}, St) -> % Ignore others
805
848
    StB = check_unused_types(Forms, StA),
806
849
    StC = check_untyped_records(Forms, StB),
807
850
    StD = check_on_load(StC),
808
 
    check_unused_records(Forms, StD).
 
851
    StE = check_unused_records(Forms, StD),
 
852
    check_callback_information(StE).
809
853
 
810
854
%% check_behaviour(State0) -> State
811
855
%% Check that the behaviour attribute is valid.
1104
1148
            St0
1105
1149
    end.
1106
1150
 
 
1151
check_callback_information(#lint{callbacks = Callbacks,
 
1152
                                 defined = Defined} = State) ->
 
1153
    case gb_sets:is_member({behaviour_info,1}, Defined) of
 
1154
        false -> State;
 
1155
        true ->
 
1156
            case dict:size(Callbacks) of
 
1157
                0 -> State;
 
1158
                _ ->
 
1159
                    CallbacksList = dict:to_list(Callbacks),
 
1160
                    FoldL =
 
1161
                        fun({Fa,Line},St) ->
 
1162
                                add_error(Line, {behaviour_info, Fa}, St)
 
1163
                        end,
 
1164
                    lists:foldl(FoldL, State, CallbacksList)
 
1165
            end
 
1166
    end.
 
1167
 
1107
1168
%% For storing the import list we use the orddict module.
1108
1169
%% We know an empty set is [].
1109
1170
 
1307
1368
        true ->
1308
1369
            add_error(Line, {redefine_function,NA}, St1);
1309
1370
        false ->
1310
 
            St2 = St1#lint{defined=gb_sets:add_element(NA, St1#lint.defined)},
1311
 
            case imported(Name, Arity, St2) of
1312
 
                {yes,_M} -> add_error(Line, {define_import,NA}, St2);
1313
 
                no -> St2
 
1371
            St2 = function_check_max_args(Line, Arity, St1),
 
1372
            St3 = St2#lint{defined=gb_sets:add_element(NA, St2#lint.defined)},
 
1373
            case imported(Name, Arity, St3) of
 
1374
                {yes,_M} -> add_error(Line, {define_import,NA}, St3);
 
1375
                no -> St3
1314
1376
            end
1315
1377
    end.
1316
1378
 
 
1379
function_check_max_args(Line, Arity, St) when Arity > ?MAX_ARGUMENTS ->
 
1380
    add_error(Line, {too_many_arguments,Arity}, St);
 
1381
function_check_max_args(_, _, St) -> St.
 
1382
 
1317
1383
%% clauses([Clause], VarTable, State) -> {VarTable, State}.
1318
1384
 
1319
1385
clauses(Cs, Vt, St) ->
1865
1931
 
1866
1932
%% is_guard_test(Expression) -> boolean().
1867
1933
%%  Test if a general expression is a guard test.
 
1934
-spec is_guard_test(Expr) -> boolean() when
 
1935
      Expr :: erl_parse:abstract_expr().
 
1936
 
1868
1937
is_guard_test(E) ->
1869
1938
    is_guard_test2(E, dict:new()).
1870
1939
 
2058
2127
                true -> {[],St};
2059
2128
                false -> {[],call_function(Line, F, A, St)}
2060
2129
            end;
2061
 
        {function,_M,_F,_A} ->
2062
 
            {[],St}
 
2130
        {function,M,F,A} when is_atom(M), is_atom(F), is_integer(A) ->
 
2131
            %% Compatibility with pre-R15 abstract format.
 
2132
            {[],St};
 
2133
        {function,M,F,A} ->
 
2134
            %% New in R15.
 
2135
            {Bvt, St1} = expr_list([M,F,A], Vt, St),
 
2136
            {vtupdate(Bvt, Vt),St1}
2063
2137
    end;
2064
2138
expr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) ->
2065
2139
    {Rvt,St1} = expr(E, Vt, St0),
2693
2767
                {var, 1}],
2694
2768
    dict:from_list([{T, -1} || T <- DefTypes]).
2695
2769
 
2696
 
%% R12B-5
2697
 
is_newly_introduced_builtin_type({module, 0}) -> true;
2698
 
is_newly_introduced_builtin_type({node, 0}) -> true;
2699
 
is_newly_introduced_builtin_type({nonempty_string, 0}) -> true;
2700
 
is_newly_introduced_builtin_type({term, 0}) -> true;
2701
 
is_newly_introduced_builtin_type({timeout, 0}) -> true;
2702
2770
%% R13
2703
2771
is_newly_introduced_builtin_type({arity, 0}) -> true;
2704
2772
is_newly_introduced_builtin_type({array, 0}) -> true; % opaque
2727
2795
        false -> check_specs(TypeSpecs, Arity, St1)
2728
2796
    end.
2729
2797
 
 
2798
%% callback_decl(Line, Fun, Types, State) -> State.
 
2799
 
 
2800
callback_decl(Line, MFA0, TypeSpecs,
 
2801
              St0 = #lint{callbacks = Callbacks, module = Mod}) ->
 
2802
    MFA = case MFA0 of
 
2803
              {F, Arity} -> {Mod, F, Arity};
 
2804
              {_M, _F, Arity} -> MFA0
 
2805
          end,
 
2806
    St1 = St0#lint{callbacks = dict:store(MFA, Line, Callbacks)},
 
2807
    case dict:is_key(MFA, Callbacks) of
 
2808
        true -> add_error(Line, {redefine_callback, MFA}, St1);
 
2809
        false -> check_specs(TypeSpecs, Arity, St1)
 
2810
    end.
 
2811
 
2730
2812
check_specs([FunType|Left], Arity, St0) ->
2731
2813
    {FunType1, CTypes} =
2732
2814
        case FunType of
3232
3314
    {attribute,Mf(L),record,{Name,modify_line1(Fields, Mf)}};
3233
3315
modify_line1({attribute,L,spec,{Fun,Types}}, Mf) ->
3234
3316
    {attribute,Mf(L),spec,{Fun,modify_line1(Types, Mf)}};
 
3317
modify_line1({attribute,L,callback,{Fun,Types}}, Mf) ->
 
3318
    {attribute,Mf(L),callback,{Fun,modify_line1(Types, Mf)}};
3235
3319
modify_line1({attribute,L,type,{TypeName,TypeDef,Args}}, Mf) ->
3236
3320
    {attribute,Mf(L),type,{TypeName,modify_line1(TypeDef, Mf),
3237
3321
                           modify_line1(Args, Mf)}};