~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 4 -*-
 
2
%%=======================================================================
2
3
%% ``The contents of this file are subject to the Erlang Public License,
3
4
%% Version 1.1, (the "License"); you may not use this file except in
4
5
%% compliance with the License. You should have received a copy of the
33
34
 
34
35
-import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]).
35
36
 
36
 
%% bool_option(OnOpt, OffOpt, Default, Options) -> true | false.
 
37
%% bool_option(OnOpt, OffOpt, Default, Options) -> bool().
37
38
%% value_option(Flag, Default, Options) -> Value.
38
39
%% value_option(Flag, Default, OnOpt, OnVal, OffOpt, OffVal, Options) ->
39
40
%%              Value.
40
41
%%  The option handling functions.
41
42
 
42
 
-spec(bool_option/4 :: (atom(), atom(), bool(), [_]) -> bool()).
 
43
-spec bool_option(atom(), atom(), bool(), [_]) -> bool().
43
44
 
44
45
bool_option(On, Off, Default, Opts) ->
45
46
    foldl(fun (Opt, _Def) when Opt =:= On -> true;
253
254
    "a binary field without size is only allowed at the end of a binary pattern";
254
255
format_error(typed_literal_string) ->
255
256
    "a literal string in a binary pattern must not have a type or a size";
 
257
format_error(utf_bittype_size_or_unit) ->
 
258
    "neither size nor unit must be given for segments of type utf8/utf16/utf32";
256
259
format_error({bad_bitsize,Type}) ->
257
260
    io_lib:format("bad ~s bit size", [Type]);
258
261
%% --- behaviours ---
276
279
    io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]);
277
280
format_error({unused_type, {TypeName, Arity}}) ->
278
281
    io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]);
 
282
format_error({new_builtin_type, {TypeName, Arity}}) ->
 
283
    io_lib:format("type ~w~s is a new builtin type; "
 
284
                  "its (re)definition is allowed only until the next release", 
 
285
                  [TypeName, gen_type_paren(Arity)]);
 
286
format_error({builtin_type, {TypeName, Arity}}) ->
 
287
    io_lib:format("type ~w~s is a builtin type; it cannot be redefined", 
 
288
                  [TypeName, gen_type_paren(Arity)]);
279
289
format_error({redefine_type, {TypeName, Arity}}) ->
280
290
    io_lib:format("type ~w~s already defined", 
281
291
                  [TypeName, gen_type_paren(Arity)]);
1319
1329
    rbia_fields(Fs, I+1, Acc);
1320
1330
rbia_fields([], _, Acc) -> Acc.
1321
1331
 
1322
 
%% is_pattern_expr(Expression) ->
1323
 
%%      true | false.
 
1332
%% is_pattern_expr(Expression) -> bool().
1324
1333
%%  Test if a general expression is a valid pattern expression.
1325
1334
 
1326
1335
is_pattern_expr(Expr) ->
1373
1382
                               {0,[],Bvt0,St0}, Es),
1374
1383
    {Esvt,Bvt,St1}.
1375
1384
 
1376
 
pattern_element({bin_element,Line,{string,_,_},Size,Ts}, _, _, {Sz,Esvt,Bvt,St0})
1377
 
  when Ts =/= default; Size =/= default  ->
1378
 
    St = add_error(Line, typed_literal_string, St0),
1379
 
    {Sz,Esvt,Bvt,St};
1380
 
pattern_element({bin_element,Line,E,Sz0,Ts}, Vt, Old, {Size0,Esvt,Bvt,St0}) ->
 
1385
pattern_element({bin_element,Line,{string,_,_},Size,Ts}=Be, Vt,
 
1386
                Old, {Sz,Esvt,Bvt,St0}=Acc) ->
 
1387
    case good_string_size_type(Size, Ts) of
 
1388
        true ->
 
1389
            pattern_element_1(Be, Vt, Old, Acc);
 
1390
        false ->
 
1391
            St = add_error(Line, typed_literal_string, St0),
 
1392
            {Sz,Esvt,Bvt,St}
 
1393
    end;
 
1394
pattern_element(Be, Vt, Old, Acc) ->
 
1395
    pattern_element_1(Be, Vt, Old, Acc).
 
1396
 
 
1397
pattern_element_1({bin_element,Line,E,Sz0,Ts}, Vt, Old, {Size0,Esvt,Bvt,St0}) ->
1381
1398
    {Pevt,Bvt1,St1} = pat_bit_expr(E, Old, Bvt, St0),
1382
1399
    %% vtmerge or vtmerge_pat doesn't matter here
1383
1400
    {Sz1,Szvt,Bvt2,St2} = pat_bit_size(Sz0, vtmerge(Vt, Esvt), Bvt, St1),
