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

« back to all changes in this revision

Viewing changes to lib/stdlib/test/erl_lint_SUITE.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 1999-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1999-2011. 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
-module(erl_lint_SUITE).
27
27
-define(privdir, "erl_lint_SUITE_priv").
28
28
-define(t, test_server).
29
29
-else.
30
 
-include("test_server.hrl").
 
30
-include_lib("test_server/include/test_server.hrl").
31
31
-define(datadir, ?config(data_dir, Conf)).
32
32
-define(privdir, ?config(priv_dir, Conf)).
33
33
-endif.
34
34
 
35
 
-export([all/1, init_per_testcase/2, fin_per_testcase/2]).
 
35
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
36
         init_per_group/2,end_per_group/2, 
 
37
         init_per_testcase/2, end_per_testcase/2]).
36
38
 
37
 
-export([unused_vars_warn/1, 
38
 
             unused_vars_warn_basic/1, 
39
 
             unused_vars_warn_lc/1, 
40
 
             unused_vars_warn_rec/1,
41
 
             unused_vars_warn_fun/1, 
42
 
             unused_vars_OTP_4858/1,
43
 
         export_vars_warn/1,
44
 
         shadow_vars/1,
45
 
         unused_import/1,
46
 
         unused_function/1,
47
 
         unsafe_vars/1,unsafe_vars2/1,
48
 
         unsafe_vars_try/1,
49
 
         guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
50
 
         otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
51
 
         otp_5917/1, otp_6585/1, otp_6885/1, export_all/1,
52
 
         bif_clash/1,
53
 
         behaviour_basic/1, behaviour_multiple/1,
54
 
         otp_7550/1,
55
 
         otp_8051/1,
56
 
         format_warn/1,
57
 
         on_load/1, on_load_successful/1, on_load_failing/1
 
39
-export([ 
 
40
          unused_vars_warn_basic/1, 
 
41
          unused_vars_warn_lc/1, 
 
42
          unused_vars_warn_rec/1,
 
43
          unused_vars_warn_fun/1, 
 
44
          unused_vars_OTP_4858/1,
 
45
          export_vars_warn/1,
 
46
          shadow_vars/1,
 
47
          unused_import/1,
 
48
          unused_function/1,
 
49
          unsafe_vars/1,unsafe_vars2/1,
 
50
          unsafe_vars_try/1,
 
51
          guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
 
52
          otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
 
53
          otp_5917/1, otp_6585/1, otp_6885/1, export_all/1,
 
54
          bif_clash/1,
 
55
          behaviour_basic/1, behaviour_multiple/1,
 
56
          otp_7550/1,
 
57
          otp_8051/1,
 
58
          format_warn/1,
 
59
          on_load_successful/1, on_load_failing/1, 
 
60
          too_many_arguments/1
58
61
        ]).
59
62
 
60
63
% Default timetrap timeout (set in init_per_testcase).
64
67
    ?line Dog = ?t:timetrap(?default_timeout),
65
68
    [{watchdog, Dog} | Config].
66
69
 
67
 
fin_per_testcase(_Case, _Config) ->
 
70
end_per_testcase(_Case, _Config) ->
68
71
    Dog = ?config(watchdog, _Config),
69
72
    test_server:timetrap_cancel(Dog),
70
73
    ok.
71
74
 
72
 
all(suite) ->
73
 
    [unused_vars_warn, export_vars_warn, 
 
75
suite() -> [{ct_hooks,[ts_install_cth]}].
 
76
 
 
77
all() -> 
 
78
    [{group, unused_vars_warn}, export_vars_warn,
74
79
     shadow_vars, unused_import, unused_function,
75
 
     unsafe_vars, unsafe_vars2, unsafe_vars_try,
76
 
     guard, otp_4886, otp_4988, otp_5091, otp_5276, otp_5338, 
77
 
     otp_5362, otp_5371, otp_7227, otp_5494, otp_5644, otp_5878, otp_5917, otp_6585,
78
 
     otp_6885, export_all, bif_clash,
79
 
     behaviour_basic, behaviour_multiple, otp_7550, otp_8051, format_warn,
80
 
     on_load].
81
 
 
82
 
unused_vars_warn(suite) ->
83
 
    [unused_vars_warn_basic, unused_vars_warn_lc, unused_vars_warn_rec, 
84
 
     unused_vars_warn_fun, unused_vars_OTP_4858].
 
80
     unsafe_vars, unsafe_vars2, unsafe_vars_try, guard,
 
81
     otp_4886, otp_4988, otp_5091, otp_5276, otp_5338,
 
82
     otp_5362, otp_5371, otp_7227, otp_5494, otp_5644,
 
83
     otp_5878, otp_5917, otp_6585, otp_6885, export_all,
 
84
     bif_clash, behaviour_basic, behaviour_multiple,
 
85
     otp_7550, otp_8051, format_warn, {group, on_load},
 
86
     too_many_arguments].
 
87
 
 
88
groups() -> 
 
89
    [{unused_vars_warn, [],
 
90
      [unused_vars_warn_basic, unused_vars_warn_lc,
 
91
       unused_vars_warn_rec, unused_vars_warn_fun,
 
92
       unused_vars_OTP_4858]},
 
93
     {on_load, [], [on_load_successful, on_load_failing]}].
 
94
 
 
95
init_per_suite(Config) ->
 
96
    Config.
 
97
 
 
98
end_per_suite(_Config) ->
 
99
    ok.
 
100
 
 
101
init_per_group(_GroupName, Config) ->
 
102
    Config.
 
103
 
 
104
end_per_group(_GroupName, Config) ->
 
105
    Config.
 
106
 
 
107
 
85
108
 
86
109
unused_vars_warn_basic(doc) ->
87
110
    "Warnings for unused variables in some simple cases.";
1784
1807
                      {15,erl_lint,{undefined_field,ok,nix}},
1785
1808
                      {16,erl_lint,{field_name_is_variable,ok,'Var'}}]}},
