diff options
Diffstat (limited to 'lib/stdlib/test/erl_lint_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 378 |
1 files changed, 143 insertions, 235 deletions
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index d946469625..29a389d4b8 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -19,7 +19,7 @@ %% -module(erl_lint_SUITE). -%-define(debug, true). +%%-define(debug, true). -ifdef(debug). -define(line, put(line, ?LINE), ). @@ -29,8 +29,8 @@ -define(t, test_server). -else. -include_lib("common_test/include/ct.hrl"). --define(datadir, ?config(data_dir, Conf)). --define(privdir, ?config(priv_dir, Conf)). +-define(datadir, proplists:get_value(data_dir, Conf)). +-define(privdir, proplists:get_value(priv_dir, Conf)). -endif. -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, @@ -69,19 +69,15 @@ record_errors/1 ]). -% Default timetrap timeout (set in init_per_testcase). --define(default_timeout, ?t:minutes(1)). - init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?default_timeout), - [{watchdog, Dog} | Config]. + Config. end_per_testcase(_Case, _Config) -> - Dog = ?config(watchdog, _Config), - test_server:timetrap_cancel(Dog), ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,1}}]. all() -> [{group, unused_vars_warn}, export_vars_warn, @@ -119,50 +115,48 @@ end_per_group(_GroupName, Config) -> -unused_vars_warn_basic(doc) -> - "Warnings for unused variables in some simple cases."; -unused_vars_warn_basic(suite) -> []; +%% Warnings for unused variables in some simple cases. unused_vars_warn_basic(Config) when is_list(Config) -> Ts = [{basic1, <<"f(F) -> % F unused. ok. - f(F, F) -> - ok. +f(F, F) -> + ok. - g(_X) -> - y. +g(_X) -> + y. - h(P) -> - P. +h(P) -> + P. - x(N) -> - case a:b() of - [N|Y] -> % Y unused. - ok - end. +x(N) -> + case a:b() of + [N|Y] -> % Y unused. + ok + end. - y(N, L) -> - lists:map(fun(T) -> T*N end, L). +y(N, L) -> + lists:map(fun(T) -> T*N end, L). - z(N, L) -> % N unused - lists:map(fun(N, T) -> T*N end, L). % N shadowed. +z(N, L) -> % N unused + lists:map(fun(N, T) -> T*N end, L). % N shadowed. - c(A) -> - case A of - 1 -> B = []; % B unused. - 2 -> B = []; % B unused. - 3 -> B = f, B - end. - ">>, +c(A) -> + case A of + 1 -> B = []; % B unused. + 2 -> B = []; % B unused. + 3 -> B = f, B + end. +">>, [warn_unused_vars], - {warnings,[{1,erl_lint,{unused_var,'F'}}, - {15,erl_lint,{unused_var,'Y'}}, - {22,erl_lint,{unused_var,'N'}}, - {23,erl_lint,{shadowed_var,'N','fun'}}, - {28,erl_lint,{unused_var,'B'}}, - {29,erl_lint,{unused_var,'B'}}]}}, +{warnings,[{1,erl_lint,{unused_var,'F'}}, + {15,erl_lint,{unused_var,'Y'}}, + {22,erl_lint,{unused_var,'N'}}, + {23,erl_lint,{shadowed_var,'N','fun'}}, + {28,erl_lint,{unused_var,'B'}}, + {29,erl_lint,{unused_var,'B'}}]}}, {basic2, <<"-record(r, {x,y}). f({X,Y}) -> {Z=X,Z=Y}; @@ -172,12 +166,10 @@ unused_vars_warn_basic(Config) when is_list(Config) -> g({M, F, Arg}) -> (Z=M):F(Z=Arg). h(X, Y) -> (Z=X) + (Z=Y).">>, [warn_unused_vars], []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_vars_warn_lc(doc) -> - "Warnings for unused variables in list comprehensions."; -unused_vars_warn_lc(suite) -> []; +%% Warnings for unused variables in list comprehensions. unused_vars_warn_lc(Config) when is_list(Config) -> Ts = [{lc1, <<"bin([X]) -> @@ -404,9 +396,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> {error,[{22,erl_lint,{unsafe_var,'U',{'case',2}}}, {27,erl_lint,{unsafe_var,'U',{'case',2}}}], [{16,erl_lint,{unused_var,'Y'}}, - % {24,erl_lint,{exported_var,'X',{'case',8}}}, {24,erl_lint,{unused_var,'U'}}, - % {26,erl_lint,{exported_var,'X',{'case',8}}}, {26,erl_lint,{unused_var,'U'}}]}}, {lc17, @@ -436,7 +426,6 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [warn_unused_vars], {error,[{22,erl_lint,{unsafe_var,'U',{'case',3}}}], [{17,erl_lint,{unused_var,'Y'}}, - % {21,erl_lint,{exported_var,'X',{'case',9}}}, {21,erl_lint,{unused_var,'U'}}]}}, {lc18, @@ -461,14 +450,12 @@ unused_vars_warn_lc(Config) when is_list(Config) -> end, [B || <<U: % U unused U>> <- X, <<B:Y>> <- Z]. % U unsafe. Y unsafe. - % U shadowed. (X exported.) + % U shadowed. (X exported.) ">>, [warn_unused_vars], {error,[{21,erl_lint,{unsafe_var,'U',{'case',2}}}, {21,erl_lint,{unsafe_var,'Y',{'case',14}}}], [{20,erl_lint,{unused_var,'U'}} - % ,{21,erl_lint,{exported_var,'X',{'case',8}}} - % ,{21,erl_lint,{shadowed_var,'U',generate}} ]}}, {lc19, @@ -522,13 +509,11 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [{14,erl_lint,{unused_var,'Q'}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_vars_warn_rec(doc) -> - "Warnings for unused variables in records."; -unused_vars_warn_rec(suite) -> []; +%% Warnings for unused variables in records. unused_vars_warn_rec(Config) when is_list(Config) -> Ts = [{rec1, % An example provided by Bjorn. <<"-record(edge, @@ -580,12 +565,10 @@ unused_vars_warn_rec(Config) when is_list(Config) -> {error,[{2,erl_lint,{redefine_field,r,a}}, {2,erl_lint,{redefine_field,r,a}}], [{2,erl_lint,{unused_var,'X'}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_vars_warn_fun(doc) -> - "Warnings for unused variables in funs."; -unused_vars_warn_fun(suite) -> []; +%% Warnings for unused variables in funs. unused_vars_warn_fun(Config) when is_list(Config) -> Ts = [{fun1, <<"a({A,B}) -> % A unused. @@ -707,12 +690,10 @@ unused_vars_warn_fun(Config) when is_list(Config) -> {33,erl_lint,{unused_var,'U'}}, {33,erl_lint,{shadowed_var,'U','fun'}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_vars_OTP_4858(doc) -> - "Bit syntax, binsize variable used in the same matching."; -unused_vars_OTP_4858(suite) -> []; +%% Bit syntax, binsize variable used in the same matching. unused_vars_OTP_4858(Config) when is_list(Config) -> Ts = [{otp_4858, <<"objs(<<Size:4/unit:8, B:Size/binary>>) -> @@ -731,7 +712,7 @@ unused_vars_OTP_4858(Config) when is_list(Config) -> {8,erl_lint,{unused_var,'B'}}, {8,erl_lint,{unused_var,'Rest'}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. unused_unsafe_vars_warn(Config) when is_list(Config) -> @@ -776,9 +757,7 @@ unused_unsafe_vars_warn(Config) when is_list(Config) -> run(Config, Ts), ok. -export_vars_warn(doc) -> - "Warnings for exported variables"; -export_vars_warn(suite) -> []; +%% Warnings for exported variables. export_vars_warn(Config) when is_list(Config) -> Ts = [{exp1, <<"u() -> @@ -868,13 +847,11 @@ export_vars_warn(Config) when is_list(Config) -> [], {warnings,[{7,erl_lint,{exported_var,'Z',{'if',2}}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -shadow_vars(doc) -> - "Shadowed variables are tested in other places, but here we test " - "that the warning can be turned off."; -shadow_vars(suite) -> []; +%% Shadowed variables are tested in other places, but here we test +%% that the warning can be turned off. shadow_vars(Config) when is_list(Config) -> Ts = [{shadow1, <<"bin(A) -> @@ -899,12 +876,10 @@ shadow_vars(Config) when is_list(Config) -> ">>, [], []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_import(doc) -> - "Test that the 'warn_unused_import' option works."; -unused_import(suite) -> []; +%% Test that the 'warn_unused_import' option works. unused_import(Config) when is_list(Config) -> Ts = [{imp1, <<"-import(lists, [map/2,foldl/3]). @@ -913,12 +888,10 @@ unused_import(Config) when is_list(Config) -> ">>, [warn_unused_import], {warnings,[{1,erl_lint,{unused_import,{{foldl,3},lists}}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unused_function(doc) -> - "Test warnings for unused functions."; -unused_function(suite) -> []; +%% Test warnings for unused functions. unused_function(Config) when is_list(Config) -> Ts = [{func1, <<"-export([t/1]). @@ -961,12 +934,10 @@ unused_function(Config) when is_list(Config) -> {[]}, %Tuple indicates no 'export_all'. []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unsafe_vars(doc) -> - "OTP-4671. Errors for unsafe variables"; -unsafe_vars(suite) -> []; +%% OTP-4671. Errors for unsafe variables. unsafe_vars(Config) when is_list(Config) -> Ts = [{unsafe1, <<"t() -> @@ -1042,7 +1013,7 @@ unsafe_vars(Config) when is_list(Config) -> D = 1; 2 -> A = 2, - % B not bound here + %% B not bound here C = 2, catch D = 2; % unsafe in two clauses 3 -> @@ -1064,12 +1035,10 @@ unsafe_vars(Config) when is_list(Config) -> {24,erl_lint,{unsafe_var,'D',{'case',2}}}], []}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unsafe_vars2(doc) -> - "OTP-4831, seq8202. No warn_unused_vars and unsafe variables"; -unsafe_vars2(suite) -> []; +%% OTP-4831, seq8202. No warn_unused_vars and unsafe variables. unsafe_vars2(Config) when is_list(Config) -> Ts = [{unsafe2_1, <<"foo(State) -> @@ -1098,12 +1067,10 @@ unsafe_vars2(Config) when is_list(Config) -> [], {errors,[{9,erl_lint,{unsafe_var,'State1',{'if',4}}}],[]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unsafe_vars_try(doc) -> - "Errors for unsafe variables in try/catch constructs."; -unsafe_vars_try(suite) -> []; +%% Errors for unsafe variables in try/catch constructs. unsafe_vars_try(Config) when is_list(Config) -> Ts = [{unsafe_try1, <<"foo2() -> @@ -1288,12 +1255,10 @@ unsafe_vars_try(Config) when is_list(Config) -> ">>, [], {errors,[{13,erl_lint,{unsafe_var,'Acc',{'try',6}}}],[]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -unsized_binary_in_bin_gen_pattern(doc) -> - "Unsized binary fields are forbidden in patterns of bit string generators"; -unsized_binary_in_bin_gen_pattern(suite) -> []; +%% Unsized binary fields are forbidden in patterns of bit string generators. unsized_binary_in_bin_gen_pattern(Config) when is_list(Config) -> Ts = [{unsized_binary_in_bin_gen_pattern, <<"t({bc,binary,Bin}) -> @@ -1326,9 +1291,7 @@ unsized_binary_in_bin_gen_pattern(Config) when is_list(Config) -> [] = run(Config, Ts), ok. -guard(doc) -> - "OTP-4670. Guards, is_record in particular."; -guard(suite) -> []; +%% OTP-4670. Guards, is_record in particular. guard(Config) when is_list(Config) -> %% Well, these could be plain code... Ts = [{guard1, @@ -1543,7 +1506,7 @@ guard(Config) when is_list(Config) -> ">>, [nowarn_obsolete_guard], []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), Ts1 = [{guard5, <<"-record(apa, {}). t3(A) when record(A, {apa}) -> @@ -1614,12 +1577,10 @@ guard(Config) when is_list(Config) -> {2,erl_lint,illegal_guard_expr}], []}} ], - ?line [] = run(Config, Ts1), + [] = run(Config, Ts1), ok. -otp_4886(doc) -> - "OTP-4886. Calling is_record with given record name."; -otp_4886(suite) -> []; +%% OTP-4886. Calling is_record with given record name. otp_4886(Config) when is_list(Config) -> Ts = [{otp_4886, <<"t() -> @@ -1638,12 +1599,10 @@ otp_4886(Config) when is_list(Config) -> {4,erl_lint,{undefined_record,foo}}, {5,erl_lint,{undefined_record,foo}}], []}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_4988(doc) -> - "OTP-4988. Error when in-lining non-existent functions."; -otp_4988(suite) -> []; +%% OTP-4988. Error when in-lining non-existent functions. otp_4988(Config) when is_list(Config) -> Ts = [{otp_4988, <<"-compile({inline, [{f,3},{f,4},{f,2},{f,a},{1,foo}]}). @@ -1665,12 +1624,10 @@ otp_4988(Config) when is_list(Config) -> {1,erl_lint,{bad_inline,{f,a}}}, {3,erl_lint,{bad_inline,{g,12}}}], []}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5091(doc) -> - "OTP-5091. Patterns and the bit syntax: invalid warnings."; -otp_5091(suite) -> []; +%% OTP-5091. Patterns and the bit syntax: invalid warnings. otp_5091(Config) when is_list(Config) -> Ts = [{otp_5091_1, <<"t() -> @@ -1883,12 +1840,10 @@ otp_5091(Config) when is_list(Config) -> <<"-record(r, {f1,f2}). t(#r{f1 = A, f2 = A}) -> a.">>, [], []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5276(doc) -> - "OTP-5276. Check the 'deprecated' attributed."; -otp_5276(suite) -> []; +%% OTP-5276. Check the 'deprecated' attributed. otp_5276(Config) when is_list(Config) -> Ts = [{otp_5276_1, <<"-deprecated([{frutt,0,next_version}]). @@ -1915,12 +1870,10 @@ otp_5276(Config) when is_list(Config) -> {9,erl_lint,{invalid_deprecated,{{badly,formed},1}}}, {11,erl_lint,{bad_deprecated,{atom_to_list,1}}}], [{13,erl_lint,{unused_function,{frutt,0}}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5917(doc) -> - "OTP-5917. Check the 'deprecated' attributed."; -otp_5917(suite) -> []; +%% OTP-5917. Check the 'deprecated' attributed. otp_5917(Config) when is_list(Config) -> Ts = [{otp_5917_1, <<"-compile(export_all). @@ -1932,12 +1885,10 @@ otp_5917(Config) when is_list(Config) -> ">>, {[]}, []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_6585(doc) -> - "OTP-6585. Check the deprecated guards list/1, pid/1, ...."; -otp_6585(suite) -> []; +%% OTP-6585. Check the deprecated guards list/1, pid/1, .... otp_6585(Config) when is_list(Config) -> Ts = [{otp_6585_1, <<"-compile(export_all). @@ -1955,12 +1906,10 @@ otp_6585(Config) when is_list(Config) -> {warnings,[{5,erl_lint,{obsolete_guard,{list,1}}}, {6,erl_lint,{obsolete_guard,{record,2}}}, {7,erl_lint,{obsolete_guard,{pid,1}}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5338(doc) -> - "OTP-5338. Bad warning in record initialization."; -otp_5338(suite) -> []; +%% OTP-5338. Bad warning in record initialization. otp_5338(Config) when is_list(Config) -> %% OTP-5878: variables like X are no longer allowed in initialisations Ts = [{otp_5338, @@ -1972,13 +1921,11 @@ otp_5338(Config) when is_list(Config) -> [], {error,[{1,erl_lint,{unbound_var,'X'}}], [{3,erl_lint,{unused_var,'X'}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5362(doc) -> - "OTP-5362. deprecated_function, " - "{nowarn_unused_funtion,FAs}, 'better' line numbers."; -otp_5362(suite) -> []; +%% OTP-5362. deprecated_function, +%% {nowarn_unused_funtion,FAs}, 'better' line numbers. otp_5362(Config) when is_list(Config) -> Ts = [{otp_5362_1, <<"-include_lib(\"stdlib/include/qlc.hrl\"). @@ -2178,12 +2125,10 @@ otp_5362(Config) when is_list(Config) -> ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5371(doc) -> - "OTP-5371. Aliases for bit syntax expressions are no longer allowed."; -otp_5371(suite) -> []; +%% OTP-5371. Aliases for bit syntax expressions are no longer allowed. otp_5371(Config) when is_list(Config) -> Ts = [{otp_5371_1, <<"t(<<A:8>> = <<B:8>>) -> @@ -2237,10 +2182,10 @@ otp_5371(Config) when is_list(Config) -> {6,v3_core,nomatch}, {8,v3_core,nomatch}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_7227(doc) -> "OTP_7227. Some aliases for bit syntax expressions were still allowed."; +%% OTP_7227. Some aliases for bit syntax expressions were still allowed. otp_7227(Config) when is_list(Config) -> Ts = [{otp_7227_1, <<"t([<<A:8>> = {C,D} = <<B:8>>]) -> @@ -2307,12 +2252,10 @@ otp_7227(Config) when is_list(Config) -> [], {errors,[{2,erl_lint,illegal_bin_pattern}],[]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5494(doc) -> - "OTP-5494. Warnings for functions exported more than once."; -otp_5494(suite) -> []; +%% OTP-5494. Warnings for functions exported more than once. otp_5494(Config) when is_list(Config) -> Ts = [{otp_5494_1, <<"-export([t/0]). @@ -2321,12 +2264,10 @@ otp_5494(Config) when is_list(Config) -> ">>, [], {warnings,[{2,erl_lint,{duplicated_export,{t,0}}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5644(doc) -> - "OTP-5644. M:F/A in record initialization."; -otp_5644(suite) -> []; +%% OTP-5644. M:F/A in record initialization. otp_5644(Config) when is_list(Config) -> %% This test is a no-op. Although {function,mfa,i,1} was %% transformed into {function,Line,i,1} by copy_expr, the module @@ -2342,12 +2283,10 @@ otp_5644(Config) when is_list(Config) -> ">>, [], []}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_5878(doc) -> - "OTP-5878. Record declaration: forward references, introduced variables."; -otp_5878(suite) -> []; +%% OTP-5878. Record declaration: forward references, introduced variables. otp_5878(Config) when is_list(Config) -> Ts = [{otp_5878_10, <<"-record(rec1, {a = #rec2{}}). @@ -2463,7 +2402,7 @@ otp_5878(Config) when is_list(Config) -> [{1,erl_lint,{unused_record,r}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), Abstr = <<"-module(lint_test, [A, B]). ">>, @@ -2480,7 +2419,7 @@ otp_5878(Config) when is_list(Config) -> X <- Z ++ [A,Y]])}). t() -> {#r1{},#r2{},#r3{}}. ">>, - ?line {error,[{8,qlc,{used_generator_variable,'A'}}, + {error,[{8,qlc,{used_generator_variable,'A'}}, {8,qlc,{used_generator_variable,'Y'}}, {8,qlc,{used_generator_variable,'Z'}}], [{6,erl_lint,{unused_var,'V'}}]} = @@ -2521,7 +2460,7 @@ otp_5878(Config) when is_list(Config) -> bar. ">>, - ?line {errors,[{6,erl_lint,{unbound_var,'A'}}, + {errors,[{6,erl_lint,{unbound_var,'A'}}, {13,erl_lint,illegal_guard_expr}, {15,erl_lint,{undefined_field,r3,q}}, {17,erl_lint,{undefined_field,r,q}}, @@ -2540,14 +2479,14 @@ otp_5878(Config) when is_list(Config) -> foo end. ">>, - ?line {errors,[{4,erl_lint,{undefined_function,{x,0}}}, + {errors,[{4,erl_lint,{undefined_function,{x,0}}}, {5,erl_lint,illegal_guard_expr}, {7,erl_lint,illegal_guard_expr}], []} = run_test2(Config, Ill2, [warn_unused_record]), Ill3 = <<"t() -> ok.">>, - ?line {errors,[{1,erl_lint,undefined_module}],[]} = + {errors,[{1,erl_lint,undefined_module}],[]} = run_test2(Config, Ill3, [warn_unused_record]), Usage1 = <<"-module(lint_test). @@ -2560,7 +2499,7 @@ otp_5878(Config) when is_list(Config) -> t() -> {#u2{}}. ">>, - ?line {warnings,[{5,erl_lint,{unused_record,u3}}, + {warnings,[{5,erl_lint,{unused_record,u3}}, {6,erl_lint,{unused_record,u4}}]} = run_test2(Config, Usage1, [warn_unused_record]), @@ -2575,7 +2514,7 @@ otp_5878(Config) when is_list(Config) -> t() -> {#u2{}}. ">>, - ?line [] = run_test2(Config, Usage2, [warn_unused_record]), + [] = run_test2(Config, Usage2, [warn_unused_record]), %% This a completely different story... %% The linter checks if qlc.hrl hasn't been included @@ -2589,7 +2528,7 @@ otp_5878(Config) when is_list(Config) -> H3 = q([X || X <- [1,2]], []), {H1,H2,H3}. ">>, - ?line {warnings,[{6,erl_lint,{missing_qlc_hrl,1}}, + {warnings,[{6,erl_lint,{missing_qlc_hrl,1}}, {7,erl_lint,{missing_qlc_hrl,2}}, {8,erl_lint,{missing_qlc_hrl,2}}]} = run_test2(Config, QLC2, [warn_unused_record]), @@ -2605,7 +2544,7 @@ otp_5878(Config) when is_list(Config) -> foo(#request{}) -> ok. ">>, - ?line [] = run_test2(Config, UsedByType, [warn_unused_record]), + [] = run_test2(Config, UsedByType, [warn_unused_record]), %% Abstract code generated by OTP 18. Note that the type info for %% record fields has been put in a separate form. @@ -2626,9 +2565,8 @@ otp_5878(Config) when is_list(Config) -> ok. -otp_6885(doc) -> - "OTP-6885. Binary fields in bit syntax matching is now only allowed at the end."; -otp_6885(suite) -> []; +%% OTP-6885. Binary fields in bit syntax matching is now only +%% allowed at the end. otp_6885(Config) when is_list(Config) -> Ts = <<"-module(otp_6885). -export([t/1]). @@ -2655,7 +2593,7 @@ otp_6885(Config) when is_list(Config) -> ok. ">>, - ?line {errors,[{3,erl_lint,unsized_binary_not_at_end}, + {errors,[{3,erl_lint,unsized_binary_not_at_end}, {4,erl_lint,unsized_binary_not_at_end}, {5,erl_lint,unsized_binary_not_at_end}, {10,erl_lint,typed_literal_string}, @@ -2665,9 +2603,7 @@ otp_6885(Config) when is_list(Config) -> []} = run_test2(Config, Ts, []), ok. -otp_10436(doc) -> - "OTP-6885. Warnings for opaque types."; -otp_10436(suite) -> []; +%% OTP-6885. Warnings for opaque types. otp_10436(Config) when is_list(Config) -> Ts = <<"-module(otp_10436). -export_type([t1/0]). @@ -2687,9 +2623,7 @@ otp_10436(Config) when is_list(Config) -> run_test2(Config, Ts2, []), ok. -otp_11254(doc) -> - "OTP-11254. M:F/A could crash the linter."; -otp_11254(suite) -> []; +%% OTP-11254. M:F/A could crash the linter. otp_11254(Config) when is_list(Config) -> Ts = <<"-module(p2). -export([manifest/2]). @@ -2701,9 +2635,7 @@ otp_11254(Config) when is_list(Config) -> run_test2(Config, Ts, []), ok. -otp_11772(doc) -> - "OTP-11772. Reintroduce errors for redefined builtin types."; -otp_11772(suite) -> []; +%% OTP-11772. Reintroduce errors for redefined builtin types. otp_11772(Config) when is_list(Config) -> Ts = <<" -module(newly). @@ -2728,9 +2660,7 @@ otp_11772(Config) when is_list(Config) -> []} = run_test2(Config, Ts, []), ok. -otp_11771(doc) -> - "OTP-11771. Do not allow redefinition of the types arity(_) &c.."; -otp_11771(suite) -> []; +%% OTP-11771. Do not allow redefinition of the types arity(_) &c.. otp_11771(Config) when is_list(Config) -> Ts = <<" -module(newly). @@ -2757,9 +2687,7 @@ otp_11771(Config) when is_list(Config) -> []} = run_test2(Config, Ts, []), ok. -otp_11872(doc) -> - "OTP-11872. The type map() undefined when exported."; -otp_11872(suite) -> []; +%% OTP-11872. The type map() undefined when exported. otp_11872(Config) when is_list(Config) -> Ts = <<" -module(map). @@ -2781,22 +2709,19 @@ otp_11872(Config) when is_list(Config) -> run_test2(Config, Ts, []), ok. -export_all(doc) -> - "OTP-7392. Warning for export_all."; +%% OTP-7392. Warning for export_all. export_all(Config) when is_list(Config) -> Ts = <<"-module(export_all_module). -compile([export_all]). id(I) -> I. ">>, - ?line [] = run_test2(Config, Ts, []), - ?line {warnings,[{2,erl_lint,export_all}]} = + [] = run_test2(Config, Ts, []), + {warnings,[{2,erl_lint,export_all}]} = run_test2(Config, Ts, [warn_export_all]), ok. -bif_clash(doc) -> - "Test warnings for functions that clash with BIFs."; -bif_clash(suite) -> []; +%% Test warnings for functions that clash with BIFs. bif_clash(Config) when is_list(Config) -> Ts = [{clash1, <<"t(X) -> @@ -3063,12 +2988,10 @@ bif_clash(Config) when is_list(Config) -> []} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -behaviour_basic(doc) -> - "Basic tests with one behaviour."; -behaviour_basic(suite) -> []; +%% Basic tests with one behaviour. behaviour_basic(Config) when is_list(Config) -> Ts = [{behaviour1, <<"-behaviour(application). @@ -3102,12 +3025,10 @@ behaviour_basic(Config) when is_list(Config) -> [], {warnings,[{1,erl_lint,{undefined_behaviour_func,{start,2},application}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -behaviour_multiple(doc) -> - "Basic tests with multiple behaviours."; -behaviour_multiple(suite) -> []; +%% Basic tests with multiple behaviours. behaviour_multiple(Config) when is_list(Config) -> Ts = [{behaviour1, <<"-behaviour(application). @@ -3205,12 +3126,10 @@ behaviour_multiple(Config) when is_list(Config) -> erl_lint, {conflicting_behaviours,{init,1},supervisor,1,gen_server}}]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_11861(doc) -> - "OTP-11861. behaviour_info() and -callback."; -otp_11861(suite) -> []; +%% OTP-11861. behaviour_info() and -callback. otp_11861(Conf) when is_list(Conf) -> CallbackFiles = [callback1, callback2, callback3, bad_behaviour1, bad_behaviour2], @@ -3391,12 +3310,12 @@ otp_11861(Conf) when is_list(Conf) -> [], []} ], - ?line [] = run(Conf, Ts), + [] = run(Conf, Ts), true = code:set_path(CodePath), ok. -otp_7550(doc) -> - "Test that the new utf8/utf16/utf32 types do not allow size or unit specifiers."; +%% Test that the new utf8/utf16/utf32 types do not allow size or +%% unit specifiers. otp_7550(Config) when is_list(Config) -> Ts = [{otp_7550, <<"f8(A) -> @@ -3432,12 +3351,11 @@ otp_7550(Config) when is_list(Config) -> {20,erl_lint,utf_bittype_size_or_unit} ], []}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -otp_8051(doc) -> - "Bugfix: -opaque with invalid type."; +%% Bugfix: -opaque with invalid type. otp_8051(Config) when is_list(Config) -> Ts = [{otp_8051, <<"-opaque foo() :: bar(). @@ -3445,12 +3363,10 @@ otp_8051(Config) when is_list(Config) -> ">>, [], {errors,[{1,erl_lint,{undefined_type,{bar,0}}}],[]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -format_warn(doc) -> - "Check that format warnings are generated."; -format_warn(suite) -> []; +%% Check that format warnings are generated. format_warn(Config) when is_list(Config) -> L1 = 14, L2 = 4, @@ -3460,18 +3376,18 @@ format_warn(Config) when is_list(Config) -> ok. format_level(Level, Count, Config) -> - ?line W = get_compilation_result(Config, "format", + W = get_compilation_result(Config, "format", [{warn_format, Level}]), %% Pick out the 'format' warnings. - ?line FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true; + FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true; (_) -> false end, W), - ?line case length(FW) of + case length(FW) of Count -> ok; Other -> - ?t:format("Expected ~w warning(s); got ~w", [Count,Other]), + io:format("Expected ~w warning(s); got ~w", [Count,Other]), fail() end, ok. @@ -3507,7 +3423,7 @@ on_load_successful(Config) when is_list(Config) -> {[]}, %Tuple indicates no 'export_all'. []} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. on_load_failing(Config) when is_list(Config) -> @@ -3555,12 +3471,10 @@ on_load_failing(Config) when is_list(Config) -> {errors, [{1,erl_lint,{undefined_on_load,{non_existing,0}}}],[]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. -too_many_arguments(doc) -> - "Test that too many arguments is not accepted."; -too_many_arguments(suite) -> []; +%% Test that too many arguments is not accepted. too_many_arguments(Config) when is_list(Config) -> Ts = [{too_many_1, <<"f(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_) -> ok.">>, @@ -3569,7 +3483,7 @@ too_many_arguments(Config) when is_list(Config) -> [{1,erl_lint,{too_many_arguments,256}}],[]}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. @@ -3652,9 +3566,7 @@ bin_syntax_errors(Config) -> [] = run(Config, Ts), ok. -predef(doc) -> - "OTP-10342: No longer predefined types: array(), digraph(), and so on"; -predef(suite) -> []; +%% OTP-10342: No longer predefined types: array(), digraph(), and so on. predef(Config) when is_list(Config) -> W = get_compilation_result(Config, "predef", []), [] = W, @@ -3781,8 +3693,7 @@ maps_type(Config) when is_list(Config) -> [] = run(Config, Ts), ok. -otp_11851(doc) -> - "OTP-11851: More atoms can be used as type names + bug fixes."; +%% OTP-11851: More atoms can be used as type names + bug fixes. otp_11851(Config) when is_list(Config) -> Ts = [ {otp_11851_1, @@ -3868,9 +3779,8 @@ otp_11851(Config) when is_list(Config) -> [] = run(Config, Ts), ok. -otp_11879(doc) -> - "OTP-11879: The -spec f/a :: (As) -> B; syntax removed, " - "and is_subtype/2 deprecated"; +%% OTP-11879: The -spec f/a :: (As) -> B; syntax removed, +%% and is_subtype/2 deprecated. otp_11879(_Config) -> Fs = [{attribute,0,file,{"file.erl",0}}, {attribute,0,module,m}, @@ -3891,8 +3801,7 @@ otp_11879(_Config) -> []} = compile:forms(Fs, [return,report]), ok. -otp_13230(doc) -> - "OTP-13230: -deprecated without -module"; +%% OTP-13230: -deprecated without -module. otp_13230(Config) when is_list(Config) -> Abstr = <<"-deprecated([{frutt,0,next_version}]).">>, {errors,[{1,erl_lint,undefined_module}, @@ -3917,7 +3826,7 @@ run(Config, Tests) -> E -> BadL; Bad -> - ?t:format("~nTest ~p failed. Expected~n ~p~n" + io:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Bad]), fail() end @@ -3927,8 +3836,8 @@ run(Config, Tests) -> %% Compiles a test file and returns the list of warnings/errors. get_compilation_result(Conf, Filename, Warnings) -> - ?line DataDir = ?datadir, - ?line File = filename:join(DataDir, Filename), + DataDir = ?datadir, + File = filename:join(DataDir, Filename), {ok,Bin} = file:read_file(File++".erl"), FileS = binary_to_list(Bin), {match,[{Start,Length}|_]} = re:run(FileS, "-module.*\\n"), @@ -3992,5 +3901,4 @@ call_format_error(L) -> L. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). |