1391
1408
    {Size1,vtmerge(Szvt,vtmerge(Pevt, Esvt)),
1392
1409
     vtmerge(Bvt2,vtmerge(Bvt, Bvt1)), St5}.
1393
1410
 
 
1411
good_string_size_type(default, default) ->
 
1412
    true;
 
1413
good_string_size_type(default, Ts) ->
 
1414
    lists:any(fun(utf8) -> true;
 
1415
                 (utf16) -> true;
 
1416
                 (utf32) -> true;
 
1417
                 (_) -> false
 
1418
              end, Ts);
 
1419
good_string_size_type(_, _) -> false.
 
1420
 
1394
1421
%% pat_bit_expr(Pattern, OldVarTable, BinVarTable,State) -> 
1395
1422
%%              {UpdVarTable,UpdBinVarTable,State}.
1396
1423
%%  Check pattern bit expression, only allow really valid patterns!
1431
1458
 
1432
1459
expr_bin(Es, Vt, St0, Check) ->
1433
1460
    {_Sz,Esvt,St1} = foldl(fun (E, Acc) -> bin_element(E, Vt, Acc, Check) end,
1434
 
                          {0,[],St0}, Es),
 
1461
                           {0,[],St0}, Es),
1435
1462
    {Esvt,St1}.
1436
1463
 
1437
1464
bin_element({bin_element,Line,E,Sz0,Ts}, Vt, {Size0,Esvt,St0}, Check) ->
1477
1504
%%   float == 32 or 64
1478
1505
 
1479
1506
bit_size_check(_Line, unknown, _, St) -> {unknown,St};
 