1786
1809
 
 
1810
          %% Nowarn_bif_clash has changed behaviour as local functions
 
1811
          %% nowdays supersede auto-imported BIFs, why nowarn_bif_clash in itself generates an error
 
1812
          %% (OTP-8579) /PaN
1787
1813
          {otp_5362_4,
1788
1814
           <<"-compile(nowarn_deprecated_function).
1789
1815
              -compile(nowarn_bif_clash).
1795
1821
             warn_deprecated_function,
1796
1822
             warn_bif_clash]},
1797
1823
           {error,
1798
 
            [{5,erl_lint,{call_to_redefined_bif,{spawn,1}}}],
1799
 
            [{3,erl_lint,{redefine_bif,{spawn,1}}},
1800
 
             {4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
 
1824
            [{5,erl_lint,{call_to_redefined_old_bif,{spawn,1}}}],
 
1825
            [{4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
1801
1826
                          "in a future release"}}]}},
1802
1827
 
1803
1828
          {otp_5362_5,
1808
1833
                  spawn(A).
1809
1834
           ">>,
1810
1835
           {[nowarn_unused_function]},
1811
 
           {warnings,
1812
 
            [{3,erl_lint,{redefine_bif,{spawn,1}}}]}},
 
1836
           {errors,
 
1837
            [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
1813
1838
 
1814
1839
          %% The special nowarn_X are not affected by general warn_X.
1815
1840
          {otp_5362_6,
1822
1847
           {[nowarn_unused_function, 
1823
1848
             warn_deprecated_function, 
1824
1849
             warn_bif_clash]},
1825
 
           {warnings,
1826
 
            [{3,erl_lint,{redefine_bif,{spawn,1}}}]}},
 
1850
           {errors,
 
1851
            [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
1827
1852
 
1828
1853
          {otp_5362_7,
1829
1854
           <<"-export([spawn/1]).
1838
1863
                  spawn(A).
1839
1864
           ">>,
1840
1865
           {[nowarn_unused_function]},
1841
 
           {error,[{4,erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}],
 
1866
           {error,[{3,erl_lint,disallowed_nowarn_bif_clash},
 
1867
                   {4,erl_lint,disallowed_nowarn_bif_clash},
 
1868
                   {4,erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}],
1842
1869
            [{5,erl_lint,{bad_nowarn_deprecated_function,{3,hash,-1}}},
1843
1870
             {5,erl_lint,{bad_nowarn_deprecated_function,{erlang,hash,-1}}},
1844
1871
             {5,erl_lint,{bad_nowarn_deprecated_function,{{a,b,c},hash,-1}}}]}
1865
1892
              t() -> #a{}.
1866
1893
          ">>,
1867
1894
           {[]},
1868
 
           []}
 
1895
           []},
 
1896
 
 
1897
          {otp_5362_10,
 
1898
           <<"-compile({nowarn_deprecated_function,{erlang,hash,2}}).
 
1899
              -compile({nowarn_bif_clash,{spawn,1}}).
 
1900
              -import(x,[spawn/1]).
 
1901
              spin(A) ->
 
1902
                  erlang:hash(A, 3000),
 
1903
                  spawn(A).
 
1904
           ">>,
 
1905
           {[nowarn_unused_function,
 
1906
             warn_deprecated_function,
 
1907
             warn_bif_clash]},
 
1908
           {errors,
 
1909
            [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}}
1869
1910
 
1870
1911
          ],
1871
1912
 
2234
2275
                   {15,erl_lint,{undefined_field,r3,q}},
2235
2276
                   {17,erl_lint,{undefined_field,r,q}},
2236
2277
                   {21,erl_lint,illegal_guard_expr},
2237
 
                   {23,erl_lint,illegal_guard_expr}],
 
2278
                   {23,erl_lint,{illegal_guard_local_call,{l,0}}}],
2238
2279
           []} = 
2239
2280
        run_test2(Config, Ill1, [warn_unused_record]),
2240
2281
 
2389
2430
                N.
2390
2431
             ">>,
2391
2432
           [],
2392
 
           {errors,[{2,erl_lint,{call_to_redefined_bif,{size,1}}}],[]}},
 
2433
           {errors,[{2,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
2393
2434
 
2394
 
          %% Verify that (some) warnings can be turned off.
 
2435
          %% Verify that warnings can not be turned off in the old way.
2395
2436
          {clash2,
2396
2437
           <<"-export([t/1,size/1]).
2397
2438
              t(X) ->
2400
2441
              size({N,_}) ->
2401
2442
                N.
2402
2443
 
2403
 
              %% My own abs/1 function works on lists too.
2404
 
              %% Unfortunately, it is not exported, so there will
2405
 
              %% be a warning that can't be turned off.
 
2444
              %% My own abs/1 function works on lists too. From R14 this really works.
2406
2445
              abs([H|T]) when $a =< H, H =< $z -> [H-($a-$A)|abs(T)];
2407
2446
              abs([H|T]) -> [H|abs(T)];
2408
2447
              abs([]) -> [];
2409
2448
              abs(X) -> erlang:abs(X).
2410
2449
             ">>,
2411
 
           {[nowarn_bif_clash]},
2412
 
           {warnings,[{11,erl_lint,{redefine_bif,{abs,1}}},
2413
 
                      {11,erl_lint,{unused_function,{abs,1}}}]}}],
 
2450
           {[nowarn_unused_function,nowarn_bif_clash]},
 
2451
           {errors,[{erl_lint,disallowed_nowarn_bif_clash}],[]}},
 
2452
          %% As long as noone calls an overridden BIF, it's totally OK
 
2453
          {clash3,
 
2454
           <<"-export([size/1]).
 
2455
              size({N,_}) ->
 
2456
                N;
 
2457
              size(X) ->
 
2458
                erlang:size(X).
 
2459
             ">>,
 
2460
           [],
 
2461
           []},
 
2462
          %% But this is totally wrong - meaning of the program changed in R14, so this is an error
 
2463
          {clash4,
 
2464
           <<"-export([size/1]).
 
2465
              size({N,_}) ->
 
2466
                N;
 
2467
              size(X) ->
 
2468
                size(X).
 
2469
             ">>,
 
2470
           [],
 
2471
           {errors,[{5,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
 
2472
          %% For a post R14 bif, its only a warning
 
2473
          {clash5,
 
2474
           <<"-export([binary_part/2]).
 
2475
              binary_part({B,_},{X,Y}) ->
 
2476
                binary_part(B,{X,Y});
 
2477
              binary_part(B,{X,Y}) ->
 
2478
                binary:part(B,X,Y).
 
2479
             ">>,
 
2480
           [],
 
2481
           {warnings,[{3,erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}},
 
2482
          %% If you really mean to call yourself here, you can "unimport" size/1
 
2483
          {clash6,
 
2484
           <<"-export([size/1]).
 
2485
              -compile({no_auto_import,[size/1]}).
 
2486
              size([]) ->
 
2487
                0;
 
2488
              size({N,_}) ->
 
2489
                N;
 
2490
              size([_|T]) ->
 
2491
                1+size(T).
 
2492
             ">>,
 
2493
           [],
 
2494
           []},
 
2495
          %% Same for the post R14 autoimport warning
 
2496
          {clash7,
 
2497
           <<"-export([binary_part/2]).
 
2498
              -compile({no_auto_import,[binary_part/2]}).
 
2499
              binary_part({B,_},{X,Y}) ->
 
2500
                binary_part(B,{X,Y});
 
2501
              binary_part(B,{X,Y}) ->
 
2502
                binary:part(B,X,Y).
 
2503
             ">>,
 
2504
           [],
 
2505
           []},
 
2506
          %% but this doesn't mean the local function is allowed in a guard...
 
2507
          {clash8,
 
2508
           <<"-export([x/1]).
 
2509
              -compile({no_auto_import,[binary_part/2]}).
 
2510
              x(X) when binary_part(X,{1,2}) =:= <<1,2>> ->
 
2511
                 hej.
 
2512
              binary_part({B,_},{X,Y}) ->
 
2513
                binary_part(B,{X,Y});
 
2514
              binary_part(B,{X,Y}) ->
 
2515
                binary:part(B,X,Y).
 
2516
             ">>,
 
2517
           [],
 
2518
           {errors,[{3,erl_lint,{illegal_guard_local_call,{binary_part,2}}}],[]}},
 
2519
          %% no_auto_import is not like nowarn_bif_clash, it actually removes the autoimport
 
2520
          {clash9,
 
2521
           <<"-export([x/1]).
 
2522
              -compile({no_auto_import,[binary_part/2]}).
 
2523
              x(X) ->
 
2524
                 binary_part(X,{1,2}) =:= <<1,2>>.
 
2525
             ">>,
 
2526
           [],
 
2527
           {errors,[{4,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
 
2528
          %% but we could import it again...
 
2529
          {clash10,
 
2530
           <<"-export([x/1]).
 
2531
              -compile({no_auto_import,[binary_part/2]}).
 
2532
              -import(erlang,[binary_part/2]).
 
2533
              x(X) ->
 
2534
                 binary_part(X,{1,2}) =:= <<1,2>>.
 
2535
             ">>,
 
2536
           [],
 
2537
           []},
 
2538
          %% and actually use it in a guard...
 
2539
          {clash11,
 
2540
           <<"-export([x/1]).
 
2541
              -compile({no_auto_import,[binary_part/2]}).
 
2542
              -import(erlang,[binary_part/2]).
 
2543
              x(X) when binary_part(X,{0,1}) =:= <<0>> ->
 
2544
                 binary_part(X,{1,2}) =:= <<1,2>>.
 
2545
             ">>,
 
2546
           [],
 
2547
           []},
 
2548
          %% but for non-obvious historical reasons, imported functions cannot be used in
 
2549
          %% fun construction without the module name...
 
2550
          {clash12,
 
2551
           <<"-export([x/1]).
 
2552
              -compile({no_auto_import,[binary_part/2]}).
 
2553
              -import(erlang,[binary_part/2]).
 
2554
              x(X) when binary_part(X,{0,1}) =:= <<0>> ->
 
2555
                 binary_part(X,{1,2}) =:= fun binary_part/2.
 
2556
             ">>,
 
2557
           [],
 
2558
           {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
 
2559
          %% Not from erlang and not from anywhere else
 
2560
          {clash13,
 
2561
           <<"-export([x/1]).
 
2562
              -compile({no_auto_import,[binary_part/2]}).
 
2563
              -import(x,[binary_part/2]).
 
2564
              x(X) ->
 
2565
                 binary_part(X,{1,2}) =:= fun binary_part/2.
 
2566
             ">>,
 
2567
           [],
 
2568
           {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
 
2569
          %% ...while real auto-import is OK.
 
2570
          {clash14,
 
2571
           <<"-export([x/1]).
 
2572
              x(X) when binary_part(X,{0,1}) =:= <<0>> ->
 
2573
                 binary_part(X,{1,2}) =:= fun binary_part/2.
 
2574
             ">>,
 
2575
           [],
 
2576
           []},
 
2577
          %% Import directive clashing with old bif is an error, regardless of if it's called or not
 
2578
          {clash15,
 
2579
           <<"-export([x/1]).
 
2580
              -import(x,[abs/1]).
 
2581
              x(X) ->
 
2582
                 binary_part(X,{1,2}).
 
2583
             ">>,
 
2584
           [],
 
2585
           {errors,[{2,erl_lint,{redefine_old_bif_import,{abs,1}}}],[]}},
 
2586
          %% For a new BIF, it's only a warning
 
2587
          {clash16,
 
2588
           <<"-export([x/1]).
 
2589
              -import(x,[binary_part/3]).
 
2590
              x(X) ->
 
2591
                 abs(X).
 
2592
             ">>,
 
2593
           [],
 
2594
           {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}},
 
2595
          %% And, you cannot redefine already imported things that aren't auto-imported
 
2596
          {clash17,
 
2597
           <<"-export([x/1]).
 
2598
              -import(x,[binary_port/3]).
 
2599
              -import(y,[binary_port/3]).
 
2600
              x(X) ->
 
2601
                 abs(X).
 
2602
             ">>,
 
2603
           [],
 
2604
           {errors,[{3,erl_lint,{redefine_import,{{binary_port,3},x}}}],[]}},
 
2605
          %% Not with local functions either
 
2606
          {clash18,
 
2607
           <<"-export([x/1]).
 
2608
              -import(x,[binary_port/3]).
 
2609
              binary_port(A,B,C) ->
 
2610
                 binary_part(A,B,C).
 
2611
              x(X) ->
 
2612
                 abs(X).
 
2613
             ">>,
 
2614
           [],
 
2615
           {errors,[{3,erl_lint,{define_import,{binary_port,3}}}],[]}},
 
2616
          %% Like clash8: Dont accept a guard if it's explicitly module-name called either
 
2617
          {clash19,
 
2618
           <<"-export([binary_port/3]).
 
2619
              -compile({no_auto_import,[binary_part/3]}).
 
2620
              -import(x,[binary_part/3]).
 
2621
              binary_port(A,B,C) when x:binary_part(A,B,C) ->
 
2622
                 binary_part(A,B,C+1).
 
2623
             ">>,
 
2624
           [],
 
2625
           {errors,[{4,erl_lint,illegal_guard_expr}],[]}},
 
2626
          %% Not with local functions either
 
2627
          {clash20,
 
2628
           <<"-export([binary_port/3]).
 
2629
              -import(x,[binary_part/3]).
 
2630
              binary_port(A,B,C) ->
 
2631
                 binary_part(A,B,C).
 
2632
             ">>,
 
2633
           [warn_unused_import],
 
2634
           {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}
 
2635
         ],
2414
2636
 
2415
2637
    ?line [] = run(Config, Ts),
2416
2638
    ok.
2597
2819
           <<"-opaque foo() :: bar().
2598
2820
             ">>,
2599
2821
           [],
2600
 
           {error,[{1,erl_lint,{type_ref,{bar,0}}}],
 
2822
           {error,[{1,erl_lint,{undefined_type,{bar,0}}}],
2601
2823
            [{1,erl_lint,{unused_type,{foo,0}}}]}}],
2602
2824
    ?line [] = run(Config, Ts),
2603
2825
    ok.
2632
2854
 
2633
2855
%% Test the -on_load(Name/0) directive.
2634
2856
 
2635
 
on_load(suite) ->
2636
 
    [on_load_successful, on_load_failing].
2637
2857
 
2638
2858
on_load_successful(Config) when is_list(Config) ->
2639
2859
    Ts = [{on_load_1,
2714
2934
    ?line [] = run(Config, Ts),
2715
2935
    ok.
2716
2936
 
 
2937
too_many_arguments(doc) ->
 
2938
    "Test that too many arguments is not accepted.";
 
2939
too_many_arguments(suite) -> [];
 
2940
too_many_arguments(Config) when is_list(Config) ->
 
2941
    Ts = [{too_many_1,
 
2942
           <<"f(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_) -> ok.">>,
 
2943
           [],
 
2944
           {errors,
 
2945
            [{1,erl_lint,{too_many_arguments,256}}],[]}}
 
2946
         ],
 
2947
          
 
2948
    ?line [] = run(Config, Ts),
 
2949
    ok.
 
2950
 
 
2951
 
2717
2952
run(Config, Tests) ->
2718
2953
    F = fun({N,P,Ws,E}, BadL) ->
2719
2954
                case catch run_test(Config, P, Ws) of