1507
bit_size_check(_Line, undefined, #bittype{type=Type}, St) ->
 
1508
    true = (Type =:= utf8) or (Type =:= utf16) or (Type =:= utf32), %Assertion.
 
1509
    {undefined,St};
1480
1510
bit_size_check(Line, all, #bittype{type=Type}, St) ->
1481
 
    if
1482
 
        Type =:= binary -> {all,St};
1483
 
        true -> {unknown,add_error(Line, illegal_bitsize, St)}
 
1511
    case Type of
 
1512
        binary -> {all,St};
 
1513
        _ -> {unknown,add_error(Line, illegal_bitsize, St)}
1484
1514
    end;
1485
1515
bit_size_check(Line, Size, #bittype{type=Type,unit=Unit}, St) ->
1486
1516
    Sz = Unit * Size,                           %Total number of bits!
1502
1532
add_bit_size(_Line, _Sz1, all, true, St) ->
1503
1533
    {all,St};
1504
1534
add_bit_size(_Line, all, _Sz2, _B, St) -> {all,St};
 
1535
add_bit_size(_Line, undefined, _Sz2, _B, St) -> {undefined,St};
1505
1536
add_bit_size(_Line, unknown, _Sz2, _B, St) -> {unknown,St};
 
1537
add_bit_size(_Line, _Sz1, undefined, _B, St) -> {unknown,St};
1506
1538
add_bit_size(_Line, _Sz1, unknown, _B, St) -> {unknown,St};
1507
1539
add_bit_size(_Line, Sz1, Sz2, _B, St) -> {Sz1 + Sz2,St}.
1508
1540
 
1657
1689
                  {vtmerge(Evt, Esvt),St1}
1658
1690
          end, {[],St}, Es).
1659
1691
 
1660
 
%% is_guard_test(Expression) -> true | false.
 
1692
%% is_guard_test(Expression) -> bool().
1661
1693
%%  Test if a general expression is a guard test.
1662
1694
is_guard_test(E) ->
1663
1695
    is_guard_test2(E, dict:new()).
1671
1703
                end, start(), RecordAttributes),
1672
1704
    is_guard_test2(zip_file_and_line(Expression, "nofile"), St0#lint.records).
1673
1705
 
1674
 
%% is_guard_test2(Expression, RecordDefs) -> true | false.
 
1706
%% is_guard_test2(Expression, RecordDefs) -> bool().
1675
1707
is_guard_test2({call,Line,{atom,Lr,record},[E,A]}, RDs) ->
1676
1708
    is_gexpr({call,Line,{atom,Lr,is_record},[E,A]}, RDs);
1677
1709
is_guard_test2({call,_Line,{atom,_La,Test},As}=Call, RDs) ->
1683
1715
    %%Everything else is a guard expression.
1684
1716
    is_gexpr(G, RDs).
1685
1717
 
1686
 
%% is_guard_expr(Expression) -> true | false.
 
1718
%% is_guard_expr(Expression) -> bool().
1687
1719
%%  Test if an expression is a guard expression.
1688
1720
 
1689
1721
is_guard_expr(E) -> is_gexpr(E, []). 
2264
2296
type_def(Line, TypeName, ProtoType, Args, St0) ->
2265
2297
    TypeDefs = St0#lint.types,
2266
2298
    Arity = length(Args),
2267
 
    case (dict:is_key({TypeName, Arity}, TypeDefs) orelse 
2268
 
          is_var_arity_type(TypeName)) of
 
2299
    TypePair = {TypeName, Arity},
 
2300
    case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of
2269
2301
        true ->
2270
 
            add_error(Line, {redefine_type, {TypeName, Arity}}, St0);
 
2302
            case dict:is_key(TypePair, default_types()) of
 
2303
                true  ->
 
2304
                    case is_newly_introduced_builtin_type(TypePair) of
 
2305
                        %% allow some types just for bootstrapping R12B-5
 
2306
                        true ->
 
2307
                            Warn = {new_builtin_type, TypePair},
 
2308
                            St1 = add_warning(Line, Warn, St0),
 
2309
                            NewDefs = dict:store(TypePair, Line, TypeDefs),
 
2310
                            CheckType = {type, -1, product, [ProtoType|Args]},
 
2311
                            check_type(CheckType, St1#lint{types=NewDefs});
 
2312
                        false ->
 
2313
                            add_error(Line, {builtin_type, TypePair}, St0)
 
2314
                    end;
 
2315
                false -> add_error(Line, {redefine_type, TypePair}, St0)
 
2316
            end;
2271
2317
        false ->
2272
 
            NewDefs = dict:store({TypeName, Arity}, Line, TypeDefs),
 
2318
            NewDefs = dict:store(TypePair, Line, TypeDefs),
2273
2319
            CheckType = {type, -1, product, [ProtoType|Args]},
2274
2320
            check_type(CheckType, St0#lint{types=NewDefs})
2275
2321
    end.
2419
2465
                {'fun', 2},
2420
2466
                {function, 0},
2421
2467
                {identifier, 0},
2422
 
                {iolist, 0},
2423
2468
                {integer, 0},
2424
2469
                {integer, 1},
 
2470
                {iolist, 0},
2425
2471
                {list, 0},
2426
2472
                {list, 1},
 
2473
                {maybe_improper_list, 0},
 
2474
                {maybe_improper_list, 2},
2427
2475
                {mfa, 0},
 
2476
                {module, 0},
 
2477
                {neg_integer, 0},
2428
2478
                {nil, 0},
2429
 
                {neg_integer, 0},
 
2479
                {no_return, 0},
 
2480
                {node, 0},
2430
2481
                {non_neg_integer, 0},
2431
 
                {no_return, 0},
2432
2482
                {none, 0},
2433
2483
                {nonempty_list, 0},
2434
2484
                {nonempty_list, 1},
2435
2485
                {nonempty_improper_list, 2},
2436
2486
                {nonempty_maybe_improper_list, 0},
2437
2487
                {nonempty_maybe_improper_list, 2},
 
2488
                {nonempty_string, 0},
2438
2489
                {number, 0},
2439
2490
                {pid, 0},
2440
2491
                {port, 0},
2441
2492
                {pos_integer, 0},
2442
 
                {maybe_improper_list, 0},
2443
 
                {maybe_improper_list, 2},
2444
2493
                {range, 2},
2445
2494
                {ref, 0},
2446
2495
                {string, 0},
 
2496
                {term, 0},
 
2497
                {timeout, 0},
2447
2498
                {var, 1}],
2448
2499
    dict:from_list([{T, -1} || T <- DefTypes]).
2449
2500
 
 
2501
is_newly_introduced_builtin_type({module, 0}) -> true;
 
2502
is_newly_introduced_builtin_type({node, 0}) -> true;
 
2503
is_newly_introduced_builtin_type({nonempty_string, 0}) -> true;
 
2504
is_newly_introduced_builtin_type({term, 0}) -> true;
 
2505
is_newly_introduced_builtin_type({timeout, 0}) -> true;
 
2506
is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
 
2507
 
2450
2508
%% spec_decl(Line, Fun, Types, State) -> State.
2451
2509
 
2452
2510
spec_decl(Line, MFA0, TypeSpecs, St0 = #lint{specs=AccSpecs}) ->
2616
2674
    Some = ordsets:subtract(vtnames(Vt1), vtnames(Vt)),
2617
2675
    Xvt = vtexport(All, In, []),
2618
2676
    Evt = vtunsafe(ordsets:subtract(Some, All), In, Xvt),
2619
 
    Unused = vtmerge(map(fun (Vt0) -> unused_vars(Vt0, Vt, St) end, Csvt)),
 
2677
    Unused = vtmerge([unused_vars(Vt0, Vt, St) || Vt0 <- Csvt]),
2620
2678
    %% Exported and unsafe variables may be unused:
2621
2679
    Uvt = vtmerge(Evt, Unused),
2622
2680
    %% Make exported and unsafe unused variables unused in subsequent code: