From 03ec5bc984264feee907408e720015e2bd9b6108 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Sun, 28 Feb 2016 14:10:25 +0100 Subject: Eliminate 'suite' and 'doc' clauses --- lib/stdlib/test/array_SUITE.erl | 49 +--- lib/stdlib/test/base64_SUITE.erl | 45 +--- lib/stdlib/test/beam_lib_SUITE.erl | 27 +- lib/stdlib/test/binary_module_SUITE.erl | 45 ++-- lib/stdlib/test/c_SUITE.erl | 53 +--- lib/stdlib/test/calendar_SUITE.erl | 62 ++--- lib/stdlib/test/dets_SUITE.erl | 344 +++++------------------- lib/stdlib/test/digraph_SUITE.erl | 20 -- lib/stdlib/test/digraph_utils_SUITE.erl | 15 +- lib/stdlib/test/edlin_expand_SUITE.erl | 15 +- lib/stdlib/test/epp_SUITE.erl | 105 ++------ lib/stdlib/test/erl_anno_SUITE.erl | 38 +-- lib/stdlib/test/erl_eval_SUITE.erl | 121 ++------- lib/stdlib/test/erl_expand_records_SUITE.erl | 49 +--- lib/stdlib/test/erl_internal_SUITE.erl | 4 +- lib/stdlib/test/erl_lint_SUITE.erl | 184 ++++--------- lib/stdlib/test/erl_pp_SUITE.erl | 94 +------ lib/stdlib/test/erl_scan_SUITE.erl | 38 +-- lib/stdlib/test/ets_SUITE.erl | 384 +++++++-------------------- lib/stdlib/test/file_sorter_SUITE.erl | 100 ++----- lib/stdlib/test/filelib_SUITE.erl | 5 +- lib/stdlib/test/fixtable_SUITE.erl | 46 +--- lib/stdlib/test/format_SUITE.erl | 5 +- lib/stdlib/test/gen_event_SUITE.erl | 46 +--- lib/stdlib/test/gen_fsm_SUITE.erl | 12 +- lib/stdlib/test/gen_server_SUITE.erl | 67 +---- lib/stdlib/test/id_transform_SUITE.erl | 2 +- lib/stdlib/test/io_SUITE.erl | 86 ++---- lib/stdlib/test/io_proto_SUITE.erl | 55 +--- lib/stdlib/test/lists_SUITE.erl | 182 ++++--------- lib/stdlib/test/ms_transform_SUITE.erl | 90 ++----- lib/stdlib/test/proc_lib_SUITE.erl | 12 +- lib/stdlib/test/qlc_SUITE.erl | 250 +++++------------ lib/stdlib/test/queue_SUITE.erl | 29 +- lib/stdlib/test/rand_SUITE.erl | 26 +- lib/stdlib/test/random_SUITE.erl | 15 +- lib/stdlib/test/re_SUITE.erl | 79 +++--- lib/stdlib/test/select_SUITE.erl | 10 +- lib/stdlib/test/shell_SUITE.erl | 141 +++------- lib/stdlib/test/slave_SUITE.erl | 4 - lib/stdlib/test/sofs_SUITE.erl | 118 -------- lib/stdlib/test/stdlib_SUITE.erl | 11 +- lib/stdlib/test/string_SUITE.erl | 76 ------ lib/stdlib/test/supervisor_bridge_SUITE.erl | 9 +- lib/stdlib/test/sys_SUITE.erl | 7 - lib/stdlib/test/tar_SUITE.erl | 47 ++-- lib/stdlib/test/timer_simple_SUITE.erl | 81 ++---- lib/stdlib/test/win32reg_SUITE.erl | 3 +- lib/stdlib/test/y2k_SUITE.erl | 46 +--- lib/stdlib/test/zip_SUITE.erl | 72 ++--- 50 files changed, 758 insertions(+), 2666 deletions(-) (limited to 'lib/stdlib/test') diff --git a/lib/stdlib/test/array_SUITE.erl b/lib/stdlib/test/array_SUITE.erl index 0807bb2051..dc949b53cd 100644 --- a/lib/stdlib/test/array_SUITE.erl +++ b/lib/stdlib/test/array_SUITE.erl @@ -146,18 +146,7 @@ t(What) -> io:format("Failed ~p:~p ~p ~p~n ~p~n", [T,Line,_E,_R, erlang:get_stacktrace()]) end - end, expand(What)). - -expand(All) -> - lists:reverse(expand(All,[])). -expand([H|T], Acc) -> - case ?MODULE:H(suite) of - [] -> expand(T,[H|Acc]); - Cs -> - R = expand(Cs, Acc), - expand(T, R) - end; -expand([], Acc) -> Acc. + end, What). %%%%% extract tests @@ -167,8 +156,6 @@ extract_tests() -> try Tests = extract_tests(In,Out,[]), Call = fun(Test) -> - io:format(Out, "~s(doc) -> [];~n", [Test]), - io:format(Out, "~s(suite) -> [];~n", [Test]), io:format(Out, "~s(Config) when is_list(Config) -> ~s_(), ok.~n", [Test, Test]) end, @@ -769,54 +756,20 @@ sparse_foldr_test_() -> set(0,0,new()))))) ]. -new_test(doc) -> []; -new_test(suite) -> []; new_test(Config) when is_list(Config) -> new_test_(), ok. -fix_test(doc) -> []; -fix_test(suite) -> []; fix_test(Config) when is_list(Config) -> fix_test_(), ok. -relax_test(doc) -> []; -relax_test(suite) -> []; relax_test(Config) when is_list(Config) -> relax_test_(), ok. -resize_test(doc) -> []; -resize_test(suite) -> []; resize_test(Config) when is_list(Config) -> resize_test_(), ok. -set_get_test(doc) -> []; -set_get_test(suite) -> []; set_get_test(Config) when is_list(Config) -> set_get_test_(), ok. -to_list_test(doc) -> []; -to_list_test(suite) -> []; to_list_test(Config) when is_list(Config) -> to_list_test_(), ok. -sparse_to_list_test(doc) -> []; -sparse_to_list_test(suite) -> []; sparse_to_list_test(Config) when is_list(Config) -> sparse_to_list_test_(), ok. -from_list_test(doc) -> []; -from_list_test(suite) -> []; from_list_test(Config) when is_list(Config) -> from_list_test_(), ok. -to_orddict_test(doc) -> []; -to_orddict_test(suite) -> []; to_orddict_test(Config) when is_list(Config) -> to_orddict_test_(), ok. -sparse_to_orddict_test(doc) -> []; -sparse_to_orddict_test(suite) -> []; sparse_to_orddict_test(Config) when is_list(Config) -> sparse_to_orddict_test_(), ok. -from_orddict_test(doc) -> []; -from_orddict_test(suite) -> []; from_orddict_test(Config) when is_list(Config) -> from_orddict_test_(), ok. -map_test(doc) -> []; -map_test(suite) -> []; map_test(Config) when is_list(Config) -> map_test_(), ok. -sparse_map_test(doc) -> []; -sparse_map_test(suite) -> []; sparse_map_test(Config) when is_list(Config) -> sparse_map_test_(), ok. -foldl_test(doc) -> []; -foldl_test(suite) -> []; foldl_test(Config) when is_list(Config) -> foldl_test_(), ok. -sparse_foldl_test(doc) -> []; -sparse_foldl_test(suite) -> []; sparse_foldl_test(Config) when is_list(Config) -> sparse_foldl_test_(), ok. -foldr_test(doc) -> []; -foldr_test(suite) -> []; foldr_test(Config) when is_list(Config) -> foldr_test_(), ok. -sparse_foldr_test(doc) -> []; -sparse_foldr_test(suite) -> []; sparse_foldr_test(Config) when is_list(Config) -> sparse_foldr_test_(), ok. diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl index 6c8eb9ca5b..074047c7c5 100644 --- a/lib/stdlib/test/base64_SUITE.erl +++ b/lib/stdlib/test/base64_SUITE.erl @@ -70,10 +70,7 @@ end_per_group(_GroupName, Config) -> %%------------------------------------------------------------------------- -base64_encode(doc) -> - ["Test base64:encode/1."]; -base64_encode(suite) -> - []; +%% Test base64:encode/1. base64_encode(Config) when is_list(Config) -> %% Two pads <<"QWxhZGRpbjpvcGVuIHNlc2FtZQ==">> = @@ -88,10 +85,7 @@ base64_encode(Config) when is_list(Config) -> base64:encode_to_string(<<"0123456789!@#0^&*();:<>,. []{}">>), ok. %%------------------------------------------------------------------------- -base64_decode(doc) -> - ["Test base64:decode/1."]; -base64_decode(suite) -> - []; +%% Test base64:decode/1. base64_decode(Config) when is_list(Config) -> %% Two pads <<"Aladdin:open sesame">> = @@ -115,28 +109,18 @@ base64_decode(Config) when is_list(Config) -> <<"MDEy MzQ1Njc4 \tOSFAIzBeJ \niooKTs6 PD4sLi \r\nBbXXt9">>), ok. %%------------------------------------------------------------------------- -base64_otp_5635(doc) -> - ["OTP-5635: Some data doesn't pass through base64:decode/1 " - "correctly"]; -base64_otp_5635(suite) -> - []; +%% OTP-5635: Some data doesn't pass through base64:decode/1 correctly. base64_otp_5635(Config) when is_list(Config) -> <<"===">> = base64:decode(base64:encode("===")), ok. %%------------------------------------------------------------------------- -base64_otp_6279(doc) -> - ["OTP-6279: Guard needed so that function fails in a correct" - "way for faulty input i.e. function_clause"]; -base64_otp_6279(suite) -> - []; +%% OTP-6279: Guard needed so that function fails in a correct +%% way for faulty input, i.e. function_clause. base64_otp_6279(Config) when is_list(Config) -> {'EXIT',{function_clause, _}} = (catch base64:decode("dGVzda==a")), ok. %%------------------------------------------------------------------------- -big(doc) -> - ["Encode and decode big binaries."]; -big(suite) -> - []; +%% Encode and decode big binaries. big(Config) when is_list(Config) -> Big = make_big_binary(300000), B = base64:encode(Big), @@ -146,10 +130,7 @@ big(Config) when is_list(Config) -> Big = base64:mime_decode(B), ok. %%------------------------------------------------------------------------- -illegal(doc) -> - ["Make sure illegal characters are rejected when decoding."]; -illegal(suite) -> - []; +%% Make sure illegal characters are rejected when decoding. illegal(Config) when is_list(Config) -> {'EXIT',{function_clause, _}} = (catch base64:decode("()")), ok. @@ -157,10 +138,8 @@ illegal(Config) when is_list(Config) -> %% mime_decode and mime_decode_to_string have different implementations %% so test both with the same input separately. Both functions have %% the same implementation for binary/string arguments. -mime_decode(doc) -> - ["Test base64:mime_decode/1."]; -mime_decode(suite) -> - []; +%% +%% Test base64:mime_decode/1. mime_decode(Config) when is_list(Config) -> %% Test correct padding <<"one">> = base64:mime_decode(<<"b25l">>), @@ -200,10 +179,8 @@ mime_decode(Config) when is_list(Config) -> %%------------------------------------------------------------------------- %% Repeat of mime_decode() tests -mime_decode_to_string(doc) -> - ["Test base64:mime_decode_to_string/1."]; -mime_decode_to_string(suite) -> - []; + +%% Test base64:mime_decode_to_string/1. mime_decode_to_string(Config) when is_list(Config) -> %% Test correct padding "one" = base64:mime_decode_to_string(<<"b25l">>), diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl index 54a0dc3259..22624e09a6 100644 --- a/lib/stdlib/test/beam_lib_SUITE.erl +++ b/lib/stdlib/test/beam_lib_SUITE.erl @@ -70,8 +70,7 @@ init_per_testcase(_Case, Config) -> end_per_testcase(_Case, _Config) -> ok. -normal(suite) -> []; -normal(doc) -> ["Read correct beam file"]; +%% Read correct beam file. normal(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, ?line Simple = filename:join(PrivDir, "simple"), @@ -146,8 +145,7 @@ verify_simple([{"Atom", AtomBin}, is_binary(ImpBin), is_binary(ExpBin) -> ok. -error(suite) -> []; -error(doc) -> ["Read invalid beam files"]; +%% Read invalid beam files. error(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, ?line Simple = filename:join(PrivDir, "simple"), @@ -244,8 +242,7 @@ do_error(BeamFile, ACopy) -> ?line verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])). -cmp(suite) -> []; -cmp(doc) -> ["Compare contents of BEAM files and directories"]; +%% Compare contents of BEAM files and directories. cmp(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, @@ -294,8 +291,7 @@ cmp(Conf) when is_list(Conf) -> file:del_dir(Dir2), ok. -cmp_literals(suite) -> []; -cmp_literals(doc) -> ["Compare contents of BEAM files having literals"]; +%% Compare contents of BEAM files having literals. cmp_literals(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, @@ -329,8 +325,7 @@ cmp_literals(Conf) when is_list(Conf) -> file:del_dir(Dir2), ok. -strip(suite) -> []; -strip(doc) -> ["Strip BEAM files"]; +%% Strip BEAM files. strip(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, ?line {SourceD1, BeamFileD1} = make_beam(PrivDir, simple, member), @@ -433,7 +428,7 @@ unwritable(Fname) -> Mode = Info#file_info.mode - 8#00200, file:write_file_info(Fname, Info#file_info{mode = Mode}). -building(doc) -> "Testing building of BEAM files."; +%% Testing building of BEAM files. building(Conf) when is_list(Conf) -> ?line PrivDir = ?privdir, @@ -482,8 +477,7 @@ building(Conf) when is_list(Conf) -> file:del_dir(Dir2), ok. -md5(suite) -> []; -md5(doc) -> ["Compare beam_lib:md5/1 and code:module_md5/1."]; +%% Compare beam_lib:md5/1 and code:module_md5/1. md5(Conf) when is_list(Conf) -> ?line Beams = collect_beams(), io:format("Found ~w beam files", [length(Beams)]), @@ -510,8 +504,7 @@ collect_beams_1([]) -> []. maybe_uncompress(<<"FOR1",_/binary>>=Beam) -> Beam; maybe_uncompress(Beam) -> zlib:gunzip(Beam). -encrypted_abstr(suite) -> []; -encrypted_abstr(doc) -> ["Test encrypted abstract format"]; +%% Test encrypted abstract format. encrypted_abstr(Conf) when is_list(Conf) -> run_if_crypto_works(fun() -> encrypted_abstr_1(Conf) end). @@ -634,9 +627,7 @@ ets_crypto_fun(Key) -> end} end. -encrypted_abstr_file(suite) -> []; -encrypted_abstr_file(doc) -> - ["Test encrypted abstract format with the key in .erlang.crypt"]; +%% Test encrypted abstract format with the key in .erlang.crypt. encrypted_abstr_file(Conf) when is_list(Conf) -> run_if_crypto_works(fun() -> encrypted_abstr_file_1(Conf) end). diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 8fd9d1e0a4..fdd0490003 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -65,8 +65,7 @@ end_per_group(_GroupName, Config) -> -define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))). -badargs(doc) -> - ["Tests various badarg exceptions in the module"]; +%% Test various badarg exceptions in the module. badargs(Config) when is_list(Config) -> ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3:3>>])), ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3>>|<<1,2>>])), @@ -262,8 +261,8 @@ badargs(Config) when is_list(Config) -> binary:at([1,2,4],2)), ok. -longest_common_trap(doc) -> - ["Whitebox test to force special trap conditions in longest_common_{prefix,suffix}"]; +%% Whitebox test to force special trap conditions in +%% longest_common_{prefix,suffix}. longest_common_trap(Config) when is_list(Config) -> ?line erts_debug:set_internal_state(available_internal_state,true), ?line io:format("oldlimit: ~p~n", @@ -357,8 +356,7 @@ subj() -> Subject. -scope_return(doc) -> - ["Test correct return values for scopes (OTP-9701)."]; +%% Test correct return values for scopes (OTP-9701). scope_return(Config) when is_list(Config) -> N=10000, Bin=binary:copy(<<"a">>,N), @@ -371,8 +369,7 @@ scope_loop(Bin,N,M) -> ?line {N,1} = binary:match(Bin,[<<"a">>,<<"b">>],[{scope,{N,1}}]), scope_loop(Bin,N+1,M). -interesting(doc) -> - ["Try some interesting patterns"]; +%% Try some interesting patterns. interesting(Config) when is_list(Config) -> X = do_interesting(binary), X = do_interesting(binref). @@ -686,8 +683,7 @@ do_interesting(Module) -> ?line <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,big)), ok. -encode_decode(doc) -> - ["test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2"]; +%% Test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2. encode_decode(Config) when is_list(Config) -> rand:seed(exsplus, {1271,769940,559934}), ?line ok = encode_decode_loop({1,200},1000), % Need to be long enough @@ -733,13 +729,11 @@ encode_decode_loop(Range, X) -> exit(mismatch) end. -guard(doc) -> - ["Smoke test of the guard BIFs binary_part/2,3"]; +%% Smoke test of the guard BIFs binary_part/2,3. guard(Config) when is_list(Config) -> {comment, "Guard tests are run in emulator test suite"}. -referenced(doc) -> - ["Test refernced_byte_size/1 bif."]; +%% Test referenced_byte_size/1 bif. referenced(Config) when is_list(Config) -> ?line badarg = ?MASK_ERROR(binary:referenced_byte_size([])), ?line badarg = ?MASK_ERROR(binary:referenced_byte_size(apa)), @@ -765,8 +759,7 @@ referenced(Config) when is_list(Config) -> -list_to_bin(doc) -> - ["Test list_to_bin/1 bif"]; +%% Test list_to_bin/1 BIF. list_to_bin(Config) when is_list(Config) -> %% Just some smoke_tests first, then go nuts with random cases ?line badarg = ?MASK_ERROR(binary:list_to_bin({})), @@ -781,8 +774,7 @@ list_to_bin(Config) when is_list(Config) -> ?line random_iolist:run(1000,F1,F2), ok. -copy(doc) -> - ["Test copy/1,2 bif's"]; +%% Test copy/1,2 BIFs. copy(Config) when is_list(Config) -> ?line <<1,2,3>> = binary:copy(<<1,2,3>>), ?line RS = random_string({1,10000}), @@ -849,8 +841,7 @@ random_copy(N) -> exit(mismatch) end. -bin_to_list(doc) -> - ["Test bin_to_list/1,2,3 bif's"]; +%% Test bin_to_list/1,2,3 BIFs. bin_to_list(Config) when is_list(Config) -> %% Just some smoke_tests first, then go nuts with random cases ?line X = <<1,2,3,4,0:1000000,5>>, @@ -913,8 +904,7 @@ random_bin_to_list(N) -> end || {A,B} <- Parts1 ], random_bin_to_list(N-1). -parts(doc) -> - ["Test the part/2,3 bif's"]; +%% Test the part/2,3 BIFs. parts(Config) when is_list(Config) -> %% Some simple smoke tests to begin with ?line Simple = <<1,2,3,4,5,6,7,8>>, @@ -970,8 +960,7 @@ random_parts(X,N) -> Len = rand:uniform((Pos * 12) div 10), [{Pos,Len} | random_parts(X-1,N)]. -random_ref_comp(doc) -> - ["Test pseudorandomly generated cases against reference imlementation"]; +%% Test pseudorandomly generated cases against reference implementation. random_ref_comp(Config) when is_list(Config) -> put(success_counter,0), rand:seed(exsplus, {1271,769940,559934}), @@ -1000,8 +989,8 @@ random_ref_comp(Config) when is_list(Config) -> erts_debug:set_internal_state(available_internal_state,false), ok. -random_ref_sr_comp(doc) -> - ["Test pseudorandomly generated cases against reference imlementation of split and replace"]; +%% Test pseudorandomly generated cases against reference implementation +%% of split and replace. random_ref_sr_comp(Config) when is_list(Config) -> put(success_counter,0), rand:seed(exsplus, {1271,769940,559934}), @@ -1018,8 +1007,8 @@ random_ref_sr_comp(Config) when is_list(Config) -> io:format("Number of successes: ~p~n",[get(success_counter)]), ok. -random_ref_fla_comp(doc) -> - ["Test pseudorandomly generated cases against reference imlementation of split and replace"]; +%% Test pseudorandomly generated cases against reference implementation +%% of split and replace. random_ref_fla_comp(Config) when is_list(Config) -> ?line put(success_counter,0), rand:seed(exsplus, {1271,769940,559934}), diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl index 47dd95f86b..395372ebf0 100644 --- a/lib/stdlib/test/c_SUITE.erl +++ b/lib/stdlib/test/c_SUITE.erl @@ -50,20 +50,14 @@ end_per_group(_GroupName, Config) -> %%% Write output to a directory other than current directory: -c_1(doc) -> - ["Checks that c:c works also with option 'outdir' [ticket OTP-1209]."]; -c_1(suite) -> - []; +%% OTP-1209: Check that c:c/2 works also with option 'outdir'. c_1(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m.erl"), ?line W = ?config(priv_dir, Config), ?line Result = c(R,[{outdir,W}]), ?line {ok, m} = Result. -c_2(doc) -> - ["Checks that c:c works also with option 'outdir' [ticket OTP-1209]."]; -c_2(suite) -> - []; +%% OTP-1209: Check that c:c/2 works also with option 'outdir'. c_2(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m"), ?line W = ?config(priv_dir, Config), @@ -74,11 +68,8 @@ c_2(Config) when is_list(Config) -> %%% Put results in current directory (or rather, change current dir %%% to the output dir): -c_3(doc) -> - ["Checks that c:c works also with option 'outdir' (same as current" - "directory). [ticket OTP-1209]."]; -c_3(suite) -> - []; +%% OTP-1209: Check that c:c/2 works also with option 'outdir' +%% (same as current directory). c_3(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m.erl"), ?line W = ?config(priv_dir, Config), @@ -86,11 +77,8 @@ c_3(Config) when is_list(Config) -> ?line Result = c(R,[{outdir,W}]), ?line {ok, m} = Result. -c_4(doc) -> - ["Checks that c:c works also with option 'outdir' (same as current" - "directory). [ticket OTP-1209]."]; -c_4(suite) -> - []; +%% OTP-1209: Check that c:c/2 works also with option 'outdir' +%% (same as current directory). c_4(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m"), ?line W = ?config(priv_dir, Config), @@ -100,20 +88,14 @@ c_4(Config) when is_list(Config) -> %%% Write output to a directory other than current directory: -nc_1(doc) -> - ["Checks that c:nc works also with option 'outdir'."]; -nc_1(suite) -> - []; +%% Check that c:nc/2 works also with option 'outdir'. nc_1(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m.erl"), ?line W = ?config(priv_dir, Config), ?line Result = nc(R,[{outdir,W}]), ?line {ok, m} = Result. -nc_2(doc) -> - ["Checks that c:nc works also with option 'outdir'."]; -nc_2(suite) -> - []; +%% Check that c:nc/2 works also with option 'outdir'. nc_2(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m"), ?line W = ?config(priv_dir, Config), @@ -124,11 +106,8 @@ nc_2(Config) when is_list(Config) -> %%% Put results in current directory (or rather, change current dir %%% to the output dir): -nc_3(doc) -> - ["Checks that c:nc works also with option 'outdir' (same as current" - "directory)."]; -nc_3(suite) -> - []; +%% Check that c:nc/2 works also with option 'outdir' +%% (same as current directory). nc_3(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m.erl"), ?line W = ?config(priv_dir, Config), @@ -136,11 +115,8 @@ nc_3(Config) when is_list(Config) -> ?line Result = nc(R,[{outdir,W}]), ?line {ok, m} = Result. -nc_4(doc) -> - ["Checks that c:nc works also with option 'outdir' (same as current" - "directory)."]; -nc_4(suite) -> - []; +%% Check that c:nc/2 works also with option 'outdir' +%% (same as current directory). nc_4(Config) when is_list(Config) -> ?line R = filename:join(?config(data_dir, Config), "m"), ?line W = ?config(priv_dir, Config), @@ -155,10 +131,7 @@ ls(Config) when is_list(Config) -> ok = c:ls(File), ok = c:ls("no_such_file"). -memory(doc) -> - ["Checks that c:memory/[0,1] returns consistent results."]; -memory(suite) -> - []; +%% Check that c:memory/[0,1] returns consistent results. memory(Config) when is_list(Config) -> try ?line ML = c:memory(), diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl index bddc3a4821..d3e56fc314 100644 --- a/lib/stdlib/test/calendar_SUITE.erl +++ b/lib/stdlib/test/calendar_SUITE.erl @@ -57,24 +57,18 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -gregorian_days(doc) -> - "Tests that date_to_gregorian_days and gregorian_days_to_date " - "are each others inverses from ?START_YEAR-01-01 up to ?END_YEAR-01-01. " - "At the same time valid_date is tested."; -gregorian_days(suite) -> - []; +%% Tests that date_to_gregorian_days and gregorian_days_to_date +%% are each others inverses from ?START_YEAR-01-01 up to ?END_YEAR-01-01. +%% At the same time valid_date is tested. gregorian_days(Config) when is_list(Config) -> ?line Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}), ?line MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}), ?line check_gregorian_days(Days, MaxDays). -gregorian_seconds(doc) -> - "Tests that datetime_to_gregorian_seconds and " - "gregorian_seconds_to_date are each others inverses for a sampled " - "number of seconds from ?START_YEAR-01-01 up to ?END_YEAR-01-01: We check " - "every 2 days + 1 second."; -gregorian_seconds(suite) -> - []; +%% Tests that datetime_to_gregorian_seconds and +%% gregorian_seconds_to_date are each others inverses for a sampled +%% number of seconds from ?START_YEAR-01-01 up to ?END_YEAR-01-01: We check +%% every 2 days + 1 second. gregorian_seconds(Config) when is_list(Config) -> ?line Secs = calendar:datetime_to_gregorian_seconds({{?START_YEAR, 1, 1}, {0, 0, 0}}), @@ -82,44 +76,29 @@ gregorian_seconds(Config) when is_list(Config) -> {0, 0, 0}}), ?line check_gregorian_seconds(Secs, MaxSecs). -day_of_the_week(doc) -> - "Tests that day_of_the_week reports correctly the day of the week from " - "year ?START_YEAR up to ?END_YEAR."; -day_of_the_week(suite) -> - []; +%% Tests that day_of_the_week reports correctly the day of the week from +%% year ?START_YEAR up to ?END_YEAR. day_of_the_week(Config) when is_list(Config) -> ?line Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}), ?line MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}), ?line DayNumber = calendar:day_of_the_week({?START_YEAR, 1, 1}), ?line check_day_of_the_week(Days, MaxDays, DayNumber). -day_of_the_week_calibrate(doc) -> - "Tests that day_of_the_week for 1997-11-11 is Tuesday (2)"; -day_of_the_week_calibrate(suite) -> - []; +%% Tests that day_of_the_week for 1997-11-11 is Tuesday (2). day_of_the_week_calibrate(Config) when is_list(Config) -> ?line 2 = calendar:day_of_the_week({1997, 11, 11}). -leap_years(doc) -> - "Tests that is_leap_year reports correctly the leap years from " - "year ?START_YEAR up to ?END_YEAR."; -leap_years(suite) -> - []; +%% Tests that is_leap_year reports correctly the leap years from +%% year ?START_YEAR up to ?END_YEAR. leap_years(Config) when is_list(Config) -> ?line check_leap_years(?START_YEAR, ?END_YEAR). -last_day_of_the_month(doc) -> - "Tests that last_day_of_the_month reports correctly from " - "year ?START_YEAR up to ?END_YEAR."; -last_day_of_the_month(suite) -> - []; +%% Tests that last_day_of_the_month reports correctly from +%% year ?START_YEAR up to ?END_YEAR. last_day_of_the_month(Config) when is_list(Config) -> ?line check_last_day_of_the_month({?START_YEAR, 1}, {?END_YEAR, 1}). -local_time_to_universal_time_dst(doc) -> - "Tests local_time_to_universal_time_dst for MET"; -local_time_to_universal_time_dst(suite) -> - []; +%% Tests local_time_to_universal_time_dst for MET. local_time_to_universal_time_dst(Config) when is_list(Config) -> case os:type() of {unix,_} -> @@ -171,13 +150,10 @@ local_time_to_universal_time_dst_x(Config) when is_list(Config) -> {comment,"Bug in mktime() in this OS"} end. -iso_week_number(doc) -> - "Test the iso week number calculation for all three possibilities." - " When the date falls on the last week of the previous year," - " when the date falls on a week within the given year and finally," - " when the date falls on the first week of the next year."; -iso_week_number(suite) -> - []; +%% Test the iso week number calculation for all three possibilities: +%% When the date falls on the last week of the previous year, +%% when the date falls on a week within the given year and finally, +%% when the date falls on the first week of the next year. iso_week_number(Config) when is_list(Config) -> ?line check_iso_week_number(). diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index d899022bab..045879ee32 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -129,10 +129,7 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -newly_started(doc) -> - ["OTP-3621"]; -newly_started(suite) -> - []; +%% OTP-3621 newly_started(Config) when is_list(Config) -> true = is_alive(), {ok, Node} = test_server:start_node(slave1, slave, []), @@ -140,17 +137,11 @@ newly_started(Config) when is_list(Config) -> test_server:stop_node(Node), ok. -basic_v8(doc) -> - ["Basic test case."]; -basic_v8(suite) -> - []; +%% Basic test case. basic_v8(Config) when is_list(Config) -> basic(Config, 8). -basic_v9(doc) -> - ["Basic test case."]; -basic_v9(suite) -> - []; +%% Basic test case. basic_v9(Config) when is_list(Config) -> basic(Config, 9). @@ -183,17 +174,9 @@ basic(Config, Version) -> ok. -open_v8(doc) -> - []; -open_v8(suite) -> - []; open_v8(Config) when is_list(Config) -> open(Config, 8). -open_v9(doc) -> - []; -open_v9(suite) -> - []; open_v9(Config) when is_list(Config) -> open(Config, 9). @@ -282,17 +265,11 @@ bad(_Tab, _Item) -> ?format("Can't find item ~p in ~p ~n", [_Item, _Tab]), exit(badtab). -sets_v8(doc) -> - ["Performs traversal and match testing on set type dets tables."]; -sets_v8(suite) -> - []; +%% Perform traversal and match testing on set type dets tables. sets_v8(Config) when is_list(Config) -> sets(Config, 8). -sets_v9(doc) -> - ["Performs traversal and match testing on set type dets tables."]; -sets_v9(suite) -> - []; +%% Perform traversal and match testing on set type dets tables. sets_v9(Config) when is_list(Config) -> sets(Config, 9). @@ -324,17 +301,11 @@ sets(Config, Version) -> check_pps(P0), ok. -bags_v8(doc) -> - ["Performs traversal and match testing on bag type dets tables."]; -bags_v8(suite) -> - []; +%% Perform traversal and match testing on bag type dets tables. bags_v8(Config) when is_list(Config) -> bags(Config, 8). -bags_v9(doc) -> - ["Performs traversal and match testing on bag type dets tables."]; -bags_v9(suite) -> - []; +%% Perform traversal and match testing on bag type dets tables. bags_v9(Config) when is_list(Config) -> bags(Config, 9). @@ -364,17 +335,11 @@ bags(Config, Version) -> ok. -duplicate_bags_v8(doc) -> - ["Performs traversal and match testing on duplicate_bag type dets tables."]; -duplicate_bags_v8(suite) -> - []; +%% Perform traversal and match testing on duplicate_bag type dets tables. duplicate_bags_v8(Config) when is_list(Config) -> duplicate_bags(Config, 8). -duplicate_bags_v9(doc) -> - ["Performs traversal and match testing on duplicate_bag type dets tables."]; -duplicate_bags_v9(suite) -> - []; +%% Perform traversal and match testing on duplicate_bag type dets tables. duplicate_bags_v9(Config) when is_list(Config) -> duplicate_bags(Config, 9). @@ -404,17 +369,9 @@ duplicate_bags(Config, Version) when is_list(Config) -> ok. -access_v8(doc) -> - []; -access_v8(suite) -> - []; access_v8(Config) when is_list(Config) -> access(Config, 8). -access_v9(doc) -> - []; -access_v9(suite) -> - []; access_v9(Config) when is_list(Config) -> access(Config, 9). @@ -447,10 +404,7 @@ access(Config, Version) -> ok. -dirty_mark(doc) -> - ["Test that the table is not marked dirty if not written"]; -dirty_mark(suite) -> - []; +%% Test that the table is not marked dirty if not written. dirty_mark(Config) when is_list(Config) -> true = is_alive(), Tab = dets_dirty_mark_test, @@ -499,10 +453,7 @@ dirty_mark(Config) when is_list(Config) -> check_pps(P0), ok. -dirty_mark2(doc) -> - ["Test that the table is flushed when auto_save is in effect"]; -dirty_mark2(suite) -> - []; +%% Test that the table is flushed when auto_save is in effect. dirty_mark2(Config) when is_list(Config) -> true = is_alive(), Tab = dets_dirty_mark2_test, @@ -570,17 +521,11 @@ dets_dirty_loop() -> end. -bag_next_v8(suite) -> - []; -bag_next_v8(doc) -> - ["Check that bags and next work as expected."]; +%% Check that bags and next work as expected. bag_next_v8(Config) when is_list(Config) -> bag_next(Config, 8). -bag_next_v9(suite) -> - []; -bag_next_v9(doc) -> - ["Check that bags and next work as expected."]; +%% Check that bags and next work as expected. bag_next_v9(Config) when is_list(Config) -> Tab = dets_bag_next_test, FName = filename(Tab, Config), @@ -633,17 +578,9 @@ bag_next(Config, Version) -> check_pps(P0), ok. -oldbugs_v8(doc) -> - []; -oldbugs_v8(suite) -> - []; oldbugs_v8(Config) when is_list(Config) -> oldbugs(Config, 8). -oldbugs_v9(doc) -> - []; -oldbugs_v9(suite) -> - []; oldbugs_v9(Config) when is_list(Config) -> oldbugs(Config, 9). @@ -661,9 +598,7 @@ oldbugs(Config, Version) -> check_pps(P0), ok. -unsafe_assumptions(suite) -> []; -unsafe_assumptions(doc) -> - "Tests that shrinking an object and then expanding it works."; +%% Test that shrinking an object and then expanding it works. unsafe_assumptions(Config) when is_list(Config) -> FName = filename(dets_suite_unsafe_assumptions_test, Config), file:delete(FName), @@ -692,17 +627,13 @@ unsafe_assumptions(Config) when is_list(Config) -> check_pps(P0), ok. -truncated_segment_array_v8(suite) -> []; -truncated_segment_array_v8(doc) -> - "Tests that a file where the segment array has been truncated " - "is possible to repair."; +%% Test that a file where the segment array has been truncated +%% is possible to repair. truncated_segment_array_v8(Config) when is_list(Config) -> trunc_seg_array(Config, 8). -truncated_segment_array_v9(suite) -> []; -truncated_segment_array_v9(doc) -> - "Tests that a file where the segment array has been truncated " - "is possible to repair."; +%% Test that a file where the segment array has been truncated +%% is possible to repair. truncated_segment_array_v9(Config) when is_list(Config) -> trunc_seg_array(Config, 9). @@ -728,17 +659,11 @@ trunc_seg_array(Config, V) -> check_pps(P0), ok. -open_file_v8(doc) -> - ["open_file/1 test case."]; -open_file_v8(suite) -> - []; +%% Test open_file/1. open_file_v8(Config) when is_list(Config) -> open_1(Config, 8). -open_file_v9(doc) -> - ["open_file/1 test case."]; -open_file_v9(suite) -> - []; +%% Test open_file/1. open_file_v9(Config) when is_list(Config) -> T = open_v9, Fname = filename(T, Config), @@ -796,17 +721,11 @@ open_1(Config, V) -> check_pps(P0), ok. -init_table_v8(doc) -> - ["initialize_table/2 and from_ets/2 test case."]; -init_table_v8(suite) -> - []; +%% Test initialize_table/2 and from_ets/2. init_table_v8(Config) when is_list(Config) -> init_table(Config, 8). -init_table_v9(doc) -> - ["initialize_table/2 and from_ets/2 test case."]; -init_table_v9(suite) -> - []; +%% Test initialize_table/2 and from_ets/2. init_table_v9(Config) when is_list(Config) -> %% Objects are returned in "time order". T = init_table_v9, @@ -1269,17 +1188,11 @@ items(I, N, C, L) when I =:= N; C =:= 0 -> items(I, N, C, L) -> items(I+1, N, C-1, [{I, item(I)} | L]). -repair_v8(doc) -> - ["open_file and repair."]; -repair_v8(suite) -> - []; +%% Test open_file and repair. repair_v8(Config) when is_list(Config) -> repair(Config, 8). -repair_v9(doc) -> - ["open_file and repair."]; -repair_v9(suite) -> - []; +%% Test open_file and repair. repair_v9(Config) when is_list(Config) -> %% Convert from format 9 to format 8. T = convert_98, @@ -1616,11 +1529,9 @@ repair(Config, V) -> check_pps(P0), ok. -hash_v8b_v8c(doc) -> - ["Test the use of different hashing algorithms in v8b and v8c of the " - "Dets file format."]; -hash_v8b_v8c(suite) -> - []; + +%% Test the use of different hashing algorithms in v8b and v8c of the +%% Dets file format. hash_v8b_v8c(Config) when is_list(Config) -> Source = filename:join(?datadir(Config), "dets_test_v8b.dets"), @@ -1695,10 +1606,7 @@ hash_v8b_v8c(Config) when is_list(Config) -> check_pps(P0), {comment, Mess}. -phash(doc) -> - ["Test version 9(b) with erlang:phash/2 as hash function."]; -phash(suite) -> - []; +%% Test version 9(b) with erlang:phash/2 as hash function. phash(Config) when is_list(Config) -> T = phash, Phash_v9bS = filename:join(?datadir(Config), "version_9b_phash.dat"), @@ -1756,17 +1664,11 @@ phash(Config) when is_list(Config) -> file:delete(Fname), ok. -fold_v8(doc) -> - ["foldl, foldr, to_ets"]; -fold_v8(suite) -> - []; +%% Test foldl, foldr, to_ets. fold_v8(Config) when is_list(Config) -> fold(Config, 8). -fold_v9(doc) -> - ["foldl, foldr, to_ets"]; -fold_v9(suite) -> - []; +%% Test foldl, foldr, to_ets. fold_v9(Config) when is_list(Config) -> fold(Config, 9). @@ -1835,17 +1737,11 @@ fold(Config, Version) -> check_pps(P0), ok. -fixtable_v8(doc) -> - ["Add objects to a fixed table."]; -fixtable_v8(suite) -> - []; +%% Add objects to a fixed table. fixtable_v8(Config) when is_list(Config) -> fixtable(Config, 8). -fixtable_v9(doc) -> - ["Add objects to a fixed table."]; -fixtable_v9(suite) -> - []; +%% Add objects to a fixed table. fixtable_v9(Config) when is_list(Config) -> fixtable(Config, 9). @@ -1935,17 +1831,11 @@ fixtable(Config, Version) when is_list(Config) -> check_pps(P0), ok. -match_v8(doc) -> - ["Matching objects of a fixed table."]; -match_v8(suite) -> - []; +%% Matching objects of a fixed table. match_v8(Config) when is_list(Config) -> match(Config, 8). -match_v9(doc) -> - ["Matching objects of a fixed table."]; -match_v9(suite) -> - []; +%% Matching objects of a fixed table. match_v9(Config) when is_list(Config) -> match(Config, 9). @@ -2117,17 +2007,11 @@ match(Config, Version) -> check_pps(P0), ok. -select_v8(doc) -> - ["Selecting objects of a fixed table."]; -select_v8(suite) -> - []; +%% Selecting objects of a fixed table. select_v8(Config) when is_list(Config) -> select(Config, 8). -select_v9(doc) -> - ["Selecting objects of a fixed table."]; -select_v9(suite) -> - []; +%% Selecting objects of a fixed table. select_v9(Config) when is_list(Config) -> select(Config, 9). @@ -2231,10 +2115,7 @@ select(Config, Version) -> check_pps(P0), ok. -update_counter(doc) -> - ["Test update_counter/1."]; -update_counter(suite) -> - []; +%% Test update_counter/1. update_counter(Config) when is_list(Config) -> T = update_counter, Fname = filename(select, Config), @@ -2268,10 +2149,7 @@ update_counter(Config) when is_list(Config) -> ok. -badarg(doc) -> - ["Call some functions with bad arguments."]; -badarg(suite) -> - []; +%% Call some functions with bad arguments. badarg(Config) when is_list(Config) -> T = badarg, Fname = filename(select, Config), @@ -2403,17 +2281,11 @@ badarg(Config) when is_list(Config) -> check_pps(P0), ok. -cache_sets_v8(doc) -> - ["Test the write cache for sets."]; -cache_sets_v8(suite) -> - []; +%% Test the write cache for sets. cache_sets_v8(Config) when is_list(Config) -> cache_sets(Config, 8). -cache_sets_v9(doc) -> - ["Test the write cache for sets."]; -cache_sets_v9(suite) -> - []; +%% Test the write cache for sets. cache_sets_v9(Config) when is_list(Config) -> cache_sets(Config, 9). @@ -2558,17 +2430,11 @@ cache_sets(Config, DelayedWrite, Extra, Sz, Version) -> check_pps(P0), ok. -cache_bags_v8(doc) -> - ["Test the write cache for bags."]; -cache_bags_v8(suite) -> - []; +%% Test the write cache for bags. cache_bags_v8(Config) when is_list(Config) -> cache_bags(Config, 8). -cache_bags_v9(doc) -> - ["Test the write cache for bags."]; -cache_bags_v9(suite) -> - []; +%% Test the write cache for bags. cache_bags_v9(Config) when is_list(Config) -> cache_bags(Config, 9). @@ -2740,17 +2606,11 @@ cache_bags(Config, DelayedWrite, Extra, Sz, Version) -> check_pps(P0), ok. -cache_duplicate_bags_v8(doc) -> - ["Test the write cache for duplicate bags."]; -cache_duplicate_bags_v8(suite) -> - []; +%% Test the write cache for duplicate bags. cache_duplicate_bags_v8(Config) when is_list(Config) -> cache_duplicate_bags(Config, 8). -cache_duplicate_bags_v9(doc) -> - ["Test the write cache for duplicate bags."]; -cache_duplicate_bags_v9(suite) -> - []; +%% Test the write cache for duplicate bags. cache_duplicate_bags_v9(Config) when is_list(Config) -> cache_duplicate_bags(Config, 9). @@ -2935,10 +2795,7 @@ symdiff(L1, L2) -> sofs:symmetric_partition(sofs:set(L1), sofs:set(L2)), {sofs:to_external(X), sofs:to_external(Y)}. -otp_4208(doc) -> - ["Read only table and traversal caused crash."]; -otp_4208(suite) -> - []; +%% Test read-only tables and traversal caused crashes. otp_4208(Config) when is_list(Config) -> Tab = otp_4208, FName = filename(Tab, Config), @@ -2957,10 +2814,7 @@ otp_4208(Config) when is_list(Config) -> ok. -otp_4989(doc) -> - ["Read only table and growth."]; -otp_4989(suite) -> - []; +%% Test read-only tables and growth. otp_4989(Config) when is_list(Config) -> Tab = otp_4989, FName = filename(Tab, Config), @@ -2988,10 +2842,7 @@ ets_init(Tab, N) -> ets:insert(Tab, {N,N}), ets_init(Tab, N - 1). -otp_8898(doc) -> - ["OTP-8898. Truncated Dets file."]; -otp_8898(suite) -> - []; +%% OTP-8898. Truncated Dets file. otp_8898(Config) when is_list(Config) -> Tab = otp_8898, FName = filename(Tab, Config), @@ -3011,10 +2862,7 @@ otp_8898(Config) when is_list(Config) -> ok. -otp_8899(doc) -> - ["OTP-8899. Several clients. Updated Head was ignored."]; -otp_8899(suite) -> - []; +%% OTP-8899. Several clients. Updated Head was ignored. otp_8899(Config) when is_list(Config) -> Tab = many_clients, FName = filename(Tab, Config), @@ -3039,10 +2887,7 @@ otp_8899(Config) when is_list(Config) -> ok. -many_clients(doc) -> - ["Several clients accessing a table simultaneously."]; -many_clients(suite) -> - []; +%% Test several clients accessing a table simultaneously. many_clients(Config) when is_list(Config) -> Tab = many_clients, FName = filename(Tab, Config), @@ -3228,10 +3073,7 @@ eval([{info,Tag,Expected} | L], Tab) -> eval(Else, _Tab) -> {error, {bad_request,Else}}. -otp_4906(doc) -> - ["More than 128k keys caused crash."]; -otp_4906(suite) -> - []; +%% More than 128k keys caused crash. otp_4906(Config) when is_list(Config) -> N = 256*512 + 400, Tab = otp_4906, @@ -3275,10 +3117,7 @@ ins_small(T, I, N) -> ok = dets:insert(T, {I}), ins_small(T, I+1, N). -otp_5402(doc) -> - ["Unwritable ramfile caused krasch."]; -otp_5402(suite) -> - []; +%% Unwritable ramfile caused crash. otp_5402(Config) when is_list(Config) -> Tab = otp_5402, File = filename:join(["cannot", "write", "this", "file"]), @@ -3305,10 +3144,7 @@ otp_5402(Config) when is_list(Config) -> {error,{file_error,_,_}} = dets:close(T), ok. -simultaneous_open(doc) -> - ["Several clients open and close tables simultaneously."]; -simultaneous_open(suite) -> - []; +%% Several clients open and close tables simultaneously. simultaneous_open(Config) -> Tab = sim_open, File = filename(Tab, Config), @@ -3527,10 +3363,7 @@ create_opened_log(File) -> crash(File, ?CLOSED_PROPERLY_POS+3, ?NOT_PROPERLY_CLOSED), ok. -insert_new(doc) -> - ["OTP-5075. insert_new/2"]; -insert_new(suite) -> - []; +%% OTP-5075. insert_new/2 insert_new(Config) -> Tab = insert_new, File = filename(Tab, Config), @@ -3558,10 +3391,7 @@ insert_new(Config) -> file:delete(File), ok. -repair_continuation(doc) -> - ["OTP-5126. repair_continuation/2"]; -repair_continuation(suite) -> - []; +%% OTP-5126. repair_continuation/2 repair_continuation(Config) -> Tab = repair_continuation_table, Fname = filename(repair_cont, Config), @@ -3584,10 +3414,7 @@ repair_continuation(Config) -> file:delete(Fname), ok. -otp_5487(doc) -> - ["OTP-5487. Growth of read-only table (again)."]; -otp_5487(suite) -> - []; +%% OTP-5487. Growth of read-only table (again). otp_5487(Config) -> otp_5487(Config, 9), otp_5487(Config, 8), @@ -3610,10 +3437,7 @@ otp_5487(Config, Version) -> ets:delete(Ets), file:delete(Fname). -otp_6206(doc) -> - ["OTP-6206. Badly formed free lists."]; -otp_6206(suite) -> - []; +%% OTP-6206. Badly formed free lists. otp_6206(Config) -> Tab = otp_6206, File = filename(Tab, Config), @@ -3632,10 +3456,7 @@ otp_6206(Config) -> file:delete(File), ok. -otp_6359(doc) -> - ["OTP-6359. select and match never return the empty list."]; -otp_6359(suite) -> - []; +%% OTP-6359. select and match never return the empty list. otp_6359(Config) -> Tab = otp_6359, File = filename(Tab, Config), @@ -3648,10 +3469,7 @@ otp_6359(Config) -> file:delete(File), ok. -otp_4738(doc) -> - ["OTP-4738. ==/2 and =:=/2."]; -otp_4738(suite) -> - []; +%% OTP-4738. ==/2 and =:=/2. otp_4738(Config) -> %% Version 8 has not been corrected. %% (The constant -12857447 is for version 9 only.) @@ -3803,10 +3621,7 @@ otp_4738_set(Version, Config) -> file:delete(File), ok. -otp_7146(doc) -> - ["OTP-7146. Bugfix: missing test when re-hashing."]; -otp_7146(suite) -> - []; +%% OTP-7146. Bugfix: missing test when re-hashing. otp_7146(Config) -> Tab = otp_7146, File = filename(Tab, Config), @@ -3829,10 +3644,7 @@ write_dets(Tab, N, Max) -> ok = dets:insert(Tab,{ N, {entry,N}}), write_dets(Tab, N+1, Max). -otp_8070(doc) -> - ["OTP-8070. Duplicated objects with insert_new() and duplicate_bag."]; -otp_8070(suite) -> - []; +%% OTP-8070. Duplicated objects with insert_new() and duplicate_bag. otp_8070(Config) when is_list(Config) -> Tab = otp_8070, File = filename(Tab, Config), @@ -3845,10 +3657,7 @@ otp_8070(Config) when is_list(Config) -> file:delete(File), ok. -otp_8856(doc) -> - ["OTP-8856. insert_new() bug."]; -otp_8856(suite) -> - []; +%% OTP-8856. insert_new() bug. otp_8856(Config) when is_list(Config) -> Tab = otp_8856, File = filename(Tab, Config), @@ -3870,10 +3679,7 @@ otp_8856(Config) when is_list(Config) -> file:delete(File), ok. -otp_8903(doc) -> - ["OTP-8903. bchunk/match/select bug."]; -otp_8903(suite) -> - []; +%% OTP-8903. bchunk/match/select bug. otp_8903(Config) when is_list(Config) -> Tab = otp_8903, File = filename(Tab, Config), @@ -3893,10 +3699,7 @@ otp_8903(Config) when is_list(Config) -> file:delete(File), ok. -otp_8923(doc) -> - ["OTP-8923. rehash due to lookup after initialization."]; -otp_8923(suite) -> - []; +%% OTP-8923. rehash due to lookup after initialization. otp_8923(Config) when is_list(Config) -> Tab = otp_8923, File = filename(Tab, Config), @@ -3926,10 +3729,7 @@ otp_8923(Config) when is_list(Config) -> file:delete(File), ok. -otp_9282(doc) -> - ["OTP-9282. The name of a table can be an arbitrary term"]; -otp_9282(suite) -> - []; +%% OTP-9282. The name of a table can be an arbitrary term. otp_9282(Config) when is_list(Config) -> some_calls(make_ref(), Config), some_calls({a,typical,name}, Config), @@ -3949,10 +3749,7 @@ some_calls(Tab, Config) -> file:delete(File). -otp_11245(doc) -> - ["OTP-11245. Tables remained fixed after traversal"]; -otp_11245(suite) -> - []; +%% OTP-11245. Tables remained fixed after traversal. otp_11245(Config) when is_list(Config) -> Tab = otp_11245, File = filename(Tab, Config), @@ -3971,10 +3768,7 @@ otp_11245(Config) when is_list(Config) -> file:delete(File), ok. -otp_11709(doc) -> - ["OTP-11709. Bugfixes."]; -otp_11709(suite) -> - []; +% OTP-11709. Bugfixes. otp_11709(Config) when is_list(Config) -> Short = <<"foo">>, Long = <<"a sufficiently long text">>, @@ -4013,8 +3807,7 @@ otp_11709(Config) when is_list(Config) -> _ = file:delete(File), ok. -otp_13229(doc) -> - ["OTP-13229. open_file() exits with badarg when given binary file name."]; +%% OTP-13229. open_file() exits with badarg when given binary file name. otp_13229(_Config) -> F = <<"binfile.tab">>, try dets:open_file(name, [{file, F}]) of @@ -4025,8 +3818,7 @@ otp_13229(_Config) -> ok end. -otp_13260(doc) -> - ["OTP-13260. Race when opening a table."]; +%% OTP-13260. Race when opening a table. otp_13260(Config) -> [ok] = lists:usort([otp_13260_1(Config) || _ <- lists:seq(1, 3)]), ok. diff --git a/lib/stdlib/test/digraph_SUITE.erl b/lib/stdlib/test/digraph_SUITE.erl index 97561196d8..d632473ae5 100644 --- a/lib/stdlib/test/digraph_SUITE.erl +++ b/lib/stdlib/test/digraph_SUITE.erl @@ -62,8 +62,6 @@ end_per_group(_GroupName, Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -opts(doc) -> []; -opts(suite) -> []; opts(Config) when is_list(Config) -> %% OTP-5985: the 'public' option has been removed ?line {'EXIT',{badarg,_}} = (catch digraph:new([public])), @@ -89,8 +87,6 @@ opts(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -degree(doc) -> []; -degree(suite) -> []; degree(Config) when is_list(Config) -> ?line G = build_graph([], [{x1,[]}, {x2,[x1]}, {x3,[x1,x2]}, {x4,[x1,x2,x3]}, {x5,[x1,x2,x3,x4]}]), @@ -124,8 +120,6 @@ degree(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -path(doc) -> []; -path(suite) -> []; path(Config) when is_list(Config) -> ?line G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]}, {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7]}]), @@ -148,8 +142,6 @@ path(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -cycle(doc) -> []; -cycle(suite) -> []; cycle(Config) when is_list(Config) -> ?line G = build_graph([], [{x1,[x2,x3]}, {x2,[x4]}, {x3,[x4]}, {x4,[x5,x6]}, {x5,[x7]}, {x6,[x7,x8]}, @@ -171,8 +163,6 @@ cycle(Config) when is_list(Config) -> -vertices(doc) -> []; -vertices(suite) -> []; vertices(Config) when is_list(Config) -> ?line G = build_graph([], [{x,[]}, {y,[]}]), ?line [] = check(digraph:vertices(G), [x,y]), @@ -181,8 +171,6 @@ vertices(Config) when is_list(Config) -> ?line digraph:delete(G), ok. -edges(doc) -> []; -edges(suite) -> []; edges(Config) when is_list(Config) -> ?line G = build_graph([], [{x, [{exy,y},{exx,x}]}, {y, [{eyx,x}]} @@ -204,8 +192,6 @@ edges(Config) when is_list(Config) -> ?line digraph:delete(G), ok. -data(doc) -> []; -data(suite) -> []; data(Config) when is_list(Config) -> ?line G = build_graph([], [{x, [{exy, y}]}, {y, []}]), @@ -233,8 +219,6 @@ data(Config) when is_list(Config) -> -otp_3522(doc) -> []; -otp_3522(suite) -> []; otp_3522(Config) when is_list(Config) -> ?line G1 = build_graph([acyclic], [{x, []}]), ?line {error, {bad_edge,_}} = digraph:add_edge(G1, x, x), @@ -261,8 +245,6 @@ otp_3522(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -otp_3630(doc) -> []; -otp_3630(suite) -> []; otp_3630(Config) when is_list(Config) -> ?line G = build_graph([], [{x, [{exy,y},{exx,x}]}, {y, [{eyy,y},{eyx,x}]} @@ -299,8 +281,6 @@ otp_3630(Config) when is_list(Config) -> ok. -otp_8066(doc) -> []; -otp_8066(suite) -> []; otp_8066(Config) when is_list(Config) -> fun() -> D = digraph:new(), diff --git a/lib/stdlib/test/digraph_utils_SUITE.erl b/lib/stdlib/test/digraph_utils_SUITE.erl index e155857bd4..25728d3552 100644 --- a/lib/stdlib/test/digraph_utils_SUITE.erl +++ b/lib/stdlib/test/digraph_utils_SUITE.erl @@ -59,8 +59,6 @@ end_per_group(_GroupName, Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -simple(doc) -> []; -simple(suite) -> []; simple(Config) when is_list(Config) -> ?line G = digraph:new(), ?line add_vertices(G, [a]), @@ -97,8 +95,6 @@ simple(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -loop(doc) -> []; -loop(suite) -> []; loop(Config) when is_list(Config) -> ?line G = digraph:new(), ?line add_vertices(G, [a,b]), @@ -119,8 +115,6 @@ loop(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -isolated(doc) -> []; -isolated(suite) -> []; isolated(Config) when is_list(Config) -> ?line G = digraph:new(), ?line add_vertices(G, [a,b]), @@ -140,8 +134,6 @@ isolated(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -topsort(doc) -> []; -topsort(suite) -> []; topsort(Config) when is_list(Config) -> ?line G = digraph:new(), ?line add_edges(G, [{a,b},{b,c},{c,d},{d,e},{e,f}]), @@ -149,8 +141,6 @@ topsort(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -subgraph(doc) -> []; -subgraph(suite) -> []; subgraph(Config) when is_list(Config) -> ?line G = digraph:new([acyclic]), ?line add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e}, @@ -197,8 +187,6 @@ subgraph(Config) when is_list(Config) -> ok. -condensation(doc) -> []; -condensation(suite) -> []; condensation(Config) when is_list(Config) -> ?line G = digraph:new([]), ?line add_edges(G, [{b,c},{b,d},{e,f},{f,fg,fgl,g},{f,fg2,fgl2,g},{g,e}, @@ -217,8 +205,7 @@ condensation(Config) when is_list(Config) -> ?line true = digraph:delete(G), ok. -tree(doc) -> ["OTP-7081"]; -tree(suite) -> []; +%% OTP-7081 tree(Config) when is_list(Config) -> ?line false = is_tree([], []), ?line true = is_tree([a], []), diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl index fcf4db3696..a53c5333d8 100644 --- a/lib/stdlib/test/edlin_expand_SUITE.erl +++ b/lib/stdlib/test/edlin_expand_SUITE.erl @@ -58,10 +58,6 @@ end_per_group(_GroupName, Config) -> Config. -normal(doc) -> - [""]; -normal(suite) -> - []; normal(Config) when is_list(Config) -> {module,expand_test} = c:l(expand_test), %% These tests might fail if another module with the prefix @@ -80,10 +76,7 @@ normal(Config) when is_list(Config) -> {yes,"arity_entirely()",[]} = do_expand("expand_test:expand0"), ok. -quoted_fun(doc) -> - ["Normal module name, some function names using quoted atoms"]; -quoted_fun(suite) -> - []; +%% Normal module name, some function names using quoted atoms. quoted_fun(Config) when is_list(Config) -> {module,expand_test} = c:l(expand_test), {module,expand_test1} = c:l(expand_test1), @@ -116,10 +109,6 @@ quoted_fun(Config) when is_list(Config) -> {yes,"(",[]} = do_expand("expand_test:module_info"), ok. -quoted_module(doc) -> - [""]; -quoted_module(suite) -> - []; quoted_module(Config) when is_list(Config) -> {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), {yes, "Caps':", []} = do_expand("'ExpandTest"), @@ -133,8 +122,6 @@ quoted_module(Config) when is_list(Config) -> {"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps':a_"), ok. -quoted_both(suite) -> - []; quoted_both(Config) when is_list(Config) -> {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'), diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 37008ca1b1..695bca3fe4 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -85,10 +85,7 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -rec_1(doc) -> - ["Recursive macros hang or crash epp (OTP-1398)."]; -rec_1(suite) -> - []; +%% Recursive macros hang or crash epp (OTP-1398). rec_1(Config) when is_list(Config) -> ?line File = filename:join(?config(data_dir, Config), "mac.erl"), ?line {ok, List} = epp_parse_file(File, [], []), @@ -97,10 +94,6 @@ rec_1(Config) when is_list(Config) -> ?line check_errors(List), ok. -include_local(doc) -> - []; -include_local(suite) -> - []; include_local(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line File = filename:join(DataDir, "include_local.erl"), @@ -179,10 +172,6 @@ check_errors([_ | Rest]) -> check_errors(Rest). -upcase_mac_1(doc) -> - []; -upcase_mac_1(suite) -> - []; upcase_mac_1(Config) when is_list(Config) -> ?line File = filename:join(?config(data_dir, Config), "mac2.erl"), ?line {ok, List} = epp:parse_file(File, [], []), @@ -190,10 +179,6 @@ upcase_mac_1(Config) when is_list(Config) -> ?line Tuple = {1, 1, 3, 3}, ok. -upcase_mac_2(doc) -> - []; -upcase_mac_2(suite) -> - []; upcase_mac_2(Config) when is_list(Config) -> ?line File = filename:join(?config(data_dir, Config), "mac2.erl"), ?line {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]), @@ -201,10 +186,6 @@ upcase_mac_2(Config) when is_list(Config) -> ?line Tuple = {5, 5, 6, 6}, ok. -predef_mac(doc) -> - []; -predef_mac(suite) -> - []; predef_mac(Config) when is_list(Config) -> ?line File = filename:join(?config(data_dir, Config), "mac3.erl"), ?line {ok, List} = epp:parse_file(File, [], []), @@ -220,10 +201,6 @@ predef_mac(Config) when is_list(Config) -> Line1 = erl_anno:line(Anno), ok. -variable_1(doc) -> - []; -variable_1(suite) -> - []; variable_1(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line File = filename:join(DataDir, "variable_1.erl"), @@ -235,10 +212,7 @@ variable_1(Config) when is_list(Config) -> lists:keysearch(a,3,List), ok. -otp_4870(doc) -> - ["undef without module declaration"]; -otp_4870(suite) -> - []; +%% undef without module declaration. otp_4870(Config) when is_list(Config) -> Ts = [{otp_4870, <<"-undef(foo). @@ -247,10 +221,7 @@ otp_4870(Config) when is_list(Config) -> ?line [] = check(Config, Ts), ok. -otp_4871(doc) -> - ["crashing erl_scan"]; -otp_4871(suite) -> - []; +%% crashing erl_scan otp_4871(Config) when is_list(Config) -> ?line Dir = ?config(priv_dir, Config), ?line File = filename:join(Dir, "otp_4871.erl"), @@ -285,10 +256,7 @@ otp_4871_parse_file(Epp) -> Other -> Other end. -otp_5362(doc) -> - ["OTP-5362. The -file attribute is recognized."]; -otp_5362(suite) -> - []; +%% OTP-5362. The -file attribute is recognized. otp_5362(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), @@ -474,10 +442,7 @@ not_circular(Config) when is_list(Config) -> ?line [] = run(Config, Ts), ok. -skip_header(doc) -> - ["Skip some bytes in the beginning of the file."]; -skip_header(suite) -> - []; +%% Skip some bytes in the beginning of the file. skip_header(Config) when is_list(Config) -> ?line PrivDir = ?config(priv_dir, Config), ?line File = filename:join([PrivDir, "epp_test_skip_header.erl"]), @@ -504,10 +469,7 @@ skip_header(Config) when is_list(Config) -> ok. -otp_6277(doc) -> - ["?MODULE before module declaration."]; -otp_6277(suite) -> - []; +%% ?MODULE before module declaration. otp_6277(Config) when is_list(Config) -> Ts = [{otp_6277, <<"-undef(ASSERT). @@ -518,10 +480,7 @@ otp_6277(Config) when is_list(Config) -> ?line [] = check(Config, Ts), ok. -otp_7702(doc) -> - ["OTP-7702. Wrong line number in stringifying macro expansion."]; -otp_7702(suite) -> - []; +%% OTP-7702. Wrong line number in stringifying macro expansion. otp_7702(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), File = filename:join(Dir, "file_7702.erl"), @@ -583,10 +542,7 @@ otp_7702(Config) when is_list(Config) -> ok. -otp_8130(doc) -> - ["OTP-8130. Misc tests."]; -otp_8130(suite) -> - []; +%% OTP-8130. Misc tests. otp_8130(Config) when is_list(Config) -> true = os:putenv("epp_inc1", "stdlib"), Ts = [{otp_8130_1, @@ -1102,10 +1058,7 @@ ifdef(Config) -> -overload_mac(doc) -> - ["Advanced test on overloading macros."]; -overload_mac(suite) -> - []; +%% Advanced test on overloading macros. overload_mac(Config) when is_list(Config) -> Cs = [ %% '-undef' removes all definitions of a macro @@ -1163,10 +1116,7 @@ overload_mac(Config) when is_list(Config) -> ?line [] = run(Config, Ts). -otp_8388(doc) -> - ["OTP-8388. More tests on overloaded macros."]; -otp_8388(suite) -> - []; +%% OTP-8388. More tests on overloaded macros. otp_8388(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), ?line File = filename:join(Dir, "otp_8388.erl"), @@ -1213,10 +1163,7 @@ otp_8388(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -otp_8470(doc) -> - ["OTP-8470. Bugfix (one request - two replies)."]; -otp_8470(suite) -> - []; +%% OTP-8470. Bugfix (one request - two replies). otp_8470(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), C = <<"-file(\"erl_parse.yrl\", 486).\n" @@ -1228,10 +1175,7 @@ otp_8470(Config) when is_list(Config) -> ?line receive _ -> fail() after 0 -> ok end, ok. -otp_8562(doc) -> - ["OTP-8562. Record with no fields is considered typed."]; -otp_8562(suite) -> - []; +%% OTP-8562. Record with no fields is considered typed. otp_8562(Config) when is_list(Config) -> Cs = [{otp_8562, <<"-define(P(), {a,b}.\n" @@ -1242,10 +1186,7 @@ otp_8562(Config) when is_list(Config) -> ?line [] = compile(Config, Cs), ok. -otp_8911(doc) -> - ["OTP-8911. -file and file inclusion bug"]; -otp_8911(suite) -> - []; +%% OTP-8911. -file and file inclusion bug. otp_8911(Config) when is_list(Config) -> case test_server:is_cover() of true -> @@ -1283,10 +1224,7 @@ do_otp_8911(Config) -> ?line file:set_cwd(CWD), ok. -otp_8665(doc) -> - ["OTP-8665. Bugfix premature end."]; -otp_8665(suite) -> - []; +%% OTP-8665. Bugfix premature end. otp_8665(Config) when is_list(Config) -> Cs = [{otp_8562, <<"-define(A, a)\n">>, @@ -1295,10 +1233,7 @@ otp_8665(Config) when is_list(Config) -> ?line [] = compile(Config, Cs), ok. -otp_10302(doc) -> - "OTP-10302. Unicode characters scanner/parser."; -otp_10302(suite) -> - []; +%% OTP-10302. Unicode characters scanner/parser. otp_10302(Config) when is_list(Config) -> %% Two messages (one too many). Keeps otp_4871 happy. Cs = [{otp_8562, @@ -1369,10 +1304,7 @@ encoding_nocom(Enc, File) -> ok = file:close(Fd), E = epp:read_encoding(File, Options). -otp_10820(doc) -> - "OTP-10820. Unicode filenames."; -otp_10820(suite) -> - []; +%% OTP-10820. Unicode filenames. otp_10820(Config) when is_list(Config) -> L = [915,953,959,973,957,953,954,959,957,964], Dir = ?config(priv_dir, Config), @@ -1394,10 +1326,7 @@ do_otp_10820(File, C, PC) -> true = test_server:stop_node(Node), ok. -otp_11728(doc) -> - ["OTP-11728. Bugfix circular macro."]; -otp_11728(suite) -> - []; +%% OTP-11728. Bugfix circular macro. otp_11728(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), H = <<"-define(MACRO,[[]++?MACRO]).">>, diff --git a/lib/stdlib/test/erl_anno_SUITE.erl b/lib/stdlib/test/erl_anno_SUITE.erl index dff40a524f..0ce17ad9b2 100644 --- a/lib/stdlib/test/erl_anno_SUITE.erl +++ b/lib/stdlib/test/erl_anno_SUITE.erl @@ -71,15 +71,13 @@ end_per_testcase(_Case, _Config) -> -define(INFO(T, V), {T, V}). -dialyzer({no_fail_call, new/1}). -new(doc) -> - ["Test erl_anno:new/1"]; +%% Test erl_anno:new/1. new(_Config) -> {'EXIT', {badarg, _}} = (catch erl_anno:new([{location,1},{text, "text"}])), % badarg ok. -is_anno(doc) -> - ["Test erl_anno:is_anno/1"]; +%% Test erl_anno:is_anno/1. is_anno(_Config) -> false = erl_anno:is_anno(a), false = erl_anno:is_anno({a}), @@ -105,8 +103,7 @@ is_anno(_Config) -> true = erl_anno:is_anno(A5), ok. -generated(doc) -> - ["Test 'generated'"]; +%% Test 'generated'. generated(_Config) -> test(1, [{generated, true}, {generated, false}]), test(1, [{generated, false}, {generated, true}, {generated, false}]), @@ -126,8 +123,7 @@ generated(_Config) -> {generated, false}]), ok. -end_location(doc) -> - ["Test 'end_location'"]; +%% Test 'end_location'. end_location(_Config) -> test({1, 17}, [{text, "TEXT", [{end_location, {1, 21}}, {length, 4}]}, {text, "TEXT\n", [{end_location, {2, 1}}, {length, 5}]}, @@ -137,23 +133,20 @@ end_location(_Config) -> {text, "TEXT\ntxt", [{end_location, 2}, {length, 8}]}]), ok. -file(doc) -> - ["Test 'file'"]; +%% Test 'file'. file(_Config) -> test(1, [{file, "name"}, {file, ""}]), test({1, 17}, [{file, "name"}, {file, ""}]), ok. -line(doc) -> - ["Test 'line'"]; +%% Test 'line'. line(_Config) -> test(1, [{line, 17, [{location, 17}]}, {location, {9, 8}, [{line, 9}, {column, 8}]}, {line, 14, [{location, {14, 8}}]}]), ok. -location(doc) -> - ["Test 'location'"]; +%% Test 'location'. location(_Config) -> test(1, [{location, 2, [{line,2}]}, {location, {1, 17}, [{line, 1}, {column, 17}]}, @@ -171,8 +164,7 @@ location(_Config) -> {location, 9, [{column, undefined}]}]), ok. -record(doc) -> - ["Test 'record'"]; +%% Test 'record'. record(_Config) -> test({1, 17}, [{record, true}, {record, false}]), test(1, [{record, true}, {record, false}]), @@ -192,8 +184,7 @@ record(_Config) -> {generated, false}]), ok. -text(doc) -> - ["Test 'text'"]; +%% Test 'text'. text(_Config) -> test(1, [{text, "text", [{end_location, 1}, {length, 4}]}, {text, "", [{end_location, 1}, {length, 0}]}]), @@ -202,8 +193,7 @@ text(_Config) -> ok. -dialyzer({[no_opaque, no_fail_call], bad/1}). -bad(doc) -> - ["Test bad annotations"]; +%% Test bad annotations. bad(_Config) -> Line = erl_anno:new(1), LineColumn = erl_anno:new({1, 17}), @@ -228,9 +218,8 @@ bad(_Config) -> (catch erl_anno:record(bad)), % 1st arg not opaque ok. -parse_abstract(doc) -> - ["Test erl_parse:new_anno/1, erl_parse:anno_to_term/1" - ", and erl_parse:anno_from_term/1"]; +%% Test erl_parse:new_anno/1, erl_parse:anno_to_term/1, +%% and erl_parse:anno_from_term/1. parse_abstract(_Config) -> T = sample_term(), A = erl_parse:abstract(T, [{line,17}]), @@ -241,8 +230,7 @@ parse_abstract(_Config) -> T = erl_parse:normalise(Abstr2), ok. -mapfold_anno(doc) -> - ["Test erl_parse:{map_anno/2,fold_anno/3, and mapfold_anno/3}"]; +%% Test erl_parse:{map_anno/2,fold_anno/3, and mapfold_anno/3}. mapfold_anno(_Config) -> T = sample_term(), Abstr = erl_parse:abstract(T), diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index 19566c4215..84e9f8bb15 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -102,10 +102,7 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -guard_1(doc) -> - ["(OTP-2405)"]; -guard_1(suite) -> - []; +%% OTP-2405 guard_1(Config) when is_list(Config) -> ?line {ok,Tokens ,_} = erl_scan:string("if a+4 == 4 -> yes; true -> no end. "), @@ -117,10 +114,7 @@ guard_1(Config) when is_list(Config) -> guard_1_compiled() -> if a+4 == 4 -> yes; true -> no end. -guard_2(doc) -> - ["Similar to guard_1, but type-correct"]; -guard_2(suite) -> - []; +%% Similar to guard_1, but type-correct. guard_2(Config) when is_list(Config) -> ?line {ok,Tokens ,_} = erl_scan:string("if 6+4 == 4 -> yes; true -> no end. "), @@ -132,10 +126,7 @@ guard_2(Config) when is_list(Config) -> guard_2_compiled() -> if 6+4 == 4 -> yes; true -> no end. -string_plusplus(doc) -> - ["OTP-3069: syntactic sugar string ++ ..."]; -string_plusplus(suite) -> - []; +%% OTP-3069: syntactic sugar string ++ ... string_plusplus(Config) when is_list(Config) -> ?line check(fun() -> case "abc" of "ab" ++ L -> L end end, "case \"abc\" of \"ab\" ++ L -> L end. ", @@ -148,10 +139,7 @@ string_plusplus(Config) when is_list(Config) -> "c"), ok. -match_pattern(doc) -> - ["OTP-2983: match operator in pattern"]; -match_pattern(suite) -> - []; +%% OTP-2983: match operator in pattern. match_pattern(Config) when is_list(Config) -> ?line check(fun() -> case {a, b} of {a, _X}=Y -> {x,Y} end end, "case {a, b} of {a, X}=Y -> {x,Y} end. ", @@ -167,10 +155,7 @@ match_pattern(Config) when is_list(Config) -> 28), ok. -match_bin(doc) -> - ["binary match problems"]; -match_bin(suite) -> - []; +%% Binary match problems. match_bin(Config) when is_list(Config) -> ?line check(fun() -> <<"abc">> = <<"abc">> end, "<<\"abc\">> = <<\"abc\">>. ", @@ -184,10 +169,7 @@ match_bin(Config) when is_list(Config) -> {2,<<"AB">>,<<"CD">>}), ok. -pattern_expr(doc) -> - ["OTP-3144: compile-time expressions in pattern"]; -pattern_expr(suite) -> - []; +%% OTP-3144: compile-time expressions in pattern. pattern_expr(Config) when is_list(Config) -> ?line check(fun() -> case 4 of 2+2 -> ok end end, "case 4 of 2+2 -> ok end. ", @@ -197,10 +179,7 @@ pattern_expr(Config) when is_list(Config) -> ok), ok. -guard_3(doc) -> - ["OTP-4518."]; -guard_3(suite) -> - []; +%% OTP-4518. guard_3(Config) when is_list(Config) -> ?line check(fun() -> if false -> false; true -> true end end, "if false -> false; true -> true end.", @@ -217,10 +196,7 @@ guard_3(Config) when is_list(Config) -> true), ok. -guard_4(doc) -> - ["OTP-4885."]; -guard_4(suite) -> - []; +%% OTP-4885. guard_4(Config) when is_list(Config) -> check(fun() -> if erlang:'+'(3,a) -> true ; true -> false end end, "if erlang:'+'(3,a) -> true ; true -> false end.", @@ -250,10 +226,7 @@ guard_4(Config) when is_list(Config) -> false), ok. -guard_5(doc) -> - ["Guards with erlang:'=='/2"]; -guard_5(suite) -> - []; +%% Guards with erlang:'=='/2. guard_5(Config) when is_list(Config) -> {ok,Tokens ,_} = erl_scan:string("case 1 of A when erlang:'=='(A, 1) -> true end."), @@ -265,10 +238,7 @@ guard_5(Config) when is_list(Config) -> guard_5_compiled() -> case 1 of A when erlang:'=='(A, 1) -> true end. -lc(doc) -> - ["OTP-4518."]; -lc(suite) -> - []; +%% OTP-4518. lc(Config) when is_list(Config) -> ?line check(fun() -> X = 32, [X || X <- [1,2,3]] end, "begin X = 32, [X || X <- [1,2,3]] end.", @@ -296,10 +266,7 @@ lc(Config) when is_list(Config) -> "[X || X <- [true,false], X].", [true]), ok. -simple_cases(doc) -> - ["Simple cases, just to cover some code."]; -simple_cases(suite) -> - []; +%% Simple cases, just to cover some code. simple_cases(Config) when is_list(Config) -> ?line check(fun() -> A = $C end, "A = $C.", $C), %% ?line check(fun() -> A = 3.14 end, "A = 3.14.", 3.14), @@ -524,10 +491,7 @@ simple_cases(Config) when is_list(Config) -> ?line check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true), ok. -unary_plus(doc) -> - ["OTP-4929. Unary plus rejects non-numbers."]; -unary_plus(suite) -> - []; +%% OTP-4929. Unary plus rejects non-numbers. unary_plus(Config) when is_list(Config) -> ?line check(fun() -> F = fun(X) -> + X end, true = -1 == F(-1) end, @@ -536,20 +500,14 @@ unary_plus(Config) when is_list(Config) -> ?line error_check("+a.", badarith), ok. -apply_atom(doc) -> - ["OTP-5064. Can no longer apply atoms."]; -apply_atom(suite) -> - []; +%% OTP-5064. Can no longer apply atoms. apply_atom(Config) when is_list(Config) -> ?line error_check("[X || X <- [[1],[2]], begin L = length, L(X) =:= 1 end].", {badfun,length}), ok. -otp_5269(doc) -> - ["OTP-5269. Bugs in the bit syntax."]; -otp_5269(suite) -> - []; +%% OTP-5269. Bugs in the bit syntax. otp_5269(Config) when is_list(Config) -> ?line check(fun() -> L = 8, F = fun(<>) -> B end, @@ -604,10 +562,7 @@ otp_5269(Config) when is_list(Config) -> ok), ok. -otp_6539(doc) -> - ["OTP-6539. try/catch bugs."]; -otp_6539(suite) -> - []; +%% OTP-6539. try/catch bugs. otp_6539(Config) when is_list(Config) -> ?line check(fun() -> F = fun(A,B) -> @@ -628,10 +583,7 @@ otp_6539(Config) when is_list(Config) -> [3, 5]), ok. -otp_6543(doc) -> - ["OTP-6543. bitlevel binaries."]; -otp_6543(suite) -> - []; +%% OTP-6543. bitlevel binaries. otp_6543(Config) when is_list(Config) -> ?line check(fun() -> << <> || <> <- [1,2,3] >> @@ -850,10 +802,7 @@ otp_6543(Config) when is_list(Config) -> ?line error_check("[X || <> <= [a,b]].",{bad_generator,[a,b]}), ok. -otp_6787(doc) -> - ["OTP-6787. bitlevel binaries."]; -otp_6787(suite) -> - []; +%% OTP-6787. bitlevel binaries. otp_6787(Config) when is_list(Config) -> ?line check( fun() -> <<16:(1024*1024)>> = <<16:(1024*1024)>> end, @@ -861,10 +810,7 @@ otp_6787(Config) when is_list(Config) -> <<16:1048576>>), ok. -otp_6977(doc) -> - ["OTP-6977. ++ bug."]; -otp_6977(suite) -> - []; +%% OTP-6977. ++ bug. otp_6977(Config) when is_list(Config) -> ?line check( fun() -> (fun([$X] ++ _) -> ok end)("X") end, @@ -872,8 +818,7 @@ otp_6977(Config) when is_list(Config) -> ok), ok. -otp_7550(doc) -> - ["OTP-7550. Support for UTF-8, UTF-16, UTF-32."]; +%% OTP-7550. Support for UTF-8, UTF-16, UTF-32. otp_7550(Config) when is_list(Config) -> %% UTF-8. @@ -947,10 +892,7 @@ otp_7550(Config) when is_list(Config) -> ok. -otp_8133(doc) -> - ["OTP-8133. Bit comprehension bug."]; -otp_8133(suite) -> - []; +%% OTP-8133. Bit comprehension bug. otp_8133(Config) when is_list(Config) -> ?line check( fun() -> @@ -1001,10 +943,7 @@ otp_8133(Config) when is_list(Config) -> ok), ok. -otp_10622(doc) -> - ["OTP-10622. Bugs."]; -otp_10622(suite) -> - []; +%% OTP-10622. Bugs. otp_10622(Config) when is_list(Config) -> check(fun() -> <<0>> = <<"\x{400}">> end, "<<0>> = <<\"\\x{400}\">>. ", @@ -1043,17 +982,13 @@ otp_10622(Config) when is_list(Config) -> ok. -otp_13228(doc) -> - ["OTP-13228. ERL-32: non-local function handler bug."]; +%% OTP-13228. ERL-32: non-local function handler bug. otp_13228(_Config) -> LFH = {value, fun(foo, [io_fwrite]) -> worked end}, EFH = {value, fun({io, fwrite}, [atom]) -> io_fwrite end}, {value, worked, []} = parse_and_run("foo(io:fwrite(atom)).", LFH, EFH). -funs(doc) -> - ["Simple cases, just to cover some code."]; -funs(suite) -> - []; +%% Simple cases, just to cover some code. funs(Config) when is_list(Config) -> do_funs(none, none), do_funs(lfh(), none), @@ -1288,10 +1223,7 @@ external_func({M,F}, As) -> -try_catch(doc) -> - ["Test try-of-catch-after-end statement"]; -try_catch(suite) -> - []; +%% Test try-of-catch-after-end statement. try_catch(Config) when is_list(Config) -> %% Match in of with catch ?line check(fun() -> try 1 of 1 -> 2 catch _:_ -> 3 end end, @@ -1401,10 +1333,7 @@ try_catch(Config) when is_list(Config) -> ok. -eval_expr_5(doc) -> - ["(OTP-7933)"]; -eval_expr_5(suite) -> - []; +%% OTP-7933. eval_expr_5(Config) when is_list(Config) -> ?line {ok,Tokens ,_} = erl_scan:string("if a+4 == 4 -> yes; true -> no end. "), diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index 892a8e1b93..0cf1fdd503 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -72,9 +72,7 @@ end_per_group(_GroupName, Config) -> Config. -attributes(doc) -> - "Import module and functions."; -attributes(suite) -> []; +%% Import module and functions. attributes(Config) when is_list(Config) -> Ts = [ <<"-import(lists, [append/2, reverse/1]). @@ -86,16 +84,14 @@ attributes(Config) when is_list(Config) -> 3 = length([1,2,3]), 3 = record_info(size, r), [a, b] = record_info(fields, r), - [] = erl_expand_records_SUITE:attributes(suite), + [_|_] = erl_expand_records_SUITE:all(), ok. ">> ], ?line run(Config, Ts), ok. -expr(doc) -> - "Some expressions."; -expr(suite) -> []; +%% Some expressions. expr(Config) when is_list(Config) -> Ts = [ <<" @@ -160,9 +156,7 @@ expr(Config) when is_list(Config) -> ok. -guard(doc) -> - "is_record in guards."; -guard(suite) -> []; +%% is_record in guards. guard(Config) when is_list(Config) -> File = filename("guard.erl", Config), Beam = filename("guard.beam", Config), @@ -207,9 +201,7 @@ guard(Config) when is_list(Config) -> ?line ok = file:delete(Beam), ok. -init(doc) -> - "Wildcard initialisation."; -init(suite) -> []; +%% Wildcard initialisation. init(Config) when is_list(Config) -> Ts = [ <<" @@ -227,9 +219,7 @@ init(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -pattern(doc) -> - "Some patterns."; -pattern(suite) -> []; +%% Some patterns. pattern(Config) when is_list(Config) -> Ts = [ <<"-import(lists, [append/2, reverse/1]). @@ -316,9 +306,6 @@ pattern(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -strict(doc) -> - ""; -strict(suite) -> []; strict(Config) when is_list(Config) -> Ts1 = [ <<"-record(r1, {a,b}). @@ -360,9 +347,7 @@ strict(Config) when is_list(Config) -> ?line run(Config, Ts2, [no_strict_record_tests]), ok. -update(doc) -> - "Record updates."; -update(suite) -> []; +%% Record updates. update(Config) when is_list(Config) -> Ts = [ <<"-record(r, {a,b,c,d,e,f}). @@ -416,9 +401,7 @@ maps(Config) when is_list(Config) -> run(Config, Ts, [strict_record_tests]), ok. -otp_5915(doc) -> - "Strict record tests in guards."; -otp_5915(suite) -> []; +%% Strict record tests in guards. otp_5915(Config) when is_list(Config) -> %% These tests are also run by the compiler's record_SUITE. Ts = [ @@ -564,9 +547,7 @@ otp_5915(Config) when is_list(Config) -> ?line run(Config, Ts, [strict_record_tests]), ok. -otp_7931(doc) -> - "Test optimization of record accesses and is_record/3 tests in guards"; -otp_7931(suite) -> []; +%% Test optimization of record accesses and is_record/3 tests in guards. otp_7931(Config) when is_list(Config) -> Ts = [ <<"-record(r, {a = 4,b}). @@ -653,9 +634,7 @@ otp_7931(Config) when is_list(Config) -> ?line run(Config, Ts, [strict_record_tests]), ok. -otp_5990(doc) -> - "OTP-5990. {erlang,is_record}."; -otp_5990(suite) -> []; +%% OTP-5990. {erlang,is_record}. otp_5990(Config) when is_list(Config) -> Ts = [ <<" @@ -690,9 +669,7 @@ otp_5990(Config) when is_list(Config) -> ok. -otp_7078(doc) -> - "OTP-7078. Record update: missing test."; -otp_7078(suite) -> []; +%% OTP-7078. Record update: missing test. otp_7078(Config) when is_list(Config) -> Ts = [ <<" @@ -725,9 +702,7 @@ otp_7078(Config) when is_list(Config) -> -record(otp_7101, {a,b,c=[],d=[],e=[]}). -otp_7101(doc) -> - "OTP-7101. Record update: more than one call to setelement/3."; -otp_7101(suite) -> []; +%% OTP-7101. Record update: more than one call to setelement/3. otp_7101(Config) when is_list(Config) -> Rec = #otp_7101{}, diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl index 057c955a25..45e67226b7 100644 --- a/lib/stdlib/test/erl_internal_SUITE.erl +++ b/lib/stdlib/test/erl_internal_SUITE.erl @@ -57,9 +57,7 @@ init_per_testcase(_Case, Config) -> end_per_testcase(_Case, _Config) -> ok. -behav(suite) -> []; -behav(doc) -> - ["Check that the behaviour callbacks are correctly defined"]; +%% Check that the behaviour callbacks are correctly defined. behav(_) -> Modules = [application, gen_server, gen_fsm, gen_event, supervisor_bridge, supervisor], diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 6d03e8e53f..62775e6007 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -115,9 +115,7 @@ 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. @@ -171,9 +169,7 @@ unused_vars_warn_basic(Config) when is_list(Config) -> ?line [] = 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]) -> @@ -522,9 +518,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> 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, @@ -579,9 +573,7 @@ unused_vars_warn_rec(Config) when is_list(Config) -> ?line [] = 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. @@ -706,9 +698,7 @@ unused_vars_warn_fun(Config) when is_list(Config) -> ?line [] = 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(<>) -> @@ -772,9 +762,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() -> @@ -867,10 +855,8 @@ export_vars_warn(Config) when is_list(Config) -> ?line [] = 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) -> @@ -898,9 +884,7 @@ shadow_vars(Config) when is_list(Config) -> ?line [] = 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]). @@ -912,9 +896,7 @@ unused_import(Config) when is_list(Config) -> ?line [] = 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]). @@ -960,9 +942,7 @@ unused_function(Config) when is_list(Config) -> ?line [] = 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() -> @@ -1063,9 +1043,7 @@ unsafe_vars(Config) when is_list(Config) -> ?line [] = 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) -> @@ -1097,9 +1075,7 @@ unsafe_vars2(Config) when is_list(Config) -> ?line [] = 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() -> @@ -1287,9 +1263,7 @@ unsafe_vars_try(Config) when is_list(Config) -> ?line [] = 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}) -> @@ -1322,9 +1296,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, @@ -1613,9 +1585,7 @@ guard(Config) when is_list(Config) -> ?line [] = 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() -> @@ -1637,9 +1607,7 @@ otp_4886(Config) when is_list(Config) -> ?line [] = 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}]}). @@ -1664,9 +1632,7 @@ otp_4988(Config) when is_list(Config) -> ?line [] = 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() -> @@ -1882,9 +1848,7 @@ otp_5091(Config) when is_list(Config) -> ?line [] = 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}]). @@ -1914,9 +1878,7 @@ otp_5276(Config) when is_list(Config) -> ?line [] = 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). @@ -1931,9 +1893,7 @@ otp_5917(Config) when is_list(Config) -> ?line [] = 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). @@ -1954,9 +1914,7 @@ otp_6585(Config) when is_list(Config) -> ?line [] = 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, @@ -1971,10 +1929,8 @@ otp_5338(Config) when is_list(Config) -> ?line [] = 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\"). @@ -2177,9 +2133,7 @@ otp_5362(Config) when is_list(Config) -> ?line [] = 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(<> = <>) -> @@ -2236,7 +2190,7 @@ otp_5371(Config) when is_list(Config) -> ?line [] = 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([<> = {C,D} = <>]) -> @@ -2306,9 +2260,7 @@ otp_7227(Config) when is_list(Config) -> ?line [] = 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]). @@ -2320,9 +2272,7 @@ otp_5494(Config) when is_list(Config) -> ?line [] = 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 @@ -2341,9 +2291,7 @@ otp_5644(Config) when is_list(Config) -> ?line [] = 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{}}). @@ -2622,9 +2570,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]). @@ -2661,9 +2608,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]). @@ -2683,9 +2628,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]). @@ -2697,9 +2640,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). @@ -2724,9 +2665,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). @@ -2753,9 +2692,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). @@ -2777,8 +2714,7 @@ 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]). @@ -2790,9 +2726,7 @@ export_all(Config) when is_list(Config) -> 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) -> @@ -3062,9 +2996,7 @@ bif_clash(Config) when is_list(Config) -> ?line [] = 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). @@ -3101,9 +3033,7 @@ behaviour_basic(Config) when is_list(Config) -> ?line [] = 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). @@ -3204,9 +3134,7 @@ behaviour_multiple(Config) when is_list(Config) -> ?line [] = 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,8 +3319,8 @@ otp_11861(Conf) when is_list(Conf) -> 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,8 +3360,7 @@ otp_7550(Config) when is_list(Config) -> 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(). @@ -3444,9 +3371,7 @@ otp_8051(Config) when is_list(Config) -> ?line [] = 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, @@ -3554,9 +3479,7 @@ on_load_failing(Config) when is_list(Config) -> ?line [] = 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.">>, @@ -3648,9 +3571,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, @@ -3777,8 +3698,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, @@ -3864,9 +3784,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}, @@ -3887,8 +3806,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}, diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index 0706b9a4ad..415c1549d4 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -95,8 +95,6 @@ end_per_group(_GroupName, Config) -> -func(suite) -> - []; func(Config) when is_list(Config) -> Ts = [{func_1, <<"-record(r1, {a,b}). @@ -153,8 +151,6 @@ func(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -call(suite) -> - []; call(Config) when is_list(Config) -> Ts = [{call_1, <<"t() -> @@ -166,8 +162,6 @@ call(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -recs(suite) -> - []; recs(Config) when is_list(Config) -> %% Evolved while testing strict record tests in guards... Ts = [{recs_1, @@ -334,8 +328,6 @@ recs(Config) when is_list(Config) -> sdafjsd,sdf,sdafsd,sdfdsf,sdfdsf,dsfds}}">>), ok. -try_catch(suite) -> - []; try_catch(Config) when is_list(Config) -> Ts = [{try_1, % copied from erl_eval_SUITE <<"t() -> try 1 of 1 -> 2 catch _:_ -> 3 end.">>}, @@ -388,8 +380,6 @@ try_catch(Config) when is_list(Config) -> after foo end">>), ok. -if_then(suite) -> - []; if_then(Config) when is_list(Config) -> Ts = [{if_1, <<"t() -> if 1 > 2 -> 1; true -> b end.">>}, @@ -401,8 +391,6 @@ if_then(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -receive_after(suite) -> - []; receive_after(Config) when is_list(Config) -> Ts = [{rec_1, <<"t() -> receive foo -> bar; bar -> foo end.">>}, @@ -426,8 +414,6 @@ receive_after(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -bits(suite) -> - []; bits(Config) when is_list(Config) -> Ts = [{bit_1, % copied from shell_SUITE <<"t() -> <<(<<\"abc\">>):3/binary>>.">>}, @@ -461,8 +447,6 @@ bits(Config) when is_list(Config) -> ?line ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>), ok. -head_tail(suite) -> - []; head_tail(Config) when is_list(Config) -> Ts = [{list_1, <<"t() -> [a | b].">>}, @@ -480,8 +464,6 @@ head_tail(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -cond1(suite) -> - []; cond1(Config) when is_list(Config) -> C = {'cond',1,[{clause,2,[],[[{tuple,2,[{atom,2,foo},{atom,2,bar}]}]], [{cons,3,{atom,3,a},{cons,3,{atom,3,b},{nil,3}}}]}, @@ -503,8 +485,6 @@ cond1(Config) when is_list(Config) -> % end">>), ok. -block(suite) -> - []; block(Config) when is_list(Config) -> Ts = [{block_1, <<"t() -> begin a,{c,d} end.">>} @@ -512,8 +492,6 @@ block(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -case1(suite) -> - []; case1(Config) when is_list(Config) -> Ts = [{case_1, <<"t() -> case {foo,bar} of @@ -534,8 +512,6 @@ case1(Config) when is_list(Config) -> end">>), ok. -ops(suite) -> - []; ops(Config) when is_list(Config) -> Ts = [{ops_1, <<"t() -> {a,b} + (3 - 2) + 4.">>}, @@ -547,8 +523,6 @@ ops(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -messages(suite) -> - []; messages(Config) when is_list(Config) -> ?line true = "{error,{some,\"error\"}}\n" =:= lists:flatten(erl_pp:form({error,{some,"error"}})), @@ -557,8 +531,6 @@ messages(Config) when is_list(Config) -> "\n" = flat_form({eof,0}), ok. -import_export(suite) -> - []; import_export(Config) when is_list(Config) -> Ts = [{import_1, <<"-import(lists, [max/1, reverse/1]). @@ -576,8 +548,6 @@ import_export(Config) when is_list(Config) -> ?line compile(Config, Ts), ok. -misc_attrs(suite) -> - []; misc_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-module(m). ">>), ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk," @@ -595,8 +565,6 @@ misc_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-custom1(#{test1 => init/2, test2 => [val/1, val/2]}). ">>), ok. -dialyzer_attrs(suite) -> - []; dialyzer_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-type foo() :: #bar{}. ">>), ok = pp_forms(<<"-opaque foo() :: {bar, fun((X, [42,...]) -> X)}. ">>), @@ -604,8 +572,6 @@ dialyzer_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-callback foo(<<_:32,_:_*4>>, T) -> T. ">>), ok. -hook(suite) -> - []; hook(Config) when is_list(Config) -> F = fun(H) -> H end, do_hook(F). @@ -693,8 +659,6 @@ hook({foo,E}, I, P, H) -> A = erl_anno:new(0), erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). -neg_indent(suite) -> - []; neg_indent(Config) when is_list(Config) -> ?line ok = pp_expr(<<"begin a end">>), ?line ok = pp_expr(<<"begin a,b end">>), @@ -752,9 +716,7 @@ neg_indent(Config) when is_list(Config) -> ok. -otp_6321(doc) -> - "OTP_6321. Bug fix of exprs()."; -otp_6321(suite) -> []; +%% OTP_6321. Bug fix of exprs(). otp_6321(Config) when is_list(Config) -> Str = "S = hopp, {hej, S}. ", {done, {ok, Tokens, _EndLine}, ""} = erl_scan:tokens("", Str, _L=1), @@ -762,9 +724,7 @@ otp_6321(Config) when is_list(Config) -> "S = hopp, {hej,S}" = lists:flatten(erl_pp:exprs(Exprs)), ok. -otp_6911(doc) -> - "OTP_6911. More newlines."; -otp_6911(suite) -> []; +%% OTP_6911. More newlines. otp_6911(Config) when is_list(Config) -> F = {function,5,thomas,1, [{clause,5, @@ -786,27 +746,21 @@ otp_6911(Config) when is_list(Config) -> ?line ok = pp_expr(<<"receive after 1 -> ok end">>), ok. -otp_6914(doc) -> - "OTP_6914. Binary comprehensions."; -otp_6914(suite) -> []; +%% OTP_6914. Binary comprehensions. otp_6914(Config) when is_list(Config) -> ?line ok = pp_expr(<<"<< <> || B <- [0,1,1] >>">>), ?line ok = pp_expr(<<"[ B || <> <= <<\"hi\">>]">>), ?line ok = pp_expr(<<"<< <<1:1>> || true >>">>), ok. -otp_8150(doc) -> - "OTP_8150. Types."; -otp_8150(suite) -> []; +%% OTP_8150. Types. otp_8150(Config) when is_list(Config) -> ?line _ = [{N,ok} = {N,pp_forms(B)} || {N,B} <- type_examples() ], ok. -otp_8238(doc) -> - "OTP_8238. Bugfix 'E'."; -otp_8238(suite) -> []; +%% OTP_8238. Bugfix 'E'. otp_8238(Config) when is_list(Config) -> Ex = [<<"-record(rec1, {}).\n" "-record(rec2, {a, b}).\n" @@ -902,9 +856,7 @@ type_examples() -> "f19 = 3 :: integer()|undefined," "f5 = 3 :: undefined|integer()}). ">>}]. -otp_8473(doc) -> - "OTP_8473. Bugfix abstract type 'fun'."; -otp_8473(suite) -> []; +%% OTP_8473. Bugfix abstract type 'fun'. otp_8473(Config) when is_list(Config) -> Ex = [{ex1,<<"-type 'fun'(A) :: A.\n" "-type funkar() :: 'fun'(fun((integer()) -> atom())).\n">>}], @@ -912,9 +864,7 @@ otp_8473(Config) when is_list(Config) -> {N,B} <- Ex], ok. -otp_8522(doc) -> - "OTP_8522. Avoid duplicated 'undefined' in record field types."; -otp_8522(suite) -> []; +%% OTP_8522. Avoid duplicated 'undefined' in record field types. otp_8522(Config) when is_list(Config) -> FileName = filename('otp_8522.erl', Config), C = <<"-module(otp_8522).\n" @@ -941,8 +891,6 @@ count_atom(L, A) when is_list(L) -> count_atom(_, _) -> 0. -maps_syntax(doc) -> "Maps syntax"; -maps_syntax(suite) -> []; maps_syntax(Config) when is_list(Config) -> Ts = [{map_fun_1, <<"t() ->\n" @@ -973,9 +921,7 @@ maps_syntax(Config) when is_list(Config) -> ok. -otp_8567(doc) -> - "OTP_8567. Avoid duplicated 'undefined' in record field types."; -otp_8567(suite) -> []; +%% OTP_8567. Avoid duplicated 'undefined' in record field types. otp_8567(Config) when is_list(Config) -> FileName = filename('otp_8567.erl', Config), C = <<"-module otp_8567.\n" @@ -1010,9 +956,7 @@ otp_8567(Config) when is_list(Config) -> ok. -otp_8664(doc) -> - "OTP_8664. Types with integer expressions."; -otp_8664(suite) -> []; +%% OTP_8664. Types with integer expressions. otp_8664(Config) when is_list(Config) -> FileName = filename('otp_8664.erl', Config), C1 = <<"-module(otp_8664).\n" @@ -1042,9 +986,7 @@ otp_8664(Config) when is_list(Config) -> ok. -otp_9147(doc) -> - "OTP_9147. Create well-formed types when adding 'undefined'."; -otp_9147(suite) -> []; +%% OTP-9147. Create well-formed types when adding 'undefined'. otp_9147(Config) when is_list(Config) -> FileName = filename('otp_9147.erl', Config), C1 = <<"-module(otp_9147).\n" @@ -1062,9 +1004,7 @@ otp_9147(Config) when is_list(Config) -> string:tokens(binary_to_list(Bin), "\n")), ok. -otp_10302(doc) -> - "OTP-10302. Unicode characters scanner/parser."; -otp_10302(suite) -> []; +%% OTP-10302. Unicode characters scanner/parser. otp_10302(Config) when is_list(Config) -> Ts = [{uni_1, <<"t() -> <<(<<\"abc\\x{aaa}\">>):3/binary>>.">>} @@ -1101,9 +1041,7 @@ unicode_hook({foo,E}, I, P, H) -> A = erl_anno:new(0), erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). -otp_10820(doc) -> - "OTP-10820. Unicode filenames."; -otp_10820(suite) -> []; +%% OTP-10820. Unicode filenames. otp_10820(Config) when is_list(Config) -> C1 = <<"%% coding: utf-8\n -module(any).">>, ok = do_otp_10820(Config, C1, "+pc latin1"), @@ -1129,9 +1067,7 @@ file_attr_is_string("-file(\"" ++ _) -> true; file_attr_is_string([_ | L]) -> file_attr_is_string(L). -otp_11100(doc) -> - "OTP-11100. Fix printing of invalid forms."; -otp_11100(suite) -> []; +%% OTP-11100. Fix printing of invalid forms. otp_11100(Config) when is_list(Config) -> %% There are a few places where the added code ("options(none)") %% doesn't make a difference (pp:bit_elem_type/1 is an example). @@ -1166,9 +1102,7 @@ otp_11100(Config) when is_list(Config) -> []}}), ok. -otp_11861(doc) -> - "OTP-11861. behaviour_info() and -callback."; -otp_11861(suite) -> []; +%% OTP-11861. behaviour_info() and -callback. otp_11861(Config) when is_list(Config) -> "-optional_callbacks([bar/0]).\n" = pf({attribute,3,optional_callbacks,[{bar,0}]}), diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 004d013da5..f307a90cd3 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -77,18 +77,12 @@ end_per_group(_GroupName, Config) -> -error_1(doc) -> - ["(OTP-2347)"]; -error_1(suite) -> - []; +%% (OTP-2347) error_1(Config) when is_list(Config) -> ?line {error, _, _} = erl_scan:string("'a"), ok. -error_2(doc) -> - ["Checks that format_error works on the error cases."]; -error_2(suite) -> - []; +%% Checks that format_error works on the error cases. error_2(Config) when is_list(Config) -> ?line lists:foreach(fun check/1, error_cases()), ok. @@ -124,8 +118,7 @@ check_error({error, Info, EndLine}, Module0) -> String = lists:flatten(Module0:format_error(Desc)), true = io_lib:printable_list(String). -iso88591(doc) -> ["Tests the support for ISO-8859-1 i.e Latin-1"]; -iso88591(suite) -> []; +%% Tests the support for ISO-8859-1 i.e Latin-1. iso88591(Config) when is_list(Config) -> ?line ok = case catch begin @@ -158,10 +151,7 @@ iso88591(Config) when is_list(Config) -> ok -> ok %Aok end. -otp_7810(doc) -> - ["OTP-7810. White spaces, comments, and more.."]; -otp_7810(suite) -> - []; +%% OTP-7810. White spaces, comments, and more... otp_7810(Config) when is_list(Config) -> ?line ok = reserved_words(), ?line ok = atoms(), @@ -911,10 +901,7 @@ more_chars() -> erl_scan:string("$\\xg", {1,1}), ok. -otp_10302(doc) -> - "OTP-10302. Unicode characters scanner/parser."; -otp_10302(suite) -> - []; +%% OTP-10302. Unicode characters scanner/parser. otp_10302(Config) when is_list(Config) -> %% From unicode(): {error,{1,erl_scan,{illegal,atom}},1} = @@ -1084,18 +1071,12 @@ otp_10302(Config) when is_list(Config) -> erl_parse_abstract("a"++[1024]++"c", [{encoding,latin1}]), ok. -otp_10990(doc) -> - "OTP-10990. Floating point number in input string."; -otp_10990(suite) -> - []; +%% OTP-10990. Floating point number in input string. otp_10990(Config) when is_list(Config) -> {'EXIT',_} = (catch {foo, erl_scan:string([$",42.0,$"],1)}), ok. -otp_10992(doc) -> - "OTP-10992. List of floats to abstract format."; -otp_10992(suite) -> - []; +%% OTP-10992. List of floats to abstract format. otp_10992(Config) when is_list(Config) -> {cons,0,{float,0,42.0},{nil,0}} = erl_parse_abstract([42.0], [{encoding,unicode}]), @@ -1107,10 +1088,7 @@ otp_10992(Config) when is_list(Config) -> erl_parse_abstract([$A,42.0], [{encoding,utf8}]), ok. -otp_11807(doc) -> - "OTP-11807. Generalize erl_parse:abstract/2."; -otp_11807(suite) -> - []; +%% OTP-11807. Generalize erl_parse:abstract/2. otp_11807(Config) when is_list(Config) -> {cons,0,{integer,0,97},{cons,0,{integer,0,98},{nil,0}}} = erl_parse_abstract("ab", [{encoding,none}]), diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 886f9049ed..78956d3346 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -225,10 +225,7 @@ memory_check_summary(_Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -t_bucket_disappears(suite) -> - []; -t_bucket_disappears(doc) -> - ["Test that a disappearing bucket during select of a non-fixed table works."]; +%% Test that a disappearing bucket during select of a non-fixed table works. t_bucket_disappears(Config) when is_list(Config) -> repeat_for_opts(t_bucket_disappears_do). @@ -247,10 +244,7 @@ t_bucket_disappears_do(Opts) -> ?line verify_etsmem(EtsMem). -t_match_spec_run(suite) -> - []; -t_match_spec_run(doc) -> - ["Check ets:match_spec_run/2."]; +%% Check ets:match_spec_run/2. t_match_spec_run(Config) when is_list(Config) -> init_externals(), ?line EtsMem = etsmem(), @@ -427,10 +421,7 @@ assert_eq(A,B) -> ct:fail("assert_eq failed"). -t_repair_continuation(suite) -> - []; -t_repair_continuation(doc) -> - ["Check ets:repair_continuation/2."]; +%% Test ets:repair_continuation/2. t_repair_continuation(Config) when is_list(Config) -> repeat_for_opts(t_repair_continuation_do). @@ -559,9 +550,7 @@ t_repair_continuation_do(Opts) -> ?line verify_etsmem(EtsMem). -default(doc) -> - ["Check correct default vaules of a new ets table"]; -default(suite) -> []; +%% Test correct default vaules of a new ets table. default(Config) when is_list(Config) -> %% Default should be set,protected ?line EtsMem = etsmem(), @@ -577,10 +566,7 @@ default(Config) when is_list(Config) -> ?line ets:delete(Def), ?line verify_etsmem(EtsMem). -select_fail(doc) -> - ["Test that select fails even if nothing can match"]; -select_fail(suite) -> - []; +%% Test that select fails even if nothing can match. select_fail(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(select_fail_do, [all_types,write_concurrency]), @@ -615,8 +601,8 @@ select_fail_do(Opts) -> %% The hardcoded expected memory sizes (in words) are the ones we expect on: %% SunOS5.8, 32-bit, non smp, private heap %% -memory(doc) -> ["Whitebox test of ets:info(X,memory)"]; -memory(suite) -> []; + +%% Whitebox test of ets:info(X, memory). memory(Config) when is_list(Config) -> ?line ok = chk_normal_tab_struct_size(), repeat_for_opts(memory_do,[compressed]), @@ -741,10 +727,7 @@ adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) -> TabDiff = ?TAB_STRUCT_SZ, {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}. -t_whitebox(doc) -> - ["Diverse whitebox testes"]; -t_whitebox(suite) -> - []; +%% Misc. whitebox tests t_whitebox(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(whitebox_1), @@ -777,10 +760,7 @@ whitebox_2(Opts) -> ok. -t_ets_dets(doc) -> - ["Test ets:to/from_dets"]; -t_ets_dets(suite) -> - []; +%% Test ets:to/from_dets. t_ets_dets(Config) when is_list(Config) -> repeat_for_opts(fun(Opts) -> t_ets_dets(Config,Opts) end). @@ -817,10 +797,7 @@ check_badarg({'EXIT', {badarg, [{M,F,Args,_} | _]}}, M, F, Args) -> check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) -> true = test_server:is_native(M) andalso length(Args) =:= A. -t_delete_all_objects(doc) -> - ["Test ets:delete_all_objects/1"]; -t_delete_all_objects(suite) -> - []; +%% Test ets:delete_all_objects/1. t_delete_all_objects(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(t_delete_all_objects_do), @@ -854,10 +831,7 @@ t_delete_all_objects_do(Opts) -> ?line ets:delete(T). -t_delete_object(doc) -> - ["Test ets:delete_object/2"]; -t_delete_object(suite) -> - []; +%% Test ets:delete_object/2. t_delete_object(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(t_delete_object_do), @@ -930,10 +904,7 @@ make_init_fun(N) -> exit(close_not_expected) end. -t_init_table(doc) -> - ["Test ets:init_table/2"]; -t_init_table(suite) -> - []; +%% Test ets:init_table/2. t_init_table(Config) when is_list(Config)-> ?line EtsMem = etsmem(), repeat_for_opts(t_init_table_do), @@ -955,10 +926,7 @@ do_fill_dbag_using_lists(T,N) -> do_fill_dbag_using_lists(T,N - 1). -t_insert_new(doc) -> - ["Test the insert_new function"]; -t_insert_new(suite) -> - []; +%% Test the insert_new function. t_insert_new(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line L = fill_sets_int(1000) ++ fill_sets_int(1000,[{write_concurrency,true}]), @@ -1012,10 +980,7 @@ t_insert_new(Config) when is_list(Config) -> L), ?line verify_etsmem(EtsMem). -t_insert_list(doc) -> - ["Test ets:insert/2 with list of objects."]; -t_insert_list(suite) -> - []; +%% Test ets:insert/2 with list of objects. t_insert_list(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(t_insert_list_do), @@ -1028,10 +993,7 @@ t_insert_list_do(Opts) -> ?line ets:delete(T). -t_test_ms(doc) -> - ["Test interface of ets:test_ms/2"]; -t_test_ms(suite) -> - []; +%% Test interface of ets:test_ms/2. t_test_ms(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line {ok,[a,b]} = ets:test_ms({a,b}, @@ -1047,10 +1009,7 @@ t_test_ms(Config) when is_list(Config) -> ?line true = (if is_list(String) -> true; true -> false end), ?line verify_etsmem(EtsMem). -t_select_reverse(doc) -> - ["Test the select reverse BIF's"]; -t_select_reverse(suite) -> - []; +%% Test the select reverse BIFs. t_select_reverse(Config) when is_list(Config) -> ?line Table = ets_new(xxx, [ordered_set]), ?line filltabint(Table,1000), @@ -1108,10 +1067,7 @@ do_reverse_chunked({L,C},Acc) -> do_reverse_chunked(ets:select_reverse(C), NewAcc). -t_select_delete(doc) -> - ["Test the ets:select_delete/2 and ets:select_count/2 BIF's"]; -t_select_delete(suite) -> - []; +%% Test the ets:select_delete/2 and ets:select_count/2 BIFs. t_select_delete(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Tables = fill_sets_int(10000) ++ fill_sets_int(10000,[{write_concurrency,true}]), @@ -1243,10 +1199,7 @@ t_select_delete(Config) when is_list(Config) -> lists:foreach(fun(Tab) -> ets:delete(Tab) end,Tables), ?line verify_etsmem(EtsMem). -partly_bound(doc) -> - ["Test that partly bound keys gives faster matches"]; -partly_bound(suite) -> - []; +%% Test that partly bound keys gives faster matches. partly_bound(Config) when is_list(Config) -> case os:type() of {win32,_} -> @@ -1293,10 +1246,7 @@ make_better_sub2() -> ok. -match_heavy(doc) -> - ["Heavy random matching, comparing set with ordered_set."]; -match_heavy(suite) -> - []; +%% Heavy random matching, comparing set with ordered_set. match_heavy(Config) when is_list(Config) -> PrivDir = ?config(priv_dir,Config), DataDir = ?config(data_dir, Config), @@ -1557,10 +1507,7 @@ do_random_test() -> ets:delete(Set), ?line verify_etsmem(EtsMem). -update_element(doc) -> - ["test various variants of update_element"]; -update_element(suite) -> - []; +%% Ttest various variants of update_element. update_element(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(update_element_opts), @@ -1723,10 +1670,7 @@ update_element_neg_do(T) -> ok. -update_counter(doc) -> - ["test various variants of update_counter"]; -update_counter(suite) -> - []; +%% test various variants of update_counter. update_counter(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(update_counter_do), @@ -2034,10 +1978,7 @@ update_counter_with_default_do(Opts) -> ok. -fixtable_next(doc) -> - ["Check that a first-next sequence always works on a fixed table"]; -fixtable_next(suite) -> - []; +%% Check that a first-next sequence always works on a fixed table. fixtable_next(Config) when is_list(Config) -> repeat_for_opts(fixtable_next_do, [write_concurrency,all_types]). @@ -2068,10 +2009,7 @@ do_fixtable_next(Tab) -> ?line false = ets:info(Tab, fixed), ?line ets:delete(Tab). -fixtable_insert(doc) -> - ["Check inserts of deleted keys in fixed bags"]; -fixtable_insert(suite) -> - []; +%% Check inserts of deleted keys in fixed bags. fixtable_insert(Config) when is_list(Config) -> Combos = [[Type,{write_concurrency,WC}] || Type<- [bag,duplicate_bag], WC <- [false,true]], @@ -2120,8 +2058,7 @@ fixtable_insert_do(Opts) -> {'EXIT',{badarg,_}} = (catch ets:next(Ets,First)), ok. -write_concurrency(doc) -> ["The 'write_concurrency' option"]; -write_concurrency(suite) -> []; +%% Test the 'write_concurrency' option. write_concurrency(Config) when is_list(Config) -> ?line EtsMem = etsmem(), Yes1 = ets_new(foo,[public,{write_concurrency,true}]), @@ -2180,8 +2117,7 @@ write_concurrency(Config) when is_list(Config) -> ok. -heir(doc) -> ["The 'heir' option"]; -heir(suite) -> []; +%% The 'heir' option. heir(Config) when is_list(Config) -> repeat_for_opts(heir_do). @@ -2321,8 +2257,7 @@ heir_1(HeirData,Mode,Opts) -> ?line Founder ! {go, Heir}, ?line {'DOWN', Mref, process, Heir, normal} = receive_any(). -give_away(doc) -> ["ets:give_way/3"]; -give_away(suite) -> []; +%% Test ets:give_way/3. give_away(Config) when is_list(Config) -> repeat_for_opts(give_away_do). @@ -2403,8 +2338,7 @@ give_away_receiver(T, Giver) -> end. -setopts(doc) -> ["ets:setopts/2"]; -setopts(suite) -> []; +%% Test ets:setopts/2. setopts(Config) when is_list(Config) -> repeat_for_opts(setopts_do,[write_concurrency,all_types]). @@ -2445,8 +2379,7 @@ setopts_do(Opts) -> exit(Heir, bang), ok. -bad_table(doc) -> ["All kinds of operations with bad table argument"]; -bad_table(suite) -> []; +%% All kinds of operations with bad table argument. bad_table(Config) when is_list(Config) -> %% Open and close disk_log to stabilize etsmem. @@ -2555,10 +2488,7 @@ bad_table_call(T,{F,Args,_,{return,Return}}) -> end. -rename(doc) -> - ["Check rename of ets tables"]; -rename(suite) -> - []; +%% Check rename of ets tables. rename(Config) when is_list(Config) -> repeat_for_opts(rename_do, [write_concurrency, all_types]). @@ -2573,10 +2503,7 @@ rename_do(Opts) -> ets:delete(ungermanbazz), ?line verify_etsmem(EtsMem). -rename_unnamed(doc) -> - ["Check rename of unnamed ets table"]; -rename_unnamed(suite) -> - []; +%% Check rename of unnamed ets table. rename_unnamed(Config) when is_list(Config) -> repeat_for_opts(rename_unnamed_do,[write_concurrency,all_types]). @@ -2591,8 +2518,7 @@ rename_unnamed_do(Opts) -> ?line ets:delete(Tab), ?line verify_etsmem(EtsMem). -evil_rename(doc) -> - "Rename a table with many fixations, and at the same time delete it."; +%% Rename a table with many fixations, and at the same time delete it. evil_rename(Config) when is_list(Config) -> ?line evil_rename_1(old_hash, new_hash, [public,named_table]), ?line EtsMem = etsmem(), @@ -2649,11 +2575,8 @@ evil_create_fixed_tab() -> ets:safe_fixtable(T, true), T. -interface_equality(doc) -> - ["Tests that the return values and errors are equal for set's and" - " ordered_set's where applicable"]; -interface_equality(suite) -> - []; +%% Tests that the return values and errors are equal for set's and +%% ordered_set's where applicable. interface_equality(Config) when is_list(Config) -> repeat_for_opts(interface_equality_do). @@ -2719,10 +2642,7 @@ maybe_sort({'EXIT',{Reason, List}}) when is_list(List) -> maybe_sort(Any) -> Any. -ordered_match(doc) -> - ["Test match, match_object and match_delete in ordered set's"]; -ordered_match(suite) -> - []; +%% Test match, match_object and match_delete in ordered set's. ordered_match(Config) when is_list(Config)-> repeat_for_opts(ordered_match_do). @@ -2768,10 +2688,7 @@ ordered_match_do(Opts) -> ?line verify_etsmem(EtsMem). -ordered(doc) -> - ["Test basic functionality in ordered_set's."]; -ordered(suite) -> - []; +%% Test basic functionality in ordered_set's. ordered(Config) when is_list(Config) -> repeat_for_opts(ordered_do). @@ -2836,8 +2753,7 @@ pick_all_backwards(T) -> -setbag(doc) -> ["Small test case for both set and bag type ets tables."]; -setbag(suite) -> []; +%% Small test case for both set and bag type ets tables. setbag(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Set = ets_new(set,[set]), @@ -2860,9 +2776,7 @@ setbag(Config) when is_list(Config) -> true = ets:delete(Bag), ?line verify_etsmem(EtsMem). -badnew(doc) -> - ["Test case to check proper return values for illegal ets_new() calls."]; -badnew(suite) -> []; +%% Test case to check proper return values for illegal ets_new() calls. badnew(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line {'EXIT',{badarg,_}} = (catch ets_new(12,[])), @@ -2872,17 +2786,14 @@ badnew(Config) when is_list(Config) -> ?line {'EXIT',{badarg,_}} = (catch ets_new(name,bag)), ?line verify_etsmem(EtsMem). -verybadnew(doc) -> - ["Test case to check that a not well formed list does not crash the " - "emulator. OTP-2314 "]; -verybadnew(suite) -> []; +%% OTP-2314. Test case to check that a non-proper list does not +%% crash the emulator. verybadnew(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])), ?line verify_etsmem(EtsMem). -named(doc) -> ["Small check to see if named tables work."]; -named(suite) -> []; +%% Small check to see if named tables work. named(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Tab = make_table(foo, @@ -2892,8 +2803,7 @@ named(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -keypos2(doc) -> ["Test case to check if specified keypos works."]; -keypos2(suite) -> []; +%% Test case to check if specified keypos works. keypos2(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Tab = make_table(foo, @@ -2903,11 +2813,8 @@ keypos2(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -privacy(doc) -> - ["Privacy check. Check that a named(public/private/protected) table " - "cannot be read by", - "the wrong process(es)."]; -privacy(suite) -> []; +%% Privacy check. Check that a named(public/private/protected) table +%% cannot be read by the wrong process(es). privacy(Config) when is_list(Config) -> repeat_for_opts(privacy_do). @@ -2985,9 +2892,7 @@ rotate_tuple(Tuple, N) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -empty(doc) -> - ["Check lookup in an empty table and lookup of a non-existing key"]; -empty(suite) -> []; +%% Check lookup in an empty table and lookup of a non-existing key. empty(Config) when is_list(Config) -> repeat_for_opts(empty_do). @@ -3000,9 +2905,7 @@ empty_do(Opts) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -badinsert(doc) -> - ["Check proper return values for illegal insert operations."]; -badinsert(suite) -> []; +%% Check proper return values for illegal insert operations. badinsert(Config) when is_list(Config) -> repeat_for_opts(badinsert_do). @@ -3024,8 +2927,7 @@ badinsert_do(Opts) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -time_lookup(doc) -> ["Lookup timing."]; -time_lookup(suite) -> []; +%% Test lookup timing. time_lookup(Config) when is_list(Config) -> %% just for timing, really ?line EtsMem = etsmem(), @@ -3050,10 +2952,8 @@ time_lookup_many(N, Tab) -> ets:lookup(Tab, {a,key}), time_lookup_many(N-1, Tab). -badlookup(doc) -> - ["Check proper return values from bad lookups in existing/non existing " - " ets tables"]; -badlookup(suite) -> []; +%% Check proper return values from bad lookups in existing/non existing +%% ets tables. badlookup(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line {'EXIT',{badarg,_}} = (catch ets:lookup(foo,key)), @@ -3062,8 +2962,7 @@ badlookup(Config) when is_list(Config) -> ?line {'EXIT',{badarg,_}} = (catch ets:lookup(Tab,key)), ?line verify_etsmem(EtsMem). -lookup_order(doc) -> ["Test that lookup returns objects in order of insertion for bag and dbag."]; -lookup_order(suite) -> []; +%% Test that lookup returns objects in order of insertion for bag and dbag. lookup_order(Config) when is_list(Config) -> EtsMem = etsmem(), repeat_for_opts(lookup_order_do, [write_concurrency,[bag,duplicate_bag]]), @@ -3157,8 +3056,7 @@ fill_tab(Tab,Val) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -lookup_element_mult(doc) -> ["Multiple return elements (OTP-2386)"]; -lookup_element_mult(suite) -> []; +%% OTP-2386. Multiple return elements. lookup_element_mult(Config) when is_list(Config) -> repeat_for_opts(lookup_element_mult_do). @@ -3198,9 +3096,7 @@ lem_crash_3(T) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -delete_elem(doc) -> - ["Check delete of an element inserted in a `filled' table."]; -delete_elem(suite) -> []; +%% Check delete of an element inserted in a `filled' table. delete_elem(Config) when is_list(Config) -> repeat_for_opts(delete_elem_do, [write_concurrency, all_types]). @@ -3216,10 +3112,8 @@ delete_elem_do(Opts) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -delete_tab(doc) -> - ["Check that ets:delete() works and releases the name of the deleted " - "table."]; -delete_tab(suite) -> []; +%% Check that ets:delete() works and releases the name of the +%% deleted table. delete_tab(Config) when is_list(Config) -> repeat_for_opts(delete_tab_do,[write_concurrency,all_types]). @@ -3233,8 +3127,7 @@ delete_tab_do(Opts) -> ?line true = ets:delete(Name), ?line verify_etsmem(EtsMem). -delete_large_tab(doc) -> - "Check that ets:delete/1 works and that other processes can run."; +%% Check that ets:delete/1 works and that other processes can run. delete_large_tab(Config) when is_list(Config) -> ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], ?line EtsMem = etsmem(), @@ -3303,8 +3196,8 @@ delete_large_tab_1(Name, Flags, Data, Fix) -> receive {'DOWN',SchedTracerMon,process,SchedTracer,_} -> ok end, ok. -delete_large_named_table(doc) -> - "Delete a large name table and try to create a new table with the same name in another process."; +%% Delete a large name table and try to create a new table with +%% the same name in another process. delete_large_named_table(Config) when is_list(Config) -> ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], ?line EtsMem = etsmem(), @@ -3340,8 +3233,7 @@ delete_large_named_table_1(Name, Flags, Data, Fix) -> receive {'DOWN',MRef,process,Pid,_} -> ok end, ok. -evil_delete(doc) -> - "Delete a large table, and kill the process during the delete."; +%% Delete a large table, and kill the process during the delete. evil_delete(Config) when is_list(Config) -> ?line Data = [{I,I*I} || I <- lists:seq(1, 100000)], repeat_for_opts(fun(Opts) -> evil_delete_do(Opts,Data) end). @@ -3412,10 +3304,6 @@ evil_delete_owner(Name, Flags, Data, Fix) -> ?line receive {'DOWN',Ref,_,_,_} -> ok end. -exit_large_table_owner(doc) -> - []; -exit_large_table_owner(suite) -> - []; exit_large_table_owner(Config) when is_list(Config) -> %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)], ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok}; @@ -3431,8 +3319,6 @@ exit_large_table_owner_do(Opts,{FEData,Config}) -> ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1), ?line verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1). -exit_many_large_table_owner(doc) -> []; -exit_many_large_table_owner(suite) -> []; exit_many_large_table_owner(Config) when is_list(Config) -> %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)], ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok}; @@ -3448,8 +3334,6 @@ exit_many_large_table_owner_do(Opts,FEData,Config) -> ?line verify_rescheduling_exit(Config, FEData, Opts, true, 1, 4), ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 1, 4). -exit_many_tables_owner(doc) -> []; -exit_many_tables_owner(suite) -> []; exit_many_tables_owner(Config) when is_list(Config) -> NoData = fun(_Do) -> ok end, ?line EtsMem = etsmem(), @@ -3457,8 +3341,6 @@ exit_many_tables_owner(Config) when is_list(Config) -> ?line verify_rescheduling_exit(Config, NoData, [named_table,{write_concurrency,true}], false, 1000, 1), ?line verify_etsmem(EtsMem). -exit_many_many_tables_owner(doc) -> []; -exit_many_many_tables_owner(suite) -> []; exit_many_many_tables_owner(Config) when is_list(Config) -> ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 50)], ?line FEData = fun(Do) -> lists:foreach(Do, Data) end, @@ -3577,8 +3459,7 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) -> -table_leak(doc) -> - "Make sure that slots for ets tables are cleared properly."; +%% Make sure that slots for ets tables are cleared properly. table_leak(Config) when is_list(Config) -> repeat_for_opts(fun(Opts) -> table_leak_1(Opts,20000) end). @@ -3588,9 +3469,7 @@ table_leak_1(Opts,N) -> ?line true = ets:delete(T), table_leak_1(Opts,N-1). -baddelete(doc) -> - ["Check proper return values for illegal delete operations."]; -baddelete(suite) -> []; +%% Check proper return values for illegal delete operations. baddelete(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line {'EXIT',{badarg,_}} = (catch ets:delete(foo)), @@ -3599,9 +3478,7 @@ baddelete(Config) when is_list(Config) -> ?line {'EXIT',{badarg,_}} = (catch ets:delete(Tab)), ?line verify_etsmem(EtsMem). -match_delete(doc) -> - ["Check that match_delete works. Also tests tab2list function."]; -match_delete(suite) -> []; +%% Check that match_delete works. Also tests tab2list function. match_delete(Config) when is_list(Config) -> ?line EtsMem = etsmem(), repeat_for_opts(match_delete_do,[write_concurrency,all_types]), @@ -3619,9 +3496,7 @@ match_delete_do(Opts) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -match_delete3(doc) -> - ["OTP-3005: check match_delete with constant argument."]; -match_delete3(suite) -> []; +%% OTP-3005: check match_delete with constant argument. match_delete3(Config) when is_list(Config) -> repeat_for_opts(match_delete3_do). @@ -3646,8 +3521,7 @@ match_delete3_do(Opts) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -firstnext(doc) -> ["Tests ets:first/1 & ets:next/2."]; -firstnext(suite) -> []; +%% Test ets:first/1 & ets:next/2. firstnext(Config) when is_list(Config) -> repeat_for_opts(firstnext_do). @@ -3669,7 +3543,7 @@ firstnext_collect(Tab,Key,List) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -firstnext_concurrent(doc) -> "Tests ets:first/1 & ets:next/2."; +%% Tests ets:first/1 & ets:next/2. firstnext_concurrent(Config) when is_list(Config) -> register(master, self()), ets_init(?MODULE, 20), @@ -3706,7 +3580,6 @@ dyn_lookup(T, K) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -slot(suite) -> []; slot(Config) when is_list(Config) -> repeat_for_opts(slot_do). @@ -3732,7 +3605,6 @@ slot_loop(Tab,SlotNo,EltsSoFar) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -match1(suite) -> []; match1(Config) when is_list(Config) -> repeat_for_opts(match1_do). @@ -3768,8 +3640,7 @@ match1_do(Opts) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -match2(doc) -> ["Tests match with specified keypos bag table."]; -match2(suite) -> []; +%% Test match with specified keypos bag table. match2(Config) when is_list(Config) -> repeat_for_opts(match2_do). @@ -3796,8 +3667,7 @@ match2_do(Opts) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -match_object(doc) -> ["Some ets:match_object test."]; -match_object(suite) -> []; +%% Some ets:match_object tests. match_object(Config) when is_list(Config) -> repeat_for_opts(match_object_do). @@ -3896,10 +3766,8 @@ match_object_do(Opts) -> true = ets:delete(Tab), verify_etsmem(EtsMem). -match_object2(suite) -> []; -match_object2(doc) -> ["Tests that db_match_object does not generate " - "a `badarg' when resuming a search with no " - "previous matches."]; +%% Tests that db_match_object does not generate a `badarg' when +%% resuming a search with no previous matches. match_object2(Config) when is_list(Config) -> repeat_for_opts(match_object2_do). @@ -3924,8 +3792,7 @@ match_object2_do(Opts) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -tab2list(doc) -> ["Tests tab2list (OTP-3319)"]; -tab2list(suite) -> []; +%% OTP-3319. Test tab2list. tab2list(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Tab = make_table(foo, @@ -3935,9 +3802,8 @@ tab2list(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -misc1(doc) -> ["Simple general small test. ", - "If this fails, ets is in really bad shape."]; -misc1(suite) -> []; +%% Simple general small test. If this fails, ets is in really bad +%% shape. misc1(Config) when is_list(Config) -> repeat_for_opts(misc1_do). @@ -3955,8 +3821,7 @@ misc1_do(Opts) -> end, ok. -safe_fixtable(doc) -> ["Check the safe_fixtable function."]; -safe_fixtable(suite) -> []; +%% Check the safe_fixtable function. safe_fixtable(Config) when is_list(Config) -> repeat_for_opts(safe_fixtable_do). @@ -4014,8 +3879,7 @@ safe_fixtable_do(Opts) -> end, ok. -info(doc) -> ["Tests ets:info result for required tuples."]; -info(suite) -> []; +%% Tests ets:info result for required tuples. info(Config) when is_list(Config) -> repeat_for_opts(info_do). @@ -4047,8 +3911,7 @@ info_do(Opts) -> ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed), ?line verify_etsmem(EtsMem). -dups(doc) -> ["Test various duplicate_bags stuff"]; -dups(suite) -> []; +%% Test various duplicate_bags stuff. dups(Config) when is_list(Config) -> repeat_for_opts(dups_do). @@ -4078,9 +3941,7 @@ dups_do(Opts) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -tab2file(doc) -> ["Check the ets:tab2file function on an empty " - "ets table."]; -tab2file(suite) -> []; +%% Test the ets:tab2file function on an empty ets table. tab2file(Config) when is_list(Config) -> ?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]), tab2file_do(FName, []), @@ -4116,9 +3977,7 @@ tab2file_do(FName, Opts) -> ?line verify_etsmem(EtsMem). -tab2file2(doc) -> ["Check the ets:tab2file function on a ", - "filled set/bag type ets table."]; -tab2file2(suite) -> []; +%% Check the ets:tab2file function on a filled set/bag type ets table. tab2file2(Config) when is_list(Config) -> repeat_for_opts({tab2file2_do,Config}, [[set,bag],compressed]). @@ -4179,10 +4038,7 @@ fill_tab2(Tab, Val, Num) -> ?line fill_tab2(Tab, Val+1, Num-1), ok. -tabfile_ext1(suite) -> - []; -tabfile_ext1(doc) -> - ["Tests verification of tables with object count extended_info"]; +%% Test verification of tables with object count extended_info. tabfile_ext1(Config) when is_list(Config) -> repeat_for_opts(fun(Opts) -> tabfile_ext1_do(Opts, Config) end). @@ -4219,10 +4075,8 @@ tabfile_ext1_do(Opts,Config) -> file:delete(FName2), ok. -tabfile_ext2(suite) -> - []; -tabfile_ext2(doc) -> - ["Tests verification of tables with md5sum extended_info"]; + +%% Test verification of tables with md5sum extended_info. tabfile_ext2(Config) when is_list(Config) -> repeat_for_opts(fun(Opts) -> tabfile_ext2_do(Opts,Config) end). @@ -4259,10 +4113,7 @@ tabfile_ext2_do(Opts,Config) -> file:delete(FName2), ok. -tabfile_ext3(suite) -> - []; -tabfile_ext3(doc) -> - ["Tests verification of (named) tables without extended info"]; +%% Test verification of (named) tables without extended info. tabfile_ext3(Config) when is_list(Config) -> ?line FName = filename:join([?config(priv_dir, Config),"namn.dat"]), ?line FName2 = filename:join([?config(priv_dir, Config),"ncountflip.dat"]), @@ -4293,10 +4144,7 @@ tabfile_ext3(Config) when is_list(Config) -> file:delete(FName2), ok. -tabfile_ext4(suite) -> - []; -tabfile_ext4(doc) -> - ["Tests verification of large table with md5 sum"]; +%% Tests verification of large table with md5 sum. tabfile_ext4(Config) when is_list(Config) -> ?line FName = filename:join([?config(priv_dir, Config),"bauta.dat"]), LL = lists:seq(1,10000), @@ -4335,10 +4183,7 @@ tabfile_ext4(Config) when is_list(Config) -> file:delete(FName), ok. -badfile(suite) -> - []; -badfile(doc) -> - ["Tests that no disk_log is left open when file has been corrupted"]; +%% Test that no disk_log is left open when file has been corrupted. badfile(Config) when is_list(Config) -> PrivDir = ?config(priv_dir,Config), File = filename:join(PrivDir, "badfile"), @@ -4396,9 +4241,8 @@ make_sub_binary(List, Num) when is_list(List) -> %% Lookup stuff like crazy... -heavy_lookup(doc) -> ["Performs multiple lookups for every key ", - "in a large table."]; -heavy_lookup(suite) -> []; + +%% Perform multiple lookups for every key in a large table. heavy_lookup(Config) when is_list(Config) -> repeat_for_opts(heavy_lookup_do). @@ -4421,9 +4265,7 @@ do_lookup(Tab, N) -> do_lookup(Tab, N-1) end. -heavy_lookup_element(doc) -> ["Performs multiple lookups for ", - "every element in a large table."]; -heavy_lookup_element(suite) -> []; +%% Perform multiple lookups for every element in a large table. heavy_lookup_element(Config) when is_list(Config) -> repeat_for_opts(heavy_lookup_element_do). @@ -4489,9 +4331,6 @@ do_heavy_concurrent_proc(Tab, N, Offs) -> do_heavy_concurrent_proc(Tab, N-1, Offs). -fold_empty(doc) -> - []; -fold_empty(suite) -> []; fold_empty(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line Tab = make_table(a, [], []), @@ -4500,9 +4339,6 @@ fold_empty(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -foldl(doc) -> - []; -foldl(suite) -> []; foldl(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line L = [{a,1}, {c,3}, {b,2}], @@ -4512,9 +4348,6 @@ foldl(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -foldr(doc) -> - []; -foldr(suite) -> []; foldr(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line L = [{a,1}, {c,3}, {b,2}], @@ -4524,9 +4357,6 @@ foldr(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -foldl_ordered(doc) -> - []; -foldl_ordered(suite) -> []; foldl_ordered(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line L = [{a,1}, {c,3}, {b,2}], @@ -4536,9 +4366,6 @@ foldl_ordered(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -foldr_ordered(doc) -> - []; -foldr_ordered(suite) -> []; foldr_ordered(Config) when is_list(Config) -> ?line EtsMem = etsmem(), ?line L = [{a,1}, {c,3}, {b,2}], @@ -4548,10 +4375,7 @@ foldr_ordered(Config) when is_list(Config) -> ?line true = ets:delete(Tab), ?line verify_etsmem(EtsMem). -member(suite) -> - []; -member(doc) -> - ["Tests ets:member BIF"]; +%% Test ets:member BIF. member(Config) when is_list(Config) -> repeat_for_opts(member_do, [write_concurrency, all_types]). @@ -5026,8 +4850,7 @@ verify2([],[]) -> false; verify2(_Err, _) -> true. -otp_7665(doc) -> ["delete_object followed by delete on fixed bag failed to delete objects."]; -otp_7665(suite) -> []; +%% delete_object followed by delete on fixed bag failed to delete objects. otp_7665(Config) when is_list(Config) -> repeat_for_opts(otp_7665_do). @@ -5164,8 +4987,7 @@ grow_shrink_3(N, ShrinkTo, T) -> true = ets:delete(T, N), grow_shrink_3(N-1, ShrinkTo, T). -grow_pseudo_deleted(doc) -> ["Grow a table that still contains pseudo-deleted objects"]; -grow_pseudo_deleted(suite) -> []; +%% Grow a table that still contains pseudo-deleted objects. grow_pseudo_deleted(Config) when is_list(Config) -> only_if_smp(fun() -> grow_pseudo_deleted_do() end). @@ -5218,8 +5040,7 @@ grow_pseudo_deleted_do(Type) -> ets:delete(T), process_flag(scheduler,0). -shrink_pseudo_deleted(doc) -> ["Shrink a table that still contains pseudo-deleted objects"]; -shrink_pseudo_deleted(suite) -> []; +%% Shrink a table that still contains pseudo-deleted objects. shrink_pseudo_deleted(Config) when is_list(Config) -> only_if_smp(fun()->shrink_pseudo_deleted_do() end). @@ -5271,7 +5092,6 @@ shrink_pseudo_deleted_do(Type) -> -meta_lookup_unnamed_read(suite) -> []; meta_lookup_unnamed_read(Config) when is_list(Config) -> InitF = fun(_) -> Tab = ets_new(unnamed,[]), true = ets:insert(Tab,{key,data}), @@ -5284,7 +5104,6 @@ meta_lookup_unnamed_read(Config) when is_list(Config) -> end, run_workers(InitF,ExecF,FiniF,10000). -meta_lookup_unnamed_write(suite) -> []; meta_lookup_unnamed_write(Config) when is_list(Config) -> InitF = fun(_) -> Tab = ets_new(unnamed,[]), {Tab,0} @@ -5296,7 +5115,6 @@ meta_lookup_unnamed_write(Config) when is_list(Config) -> end, run_workers(InitF,ExecF,FiniF,10000). -meta_lookup_named_read(suite) -> []; meta_lookup_named_read(Config) when is_list(Config) -> InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)), Tab = ets_new(Name,[named_table]), @@ -5310,7 +5128,6 @@ meta_lookup_named_read(Config) when is_list(Config) -> end, run_workers(InitF,ExecF,FiniF,10000). -meta_lookup_named_write(suite) -> []; meta_lookup_named_write(Config) when is_list(Config) -> InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)), Tab = ets_new(Name,[named_table]), @@ -5323,7 +5140,6 @@ meta_lookup_named_write(Config) when is_list(Config) -> end, run_workers(InitF,ExecF,FiniF,10000). -meta_newdel_unnamed(suite) -> []; meta_newdel_unnamed(Config) when is_list(Config) -> InitF = fun(_) -> ok end, ExecF = fun(_) -> Tab = ets_new(unnamed,[]), @@ -5332,7 +5148,6 @@ meta_newdel_unnamed(Config) when is_list(Config) -> FiniF = fun(_) -> ok end, run_workers(InitF,ExecF,FiniF,10000). -meta_newdel_named(suite) -> []; meta_newdel_named(Config) when is_list(Config) -> InitF = fun([ProcN|_]) -> list_to_atom(integer_to_list(ProcN)) end, @@ -5343,8 +5158,7 @@ meta_newdel_named(Config) when is_list(Config) -> FiniF = fun(_) -> ok end, run_workers(InitF,ExecF,FiniF,10000). -smp_insert(doc) -> ["Concurrent insert's on same table"]; -smp_insert(suite) -> []; +%% Concurrent insert's on same table. smp_insert(Config) when is_list(Config) -> ets_new(smp_insert,[named_table,public,{write_concurrency,true}]), InitF = fun(_) -> ok end, @@ -5355,8 +5169,7 @@ smp_insert(Config) when is_list(Config) -> verify_table_load(smp_insert), ets:delete(smp_insert). -smp_fixed_delete(doc) -> ["Concurrent delete's on same fixated table"]; -smp_fixed_delete(suite) -> []; +%% Concurrent deletes on same fixated table. smp_fixed_delete(Config) when is_list(Config) -> only_if_smp(fun()->smp_fixed_delete_do() end). @@ -5389,8 +5202,7 @@ smp_fixed_delete_do() -> num_of_buckets(T) -> ?line element(1,ets:info(T,stats)). -smp_unfix_fix(doc) -> ["Fixate hash table while other process is busy doing unfix"]; -smp_unfix_fix(suite) -> []; +%% Fixate hash table while other process is busy doing unfix. smp_unfix_fix(Config) when is_list(Config) -> only_if_smp(fun()-> smp_unfix_fix_do() end). @@ -5458,8 +5270,7 @@ smp_unfix_fix_do() -> ets:delete(T), process_flag(scheduler,0). -otp_8166(doc) -> ["Unsafe unfix was done by trapping select/match"]; -otp_8166(suite) -> []; +%% Unsafe unfix was done by trapping select/match. otp_8166(Config) when is_list(Config) -> only_if_smp(3, fun()-> otp_8166_do(false), otp_8166_do(true) @@ -5581,7 +5392,7 @@ verify_table_load(T) -> end. -otp_8732(doc) -> ["ets:select on a tree with NIL key object"]; +%% ets:select on a tree with NIL key object. otp_8732(Config) when is_list(Config) -> Tab = ets_new(noname,[ordered_set]), filltabstr(Tab,999), @@ -5590,9 +5401,7 @@ otp_8732(Config) when is_list(Config) -> ok. -smp_select_delete(suite) -> []; -smp_select_delete(doc) -> - ["Run concurrent select_delete (and inserts) on same table."]; +%% Run concurrent select_delete (and inserts) on same table. smp_select_delete(Config) when is_list(Config) -> T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}]), Mod = 17, @@ -5647,7 +5456,7 @@ smp_select_delete(Config) when is_list(Config) -> ?line false = ets:info(T,fixed), ets:delete(T). -types(doc) -> ["Test different types"]; +%% Test different types. types(Config) when is_list(Config) -> init_externals(), repeat_for_opts(types_do,[[set,ordered_set],compressed]). @@ -5690,7 +5499,8 @@ otp_9932(Config) when is_list(Config) -> ets:delete(T). -otp_9423(doc) -> ["vm-deadlock caused by race between ets:delete and others on write_concurrency table"]; +%% vm-deadlock caused by race between ets:delete and others on +%% write_concurrency table. otp_9423(Config) when is_list(Config) -> InitF = fun(_) -> {0,0} end, ExecF = fun({S,F}) -> diff --git a/lib/stdlib/test/file_sorter_SUITE.erl b/lib/stdlib/test/file_sorter_SUITE.erl index 6b2ccbd1cc..790ea88f2b 100644 --- a/lib/stdlib/test/file_sorter_SUITE.erl +++ b/lib/stdlib/test/file_sorter_SUITE.erl @@ -82,10 +82,7 @@ end_per_group(_GroupName, Config) -> Config. -basic(doc) -> - ["Basic test case."]; -basic(suite) -> - []; +%% Basic test case. basic(Config) when is_list(Config) -> Fmt = binary, Arg = {format,Fmt}, @@ -136,10 +133,7 @@ basic(Config) when is_list(Config) -> ok. -badarg(doc) -> - ["Call functions with bad arguments."]; -badarg(suite) -> - []; +%% Call functions with bad arguments. badarg(Config) when is_list(Config) -> PrivDir = ?privdir(Config), BadFile = filename:join(PrivDir, "not_a_file"), @@ -300,10 +294,7 @@ do_badarg_opt(F, KF) -> ?line {'EXIT', {{badarg, kp}, _}} = (catch KF([1 | kp], [], foo, [])), ok. -term_sort(doc) -> - ["Sort terms on files."]; -term_sort(suite) -> - []; +%% Sort terms on files. term_sort(Config) when is_list(Config) -> ?line sort(term, [{compressed,false}], Config), ?line sort(term, [{order, fun compare/2}], Config), @@ -311,19 +302,13 @@ term_sort(Config) when is_list(Config) -> ?line sort(term, [{order, descending}], Config), ok. -term_keysort(doc) -> - ["Keysort terms on files."]; -term_keysort(suite) -> - []; +%% Keysort terms on files. term_keysort(Config) when is_list(Config) -> ?line keysort(term, [{tmpdir, ""}], Config), ?line keysort(term, [{order,descending}], Config), ok. -binary_term_sort(doc) -> - ["Sort binary terms on files."]; -binary_term_sort(suite) -> - []; +%% Sort binary terms on files. binary_term_sort(Config) when is_list(Config) -> PrivDir = ?privdir(Config), ?line sort({2, binary_term}, [], Config), @@ -334,20 +319,14 @@ binary_term_sort(Config) when is_list(Config) -> ?line sort(binary_term, [{order,descending}], Config), ok. -binary_term_keysort(doc) -> - ["Keysort binary terms on files."]; -binary_term_keysort(suite) -> - []; +%% Keysort binary terms on files. binary_term_keysort(Config) when is_list(Config) -> ?line keysort({3, binary_term}, [], Config), ?line keysort(binary_term, [], Config), ?line keysort(binary_term, [{order,descending}], Config), ok. -binary_sort(doc) -> - ["Sort binaries on files."]; -binary_sort(suite) -> - []; +%% Sort binaries on files. binary_sort(Config) when is_list(Config) -> PrivDir = ?privdir(Config), ?line sort({2, binary}, [], Config), @@ -358,40 +337,28 @@ binary_sort(Config) when is_list(Config) -> ?line sort(binary, [{order,descending}], Config), ok. -term_merge(doc) -> - ["Merge terms on files."]; -term_merge(suite) -> - []; +%% Merge terms on files. term_merge(Config) when is_list(Config) -> ?line merge(term, [{order, fun compare/2}], Config), ?line merge(term, [{order, ascending}, {compressed,true}], Config), ?line merge(term, [{order, descending}, {compressed,false}], Config), ok. -term_keymerge(doc) -> - ["Keymerge terms on files."]; -term_keymerge(suite) -> - []; +%% Keymerge terms on files. term_keymerge(Config) when is_list(Config) -> ?line keymerge(term, [], Config), ?line keymerge(term, [{order, descending}], Config), ?line funmerge(term, [], Config), ok. -binary_term_merge(doc) -> - ["Merge binary terms on files."]; -binary_term_merge(suite) -> - []; +%% Merge binary terms on files. binary_term_merge(Config) when is_list(Config) -> ?line merge(binary_term, [], Config), ?line merge({7, binary_term}, [], Config), ?line merge({3, binary_term}, [{order, fun compare/2}], Config), ok. -binary_term_keymerge(doc) -> - ["Keymerge binary terms on files."]; -binary_term_keymerge(suite) -> - []; +%% Keymerge binary terms on files. binary_term_keymerge(Config) when is_list(Config) -> ?line keymerge({3, binary_term}, [], Config), ?line keymerge(binary_term, [], Config), @@ -399,60 +366,39 @@ binary_term_keymerge(Config) when is_list(Config) -> ?line funmerge(binary_term, [], Config), ok. -binary_merge(doc) -> - ["Merge binaries on files."]; -binary_merge(suite) -> - []; +%% Merge binaries on files. binary_merge(Config) when is_list(Config) -> ?line merge(binary, [], Config), ?line merge({7, binary}, [], Config), ?line merge({3, binary}, [{order, fun compare/2}], Config), ok. -term_check(doc) -> - ["Check terms on files."]; -term_check(suite) -> - []; +%% Check terms on files. term_check(Config) when is_list(Config) -> ?line check(term, Config), ok. -binary_term_check(doc) -> - ["Check binary terms on files."]; -binary_term_check(suite) -> - []; +%% Check binary terms on files. binary_term_check(Config) when is_list(Config) -> ?line check(binary_term, Config), ok. -term_keycheck(doc) -> - ["Keycheck terms on files."]; -term_keycheck(suite) -> - []; +%% Keycheck terms on files. term_keycheck(Config) when is_list(Config) -> ?line keycheck(term, Config), ok. -binary_term_keycheck(doc) -> - ["Keycheck binary terms on files."]; -binary_term_keycheck(suite) -> - []; +%% Keycheck binary terms on files. binary_term_keycheck(Config) when is_list(Config) -> ?line keycheck(binary_term, Config), ok. -binary_check(doc) -> - ["Check binary terms on files."]; -binary_check(suite) -> - []; +%% Check binary terms on files. binary_check(Config) when is_list(Config) -> ?line check(binary, Config), ok. -inout(doc) -> - ["Funs as input or output."]; -inout(suite) -> - []; +%% Funs as input or output. inout(Config) when is_list(Config) -> BTF = {format, binary_term}, Foo = outfile("foo", Config), @@ -517,10 +463,7 @@ ofv(Value, A) -> ofv(Value, [L | A]) end. -many(doc) -> - ["Many temporary files."]; -many(suite) -> - []; +%% Many temporary files. many(Config) when is_list(Config) -> Foo = outfile("foo", Config), PrivDir = ?privdir(Config), @@ -581,10 +524,7 @@ many(Config) when is_list(Config) -> ?line true = P0 =:= pps(), ok. -misc(doc) -> - ["Some other tests."]; -misc(suite) -> - []; +%% Some other tests. misc(Config) when is_list(Config) -> BTF = {format, binary_term}, Foo = outfile("foo", Config), diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index fed6f9250f..58a235e737 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -327,10 +327,7 @@ del([H|T]) -> del(T); del([]) -> ok. -otp_5960(suite) -> - []; -otp_5960(doc) -> - ["Test that filelib:ensure_dir/1 returns ok or {error,Reason}"]; +%% Test that filelib:ensure_dir/1 returns ok or {error,Reason}. otp_5960(Config) when is_list(Config) -> ?line PrivDir = ?config(priv_dir, Config), ?line Dir = filename:join(PrivDir, "otp_5960_dir"), diff --git a/lib/stdlib/test/fixtable_SUITE.erl b/lib/stdlib/test/fixtable_SUITE.erl index 655002c611..270e4460e2 100644 --- a/lib/stdlib/test/fixtable_SUITE.erl +++ b/lib/stdlib/test/fixtable_SUITE.erl @@ -97,11 +97,8 @@ show(Term, Line) -> -endif. -fixbag(doc) -> - ["Check for bug OTP-5087, safe_fixtable for bags could give " - "incorrect lookups"]; -fixbag(suite) -> - []; +%% Check for bug OTP-5087; safe_fixtable for bags could give incorrect +%% lookups. fixbag(Config) when is_list(Config) -> ?line T = ets:new(x,[bag]), ?line ets:insert(T,{a,1}), @@ -116,10 +113,8 @@ fixbag(Config) when is_list(Config) -> -insert_same_key(doc) -> - ["Check correct behaviour if a key is deleted and reinserted during fixation."]; -insert_same_key(suite) -> - []; +%% Check correct behaviour if a key is deleted and reinserted during +%% fixation. insert_same_key(Config) when is_list(Config) -> ?line {ok,Dets1} = dets:open_file(?DETS_TMP1, [{file, dets_filename(?DETS_TMP1,Config)}]), @@ -195,10 +190,7 @@ insert_same_key(Tab,Mod,_Config) -> -owner_dies(doc) -> - ["Check correct behaviour if the table owner dies."]; -owner_dies(suite) -> - []; +%% Check correct behaviour if the table owner dies. owner_dies(Config) when is_list(Config) -> ?line P1 = start_commander(), ?line Ets1 = command(P1,{ets,new,[ets,[]]}), @@ -248,13 +240,8 @@ owner_dies(Config) when is_list(Config) -> ok. -other_process_closes(doc) -> - ["When another process closes an dets table, different " - "things should happen depending on if it has opened it before."]; - -other_process_closes(suite) -> - []; - +%% When another process closes an dets table, different things should +%% happen depending on if it has opened it before. other_process_closes(Config) when is_list(Config) -> ?line {ok,Dets} = dets:open_file(?DETS_TMP1, [{file, dets_filename(tmp1,Config)}]), @@ -279,11 +266,8 @@ other_process_closes(Config) when is_list(Config) -> ?line undefined = dets:info(Dets, safe_fixed), ok. -other_process_deletes(doc) -> - ["Check that fixtable structures are cleaned up if another process " - "deletes an ets table"]; -other_process_deletes(suite) -> - []; +%% Check that fixtable structures are cleaned up if another process +%% deletes an ets table. other_process_deletes(Config) when is_list(Config) -> ?line Ets = ets:new(ets,[public]), ?line P = start_commander(), @@ -297,10 +281,7 @@ other_process_deletes(Config) when is_list(Config) -> ?line undefined = ets:info(Ets, safe_fixed), ok. -multiple_fixes(doc) -> - ["Check that multiple safe_fixtable keeps the reference counter."]; -multiple_fixes(suite) -> - []; +%% Check that multiple safe_fixtable keeps the reference counter. multiple_fixes(Config) when is_list(Config) -> ?line {ok,Dets} = dets:open_file(?DETS_TMP1, [{file, dets_filename(?DETS_TMP1,Config)}]), @@ -331,11 +312,8 @@ multiple_fixes(Tab, Mod) -> ?line false = Mod:info(Tab, safe_fixed), ?line false = Mod:info(Tab,fixed). -multiple_processes(doc) -> - ["Check that multiple safe_fixtable across processes are reference " - "counted OK"]; -multiple_processes(suite) -> - []; +%% Check that multiple safe_fixtable across processes are reference +%% counted OK. multiple_processes(Config) when is_list(Config) -> ?line {ok,Dets} = dets:open_file(?DETS_TMP1,[{file, dets_filename(?DETS_TMP1, diff --git a/lib/stdlib/test/format_SUITE.erl b/lib/stdlib/test/format_SUITE.erl index b653623879..86a9779ec3 100644 --- a/lib/stdlib/test/format_SUITE.erl +++ b/lib/stdlib/test/format_SUITE.erl @@ -56,10 +56,7 @@ end_per_group(_GroupName, Config) -> Config. -hang_1(doc) -> - ["Bad args can hang (OTP-2400)"]; -hang_1(suite) -> - []; +%% OTP-2400. Bad args can hang. hang_1(Config) when is_list(Config) -> ?line _ = (catch io:format(a, "", [])), ?line _ = (catch io:format({}, "", [])), diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index 0f645a1381..de76d5d6f9 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -59,8 +59,6 @@ end_per_group(_GroupName, Config) -> %% Start an event manager. %% -------------------------------------- -start(doc) -> []; -start(suite) -> []; start(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -232,8 +230,6 @@ is_not_in_erlang_hibernate_1(N, Pid) -> end. -add_handler(doc) -> []; -add_handler(suite) -> []; add_handler(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line {error, my_error} = @@ -253,8 +249,6 @@ add_handler(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -add_sup_handler(doc) -> []; -add_sup_handler(suite) -> []; add_sup_handler(Config) when is_list(Config) -> ?line {ok,Pid} = gen_event:start({local, my_dummy_handler}), ?line {error, my_error} = @@ -295,8 +289,6 @@ add_sup_handler(Config) when is_list(Config) -> end, ok. -delete_handler(doc) -> []; -delete_handler(suite) -> []; delete_handler(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -327,8 +319,6 @@ delete_handler(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -swap_handler(doc) -> []; -swap_handler(suite) -> []; swap_handler(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -356,8 +346,6 @@ swap_handler(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -swap_sup_handler(doc) -> []; -swap_sup_handler(suite) -> []; swap_sup_handler(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), @@ -398,8 +386,6 @@ swap_sup_handler(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -notify(doc) -> []; -notify(suite) -> []; notify(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -510,8 +496,6 @@ notify(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -sync_notify(doc) -> []; -sync_notify(suite) -> []; sync_notify(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -625,8 +609,6 @@ sync_notify(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -call(doc) -> []; -call(suite) -> []; call(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -767,8 +749,6 @@ call(Config) when is_list(Config) -> flush() -> receive _ -> flush() after 0 -> ok end. -info(doc) -> []; -info(suite) -> []; info(Config) when is_list(Config) -> ?line {ok,_} = gen_event:start({local, my_dummy_handler}), ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]), @@ -893,10 +873,7 @@ info(Config) when is_list(Config) -> ?line ok = gen_event:stop(my_dummy_handler), ok. -call_format_status(suite) -> - []; -call_format_status(doc) -> - ["Test that sys:get_status/1,2 calls format_status/2"]; +%% Test that sys:get_status/1,2 calls format_status/2. call_format_status(Config) when is_list(Config) -> ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}), %% State here intentionally differs from what we expect from format_status @@ -914,10 +891,8 @@ call_format_status(Config) when is_list(Config) -> ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo2, ok. -call_format_status_anon(suite) -> - []; -call_format_status_anon(doc) -> - ["Test that sys:get_status/1,2 calls format_status/2 for anonymous gen_event processes"]; +%% Test that sys:get_status/1,2 calls format_status/2 for anonymous +%% gen_event processes. call_format_status_anon(Config) when is_list(Config) -> ?line {ok, Pid} = gen_event:start(), %% The 'Name' of the gen_event process will be a pid() here, so @@ -930,10 +905,7 @@ call_format_status_anon(Config) when is_list(Config) -> ok. -error_format_status(suite) -> - []; -error_format_status(doc) -> - ["Test that a handler error calls format_status/2"]; +%% Test that a handler error calls format_status/2. error_format_status(Config) when is_list(Config) -> ?line error_logger_forwarder:register(), OldFl = process_flag(trap_exit, true), @@ -961,10 +933,7 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. -get_state(suite) -> - []; -get_state(doc) -> - ["Test that sys:get_state/1,2 return the gen_event state"]; +%% Test that sys:get_state/1,2 return the gen_event state. get_state(Config) when is_list(Config) -> {ok, Pid} = gen_event:start({local, my_dummy_handler}), State1 = self(), @@ -984,10 +953,7 @@ get_state(Config) when is_list(Config) -> ok = gen_event:stop(Pid), ok. -replace_state(suite) -> - []; -replace_state(doc) -> - ["Test that replace_state/2,3 replace the gen_event state"]; +%% Test that replace_state/2,3 replace the gen_event state. replace_state(Config) when is_list(Config) -> {ok, Pid} = gen_event:start({local, my_dummy_handler}), State1 = self(), diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index 66c049de08..e73cef4175 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -135,7 +135,6 @@ start3(Config) when is_list(Config) -> ok. %% anonymous with ignore -start4(suite) -> []; start4(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -146,7 +145,6 @@ start4(Config) when is_list(Config) -> ok. %% anonymous with stop -start5(suite) -> []; start5(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -386,7 +384,6 @@ stop10(_Config) -> ok. %% Check that time outs in calls work -abnormal1(suite) -> []; abnormal1(Config) when is_list(Config) -> {ok, _Pid} = gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []), @@ -399,7 +396,6 @@ abnormal1(Config) when is_list(Config) -> %% Check that bad return values makes the fsm crash. Note that we must %% trap exit since we must link to get the real bad_return_ error -abnormal2(suite) -> []; abnormal2(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), ?line {ok, Pid} = @@ -718,13 +714,7 @@ is_not_in_erlang_hibernate_1(N, Pid) -> ok end. -%%sys1(suite) -> []; -%%sys1(_) -> - -enter_loop(suite) -> - []; -enter_loop(doc) -> - ["Test gen_fsm:enter_loop/4,5,6"]; +%% Test gen_fsm:enter_loop/4,5,6. enter_loop(Config) when is_list(Config) -> OldFlag = process_flag(trap_exit, true), diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 5f509cad62..484ca60a9c 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -110,7 +110,6 @@ end_per_testcase(_Case, Config) -> %% Start and stop a gen_server. %% -------------------------------------- -start(suite) -> []; start(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -412,7 +411,6 @@ crash(Config) when is_list(Config) -> %% handle_call. %% -------------------------------------- -call(suite) -> []; call(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -456,7 +454,6 @@ start_node(Name) -> global:sync(), N. -call_remote1(suite) -> []; call_remote1(Config) when is_list(Config) -> N = hubba, ?line Node = proplists:get_value(node,Config), @@ -469,7 +466,6 @@ call_remote1(Config) when is_list(Config) -> ?line true = (Reason == noproc) orelse (Reason == boom), ok. -call_remote2(suite) -> []; call_remote2(Config) when is_list(Config) -> ?line N = hubba, ?line Node = proplists:get_value(node,Config), @@ -483,7 +479,6 @@ call_remote2(Config) when is_list(Config) -> ?line true = (Reason == noproc) orelse (Reason == boom), ok. -call_remote3(suite) -> []; call_remote3(Config) when is_list(Config) -> ?line Node = proplists:get_value(node,Config), @@ -500,7 +495,6 @@ call_remote3(Config) when is_list(Config) -> %% Test call to nonexisting node %% -------------------------------------- -call_remote_n1(suite) -> []; call_remote_n1(Config) when is_list(Config) -> ?line N = hubba, ?line Node = proplists:get_value(node,Config), @@ -512,7 +506,6 @@ call_remote_n1(Config) when is_list(Config) -> ok. -call_remote_n2(suite) -> []; call_remote_n2(Config) when is_list(Config) -> ?line N = hubba, ?line Node = proplists:get_value(node,Config), @@ -525,7 +518,6 @@ call_remote_n2(Config) when is_list(Config) -> ok. -call_remote_n3(suite) -> []; call_remote_n3(Config) when is_list(Config) -> ?line Node = proplists:get_value(node,Config), @@ -543,7 +535,6 @@ call_remote_n3(Config) when is_list(Config) -> %% handle_cast. %% -------------------------------------- -cast(suite) -> []; cast(Config) when is_list(Config) -> ?line {ok, Pid} = gen_server:start({local, my_test_name}, @@ -576,8 +567,7 @@ cast(Config) when is_list(Config) -> end, ok. -cast_fast(suite) -> []; -cast_fast(doc) -> ["Test that cast really return immediately"]; +%% Test that cast really return immediately. cast_fast(Config) when is_list(Config) -> ?line {ok,Node} = start_node(hubba), ?line {_,"@"++Host} = lists:splitwith(fun ($@) -> false; (_) -> true end, @@ -610,7 +600,6 @@ cast_fast_messup() -> %% Test handle_info. %% -------------------------------------- -info(suite) -> []; info(Config) when is_list(Config) -> ?line {ok, Pid} = gen_server:start({local, my_test_name}, @@ -749,7 +738,6 @@ is_in_erlang_hibernate_1(N, Pid) -> %% handle_cast. %% -------------------------------------- -abcast(suite) -> []; abcast(Config) when is_list(Config) -> ?line {ok, Pid} = gen_server:start({local, my_test_name}, @@ -789,7 +777,6 @@ abcast(Config) when is_list(Config) -> %% handle_call. %% -------------------------------------- -multicall(suite) -> []; multicall(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), @@ -829,7 +816,6 @@ multicall(Config) when is_list(Config) -> ok. %% OTP-3587 -multicall_down(suite) -> []; multicall_down(Config) when is_list(Config) -> %% We need a named host which is inaccessible. ?line Name = node@test01, @@ -855,11 +841,8 @@ busy_wait_for_process(Pid,N) -> ok end. %%-------------------------------------------------------------- -spec_init(doc) -> - ["Test gen_server:enter_loop/[3,4,5]. Used when you want to write " - "your own special init-phase."]; -spec_init(suite) -> - []; +%% Test gen_server:enter_loop/[3,4,5]. Used when you want to write +%% your own special init-phase. spec_init(Config) when is_list(Config) -> OldFlag = process_flag(trap_exit, true), @@ -953,10 +936,8 @@ spec_init(Config) when is_list(Config) -> ok. %%-------------------------------------------------------------- -spec_init_local_registered_parent(doc) -> - ["Test that terminate is run when the parent is a locally registered " - "process OTP-4820"]; -spec_init_local_registered_parent(suite) -> []; +%% OTP-4820. Test that terminate is run when the parent is a locally +%% registered process. spec_init_local_registered_parent(Config) when is_list(Config) -> register(foobar, self()), @@ -973,11 +954,10 @@ spec_init_local_registered_parent(Config) when is_list(Config) -> end, unregister(foobar), ok. + %%-------------------------------------------------------------- -spec_init_global_registered_parent(doc) -> - ["Test that terminate is run when the parent is a global registered " - "process OTP-4820"]; -spec_init_global_registered_parent(suite) -> []; +%% OTP-4820. Test that terminate is run when the parent is a global registered +%% process. spec_init_global_registered_parent(Config) when is_list(Config) -> global:register_name(foobar, self()), @@ -996,11 +976,10 @@ spec_init_global_registered_parent(Config) when is_list(Config) -> end, global:unregister_name(foobar), ok. + %%-------------------------------------------------------------- -otp_5854(suite) -> - []; -otp_5854(doc) -> - ["Test check for registered name in enter_loop/3,4,5"]; + +%% Test check for registered name in enter_loop/3,4,5. otp_5854(Config) when is_list(Config) -> OldFlag = process_flag(trap_exit, true), @@ -1092,12 +1071,7 @@ do_otp_7669_stop() -> ?MODULE, stop, []), ?line undefined = global:whereis_name(?MODULE). -%% Verify that sys:get_status correctly calls our format_status/2 fun -%% -call_format_status(suite) -> - []; -call_format_status(doc) -> - ["Test that sys:get_status/1,2 calls format_status/2"]; +%% Verify that sys:get_status correctly calls our format_status/2 fun. call_format_status(Config) when is_list(Config) -> ?line {ok, Pid} = gen_server:start_link({local, call_format_status}, ?MODULE, [], []), @@ -1131,12 +1105,7 @@ call_format_status(Config) when is_list(Config) -> ?line [format_status_called | _] = lists:reverse(Data5), ok. -%% Verify that error termination correctly calls our format_status/2 fun -%% -error_format_status(suite) -> - []; -error_format_status(doc) -> - ["Test that an error termination calls format_status/2"]; +%% Verify that error termination correctly calls our format_status/2 fun. error_format_status(Config) when is_list(Config) -> ?line error_logger_forwarder:register(), OldFl = process_flag(trap_exit, true), @@ -1188,11 +1157,6 @@ terminate_crash_format(Config) when is_list(Config) -> ok. %% Verify that sys:get_state correctly returns gen_server state -%% -get_state(suite) -> - []; -get_state(doc) -> - ["Test that sys:get_state/1,2 return the gen_server state"]; get_state(Config) when is_list(Config) -> State = self(), {ok, _Pid} = gen_server:start_link({local, get_state}, @@ -1208,11 +1172,6 @@ get_state(Config) when is_list(Config) -> ok. %% Verify that sys:replace_state correctly replaces gen_server state -%% -replace_state(suite) -> - []; -replace_state(doc) -> - ["Test that sys:replace_state/1,2 replace the gen_server state"]; replace_state(Config) when is_list(Config) -> State = self(), {ok, _Pid} = gen_server:start_link({local, replace_state}, diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl index 4e862053b1..a0c3e9f9e5 100644 --- a/lib/stdlib/test/id_transform_SUITE.erl +++ b/lib/stdlib/test/id_transform_SUITE.erl @@ -55,7 +55,7 @@ end_per_group(_GroupName, Config) -> Config. -id_transform(doc) -> "Test erl_id_trans."; +%% Test erl_id_trans. id_transform(Config) when is_list(Config) -> File = filename:join([code:lib_dir(stdlib),"examples", "erl_id_trans.erl"]), diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 88d0f54d99..78bff49577 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -88,10 +88,7 @@ end_per_group(_GroupName, Config) -> Config. -error_1(doc) -> - ["Error cases for output"]; -error_1(suite) -> - []; +%% Error cases for output. error_1(Config) when is_list(Config) -> %% We don't do erroneous output on stdout - the test server %% seems to catch that somehow. @@ -195,10 +192,7 @@ float_g(Config) when is_list(Config) -> float_g_1(Fmt, V, Min, Max) -> [fmt(Fmt, [V*math:pow(10, E)]) || E <- lists:seq(Min, Max)]. -otp_5403(doc) -> - ["OTP-5403. ~s formats I/O lists and a single binary."]; -otp_5403(suite) -> - []; +%% OTP-5403. ~s formats I/O lists and a single binary. otp_5403(Config) when is_list(Config) -> ?line "atom" = fmt("~s", [atom]), ?line "binary" = fmt("~s", [<<"binary">>]), @@ -207,10 +201,7 @@ otp_5403(Config) when is_list(Config) -> ?line "somebinaries" = fmt("~s", [[<<"some">>,[<<"binaries">>]]]), ok. -otp_5813(doc) -> - ["OTP-5813. read/3 is new."]; -otp_5813(suite) -> - []; +%% OTP-5813. read/3 is new. otp_5813(Config) when is_list(Config) -> ?line PrivDir = ?privdir(Config), ?line File = filename:join(PrivDir, "test"), @@ -229,10 +220,7 @@ otp_5813(Config) when is_list(Config) -> file:delete(File), ok. -otp_6230(doc) -> - ["OTP-6230. ~p and ~P with (huge) binaries."]; -otp_6230(suite) -> - []; +%% OTP-6230. ~p and ~P with (huge) binaries. otp_6230(Config) when is_list(Config) -> %% The problem is actually huge binaries, but the small tests here %% just run through most of the modified code. @@ -254,10 +242,7 @@ otp_6230(Config) when is_list(Config) -> ?line "<<\"aaaa"++_ = fmt("~P", [B, 20000]), ok. -otp_6282(doc) -> - ["OTP-6282. ~p truncates strings (like binaries) depending on depth."]; -otp_6282(suite) -> - []; +%% OTP-6282. ~p truncates strings (like binaries) depending on depth. otp_6282(Config) when is_list(Config) -> ?line "[]" = p("", 1, 20, 1), ?line "[]" = p("", 1, 20, -1), @@ -301,10 +286,7 @@ otp_6282(Config) when is_list(Config) -> ok. -otp_6354(doc) -> - ["OTP-6354. io_lib_pretty rewritten."]; -otp_6354(suite) -> - []; +%% OTP-6354. io_lib_pretty rewritten. otp_6354(Config) when is_list(Config) -> %% A few tuples: ?line "{}" = p({}, 1, 20, -1), @@ -960,28 +942,19 @@ otp_6354(Config) when is_list(Config) -> ?line "{a,b,...}" = fmt("~W", [{a,b,c,d,e}, 3]), ok. -otp_6495(doc) -> - ["OTP-6495. io_lib_pretty bugfix."]; -otp_6495(suite) -> - []; +%% OTP-6495. io_lib_pretty bugfix. otp_6495(Config) when is_list(Config) -> ?line bt(<<"[120,120,120,120,120,120,120,120,120,120,120,120,120,120," "120,120,120,120,120]<<1>>">>, fmt("~w~p", ["xxxxxxxxxxxxxxxxxxx", <<1>>])), ok. -otp_6517(doc) -> - ["OTP-6517. The Format argument of fwrite can be a binary."]; -otp_6517(suite) -> - []; +%% OTP-6517. The Format argument of fwrite can be a binary. otp_6517(Config) when is_list(Config) -> ?line "string" = fmt(<<"~s">>, [<<"string">>]), ok. -otp_6502(doc) -> - ["OTP-6502. Bits."]; -otp_6502(suite) -> - []; +%% OTP-6502. Bits. otp_6502(Config) when is_list(Config) -> ?line bt(<< "[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25]" @@ -991,10 +964,7 @@ otp_6502(Config) when is_list(Config) -> fmt("~w~p", [lists:seq(0, 25), <<17:25>>])), ok. -otp_7421(doc) -> - ["OTP-7421. Soft limit of 60 chars removed when pretty printing."]; -otp_7421(suite) -> - []; +%% OTP-7421. Soft limit of 60 chars removed when pretty printing. otp_7421(Config) when is_list(Config) -> bt(<<"{aa,bb,\n" " c,dd,\n" @@ -1062,10 +1032,7 @@ rfd(aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa, 0) -> rfd(_, _) -> no. -manpage(doc) -> - ["The examples in io(3) and io_lib(3)."]; -manpage(suite) -> - []; +%% The examples in io(3) and io_lib(3). manpage(Config) when is_list(Config) -> %% The examples that write or print only, not the ones that read... @@ -1131,10 +1098,7 @@ manpage(Config) when is_list(Config) -> lists:flatten(io_lib:write({1,[2],[3],[4,5],6,7,8,9}, 5))), ok. -otp_6708(doc) -> - ["OTP-6708. Fewer newlines when pretty-printing."]; -otp_6708(suite) -> - []; +%% OTP-6708. Fewer newlines when pretty-printing. otp_6708(Config) when is_list(Config) -> ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n" " 23,24,25,26,27,28,29|...]">>, @@ -1239,10 +1203,7 @@ otp_6708(Config) when is_list(Config) -> otp_7084() -> [{timetrap,{minutes,3}}]. -otp_7084(doc) -> - ["OTP-7084. Printing floating point numbers nicely."]; -otp_7084(suite) -> - []; +%% OTP-7084. Printing floating point numbers nicely. otp_7084(Config) when is_list(Config) -> L = [{g_warm_up, fun g_warm_up/0}, {g_big_pos_float, fun g_big_pos_float/0}, @@ -1934,8 +1895,7 @@ read_newlines(Fd, Acc, N0) -> -otp_8989(doc) -> - "OTP-8989 io:format for ~F.Ps ignores P in some cases"; +%% OTP-8989 io:format for ~F.Ps ignores P in some cases. otp_8989(Suite) when is_list(Suite) -> Hello = "Hello", ?line " Hello" = fmt("~6.6s", [Hello]), @@ -2010,8 +1970,7 @@ otp_8989(Suite) when is_list(Suite) -> ?line "Hel " = fmt("~*.*s", [-4,3,Hello]), ok. -io_lib_fread_literal(doc) -> - "OTP-9439 io_lib:fread bug for literate at end"; +%% OTP-9439 io_lib:fread bug for literate at end. io_lib_fread_literal(Suite) when is_list(Suite) -> ?line {more,"~d",0,""} = io_lib:fread("~d", ""), ?line {error,{fread,integer}} = io_lib:fread("~d", " "), @@ -2037,8 +1996,7 @@ io_lib_fread_literal(Suite) when is_list(Suite) -> ok. -printable_range(doc) -> - "Check that the printable range set by the user actually works"; +%% Check that the printable range set by the user actually works. printable_range(Suite) when is_list(Suite) -> Pa = filename:dirname(code:which(?MODULE)), {ok, UNode} = test_server:start_node(printable_range_unicode, slave, @@ -2140,8 +2098,7 @@ flush_from_port(P) -> ok end. -io_lib_print_binary_depth_one(doc) -> - "Test binaries printed with a depth of one behave correctly"; +%% Test binaries printed with a depth of one behave correctly. io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> ?line "<<>>" = fmt("~W", [<<>>, 1]), ?line "<<>>" = fmt("~P", [<<>>, 1]), @@ -2151,8 +2108,7 @@ io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> ?line "<<...>>" = fmt("~P", [<<1:7>>, 1]), ok. -otp_10302(doc) -> - "OTP-10302. Unicode"; +%% OTP-10302. Unicode. otp_10302(Suite) when is_list(Suite) -> Pa = filename:dirname(code:which(?MODULE)), {ok, UNode} = test_server:start_node(printable_range_unicode, slave, @@ -2208,15 +2164,13 @@ pretty(Term, Opts) when is_list(Opts) -> is_latin1(S) -> S >= 0 andalso S =< 255. -otp_10836(doc) -> - "OTP-10836. ~ts extended to latin1"; +%% OTP-10836. ~ts extended to latin1. otp_10836(Suite) when is_list(Suite) -> S = io_lib:format("~ts", [[<<"äpple"/utf8>>, <<"äpple">>]]), "äppleäpple" = lists:flatten(S), ok. -otp_10755(doc) -> - "OTP-10755. The 'l' modifier"; +%% OTP-10755. The 'l' modifier otp_10755(Suite) when is_list(Suite) -> S = "string", "\"string\"" = fmt("~p", [S]), diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index 4a009814fa..0f670a5994 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -110,10 +110,7 @@ end_per_group(_GroupName, Config) -> uprompt(_L) -> [1050,1072,1082,1074,1086,32,1077,32,85,110,105,99,111,100,101,32,63]. -unicode_prompt(suite) -> - []; -unicode_prompt(doc) -> - ["Test that an Unicode prompt does not crash the shell"]; +%% Test that an Unicode prompt does not crash the shell. unicode_prompt(Config) when is_list(Config) -> ?line PA = filename:dirname(code:which(?MODULE)), case proplists:get_value(default_shell,Config) of @@ -153,10 +150,7 @@ unicode_prompt(Config) when is_list(Config) -> ok. -setopts_getopts(suite) -> - []; -setopts_getopts(doc) -> - ["Check io:setopts and io:getopts functions"]; +%% Check io:setopts and io:getopts functions. setopts_getopts(Config) when is_list(Config) -> ?line FileName = filename:join([?config(priv_dir,Config), "io_proto_SUITE_setopts_getopts.dat"]), @@ -276,10 +270,7 @@ get_lc_ctype() -> "ISO-8859-1" end. -unicode_options(suite) -> - []; -unicode_options(doc) -> - ["Tests various unicode options"]; +%% Test various unicode options. unicode_options(Config) when is_list(Config) -> DataDir = ?config(data_dir,Config), PrivDir = ?config(priv_dir,Config), @@ -669,10 +660,7 @@ random_unicode(N) -> end. -binary_options(suite) -> - []; -binary_options(doc) -> - ["Tests variants with binary option"]; +%% Test variants with binary option. binary_options(Config) when is_list(Config) -> DataDir = ?config(data_dir,Config), PrivDir = ?config(priv_dir,Config), @@ -758,10 +746,7 @@ binary_options(Config) when is_list(Config) -> ],[],[],"-oldshell"), ok. -bc_with_r12(suite) -> - []; -bc_with_r12(doc) -> - ["Test io protocol compatibility with R12 nodes"]; +%% Test io protocol compatibility with R12 nodes. bc_with_r12(Config) when is_list(Config) -> case test_server:is_release_available("r12b") of true -> bc_with_r12_1(Config); @@ -911,10 +896,7 @@ hold_the_line(Parent,Filename,Options) -> end. -bc_with_r12_gl(suite) -> - []; -bc_with_r12_gl(doc) -> - ["Test io protocol compatibility with R12 nodes (terminals)"]; +%% Test io protocol compatibility with R12 nodes (terminals). bc_with_r12_gl(Config) when is_list(Config) -> case test_server:is_release_available("r12b") of true -> @@ -928,10 +910,7 @@ bc_with_r12_gl(Config) when is_list(Config) -> {skip,"No R12B found"} end. -bc_with_r12_ogl(suite) -> - []; -bc_with_r12_ogl(doc) -> - ["Test io protocol compatibility with R12 nodes (oldshell)"]; +%% Test io protocol compatibility with R12 nodes (oldshell). bc_with_r12_ogl(Config) when is_list(Config) -> case test_server:is_release_available("r12b") of true -> @@ -1171,10 +1150,7 @@ answering_machine2(OthNode,OthReg,Me) -> ok. -read_modes_ogl(suite) -> - []; -read_modes_ogl(doc) -> - ["Test various modes when reading from the group leade from another machine"]; +%% Test various modes when reading from the group leade from another machine. read_modes_ogl(Config) when is_list(Config) -> case get_progs() of {error,Reason} -> @@ -1183,10 +1159,7 @@ read_modes_ogl(Config) when is_list(Config) -> read_modes_gl_1(Config,answering_machine2) end. -read_modes_gl(suite) -> - []; -read_modes_gl(doc) -> - ["Test various modes when reading from the group leade from another machine"]; +%% Test various modes when reading from the group leade from another machine. read_modes_gl(Config) when is_list(Config) -> case {get_progs(),proplists:get_value(default_shell,Config)} of {{error,Reason},_} -> @@ -1276,10 +1249,7 @@ read_modes_gl_1(_Config,Machine) -> ok. -broken_unicode(suite) -> - []; -broken_unicode(doc) -> - ["Test behaviour when reading broken Unicode files"]; +%% Test behaviour when reading broken Unicode files broken_unicode(Config) when is_list(Config) -> Dir = ?config(priv_dir,Config), Latin1Name = filename:join([Dir,"latin1_data_file.dat"]), @@ -1311,10 +1281,7 @@ loop_through_file2(F,Bin,Chunk,Enc) when is_binary(Bin) -> -eof_on_pipe(suite) -> - []; -eof_on_pipe(doc) -> - ["tests eof before newline on stdin when erlang is in pipe"]; +%% Test eof before newline on stdin when erlang is in pipe. eof_on_pipe(Config) when is_list(Config) -> case {get_progs(),os:type()} of {{error,Reason},_} -> diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index 1f60ed50fe..8d3aa9de7b 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -146,8 +146,6 @@ end_per_testcase(_Case, _Config) -> % Test cases starts here. % -append_1(doc) -> []; -append_1(suite) -> []; append_1(Config) when is_list(Config) -> ?line "abcdef"=lists:append(["abc","def"]), ?line [hej, du,[glade, [bagare]]]= @@ -155,20 +153,15 @@ append_1(Config) when is_list(Config) -> ?line [10, [elem]]=lists:append([[10], [[elem]]]), ok. -append_2(doc) -> []; -append_2(suite) -> []; append_2(Config) when is_list(Config) -> ?line "abcdef"=lists:append("abc", "def"), ?line [hej, du]=lists:append([hej], [du]), ?line [10, [elem]]=lists:append([10], [[elem]]), ok. -reverse(suite) -> - []; -reverse(doc) -> - ["Tests the lists:reverse() implementation. The function is " - "`non-blocking', and only processes a fixed number of elements " - "at a time."]; +%% Tests the lists:reverse() implementation. The function is +%% `non-blocking', and only processes a fixed number of elements at a +%% time. reverse(Config) when is_list(Config) -> ?line reverse_test(0), ?line reverse_test(1), @@ -203,10 +196,8 @@ reverse_test(Num) -> List0 = lists:reverse(List), ok. -member(doc) -> - ["Tests the lists:member() implementation." - "This test case depends on lists:reverse() to work, " - "wich is tested in a separate test case."]; +%% Test the lists:member() implementation. This test case depends on +%% lists:reverse() to work, wich is tested in a separate test case. member(Config) when is_list(Config) -> ?line {'EXIT',{badarg,_}} = (catch lists:member(45, {a,b,c})), ?line {'EXIT',{badarg,_}} = (catch lists:member(45, [0|non_list_tail])), @@ -379,9 +370,6 @@ takewhile(Config) when is_list(Config) -> ok. -keystore(doc) -> - ["OTP-XXX."]; -keystore(suite) -> []; keystore(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch lists:keystore(key, 0, [], {1})), ?line {'EXIT',_} = (catch lists:keystore(key, 1, {}, {})), @@ -398,9 +386,6 @@ keystore(Config) when is_list(Config) -> ?line [{1,a}] = lists:keystore(foo, 1, [], {1,a}), ok. -keytake(doc) -> - ["OTP-XXX."]; -keytake(suite) -> []; keytake(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch lists:keytake(key, 0, [])), ?line {'EXIT',_} = (catch lists:keytake(key, 1, {})), @@ -427,8 +412,6 @@ keyreplace(Config) when is_list(Config) -> {'EXIT',_} = (catch lists:keyreplace(k, 0, [], {a,b})), ok. -merge(doc) -> ["merge functions"]; -merge(suite) -> []; merge(Config) when is_list(Config) -> %% merge list of lists @@ -490,8 +473,7 @@ merge(Config) when is_list(Config) -> ok. -rmerge(doc) -> ["reverse merge functions"]; -rmerge(suite) -> []; +%% reverse merge functions rmerge(Config) when is_list(Config) -> Two = [2,1], @@ -533,8 +515,6 @@ rmerge(Config) when is_list(Config) -> ok. -sort_1(doc) -> ["sort/1"]; -sort_1(suite) -> []; sort_1(Config) when is_list(Config) -> ?line [] = lists:sort([]), ?line [a] = lists:sort([a]), @@ -552,8 +532,7 @@ sort_1(Config) when is_list(Config) -> ?line lists:foreach(fun check/1, perms([1,2,3,4,5,6,7,8])), ok. -sort_rand(doc) -> ["sort/1 on big randomized lists"]; -sort_rand(suite) -> []; +%% sort/1 on big randomized lists sort_rand(Config) when is_list(Config) -> ?line ok = check(biglist(10)), ?line ok = check(biglist(100)), @@ -564,8 +543,8 @@ sort_rand(Config) when is_list(Config) -> %% sort/1 was really stable for a while - the order of equal elements %% was kept - but since the performance suffered a bit, this "feature" %% was removed. -sort_stable(doc) -> ["sort/1 should be stable for equal terms."]; -sort_stable(suite) -> []; + +%% sort/1 should be stable for equal terms. sort_stable(Config) when is_list(Config) -> ?line ok = check_stability(bigfunlist(10)), ?line ok = check_stability(bigfunlist(100)), @@ -612,8 +591,6 @@ expl_pid([], L) -> L. -usort_1(suite) -> []; -usort_1(doc) -> [""]; usort_1(Conf) when is_list(Conf) -> ?line [] = lists:usort([]), ?line [1] = lists:usort([1]), @@ -635,8 +612,6 @@ usort_1(Conf) when is_list(Conf) -> ok. -umerge(suite) -> []; -umerge(doc) -> [""]; umerge(Conf) when is_list(Conf) -> %% merge list of lists ?line [] = lists:umerge([]), @@ -710,8 +685,6 @@ umerge(Conf) when is_list(Conf) -> ok. -rumerge(suite) -> []; -rumerge(doc) -> [""]; rumerge(Conf) when is_list(Conf) -> Two = [2,1], Six = [6,5,4,3,2,1], @@ -769,8 +742,7 @@ rumerge(Conf) when is_list(Conf) -> lists:reverse(lists:rumerge(lists:reverse(L1), lists:reverse(L2))), ok. -usort_rand(doc) -> ["usort/1 on big randomized lists"]; -usort_rand(suite) -> []; +%% usort/1 on big randomized lists. usort_rand(Config) when is_list(Config) -> ?line ok = ucheck(biglist(10)), ?line ok = ucheck(biglist(100)), @@ -783,8 +755,7 @@ usort_rand(Config) when is_list(Config) -> ?line ok = ucheck(ubiglist(10000)), ok. -usort_stable(doc) -> ["usort/1 should keep the first duplicate."]; -usort_stable(suite) -> []; +%% usort/1 should keep the first duplicate. usort_stable(Config) when is_list(Config) -> ?line ok = ucheck_stability(bigfunlist(3)), ?line ok = ucheck_stability(bigfunlist(10)), @@ -822,8 +793,7 @@ ucheck_stability(L) -> check_stab(L, U, S, "usort/1", "ukeysort/2"). -keymerge(doc) -> ["Key merge two lists."]; -keymerge(suite) -> []; +%% Key merge two lists. keymerge(Config) when is_list(Config) -> Two = [{1,a},{2,b}], @@ -856,8 +826,7 @@ keymerge(Config) when is_list(Config) -> ok. -rkeymerge(doc) -> ["Reverse key merge two lists."]; -rkeymerge(suite) -> []; +%% Reverse key merge two lists. rkeymerge(Config) when is_list(Config) -> Two = [{2,b},{1,a}], @@ -894,8 +863,6 @@ rkeymerge(Config) when is_list(Config) -> ok. -keysort_1(doc) -> ["keysort"]; -keysort_1(suite) -> []; keysort_1(Config) when is_list(Config) -> ?line ok = keysort_check(1, [], []), ?line ok = keysort_check(1, [{a,b}], [{a,b}]), @@ -929,8 +896,7 @@ keysort_1(Config) when is_list(Config) -> ok. -keysort_stable(doc) -> ["keysort should be stable"]; -keysort_stable(suite) -> []; +%% keysort should be stable keysort_stable(Config) when is_list(Config) -> ?line ok = keysort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]), ?line ok = keysort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]), @@ -942,8 +908,7 @@ keysort_stable(Config) when is_list(Config) -> [{1,a},{1,b},{1,a},{1,a}]), ok. -keysort_error(doc) -> ["keysort should exit when given bad arguments"]; -keysort_error(suite) -> []; +%% keysort should exit when given bad arguments keysort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:keysort(0, [{1,b},{1,c}])), ?line {'EXIT', _} = (catch lists:keysort(3, [{1,b},{1,c}])), @@ -955,14 +920,12 @@ keysort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:keysort(1, [{1,b} | {1,c}])), ok. -keysort_i(doc) -> ["keysort with other key than first element"]; -keysort_i(suite) -> []; +%% keysort with other key than first element keysort_i(Config) when is_list(Config) -> ?line ok = keysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]), ok. -keysort_rand(doc) -> ["keysort on big randomized lists"]; -keysort_rand(suite) -> []; +%% keysort on big randomized lists keysort_rand(Config) when is_list(Config) -> ?line ok = keysort_check3(1, biglist(10)), ?line ok = keysort_check3(1, biglist(100)), @@ -1013,8 +976,7 @@ keycompare(I, J, A, B) when element(I, A) == element(I, B), ok. -ukeymerge(suite) -> []; -ukeymerge(doc) -> ["Merge two lists while removing duplicates."]; +%% Merge two lists while removing duplicates. ukeymerge(Conf) when is_list(Conf) -> Two = [{1,a},{2,b}], @@ -1068,9 +1030,7 @@ ukeymerge(Conf) when is_list(Conf) -> ok. -rukeymerge(suite) -> []; -rukeymerge(doc) -> - ["Reverse merge two lists while removing duplicates."]; +%% Reverse merge two lists while removing duplicates. rukeymerge(Conf) when is_list(Conf) -> Two = [{2,b},{1,a}], @@ -1124,8 +1084,6 @@ rukeymerge(Conf) when is_list(Conf) -> ok. -ukeysort_1(doc) -> ["ukeysort"]; -ukeysort_1(suite) -> []; ukeysort_1(Config) when is_list(Config) -> ?line ok = ukeysort_check(1, [], []), ?line ok = ukeysort_check(1, [{a,b}], [{a,b}]), @@ -1186,8 +1144,7 @@ ukeysort_1(Config) when is_list(Config) -> ok. -ukeysort_stable(doc) -> ["ukeysort should keep the first duplicate"]; -ukeysort_stable(suite) -> []; +%% ukeysort should keep the first duplicate. ukeysort_stable(Config) when is_list(Config) -> ?line ok = ukeysort_check(1, [{1,b},{1,c}], [{1,b}]), ?line ok = ukeysort_check(1, [{1,c},{1,b}], [{1,c}]), @@ -1208,8 +1165,7 @@ ukeysort_stable(Config) when is_list(Config) -> end, ok. -ukeysort_error(doc) -> ["ukeysort should exit when given bad arguments"]; -ukeysort_error(suite) -> []; +%% ukeysort should exit when given bad arguments. ukeysort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:ukeysort(0, [{1,b},{1,c}])), ?line {'EXIT', _} = (catch lists:ukeysort(3, [{1,b},{1,c}])), @@ -1221,14 +1177,12 @@ ukeysort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:ukeysort(1, [{1,b} | {1,c}])), ok. -ukeysort_i(doc) -> ["ukeysort with other key than first element"]; -ukeysort_i(suite) -> []; +%% ukeysort with other key than first element. ukeysort_i(Config) when is_list(Config) -> ?line ok = ukeysort_check(2, [{a,2},{b,1},{c,3}], [{b,1},{a,2},{c,3}]), ok. -ukeysort_rand(doc) -> ["ukeysort on big randomized lists"]; -ukeysort_rand(suite) -> []; +%% ukeysort on big randomized lists. ukeysort_rand(Config) when is_list(Config) -> ?line ok = ukeysort_check3(2, biglist(10)), ?line ok = ukeysort_check3(2, biglist(100)), @@ -1302,8 +1256,7 @@ ukeycompare(I, J, A, B) when A =/= B, -funmerge(doc) -> ["Merge two lists using a fun."]; -funmerge(suite) -> []; +%% Merge two lists using a fun. funmerge(Config) when is_list(Config) -> Two = [1,2], @@ -1332,8 +1285,7 @@ funmerge(Config) when is_list(Config) -> ok. -rfunmerge(doc) -> ["Reverse merge two lists using a fun."]; -rfunmerge(suite) -> []; +%% Reverse merge two lists using a fun. rfunmerge(Config) when is_list(Config) -> Two = [2,1], @@ -1366,8 +1318,6 @@ rfunmerge(Config) when is_list(Config) -> ok. -funsort_1(doc) -> ["sort/2"]; -funsort_1(suite) -> []; funsort_1(Config) when is_list(Config) -> ?line ok = funsort_check(1, [], []), ?line ok = funsort_check(1, [{a,b}], [{a,b}]), @@ -1393,8 +1343,7 @@ funsort_1(Config) when is_list(Config) -> ok. -funsort_stable(doc) -> ["sort/2 should be stable"]; -funsort_stable(suite) -> []; +%% sort/2 should be stable. funsort_stable(Config) when is_list(Config) -> ?line ok = funsort_check(1, [{1,b},{1,c}], [{1,b},{1,c}]), ?line ok = funsort_check(1, [{1,c},{1,b}], [{1,c},{1,b}]), @@ -1403,16 +1352,14 @@ funsort_stable(Config) when is_list(Config) -> [{1,c},{1,b},{2,x},{2,a},{3,p}]), ok. -funsort_error(doc) -> ["sort/2 should exit when given bad arguments"]; -funsort_error(suite) -> []; +%% sort/2 should exit when given bad arguments. funsort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:sort(1, [{1,b} , {1,c}])), ?line {'EXIT', _} = (catch lists:sort(fun(X,Y) -> X =< Y end, [{1,b} | {1,c}])), ok. -funsort_rand(doc) -> ["sort/2 on big randomized lists"]; -funsort_rand(suite) -> []; +%% sort/2 on big randomized lists. funsort_rand(Config) when is_list(Config) -> ?line ok = funsort_check3(1, biglist(10)), ?line ok = funsort_check3(1, biglist(100)), @@ -1434,8 +1381,7 @@ funsort_check(I, Input, Expected) -> check_sorted(I, Input, Expected). -ufunmerge(suite) -> []; -ufunmerge(doc) -> ["Merge two lists while removing duplicates using a fun."]; +%% Merge two lists while removing duplicates using a fun. ufunmerge(Conf) when is_list(Conf) -> Two = [1,2], @@ -1474,9 +1420,7 @@ ufunmerge(Conf) when is_list(Conf) -> ok. -rufunmerge(suite) -> []; -rufunmerge(doc) -> - ["Reverse merge two lists while removing duplicates using a fun."]; +%% Reverse merge two lists while removing duplicates using a fun. rufunmerge(Conf) when is_list(Conf) -> Two = [2,1], Six = [6,5,4,3,2,1], @@ -1519,8 +1463,6 @@ rufunmerge(Conf) when is_list(Conf) -> ok. -ufunsort_1(doc) -> ["usort/2"]; -ufunsort_1(suite) -> []; ufunsort_1(Config) when is_list(Config) -> ?line ok = ufunsort_check(1, [], []), ?line ok = ufunsort_check(1, [{a,b}], [{a,b}]), @@ -1575,8 +1517,7 @@ ufunsort_1(Config) when is_list(Config) -> ok. -ufunsort_stable(doc) -> ["usort/2 should be stable"]; -ufunsort_stable(suite) -> []; +%% usort/2 should be stable. ufunsort_stable(Config) when is_list(Config) -> ?line ok = ufunsort_check(1, [{1,b},{1,c}], [{1,b}]), ?line ok = ufunsort_check(1, [{1,c},{1,b}], [{1,c}]), @@ -1593,16 +1534,14 @@ ufunsort_stable(Config) when is_list(Config) -> end, ok. -ufunsort_error(doc) -> ["usort/2 should exit when given bad arguments"]; -ufunsort_error(suite) -> []; +%% usort/2 should exit when given bad arguments. ufunsort_error(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:usort(1, [{1,b} , {1,c}])), ?line {'EXIT', _} = (catch lists:usort(fun(X,Y) -> X =< Y end, [{1,b} | {1,c}])), ok. -ufunsort_rand(doc) -> ["usort/2 on big randomized lists"]; -ufunsort_rand(suite) -> []; +%% usort/2 on big randomized lists. ufunsort_rand(Config) when is_list(Config) -> ?line ok = ufunsort_check3(1, biglist(10)), ?line ok = ufunsort_check3(1, biglist(100)), @@ -2116,18 +2055,12 @@ rkeymerge2_2(_I, T1, _E1, [], M, H1) -> %%%------------------------------------------------------------ -seq_loop(doc) -> - ["Test for infinite loop (OTP-2404)."]; -seq_loop(suite) -> - []; +%% Test for infinite loop (OTP-2404). seq_loop(Config) when is_list(Config) -> ?line _ = (catch lists:seq(1, 5, -1)), ok. -seq_2(doc) -> - ["Non-error cases for seq/2"]; -seq_2(suite) -> - []; +%% Non-error cases for seq/2. seq_2(Config) when is_list(Config) -> ?line [1,2,3] = lists:seq(1,3), ?line [1] = lists:seq(1,1), @@ -2137,10 +2070,7 @@ seq_2(Config) when is_list(Config) -> ?line [Big, Big1, Big2] = lists:seq(Big, Big+2), ok. -seq_2_e(doc) -> - ["Error cases for seq/2"]; -seq_2_e(suite) -> - []; +%% Error cases for seq/2. seq_2_e(Config) when is_list(Config) -> ?line seq_error([4, 2]), ?line seq_error([1, a]), @@ -2150,10 +2080,7 @@ seq_2_e(Config) when is_list(Config) -> seq_error(Args) -> {'EXIT', _} = (catch apply(lists, seq, Args)). -seq_3(doc) -> - ["Non-error cases for seq/3"]; -seq_3(suite) -> - []; +%% Non-error cases for seq/3. seq_3(Config) when is_list(Config) -> ?line [1,2,3] = lists:seq(1,3,1), ?line [1] = lists:seq(1,1,1), @@ -2174,10 +2101,7 @@ seq_3(Config) when is_list(Config) -> ?line [1] = lists:seq(1, 1, 0), %OTP-2613 ok. -seq_3_e(doc) -> - ["Error cases for seq/3"]; -seq_3_e(suite) -> - []; +%% Error cases for seq/3. seq_3_e(Config) when is_list(Config) -> ?line seq_error([4, 2, 1]), ?line seq_error([3, 5, -1]), @@ -2191,10 +2115,7 @@ seq_3_e(Config) when is_list(Config) -> ?line seq_error([a, a, 0]), ok. -otp_7230(doc) -> - ["OTP-7230. seq/1,2 returns the empty list"]; -otp_7230(suite) -> - []; +%% OTP-7230. seq/1,2 returns the empty list. otp_7230(Config) when is_list(Config) -> From = -10, To = 10, @@ -2266,8 +2187,6 @@ property(From, To, Step) -> -define(sublist_error2(X,Y), ?line {'EXIT', _} = (catch lists:sublist(X,Y))). -define(sublist_error3(X,Y,Z), ?line {'EXIT', _} = (catch lists:sublist(X,Y,Z))). -sublist_2(doc) -> ["sublist/2"]; -sublist_2(suite) -> []; sublist_2(Config) when is_list(Config) -> ?line [] = lists:sublist([], 0), ?line [] = lists:sublist([], 1), @@ -2280,8 +2199,7 @@ sublist_2(Config) when is_list(Config) -> ok. -sublist_2_e(doc) -> ["sublist/2 error cases"]; -sublist_2_e(suite) -> []; +%% sublist/2 error cases. sublist_2_e(Config) when is_list(Config) -> ?sublist_error2([], -1), ?sublist_error2(a, -1), @@ -2293,8 +2211,6 @@ sublist_2_e(Config) when is_list(Config) -> ?sublist_error2([], 1.5), ok. -sublist_3(doc) -> ["sublist/3"]; -sublist_3(suite) -> []; sublist_3(Config) when is_list(Config) -> ?line [] = lists:sublist([], 1, 0), ?line [] = lists:sublist([], 1, 1), @@ -2321,8 +2237,7 @@ sublist_3(Config) when is_list(Config) -> ok. -sublist_3_e(doc) -> ["sublist/3 error cases"]; -sublist_3_e(suite) -> []; +%% sublist/3 error cases sublist_3_e(Config) when is_list(Config) -> ?sublist_error3([], 1, -1), ?sublist_error3(a, 1, -1), @@ -2378,8 +2293,7 @@ lists_flatten(List) -> Len = length(Flat), Flat. -flatten_1_e(doc) -> ["flatten/1 error cases"]; -flatten_1_e(suite) -> []; +%% flatten/1 error cases flatten_1_e(Config) when is_list(Config) -> ?flatten_error1(a), ?flatten_error1([a|b]), @@ -2397,8 +2311,7 @@ flatten_2(Config) when is_list(Config) -> [a,b,c,[no,flatten]] = lists:flatten([[a,[b,c]]], [[no,flatten]]), ok. -flatten_2_e(doc) -> ["flatten/2 error cases"]; -flatten_2_e(suite) -> []; +%% flatten/2 error cases. flatten_2_e(Config) when is_list(Config) -> ok. @@ -2521,8 +2434,7 @@ filpart(F, All, Exp) -> {Exp,Other} = lists:partition(F, All). -otp_5939(doc) -> ["OTP-5939. Guard tests added."]; -otp_5939(suite) -> []; +%% OTP-5939. Guard tests added. otp_5939(Config) when is_list(Config) -> Fun1 = fun(A) -> A end, Fun2 = fun(A, B) -> {A,B} end, @@ -2589,16 +2501,14 @@ otp_5939(Config) when is_list(Config) -> ok. -otp_6023(doc) -> ["OTP-6023. lists:keyreplace/4, a typecheck."]; -otp_6023(suite) -> []; +%% OTP-6023. lists:keyreplace/4, a typecheck. otp_6023(Config) when is_list(Config) -> ?line {'EXIT', _} = (catch lists:keyreplace(a, 2, [{1,a}], b)), ?line [{2,b}] = lists:keyreplace(a, 2, [{1,a}], {2,b}), ok. -otp_6606(doc) -> ["OTP-6606. sort and keysort bug"]; -otp_6606(suite) -> []; +%% OTP-6606. sort and keysort bug. otp_6606(Config) when is_list(Config) -> I = 1, F = float(1), diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index e8d16e9486..f728248a92 100644 --- a/lib/stdlib/test/ms_transform_SUITE.erl +++ b/lib/stdlib/test/ms_transform_SUITE.erl @@ -79,10 +79,8 @@ end_per_group(_GroupName, Config) -> %% This may be subject to change -define(WARN_NUMBER_SHADOW,50). -warnings(suite) -> - []; -warnings(doc) -> - ["Check that shadowed variables in fun head generate warning"]; + +%% Check that shadowed variables in fun head generate warning. warnings(Config) when is_list(Config) -> ?line setup(Config), Prog = <<"A=5, " @@ -160,11 +158,8 @@ warnings(Config) when is_list(Config) -> compile_ww(Prog7), ok. -no_warnings(suite) -> - []; -no_warnings(doc) -> - ["Check that variables bound in other function clauses don't generate " - "warning"]; +%% Check that variables bound in other function clauses don't generate +%% warning. no_warnings(Config) when is_list(Config) -> ?line setup(Config), Prog = <<"tmp(X) when X > 100 ->\n", @@ -188,10 +183,7 @@ no_warnings(Config) when is_list(Config) -> ?line [] = compile_no_ww(Prog2), ok. -andalso_orelse(suite) -> - []; -andalso_orelse(doc) -> - ["Tests that andalso and orelse are allowed in guards."]; +%% Test that andalso and orelse are allowed in guards. andalso_orelse(Config) when is_list(Config) -> ?line setup(Config), ?line [{{'$1','$2'}, @@ -225,10 +217,7 @@ andalso_orelse(Config) when is_list(Config) -> ok. -bitsyntax(suite) -> - []; -bitsyntax(doc) -> - ["Tests that bitsyntax works and does not work where appropriate"]; +%% Test that bitsyntax works and does not work where appropriate. bitsyntax(Config) when is_list(Config) -> ?line setup(Config), ?line [{'_',[], @@ -263,10 +252,7 @@ bitsyntax(Config) when is_list(Config) -> " end)">>), ok. -record_defaults(suite) -> - []; -record_defaults(doc) -> - ["Tests that record defaults works"]; +%% Test that record defaults works. record_defaults(Config) when is_list(Config) -> ?line setup(Config), ?line [{{<<27>>,{a,5,'$1',hej,hej}}, @@ -278,10 +264,7 @@ record_defaults(Config) when is_list(Config) -> "end)">>), ok. -basic_ets(suite) -> - []; -basic_ets(doc) -> - ["Tests basic ets:fun2ms"]; +%% Test basic ets:fun2ms. basic_ets(Config) when is_list(Config) -> ?line setup(Config), ?line [{{a,b},[],[true]}] = compile_and_run( @@ -299,10 +282,7 @@ basic_ets(Config) when is_list(Config) -> compile_and_run(<<"ets:fun2ms(fun({A,B}) -> [B,A] end)">>), ok. -basic_dbg(suite) -> - []; -basic_dbg(doc) -> - ["Tests basic ets:fun2ms"]; +%% Tests basic ets:fun2ms. basic_dbg(Config) when is_list(Config) -> ?line setup(Config), ?line [{[a,b],[],[{message,banan},{return_trace}]}] = @@ -318,10 +298,7 @@ basic_dbg(Config) when is_list(Config) -> compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> object() end)">>), ok. -from_shell(suite) -> - []; -from_shell(doc) -> - ["Test calling of ets/dbg:fun2ms from the shell"]; +%% Test calling of ets/dbg:fun2ms from the shell. from_shell(Config) when is_list(Config) -> ?line setup(Config), ?line Fun = do_eval("fun({a,b}) -> true end"), @@ -335,10 +312,7 @@ from_shell(Config) when is_list(Config) -> "dbg:fun2ms(fun([a,b]) -> message(banan), return_trace() end)"), ok. -records(suite) -> - []; -records(doc) -> - ["Tests expansion of records in fun2ms"]; +%% Tests expansion of records in fun2ms. records(Config) when is_list(Config) -> ?line setup(Config), ?line RD = <<"-record(t, {" @@ -385,10 +359,7 @@ records(Config) when is_list(Config) -> ok. -record_index(suite) -> - []; -record_index(doc) -> - ["Tests expansion of records in fun2ms, part 2"]; +%% Test expansion of records in fun2ms, part 2. record_index(Config) when is_list(Config) -> ?line setup(Config), ?line RD = <<"-record(a,{a,b}).">>, @@ -400,10 +371,7 @@ record_index(Config) when is_list(Config) -> <<"ets:fun2ms(fun({#a.a,A}) when A > #a.a -> #a.a end)">>), ok. -top_match(suite) -> - []; -top_match(doc) -> - ["Tests matching on top level in head to give alias for object()"]; +%% Tests matching on top level in head to give alias for object(). top_match(Config) when is_list(Config) -> ?line setup(Config), ?line RD = <<"-record(a,{a,b}).">>, @@ -427,10 +395,7 @@ top_match(Config) when is_list(Config) -> <<"ets:fun2ms(fun(A#a{a = 2}) -> A end)">>), ok. -multipass(suite) -> - []; -multipass(doc) -> - ["Tests that multi-defined fields in records give errors."]; +%% Tests that multi-defined fields in records give errors. multipass(Config) when is_list(Config) -> ?line setup(Config), ?line RD = <<"-record(a,{a,b}).">>, @@ -451,10 +416,7 @@ multipass(Config) when is_list(Config) -> ok. -old_guards(suite) -> - []; -old_guards(doc) -> - ["Tests that old type tests in guards are translated"]; +%% Test that old type tests in guards are translated. old_guards(Config) when is_list(Config) -> ?line setup(Config), Tests = [ @@ -511,11 +473,8 @@ old_guards(Config) when is_list(Config) -> >>), ok. -autoimported(suite) -> - []; -autoimported(doc) -> - ["Tests use of autoimported bif's used like erlang:'+'(A,B) in guards" - " and body."]; +%% Test use of autoimported BIFs used like erlang:'+'(A,B) in guards +%% and body. autoimported(Config) when is_list(Config) -> ?line setup(Config), Allowed = [ @@ -687,10 +646,7 @@ autoimported(Config) when is_list(Config) -> Allowed), ok. -semicolon(suite) -> - []; -semicolon(doc) -> - ["Tests semicolon in guards of match_specs."]; +%% Test semicolon in guards of match_specs. semicolon(Config) when is_list(Config) -> ?line setup(Config), ?line Res01 = compile_and_run @@ -711,10 +667,7 @@ semicolon(Config) when is_list(Config) -> ok. -float_1_function(suite) -> - []; -float_1_function(doc) -> - ["OTP-5297. The function float/1."]; +%% OTP-5297. The function float/1. float_1_function(Config) when is_list(Config) -> ?line setup(Config), RunMS = fun(L, MS) -> @@ -759,10 +712,7 @@ float_1_function(Config) when is_list(Config) -> ok. -action_function(suite) -> - []; -action_function(doc) -> - ["Test all 'action functions'."]; +%% Test all 'action functions'. action_function(Config) when is_list(Config) -> ?line setup(Config), ?line [{['$1','$2'],[], diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index f877313069..4c85d4f18f 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -371,10 +371,7 @@ hib_receive_messages(N) -> Any -> [Any|hib_receive_messages(N-1)] end. -otp_6345(suite) -> - []; -otp_6345(doc) -> - ["'monitor' spawn_opt option"]; +%% 'monitor' spawn_opt option. otp_6345(Config) when is_list(Config) -> Opts = [link,monitor], {'EXIT', {badarg,[{proc_lib,check_for_monitor,_,_}|_Stack]}} = @@ -392,11 +389,8 @@ otp_6345_loop() -> otp_6345_loop() end. -%% OTP-9803 -init_dont_hang(suite) -> - []; -init_dont_hang(doc) -> - ["Check that proc_lib:start don't hang if spawned process crashes before proc_lib:init_ack/2"]; +%% OTP-9803. Check that proc_lib:start() doesn't hang if spawned process +%% crashes before proc_lib:init_ack/2. init_dont_hang(Config) when is_list(Config) -> %% Start should behave as start_link process_flag(trap_exit, true), diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index a4093a58b1..0840d88daf 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -155,9 +155,6 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -badarg(doc) -> - "Badarg."; -badarg(suite) -> []; badarg(Config) when is_list(Config) -> Ts = [{badarg, @@ -181,9 +178,7 @@ badarg(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -nested_qlc(doc) -> - "Nested qlc expressions."; -nested_qlc(suite) -> []; +%% Nested qlc expressions. nested_qlc(Config) when is_list(Config) -> %% Nested QLC expressions. X is bound before the first one; Z and X %% before the second one. @@ -226,9 +221,7 @@ nested_qlc(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -unused_var(doc) -> - "Unused variable with a name that should not be introduced."; -unused_var(suite) -> []; +%% Unused variable with a name that should not be introduced. unused_var(Config) when is_list(Config) -> Ts = [{unused_var, @@ -243,9 +236,7 @@ unused_var(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -lc(doc) -> - "Ordinary LC expression."; -lc(suite) -> []; +%% Ordinary LC expression. lc(Config) when is_list(Config) -> Ts = [{lc, @@ -257,9 +248,7 @@ lc(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -fun_clauses(doc) -> - "Fun with several clauses."; -fun_clauses(suite) -> []; +%% Fun with several clauses. fun_clauses(Config) when is_list(Config) -> Ts = [{fun_clauses, @@ -278,9 +267,7 @@ fun_clauses(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -filter_var(doc) -> - "Variable introduced in filter."; -filter_var(suite) -> []; +%% Variable introduced in filter. filter_var(Config) when is_list(Config) -> Ts = [{filter_var, @@ -309,9 +296,7 @@ filter_var(Config) when is_list(Config) -> ok. -single(doc) -> - "Unused pattern variable."; -single(suite) -> []; +%% Unused pattern variable. single(Config) when is_list(Config) -> Ts = [{single, @@ -324,9 +309,7 @@ single(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -exported_var(doc) -> - "Exported variable in list expression (rhs of generator)."; -exported_var(suite) -> []; +%% Exported variable in list expression (rhs of generator). exported_var(Config) when is_list(Config) -> Ts = [{exported_var, @@ -346,9 +329,7 @@ exported_var(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -generator_vars(doc) -> - "Errors for generator variable used in list expression."; -generator_vars(suite) -> []; +%% Errors for generator variable used in list expression. generator_vars(Config) when is_list(Config) -> Ts = [{generator_vars, @@ -373,9 +354,7 @@ generator_vars(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -nomatch(doc) -> - "Unreachable clauses also found when compiling."; -nomatch(suite) -> []; +%% Unreachable clauses also found when compiling. nomatch(Config) when is_list(Config) -> Ts = [{unreachable1, @@ -451,9 +430,7 @@ nomatch(Config) when is_list(Config) -> ok. -errors(doc) -> - "Errors within qlc expressions also found when compiling."; -errors(suite) -> []; +%% Errors within qlc expressions also found when compiling. errors(Config) when is_list(Config) -> Ts = [{errors1, @@ -465,9 +442,7 @@ errors(Config) when is_list(Config) -> ?line [] = compile(Config, Ts), ok. -pattern(doc) -> - "Patterns."; -pattern(suite) -> []; +%% Patterns. pattern(Config) when is_list(Config) -> Ts = [ <<"%% Records in patterns. No lookup. @@ -494,9 +469,7 @@ pattern(Config) when is_list(Config) -> ok. -eval(doc) -> - "eval/2"; -eval(suite) -> []; +%% eval/2 eval(Config) when is_list(Config) -> ScratchDir = filename:join([?privdir, "scratch","."]), @@ -615,9 +588,7 @@ eval(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -cursor(doc) -> - "cursor/2"; -cursor(suite) -> []; +%% cursor/2 cursor(Config) when is_list(Config) -> ScratchDir = filename:join([?privdir, "scratch","."]), Ts = [<<"{'EXIT',{badarg,_}} = @@ -729,9 +700,7 @@ cursor(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -fold(doc) -> - "fold/4"; -fold(suite) -> []; +%% fold/4 fold(Config) when is_list(Config) -> ScratchDir = filename:join([?privdir, "scratch","."]), Ts = [<<"Q = qlc:q([X || X <- [1,2,1,2,1]]), @@ -824,9 +793,7 @@ fold(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -eval_unique(doc) -> - "Test the unique_all option of eval."; -eval_unique(suite) -> []; +%% Test the unique_all option of eval. eval_unique(Config) when is_list(Config) -> Ts = [<<"QLC1 = qlc:q([X || X <- qlc:append([[1,1,2], [1,2,3,2,3]])]), [1,2,3] = qlc:eval(QLC1, {unique_all,true}), @@ -921,9 +888,7 @@ eval_unique(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -eval_cache(doc) -> - "Test the cache_all and unique_all options of eval."; -eval_cache(suite) -> []; +%% Test the cache_all and unique_all options of eval. eval_cache(Config) when is_list(Config) -> Ts = [ <<"E = ets:new(apa, [ordered_set]), @@ -1055,9 +1020,7 @@ eval_cache(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -append(doc) -> - "Test the append function."; -append(suite) -> []; +%% Test the append function. append(Config) when is_list(Config) -> Ts = [<<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3], begin 10/X > 0.0 end])), R = (catch qlc:next_answers(C)), @@ -1178,9 +1141,7 @@ append(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -evaluator(doc) -> - "Simple call from evaluator."; -evaluator(suite) -> []; +%% Simple call from evaluator. evaluator(Config) when is_list(Config) -> ?line true = is_alive(), evaluator_2(Config, []), @@ -1216,9 +1177,7 @@ start_node(Name) -> ?line PA = filename:dirname(code:which(?MODULE)), test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]). -string_to_handle(doc) -> - "string_to_handle/1,2."; -string_to_handle(suite) -> []; +%% string_to_handle/1,2. string_to_handle(Config) when is_list(Config) -> ?line {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)), ?line {'EXIT',{badarg,_}} = @@ -1265,9 +1224,7 @@ string_to_handle(Config) when is_list(Config) -> ?line ets:delete(Ets), ok. -table(doc) -> - "table"; -table(suite) -> []; +%% table table(Config) when is_list(Config) -> dets:start(), Ts = [ @@ -1484,9 +1441,7 @@ table(Config) when is_list(Config) -> ok. -process_dies(doc) -> - "Caller or cursor process dies."; -process_dies(suite) -> []; +%% Caller or cursor process dies. process_dies(Config) when is_list(Config) -> Ts = [ <<"E = ets:new(test, []), @@ -1628,9 +1583,7 @@ process_dies(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -sort(doc) -> - "The sort option."; -sort(suite) -> []; +%% The sort option. sort(Config) when is_list(Config) -> Ts = [ <<"H = qlc:q([X || X <- qlc:sort([1,2,3,2], {unique,true})]), @@ -1740,9 +1693,7 @@ sort(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -keysort(doc) -> - "The sort option."; -keysort(suite) -> []; +%% The sort option. keysort(Config) when is_list(Config) -> Ts = [ @@ -1865,9 +1816,7 @@ keysort(Config) when is_list(Config) -> ok. -filesort(doc) -> - "keysort/1,2, using a file."; -filesort(suite) -> []; +%% keysort/1,2, using a file. filesort(Config) when is_list(Config) -> Ts = [ <<"Q = qlc:q([X || X <- [{3},{1},{2}]]), @@ -1879,9 +1828,7 @@ filesort(Config) when is_list(Config) -> ok. -cache(doc) -> - "The cache option."; -cache(suite) -> []; +%% The cache option. cache(Config) when is_list(Config) -> Ts = [ <<"{'EXIT', {badarg, _}} = (catch qlc:q([X || X <- [1,2]], badarg))">>, @@ -2042,9 +1989,7 @@ cache(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -cache_list(doc) -> - "OTP-6038. The {cache,list} option."; -cache_list(suite) -> []; +%% OTP-6038. The {cache,list} option. cache_list(Config) when is_list(Config) -> Ts = [ begin @@ -2333,9 +2278,7 @@ cache_list(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -filter(doc) -> - "Filters and match specs."; -filter(suite) -> []; +%% Filters and match specs. filter(Config) when is_list(Config) -> Ts = [ <<"L = [1,2,3,4,5], @@ -2460,9 +2403,7 @@ filter(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -info(doc) -> - "info/2."; -info(suite) -> []; +%% info/2. info(Config) when is_list(Config) -> Ts = [ <<"{list, [1,2]} = i(qlc:q([X || X <- [1,2]])), @@ -2685,9 +2626,7 @@ info(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -nested_info(doc) -> - "Nested QLC expressions. QLC expressions in filter and template."; -nested_info(suite) -> []; +%% Nested QLC expressions. QLC expressions in filter and template. nested_info(Config) when is_list(Config) -> Ts = [ <<"L = [{1,a},{2,b},{3,c}], @@ -2792,9 +2731,7 @@ nested_info(Config) when is_list(Config) -> ok. -lookup1(doc) -> - "Lookup keys. Mostly test of patterns."; -lookup1(suite) -> []; +%% Lookup keys. Mostly test of patterns. lookup1(Config) when is_list(Config) -> Ts = [ <<"etsc(fun(E) -> @@ -3002,9 +2939,7 @@ lookup1(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -lookup2(doc) -> - "Lookup keys. Mostly test of filters."; -lookup2(suite) -> []; +%% Lookup keys. Mostly test of filters. lookup2(Config) when is_list(Config) -> Ts = [ <<"%% Only guards are inspected. No lookup. @@ -3704,9 +3639,7 @@ lookup2(Config) when is_list(Config) -> ok. -lookup_rec(doc) -> - "Lookup keys. With records."; -lookup_rec(suite) -> []; +%% Lookup keys. With records. lookup_rec(Config) when is_list(Config) -> Ts = [ <<"etsc(fun(E) -> @@ -3777,9 +3710,7 @@ lookup_rec(Config) when is_list(Config) -> ?line run(Config, <<"-record(r, {a}).\n">>, Ts), ok. -indices(doc) -> - "Using indices for lookup."; -indices(suite) -> []; +%% Using indices for lookup. indices(Config) when is_list(Config) -> Ts = [ <<"L = [{1,a},{2,b},{3,c}], @@ -3844,9 +3775,7 @@ indices(Config) when is_list(Config) -> ?line run(Config, <<"-record(r, {a}).\n">>, Ts), ok. -pre_fun(doc) -> - "Test the table/2 callback functions parent_fun and stop_fun."; -pre_fun(suite) -> []; +%% Test the table/2 callback functions parent_fun and stop_fun. pre_fun(Config) when is_list(Config) -> Ts = [ <<"PF = process_flag(trap_exit, true), @@ -3925,9 +3854,7 @@ pre_fun(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -skip_filters(doc) -> - "Lookup keys. With records."; -skip_filters(suite) -> []; +%% Lookup keys. With records. skip_filters(Config) when is_list(Config) -> %% Skipped filters TsS = [ @@ -4330,9 +4257,7 @@ skip_filters(Config) when is_list(Config) -> ok. -ets(doc) -> - "ets:table/1,2."; -ets(suite) -> []; +%% ets:table/1,2. ets(Config) when is_list(Config) -> Ts = [ <<"E = ets:new(t, [ordered_set]), @@ -4376,9 +4301,7 @@ ets(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -dets(doc) -> - "dets:table/1,2."; -dets(suite) -> []; +%% dets:table/1,2. dets(Config) when is_list(Config) -> dets:start(), T = t, @@ -4476,9 +4399,7 @@ dets(Config) when is_list(Config) -> ok. -join_option(doc) -> - "The 'join' option (any, lookup, merge, nested_loop). Also cache/unique."; -join_option(suite) -> []; +%% The 'join' option (any, lookup, merge, nested_loop). Also cache/unique. join_option(Config) when is_list(Config) -> Ts = [ <<"Q1 = qlc:q([X || X <- [1,2,3]],{join,merge}), @@ -4655,9 +4576,7 @@ join_option(Config) when is_list(Config) -> ok. -join_filter(doc) -> - "Various aspects of filters and join."; -join_filter(suite) -> []; +%% Various aspects of filters and join. join_filter(Config) when is_list(Config) -> Ts = [ <<"E1 = create_ets(1, 10), @@ -4697,9 +4616,7 @@ join_filter(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -join_lookup(doc) -> - "Lookup join."; -join_lookup(suite) -> []; +%% Lookup join. join_lookup(Config) when is_list(Config) -> Ts = [ <<"E1 = create_ets(1, 10), @@ -4792,9 +4709,7 @@ join_lookup(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -join_merge(doc) -> - "Merge join."; -join_merge(suite) -> []; +%% Merge join. join_merge(Config) when is_list(Config) -> Ts = [ <<"Q = qlc:q([{X,Y} || {X} <- [], {Y} <- [{1}], X =:= Y], @@ -5408,9 +5323,7 @@ join_merge(Config) when is_list(Config) -> ok. -join_sort(doc) -> - "Merge join optimizations (avoid unnecessary sorting)."; -join_sort(suite) -> []; +%% Merge join optimizations (avoid unnecessary sorting). join_sort(Config) when is_list(Config) -> Ts = [ <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]), @@ -5693,9 +5606,7 @@ join_sort(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -join_complex(doc) -> - "Join of more than two columns."; -join_complex(suite) -> []; +%% Join of more than two columns. join_complex(Config) when is_list(Config) -> Ts = [{three, <<"three() -> @@ -5757,9 +5668,7 @@ join_complex(Config) when is_list(Config) -> ok. -otp_5644(doc) -> - "OTP-5644. Handle the new language element M:F/A."; -otp_5644(suite) -> []; +%% OTP-5644. Handle the new language element M:F/A. otp_5644(Config) when is_list(Config) -> Ts = [ <<"Q = qlc:q([fun modul:mfa/0 || _ <- [1,2], @@ -5770,9 +5679,7 @@ otp_5644(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -otp_5195(doc) -> - "OTP-5195. Allow traverse functions returning terms."; -otp_5195(suite) -> []; +%% OTP-5195. Allow traverse functions returning terms. otp_5195(Config) when is_list(Config) -> %% Several minor improvements have been implemented in OTP-5195. %% The test cases are spread all over... except these. @@ -5863,9 +5770,7 @@ otp_5195(Config) when is_list(Config) -> ok. -otp_6038_bug(doc) -> - "OTP-6038. Bug fixes: unique and keysort; cache."; -otp_6038_bug(suite) -> []; +%% OTP-6038. Bug fixes: unique and keysort; cache. otp_6038_bug(Config) when is_list(Config) -> %% The 'unique' option can no longer be merged with the keysort options. %% This used to return [{1,a},{1,c},{2,b},{2,d}], but since @@ -5908,9 +5813,7 @@ otp_6038_bug(Config) when is_list(Config) -> ok. -otp_6359(doc) -> - "OTP-6359. dets:select() never returns the empty list."; -otp_6359(suite) -> []; +%% OTP-6359. dets:select() never returns the empty list. otp_6359(Config) when is_list(Config) -> dets:start(), T = luna, @@ -5932,9 +5835,7 @@ otp_6359(Config) when is_list(Config) -> ?line run(Config, Ts), ok. -otp_6562(doc) -> - "OTP-6562. compressed = false (should be []) when sorting before join."; -otp_6562(suite) -> []; +%% OTP-6562. compressed = false (should be []) when sorting before join. otp_6562(Config) when is_list(Config) -> Bug = [ %% This example uses a file to sort E2 on the second column. It is @@ -5974,9 +5875,7 @@ otp_6562(Config) when is_list(Config) -> ok. -otp_6590(doc) -> - "OTP-6590. Bug fix (join info)."; -otp_6590(suite) -> []; +%% OTP-6590. Bug fix (join info). otp_6590(Config) when is_list(Config) -> Ts = [<<"fun(Tab1Value) -> Q = qlc:q([T1#tab1.id || T1 <- [#tab1{id = id1, @@ -5992,9 +5891,7 @@ otp_6590(Config) when is_list(Config) -> -record(tab2, {id, value}).\n">>, Ts), ok. -otp_6673(doc) -> - "OTP-6673. Optimizations and fixes."; -otp_6673(suite) -> []; +%% OTP-6673. Optimizations and fixes. otp_6673(Config) when is_list(Config) -> Ts_PT = [<<"etsc(fun(E1) -> @@ -6091,9 +5988,7 @@ otp_6673(Config) when is_list(Config) -> ok. -otp_6964(doc) -> - "OTP-6964. New option 'tmpdir_usage'."; -otp_6964(suite) -> []; +%% OTP-6964. New option 'tmpdir_usage'. otp_6964(Config) when is_list(Config) -> T1 = [ <<"Q1 = qlc:q([{X} || X <- [1,2]]), @@ -6224,9 +6119,7 @@ otp_6964(Config) when is_list(Config) -> ?line run(Config, T4), ok. -otp_7238(doc) -> - "OTP-7238. info-option 'depth', &c."; -otp_7238(suite) -> []; +%% OTP-7238. info-option 'depth', &c. otp_7238(Config) when is_list(Config) -> dets:start(), T = otp_7238, @@ -6615,9 +6508,7 @@ otp_7238(Config) when is_list(Config) -> ok. -otp_7114(doc) -> - "OTP-7114. Match spec, table and duplicated objects.."; -otp_7114(suite) -> []; +%% OTP-7114. Match spec, table and duplicated objects... otp_7114(Config) when is_list(Config) -> Ts = [<<"T = ets:new(t, [bag]), [ets:insert(T, {t, I, I div 2}) || I <- lists:seq(1,10)], @@ -6630,9 +6521,7 @@ otp_7114(Config) when is_list(Config) -> ok">>], ?line run(Config, Ts). -otp_7232(doc) -> - "OTP-7232. qlc:info() bug (pids, ports, refs, funs)."; -otp_7232(suite) -> []; +%% OTP-7232. qlc:info() bug (pids, ports, refs, funs). otp_7232(Config) when is_list(Config) -> Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"), erlang:make_ref()], @@ -6662,9 +6551,7 @@ otp_7232(Config) when is_list(Config) -> ], ?line run(Config, Ts). -otp_7552(doc) -> - "OTP-7552. Merge join bug."; -otp_7552(suite) -> []; +%% OTP-7552. Merge join bug. otp_7552(Config) when is_list(Config) -> %% The poor performance cannot be observed unless the %% (redundant) join filter is skipped. @@ -6689,9 +6576,7 @@ otp_7552(Config) when is_list(Config) -> lists:sort(qlc:e(Qn))">>], ?line run(Config, Ts). -otp_7714(doc) -> - "OTP-7714. Merge join bug."; -otp_7714(suite) -> []; +%% OTP-7714. Merge join bug. otp_7714(Config) when is_list(Config) -> %% The original example uses Mnesia. This one does not. Ts = [<<"E1 = ets:new(set,[]), @@ -6708,9 +6593,7 @@ otp_7714(Config) when is_list(Config) -> ets:delete(E2)">>], ?line run(Config, Ts). -otp_11758(doc) -> - "OTP-11758. Bug."; -otp_11758(suite) -> []; +%% OTP-11758. Bug. otp_11758(Config) when is_list(Config) -> Ts = [<<"T = ets:new(r, [{keypos, 2}]), L = [{rrr, xxx, aaa}, {rrr, yyy, bbb}], @@ -6721,9 +6604,7 @@ otp_11758(Config) when is_list(Config) -> ets:delete(T)">>], run(Config, Ts). -otp_6674(doc) -> - "OTP-6674. match/comparison."; -otp_6674(suite) -> []; +%% OTP-6674. match/comparison. otp_6674(Config) when is_list(Config) -> ?line ok = compile_gb_table(Config), @@ -7151,9 +7032,7 @@ otp_6674(Config) when is_list(Config) -> ?line run(Config, Ts). -otp_12946(doc) -> - ["Syntax error."]; -otp_12946(suite) -> []; +%% Syntax error. otp_12946(Config) when is_list(Config) -> Text = <<"-export([init/0]). @@ -7163,9 +7042,7 @@ otp_12946(Config) when is_list(Config) -> {errors,[{4,erl_parse,_}],[]} = compile_file(Config, Text, []), ok. -manpage(doc) -> - "Examples from qlc(3)."; -manpage(suite) -> []; +%% Examples from qlc(3). manpage(Config) when is_list(Config) -> ?line ok = compile_gb_table(Config), @@ -7429,9 +7306,7 @@ gb_iter(I0, N, EFun) -> ">>. -backward(doc) -> - "OTP-6674. Join info and extra constants."; -backward(suite) -> []; +%% OTP-6674. Join info and extra constants. backward(Config) when is_list(Config) -> try_old_join_info(Config), ok. @@ -7466,9 +7341,6 @@ try_old_join_info(Config) -> qlc:info(H2, {format,debug}), [{1,1},{2,2}] = qlc:e(H2). -forward(doc) -> - ""; -forward(suite) -> []; forward(Config) when is_list(Config) -> Ts = [ %% LC_fun() returns something unknown. diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl index d0943e7a2a..08c78b93d8 100644 --- a/lib/stdlib/test/queue_SUITE.erl +++ b/lib/stdlib/test/queue_SUITE.erl @@ -56,10 +56,6 @@ end_per_group(_GroupName, Config) -> Config. -do(doc) -> - [""]; -do(suite) -> - []; do(Config) when is_list(Config) -> ?line L = [{in, 1}, {in, 2}, @@ -77,10 +73,7 @@ do(Config) when is_list(Config) -> ?line 0 = queue:len(Q), ok. -to_list(doc) -> - ["OTP-2701"]; -to_list(suite) -> - []; +%% OTP-2701 to_list(Config) when is_list(Config) -> ?line E = queue:new(), ?line Q = do_queue(E, [{in, 1}, @@ -115,10 +108,7 @@ do_queue_1({out, E}, Q) -> end. -io_test(doc) -> - "Test input and output"; -io_test(suite) -> - []; +%% Test input and output. io_test(Config) when is_list(Config) -> E = queue:new(), do_io_test(E), @@ -295,10 +285,7 @@ io([], Q, QQ, _X) -> QQ. -op_test(doc) -> - "Test operations on whole queues"; -op_test(suite) -> - []; +%% Test operations on whole queues. op_test(Config) when is_list(Config) -> do_op_test(fun id/1), ok. @@ -393,10 +380,7 @@ do_op_test(F) -> %% ok. -error(doc) -> - "Test queue errors"; -error(suite) -> - []; +%% Test queue errors. error(Config) when is_list(Config) -> do_error(fun id/1, illegal_queue), do_error(fun id/1, {[],illegal_queue}), @@ -460,10 +444,7 @@ do_error(F, IQ) -> id(X) -> X. -oops(doc) -> - "Test queue errors"; -oops(suite) -> - []; +%% Test queue errors. oops(Config) when is_list(Config) -> ?line N = 3142, ?line Optab = optab(), diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index b941ac9c53..6830101e96 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -83,10 +83,7 @@ algs() -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -seed(doc) -> - ["Test that seed and seed_s and export_seed/0 is working."]; -seed(suite) -> - []; +%% Test that seed and seed_s and export_seed/0 is working. seed(Config) when is_list(Config) -> Algs = algs(), Test = fun(Alg) -> @@ -137,10 +134,7 @@ seed_1(Alg) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -api_eq(doc) -> - ["Check that both api's are consistent with each other."]; -api_eq(suite) -> - []; +%% Check that both APIs are consistent with each other. api_eq(_Config) -> Algs = algs(), Small = fun(Alg) -> @@ -186,10 +180,7 @@ api_eq_1(S00) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -interval_int(doc) -> - ["Check that uniform/1 returns values within the proper interval."]; -interval_int(suite) -> - []; +%% Check that uniform/1 returns values within the proper interval. interval_int(Config) when is_list(Config) -> Algs = algs(), Small = fun(Alg) -> @@ -223,10 +214,7 @@ interval_int_1(N, Top, Max) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -interval_float(doc) -> - ["Check that uniform/0 returns values within the proper interval."]; -interval_float(suite) -> - []; +%% Check that uniform/0 returns values within the proper interval. interval_float(Config) when is_list(Config) -> Algs = algs(), Test = fun(Alg) -> @@ -250,8 +238,7 @@ interval_float_1(N) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -reference(doc) -> ["Check if exs64 algorithm generates the proper sequence."]; -reference(suite) -> []; +%% Check if exs64 algorithm generates the proper sequence. reference(Config) when is_list(Config) -> [reference_1(Alg) || Alg <- algs()], ok. @@ -366,8 +353,7 @@ basic_normal_1(0, {#{type:=Alg}, _}, Sum, SumSq) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -plugin(doc) -> ["Test that the user can write algorithms"]; -plugin(suite) -> []; +%% Test that the user can write algorithms. plugin(Config) when is_list(Config) -> _ = lists:foldl(fun(_, S0) -> {V1, S1} = rand:uniform_s(10000, S0), diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl index 02c2754a44..d261b92514 100644 --- a/lib/stdlib/test/random_SUITE.erl +++ b/lib/stdlib/test/random_SUITE.erl @@ -56,10 +56,7 @@ end_per_group(_GroupName, Config) -> Config. -seed0(doc) -> - ["Test that seed is set implicitly, and always the same."]; -seed0(suite) -> - []; +%% Test that seed is set implicitly, and always the same. seed0(Config) when is_list(Config) -> ?line Self = self(), ?line _ = spawn(fun() -> Self ! random:uniform() end), @@ -74,10 +71,7 @@ seed0(Config) when is_list(Config) -> ?line F1 = F2, ok. -seed(doc) -> - ["Test that seed/1 and seed/3 is equivalent."]; -seed(suite) -> - []; +%% Test that seed/1 and seed/3 are equivalent. seed(Config) when is_list(Config) -> ?line Self = self(), Seed = {S1, S2, S3} = erlang:timestamp(), @@ -101,10 +95,7 @@ seed(Config) when is_list(Config) -> ok. -interval_1(doc) -> - ["Check that uniform/1 returns values within the proper interval."]; -interval_1(suite) -> - []; +%% Check that uniform/1 returns values within the proper interval. interval_1(Config) when is_list(Config) -> ?line Top = 7, ?line N = 10, diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index d1720bd4bc..a27f1e8a7d 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -63,16 +63,14 @@ end_per_group(_GroupName, Config) -> Config. -pcre(doc) -> - ["Run all applicable tests from the PCRE testsuites."]; +%% Run all applicable tests from the PCRE testsuites. pcre(Config) when is_list(Config) -> RootDir = ?config(data_dir, Config), Res = run_pcre_tests:test(RootDir), 0 = lists:sum([ X || {X,_,_} <- Res ]), {comment,Res}. -compile_options(doc) -> - ["Test all documented compile options"]; +%% Test all documented compile options. compile_options(Config) when is_list(Config) -> ?line ok = ctest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}), ?line ok = ctest("ABDabcdABCD","abcd",[anchored],true,nomatch), @@ -111,8 +109,7 @@ compile_options(Config) when is_list(Config) -> ?line ok = ctest("abcdABCabcd\n","abcd$",[{newline,anycrlf}],true,{match,[{7,4}]}), ok. -run_options(doc) -> - ["Test all documented run specific options"]; +%% Test all documented run specific options. run_options(Config) when is_list(Config) -> ?line rtest("ABCabcdABC","abc",[],[],true), ?line rtest("ABCabcdABC","abc",[anchored],[],false), @@ -197,8 +194,7 @@ run_options(Config) when is_list(Config) -> -combined_options(doc) -> - ["Test compile options given directly to run"]; +%% Test compile options given directly to run. combined_options(Config) when is_list(Config) -> ?line ok = crtest("ABDabcdABCD","abcd",[],true,{match,[{3,4}]}), ?line ok = crtest("ABDabcdABCD","abcd",[anchored],true,nomatch), @@ -267,14 +263,12 @@ combined_options(Config) when is_list(Config) -> ?line nomatch = re:run("ABC\nD","[a-z]*",[{newline,crlf},notempty]), ok. -replace_autogen(doc) -> - ["Test replace with autogenerated erlang module"]; +%% Test replace with autogenerated erlang module. replace_autogen(Config) when is_list(Config) -> re_testoutput1_replacement_test:run(), ok. -global_capture(doc) -> - ["Tests capture options together with global searching"]; +%% Test capture options together with global searching. global_capture(Config) when is_list(Config) -> ?line {match,[{3,4}]} = re:run("ABCabcdABC",".*(?abcd).*",[{capture,[1]}]), ?line {match,[{10,4}]} = re:run("ABCabcdABCabcdA",".*(?abcd).*",[{capture,[1]}]), @@ -301,16 +295,14 @@ global_capture(Config) when is_list(Config) -> ?line {match,[[{3,5},{5,3}],[{11,4},{12,3}]]} = re:run("ABCÅbcdABCabcdA",".(?bcd)",[global,{capture,all,index},unicode]), ok. -replace_input_types(doc) -> - ["Tests replace with different input types"]; +%% Test replace with different input types. replace_input_types(Config) when is_list(Config) -> ?line <<"abcd">> = re:replace("abcd","Z","X",[{return,binary},unicode]), ?line <<"abcd">> = re:replace("abcd","\x{400}","X",[{return,binary},unicode]), ?line <<"a",208,128,"cd">> = re:replace(<<"abcd">>,"b","\x{400}",[{return,binary},unicode]), ok. -replace_return(doc) -> - ["Tests return options of replace together with global searching"]; +%% Test return options of replace together with global searching. replace_return(Config) when is_list(Config) -> {'EXIT',{badarg,_}} = (catch re:replace("na","(a","")), ok = replacetest(<<"nisse">>,"i","a",[{return,binary}],<<"nasse">>), @@ -404,14 +396,12 @@ copt(ungreedy) -> true; copt(unicode) -> true; copt(_) -> false. -split_autogen(doc) -> - ["Test split with autogenerated erlang module"]; +%% Test split with autogenerated erlang module. split_autogen(Config) when is_list(Config) -> re_testoutput1_split_test:run(), ok. -split_options(doc) -> - ["Test special options to split."]; +%% Test special options to split. split_options(Config) when is_list(Config) -> ok = splittest("a b c ","( )",[group,trim],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]]), ok = splittest("a b c ","( )",[group,{parts,0}],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]]), @@ -436,8 +426,7 @@ join([]) -> []; join([A]) -> [A]; join([H|T]) -> [H,<<":">>|join(T)]. -split_specials(doc) -> - ["Some special cases of split that are easy to get wrong."]; +%% Some special cases of split that are easy to get wrong. split_specials(Config) when is_list(Config) -> %% More or less just to remember these icky cases ?line <<"::abd:f">> = @@ -613,22 +602,21 @@ error_handling() -> (catch re:split("apa","(p",[banana])), ok. -pcre_cve_2008_2371(doc) -> - "Fix as in http://vcs.pcre.org/viewvc?revision=360&view=revision"; +%% Fix as in http://vcs.pcre.org/viewvc?revision=360&view=revision pcre_cve_2008_2371(Config) when is_list(Config) -> %% Make sure it doesn't crash the emulator. re:compile(<<"(?i)[\xc3\xa9\xc3\xbd]|[\xc3\xa9\xc3\xbdA]">>, [unicode]), ok. -pcre_compile_workspace_overflow(doc) -> - "Patch from http://vcs.pcre.org/viewvc/code/trunk/pcre_compile.c?r1=504&r2=505&view=patch"; +%% Patch from +%% http://vcs.pcre.org/viewvc/code/trunk/pcre_compile.c?r1=504&r2=505&view=patch pcre_compile_workspace_overflow(Config) when is_list(Config) -> N = 819, ?line {error,{"internal error: overran compiling workspace",799}} = re:compile([lists:duplicate(N, $(), lists:duplicate(N, $))]), ok. -re_infinite_loop(doc) -> - "Make sure matches that really loop infinitely actually fail"; + +%% Make sure matches that really loop infinitely actually fail. re_infinite_loop(Config) when is_list(Config) -> Str = "http:/www.flickr.com/slideShow/index.gne?group_id=&user_id=69845378@N0", @@ -642,16 +630,16 @@ re_infinite_loop(Config) when is_list(Config) -> {error,match_limit} = re:run(Str, EMail_regex,[report_errors]), {error,match_limit} = re:run(Str, EMail_regex,[report_errors,global]), ok. -re_backwards_accented(doc) -> - "Check for nasty bug where accented graphemes can make PCRE back past " - "beginning of subject"; + +%% Check for nasty bug where accented graphemes can make PCRE back +%% past beginning of subject. re_backwards_accented(Config) when is_list(Config) -> ?line match = re:run(<<65,204,128,65,204,128,97,98,99>>, <<"\\X?abc">>, [unicode,{capture,none}]), ok. -opt_dupnames(doc) -> - "Check correct handling of dupnames option to re"; + +%% Check correct handling of dupnames option to re. opt_dupnames(Config) when is_list(Config) -> Days = ["Monday","Tuesday","Wednesday","Thursday","Friday","Saturday","Sunday"], _ = [ begin @@ -739,8 +727,7 @@ opt_dupnames(Config) when is_list(Config) -> "h","a","n","T","e","then"],binary}]), ok. -opt_all_names(doc) -> - "Test capturing of all_names"; +%% Test capturing of all_names. opt_all_names(Config) when is_list(Config) -> Days = ["Monday","Tuesday","Wednesday","Thursday","Friday","Saturday","Sunday"], {match,[{1,3},{0,1},{7,1}]} = re:run("SMondayX","(?.)(?Mon|Fri|Sun)(?:day)?(?.)|" @@ -812,8 +799,7 @@ opt_all_names(Config) when is_list(Config) -> [dupnames,{capture,all_names,binary}]), ok. -inspect(doc) -> - "Test the minimal inspect function"; +%% Test the minimal inspect function. inspect(Config) when is_list(Config)-> {ok,MP} = re:compile("(?A)|(?B)|(?C)."), {namelist,[<<"A">>,<<"B">>,<<"C">>]} = re:inspect(MP,namelist), @@ -826,15 +812,13 @@ inspect(Config) when is_list(Config)-> {'EXIT',{badarg,_}} = (catch re:inspect({re_pattern,3,0,0,<<"kalle",2:2>>},namelist)), ok. -opt_no_start_optimize(doc) -> - "Test that the no_start_optimize compilation flag works"; +%% Test that the no_start_optimize compilation flag works. opt_no_start_optimize(Config) when is_list(Config) -> {match, [{3,3}]} = re:run("DEFABC","(*COMMIT)ABC",[]), % Start optimization makes this result wrong! nomatch = re:run("DEFABC","(*COMMIT)ABC",[no_start_optimize]), % This is the correct result... ok. -opt_never_utf(doc) -> - "Check that the never_utf option works"; +%% Check that the never_utf option works. opt_never_utf(Config) when is_list(Config) -> {match,[{0,3}]} = re:run("ABC","ABC",[never_utf]), {match,[{0,3}]} = re:run("ABC","(*UTF)ABC",[]), @@ -848,8 +832,8 @@ opt_never_utf(Config) when is_list(Config) -> {error,_} = (catch re:compile("(*UTF)ABC",[never_utf])), {error,_} = (catch re:compile("(*UTF8)ABC",[never_utf])), ok. -opt_ucp(doc) -> - "Check that the ucp option is passed to PCRE"; + +%% Check that the ucp option is passed to PCRE. opt_ucp(Config) when is_list(Config) -> {match,[{0,1}]} = re:run([$a],"\\w",[unicode]), {match,[{0,2}]} = re:run([229],"\\w",[unicode]), % Latin1 works without UCP, as we have a default @@ -857,8 +841,8 @@ opt_ucp(Config) when is_list(Config) -> nomatch = re:run([1024],"\\w",[unicode]), % Latin1 word characters only, 1024 is not latin1 {match,[{0,2}]} = re:run([1024],"\\w",[unicode,ucp]), % Any Unicode word character works with 'ucp' ok. -match_limit(doc) -> - "Check that the match_limit and match_limit_recursion options work"; + +%% Check that the match_limit and match_limit_recursion options work. match_limit(Config) when is_list(Config) -> nomatch = re:run("aaaaaaaaaaaaaz","(a+)*zz",[]), nomatch = re:run("aaaaaaaaaaaaaz","(a+)*zz",[{match_limit,3000}]), @@ -893,9 +877,8 @@ match_limit(Config) when is_list(Config) -> [{match_limit,-1}, report_errors,global])), ok. -sub_binaries(doc) -> - "test that we get sub-binaries if subject is a binary and we " - "capture binaries"; +%% Test that we get sub-binaries if subject is a binary and we capture +%% binaries. sub_binaries(Config) when is_list(Config) -> Bin = list_to_binary(lists:seq(1,255)), {match,[B,C]}=re:run(Bin,"(a)",[{capture,all,binary}]), diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl index 4970b6d47f..298026ad38 100644 --- a/lib/stdlib/test/select_SUITE.erl +++ b/lib/stdlib/test/select_SUITE.erl @@ -93,17 +93,11 @@ end_per_group(_GroupName, Config) -> Config. -select_test(suite) -> - []; -select_test(doc) -> - ["Tests select in numerous ways"]; +%% Test select in numerous ways. select_test(Config) when is_list(Config) -> do_test(Config). -return_values(suite) -> - []; -return_values(doc) -> - ["Tests return values in specific situations for select/3 and select/1"]; +%% Test return values in specific situations for select/3 and select/1. return_values(Config) when is_list(Config) -> do_return_values(). diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index 7cd87f4871..a4802b130d 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -109,10 +109,7 @@ end_per_group(_GroupName, Config) -> -record(state, {bin, reply, leader, unic = latin1}). -start_restricted_from_shell(doc) -> - ["Test that a restricted shell can be started from the normal shell"]; -start_restricted_from_shell(suite) -> - []; +%% Test that a restricted shell can be started from the normal shell. start_restricted_from_shell(Config) when is_list(Config) -> ?line [{error,nofile}] = scan(<<"begin shell:start_restricted(" "nonexisting_module) end.">>), @@ -188,10 +185,7 @@ start_restricted_from_shell(Config) when is_list(Config) -> application:get_env(stdlib, restricted_shell), ok. -start_restricted_on_command_line(doc) -> - ["Check restricted shell when started from the command line"]; -start_restricted_on_command_line(suite) -> - []; +%% Check restricted shell when started from the command line. start_restricted_on_command_line(Config) when is_list(Config) -> ?line {ok,Node} = start_node(shell_suite_helper_1, "-pa "++?config(priv_dir,Config)++ @@ -241,10 +235,8 @@ start_restricted_on_command_line(Config) when is_list(Config) -> ?line test_server:stop_node(Node2), ok. -restricted_local(suite) -> - []; -restricted_local(doc) -> - ["Tests calling local shell functions with spectacular arguments in restricted shell"]; +%% Tests calling local shell functions with spectacular arguments in +%% restricted shell. restricted_local(Config) when is_list(Config) -> ?line [{error,nofile}] = scan(<<"begin shell:start_restricted(" "nonexisting_module) end.">>), @@ -308,10 +300,7 @@ restricted_local(Config) when is_list(Config) -> ok. -forget(doc) -> - ["f/0 and f/1"]; -forget(suite) -> - []; +%% f/0 and f/1. forget(Config) when is_list(Config) -> %% f/0 ?line [ok] = scan(<<"begin f() end.">>), @@ -328,10 +317,7 @@ forget(Config) when is_list(Config) -> comm_err(<<"f(a).">>), ok. -records(doc) -> - ["Test of the record support. OTP-5063."]; -records(suite) -> - []; +%% Test of the record support. OTP-5063. records(Config) when is_list(Config) -> %% rd/2 ?line [{attribute,_,record,{bar,_}},ok] = @@ -490,19 +476,13 @@ records(Config) when is_list(Config) -> ok. -known_bugs(doc) -> - ["Known bugs."]; -known_bugs(suite) -> - []; +%% Known bugs. known_bugs(Config) when is_list(Config) -> %% erl_eval:merge_bindings/2 cannot handle _removal_ of bindings. ?line [3] = scan(<<"A = 3, length(begin f(A), [3] end), A.">>), ok. -otp_5226(doc) -> - ["OTP-5226. Wildcards accepted when reading BEAM files using rr/1,2,3."]; -otp_5226(suite) -> - []; +%% OTP-5226. Wildcards accepted when reading BEAM files using rr/1,2,3. otp_5226(Config) when is_list(Config) -> Test1 = <<"-module(test1). -record('_test1', {a,b}).">>, @@ -523,10 +503,7 @@ otp_5226(Config) when is_list(Config) -> file:delete(File2), ok. -otp_5327(doc) -> - ["OTP-5226. Test of eval_bits, mostly."]; -otp_5327(suite) -> - []; +%% OTP-5226. Test of eval_bits, mostly. otp_5327(Config) when is_list(Config) -> ?line "exception error: bad argument" = comm_err(<<"<<\"hej\":default>>.">>), @@ -596,10 +573,7 @@ otp_5327(Config) when is_list(Config) -> (catch evaluate(<<"<<32/unit:8>>.">>, [])), ok. -otp_5435(doc) -> - ["OTP-5435. sys_pre_expand not in the path."]; -otp_5435(suite) -> - []; +%% OTP-5435. sys_pre_expand not in the path. otp_5435(Config) when is_list(Config) -> ?line true = <<103133:64/float>> =:= evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []), @@ -625,10 +599,7 @@ otp_5435_2() -> rl(bar).">>), ok. -otp_5195(doc) -> - ["OTP-5195. QLC, mostly."]; -otp_5195(suite) -> - []; +%% OTP-5195. QLC, mostly. otp_5195(Config) when is_list(Config) -> %% QLC. It was easier to put these cases here than in qlc_SUITE. ?line "[#a{b = undefined}].\n" = @@ -661,10 +632,7 @@ otp_5195(Config) when is_list(Config) -> ok. -otp_5915(doc) -> - ["OTP-5915. Strict record tests in guards."]; -otp_5915(suite) -> - []; +%% OTP-5915. Strict record tests in guards. otp_5915(Config) when is_list(Config) -> C = <<" rd(r, {a = 4,b}), @@ -806,10 +774,7 @@ otp_5915(Config) when is_list(Config) -> [ok] = scan(C), ok. -otp_5916(doc) -> - ["OTP-5916. erlang:is_record/3 allowed in guards."]; -otp_5916(suite) -> - []; +%% OTP-5916. erlang:is_record/3 allowed in guards. otp_5916(Config) when is_list(Config) -> C = <<" rd(r1, {a,b}), @@ -826,10 +791,7 @@ otp_5916(Config) when is_list(Config) -> ok. -bs_match_misc_SUITE(doc) -> - ["OTP-5327. Adopted from parts of emulator/test/bs_match_misc_SUITE.erl."]; -bs_match_misc_SUITE(suite) -> - []; +%% OTP-5327. Adopted from parts of emulator/test/bs_match_misc_SUITE.erl. bs_match_misc_SUITE(Config) when is_list(Config) -> C = <<" F1 = fun() -> 3.1415 end, @@ -979,10 +941,8 @@ bs_match_misc_SUITE(Config) when is_list(Config) -> ok = evaluate(C, []). %% This one is not run during night builds since it takes several minutes. -bs_match_int_SUITE(doc) -> - ["OTP-5327. Adopted from emulator/test/bs_match_int_SUITE.erl."]; -bs_match_int_SUITE(suite) -> - []; + +%% OTP-5327. Adopted from emulator/test/bs_match_int_SUITE.erl. bs_match_int_SUITE(Config) when is_list(Config) -> C = <<" FunClause = fun({'EXIT',{function_clause,_}}) -> ok end, @@ -1199,10 +1159,7 @@ bs_match_int_SUITE(Config) when is_list(Config) -> [ok] = scan(C), ok = evaluate(C, []). -bs_match_tail_SUITE(doc) -> - ["OTP-5327. Adopted from emulator/test/bs_match_tail_SUITE.erl."]; -bs_match_tail_SUITE(suite) -> - []; +%% OTP-5327. Adopted from emulator/test/bs_match_tail_SUITE.erl. bs_match_tail_SUITE(Config) when is_list(Config) -> C = <<" GetTailUsed = fun(<>) -> {A,T} end, @@ -1274,10 +1231,7 @@ bs_match_tail_SUITE(Config) when is_list(Config) -> [ok] = scan(C), ok = evaluate(C, []). -bs_match_bin_SUITE(doc) -> - ["OTP-5327. Adopted from emulator/test/bs_match_bin_SUITE.erl."]; -bs_match_bin_SUITE(suite) -> - []; +%% OTP-5327. Adopted from emulator/test/bs_match_bin_SUITE.erl. bs_match_bin_SUITE(Config) when is_list(Config) -> ByteSplitBinary = <<"ByteSplit = @@ -1392,10 +1346,7 @@ bs_match_bin_SUITE(Config) when is_list(Config) -> end)(Nonliteral(" ??Int0 ")), true = <<" ??Int0 ":64/float>> =:= <<(float("??Int0")):64/float>>"). -bs_construct_SUITE(doc) -> - ["OTP-5327. Adopted from parts of emulator/test/bs_construct_SUITE.erl."]; -bs_construct_SUITE(suite) -> - []; +%% OTP-5327. Adopted from parts of emulator/test/bs_construct_SUITE.erl. bs_construct_SUITE(Config) when is_list(Config) -> C1 = <<" @@ -1546,10 +1497,7 @@ evaluate(Str, Vars) -> end. -refman_bit_syntax(doc) -> - ["Bit syntax examples from the Reference Manual. OTP-5237."]; -refman_bit_syntax(suite) -> - []; +%% Bit syntax examples from the Reference Manual. OTP-5237. refman_bit_syntax(Config) when is_list(Config) -> %% Reference Manual "Bit Syntax Expressions" ?line Bin1 = <<1,17,42>>, @@ -1590,10 +1538,8 @@ refman_bit_syntax(Config) when is_list(Config) -> -define(IP_VERSION, 4). -define(IP_MIN_HDR_LEN, 5). -progex_bit_syntax(doc) -> - ["Bit syntax examples from Programming Examples. OTP-5237."]; -progex_bit_syntax(suite) -> - []; + +%% Bit syntax examples from Programming Examples. OTP-5237. progex_bit_syntax(Config) when is_list(Config) -> Bin11 = <<1, 17, 42>>, true = [1, 17, 42] =:= binary_to_list(Bin11), @@ -1723,10 +1669,7 @@ triples_to_bin2([{X,Y,Z} | T], Acc) -> triples_to_bin2([], Acc) -> list_to_binary(lists:reverse(Acc)). -progex_records(doc) -> - ["Record examples from Programming Examples. OTP-5237."]; -progex_records(suite) -> - []; +%% Record examples from Programming Examples. OTP-5237. progex_records(Config) when is_list(Config) -> Test1 = <<"-module(recs). @@ -1879,10 +1822,7 @@ progex_records(Config) when is_list(Config) -> ?line ok = run_file(Config, recs, Test2), ok. -progex_lc(doc) -> - ["List comprehension examples from Programming Examples. OTP-5237."]; -progex_lc(suite) -> - []; +%% List comprehension examples from Programming Examples. OTP-5237. progex_lc(Config) when is_list(Config) -> Test1 = <<"-module(lc). @@ -2016,10 +1956,7 @@ progex_lc(Config) when is_list(Config) -> ?line [ok] = scan(Test1_shell), ok. -progex_funs(doc) -> - ["Funs examples from Programming Examples. OTP-5237."]; -progex_funs(suite) -> - []; +%% Funs examples from Programming Examples. OTP-5237. progex_funs(Config) when is_list(Config) -> Test1 = <<"-module(funs). @@ -2278,9 +2215,7 @@ progex_funs(Config) when is_list(Config) -> ok. -otp_5990(doc) -> - "OTP-5990. {erlang,is_record}."; -otp_5990(suite) -> []; +%% OTP-5990. {erlang,is_record}. otp_5990(Config) when is_list(Config) -> ?line [true] = scan(<<"rd('OrdSet', {orddata = {},ordtype = type}), " @@ -2288,9 +2223,7 @@ otp_5990(Config) when is_list(Config) -> "if tuple(S#'OrdSet'.ordtype) -> true; true -> false end.">>), ok. -otp_6166(doc) -> - "OTP-6166. Order of record definitions."; -otp_6166(suite) -> []; +%% OTP-6166. Order of record definitions. otp_6166(Config) when is_list(Config) -> Test1 = filename:join(?config(priv_dir, Config), "test1.hrl"), Contents1 = <<"-module(test1). @@ -2320,9 +2253,7 @@ otp_6166(Config) when is_list(Config) -> file:delete(Test2), ok. -otp_6554(doc) -> - "OTP-6554. Formatted exits and error messages."; -otp_6554(suite) -> []; +%% OTP-6554. Formatted exits and error messages. otp_6554(Config) when is_list(Config) -> %% Should check the stacktrace as well... ?line "exception error: bad argument" = @@ -2549,9 +2480,7 @@ otp_6554(Config) when is_list(Config) -> ok. -otp_7184(doc) -> - "OTP-7184. Propagate exit signals from dying evaluator process."; -otp_7184(suite) -> []; +%% OTP-7184. Propagate exit signals from dying evaluator process. otp_7184(Config) when is_list(Config) -> register(otp_7184, self()), ?line catch @@ -2602,9 +2531,7 @@ otp_7184(Config) when is_list(Config) -> ok. -otp_7232(doc) -> - "OTP-7232. qlc:info() bug."; -otp_7232(suite) -> []; +%% OTP-7232. qlc:info() bug. otp_7232(Config) when is_list(Config) -> Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [55296,56296]]), " "{order, fun(A,B)-> A>B end})).">>, @@ -2615,9 +2542,7 @@ otp_7232(Config) when is_list(Config) -> " end}])" = evaluate(Info, []), ok. -otp_8393(doc) -> - "OTP-8393. Prompt string."; -otp_8393(suite) -> []; +%% OTP-8393. Prompt string. otp_8393(Config) when is_list(Config) -> ?line _ = shell:prompt_func(default), ?line "Bad prompt function: '> '" = @@ -2744,9 +2669,7 @@ prompt_err(B) -> S = string:strip(S2, both, $"), string:strip(S, right, $.). -otp_10302(doc) -> - "OTP-10302. Unicode."; -otp_10302(suite) -> []; +%% OTP-10302. Unicode. otp_10302(Config) when is_list(Config) -> {ok,Node} = start_node(shell_suite_helper_2, "-pa "++?config(priv_dir,Config)++ diff --git a/lib/stdlib/test/slave_SUITE.erl b/lib/stdlib/test/slave_SUITE.erl index 165dfef73b..cb171d1dc6 100644 --- a/lib/stdlib/test/slave_SUITE.erl +++ b/lib/stdlib/test/slave_SUITE.erl @@ -52,7 +52,6 @@ end_per_group(_GroupName, Config) -> Config. -t_start_link(suite) -> []; t_start_link(Config) when is_list(Config) -> %% Define useful variables. @@ -99,7 +98,6 @@ t_start_link(Config) when is_list(Config) -> %% Test that slave:start_link() works when the master exits. -start_link_nodedown(suite) -> []; start_link_nodedown(Config) when is_list(Config) -> %% Define useful variables. @@ -124,7 +122,6 @@ start_a_slave(ReplyTo, Host, Name) -> %% Test slave:start(). -t_start(suite) -> []; t_start(Config) when is_list(Config) -> %% Define useful variables. @@ -172,7 +169,6 @@ t_start(Config) when is_list(Config) -> %% Test the various error conditions in parallell (since the timeout %% in slave is 32 seconds). -errors(suite) -> []; errors(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Pa = filename:dirname(code:which(?MODULE)), diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl index c227575a50..72441e1cc9 100644 --- a/lib/stdlib/test/sofs_SUITE.erl +++ b/lib/stdlib/test/sofs_SUITE.erl @@ -140,8 +140,6 @@ end_per_testcase(_Case, _Config) -> %% [{1,a,b},{2,b}] == lists:keysort(1,[{2,b},{1,a,b}]) -from_term_1(suite) -> []; -from_term_1(doc) -> [""]; from_term_1(Conf) when is_list(Conf) -> %% would go wrong: projection(1,from_term([{2,b},{1,a,b}])), @@ -228,8 +226,6 @@ from_term_1(Conf) when is_list(Conf) -> ok. -set_1(suite) -> []; -set_1(doc) -> [""]; set_1(Conf) when is_list(Conf) -> %% set/1 ?line {'EXIT', {badarg, _}} = (catch set(a)), @@ -260,8 +256,6 @@ set_1(Conf) when is_list(Conf) -> ok. -from_sets_1(suite) -> []; -from_sets_1(doc) -> [""]; from_sets_1(Conf) when is_list(Conf) -> ?line E = empty_set(), @@ -297,8 +291,6 @@ from_sets_1(Conf) when is_list(Conf) -> ?line eval(from_sets({from_term({a}),E}), from_term({{a},[]})), ok. -relation_1(suite) -> []; -relation_1(doc) -> [""]; relation_1(Conf) when is_list(Conf) -> %% relation/1 ?line eval(relation([]), from_term([], [{atom,atom}])), @@ -330,8 +322,6 @@ relation_1(Conf) when is_list(Conf) -> from_term([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}])), ok. -a_function_1(suite) -> []; -a_function_1(doc) -> [""]; a_function_1(Conf) when is_list(Conf) -> %% a_function/1 ?line eval(a_function([]), from_term([], [{atom,atom}])), @@ -377,8 +367,6 @@ a_function_1(Conf) when is_list(Conf) -> from_term([{[a,b],c}])), ok. -family_1(suite) -> []; -family_1(doc) -> [""]; family_1(Conf) when is_list(Conf) -> %% family/1 ?line eval(family([]), from_term([],[{atom,[atom]}])), @@ -438,8 +426,6 @@ family_1(Conf) when is_list(Conf) -> from_term([{[a,b],[a]},{[b,a],[a,a]}])), ok. -projection(suite) -> []; -projection(doc) -> [""]; projection(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -560,8 +546,6 @@ projection(Conf) when is_list(Conf) -> ok. -substitution(suite) -> []; -substitution(doc) -> [""]; substitution(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -658,8 +642,6 @@ substitution(Conf) when is_list(Conf) -> ok. -restriction(suite) -> []; -restriction(doc) -> [""]; restriction(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -777,8 +759,6 @@ restriction(Conf) when is_list(Conf) -> from_term([], [atom]))), ok. -drestriction(suite) -> []; -drestriction(doc) -> [""]; drestriction(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -894,8 +874,6 @@ drestriction(Conf) when is_list(Conf) -> from_term([], [atom]))), ok. -strict_relation_1(suite) -> []; -strict_relation_1(doc) -> [""]; strict_relation_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -915,8 +893,6 @@ strict_relation_1(Conf) when is_list(Conf) -> end, ok. -extension(suite) -> []; -extension(doc) -> [""]; extension(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -958,8 +934,6 @@ extension(Conf) when is_list(Conf) -> lextension(R, S, C) -> union(R, drestriction(1, constant_function(S, C), domain(R))). -weak_relation_1(suite) -> []; -weak_relation_1(doc) -> [""]; weak_relation_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -991,8 +965,6 @@ weak_relation_1(Conf) when is_list(Conf) -> end, ok. -to_sets_1(suite) -> []; -to_sets_1(doc) -> [""]; to_sets_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch to_sets(from_term(a))), ?line {'EXIT', {function_clause, _}} = (catch to_sets(a)), @@ -1013,8 +985,6 @@ to_sets_1(Conf) when is_list(Conf) -> ok. -specification(suite) -> []; -specification(doc) -> [""]; specification(Conf) when is_list(Conf) -> Fun = {external, fun(I) when is_integer(I) -> true; (_) -> false end}, ?line [1,2,3] = to_external(specification(Fun, set([a,1,b,2,c,3]))), @@ -1039,8 +1009,6 @@ specification(Conf) when is_list(Conf) -> (catch specification(Fun, a)), ok. -union_1(suite) -> []; -union_1(doc) -> [""]; union_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -1069,8 +1037,6 @@ union_1(Conf) when is_list(Conf) -> ?line eval(union(from_term([[a,b]])), from_term([a,b])), ok. -intersection_1(suite) -> []; -intersection_1(doc) -> [""]; intersection_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line {'EXIT', {badarg, _}} = (catch intersection(from_term([a,b]))), @@ -1093,8 +1059,6 @@ intersection_1(Conf) when is_list(Conf) -> set([d])), ok. -difference(suite) -> []; -difference(doc) -> [""]; difference(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line {'EXIT', {type_mismatch, _}} = @@ -1114,8 +1078,6 @@ difference(Conf) when is_list(Conf) -> set([a,b,d,e,f])), ok. -symdiff(suite) -> []; -symdiff(doc) -> [""]; symdiff(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line {'EXIT', {type_mismatch, _}} = @@ -1139,8 +1101,6 @@ symdiff(Conf) when is_list(Conf) -> union(set([c,g,k]), set([e,i,m,n,o,p]))), ok. -symmetric_partition(suite) -> []; -symmetric_partition(doc) -> [""]; symmetric_partition(Conf) when is_list(Conf) -> ?line E = set([]), ?line S1 = set([1,2,3,4]), @@ -1173,8 +1133,6 @@ symmetric_partition(Conf) when is_list(Conf) -> ok. -is_sofs_set_1(suite) -> []; -is_sofs_set_1(doc) -> [""]; is_sofs_set_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line true = is_sofs_set(E), @@ -1184,8 +1142,6 @@ is_sofs_set_1(Conf) when is_list(Conf) -> ?line false = is_sofs_set(a), ok. -is_set_1(suite) -> []; -is_set_1(doc) -> [""]; is_set_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line true = is_set(E), @@ -1202,8 +1158,6 @@ is_set_1(Conf) when is_list(Conf) -> ok. -is_equal(suite) -> []; -is_equal(doc) -> [""]; is_equal(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line true = is_equal(E, E), @@ -1237,8 +1191,6 @@ is_equal(Conf) when is_list(Conf) -> ok. -is_subset(suite) -> []; -is_subset(doc) -> [""]; is_subset(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line true = is_subset(E, E), @@ -1255,8 +1207,6 @@ is_subset(Conf) when is_list(Conf) -> (catch is_subset(set([a]), from_term([a,b], [at]))), ok. -is_a_function_1(suite) -> []; -is_a_function_1(doc) -> [""]; is_a_function_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([], 2), @@ -1279,8 +1229,6 @@ is_a_function_1(Conf) when is_list(Conf) -> end, ok. -is_disjoint(suite) -> []; -is_disjoint(doc) -> [""]; is_disjoint(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line {'EXIT', {type_mismatch, _}} = @@ -1293,8 +1241,6 @@ is_disjoint(Conf) when is_list(Conf) -> ?line true = is_disjoint(set([a,c,e]),set([b,d,f])), ok. -join(suite) -> []; -join(doc) -> [""]; join(Conf) when is_list(Conf) -> ?line E = empty_set(), @@ -1331,8 +1277,6 @@ join(Conf) when is_list(Conf) -> from_term([{a,b,1},{b,c,3},{b,c,4}])), ok. -canonical(suite) -> []; -canonical(doc) -> [""]; canonical(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line {'EXIT', {badarg, _}} = @@ -1343,8 +1287,6 @@ canonical(Conf) when is_list(Conf) -> from_term([{a,[a,b,c]},{b,[a,b,c]},{c,[a,b,c]}])), ok. -relation_to_family_1(suite) -> []; -relation_to_family_1(doc) -> [""]; relation_to_family_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -1358,8 +1300,6 @@ relation_to_family_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch relation_to_family(set([a]))), ok. -domain_1(suite) -> []; -domain_1(doc) -> [""]; domain_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1380,8 +1320,6 @@ domain_1(Conf) when is_list(Conf) -> end, ok. -range_1(suite) -> []; -range_1(doc) -> [""]; range_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1392,8 +1330,6 @@ range_1(Conf) when is_list(Conf) -> ?line eval(range(relation([{a,1},{b,2},{c,3}])), set([1,2,3])), ok. -inverse_1(suite) -> []; -inverse_1(doc) -> [""]; inverse_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1416,8 +1352,6 @@ inverse_1(Conf) when is_list(Conf) -> end, ok. -converse_1(suite) -> []; -converse_1(doc) -> [""]; converse_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1432,8 +1366,6 @@ converse_1(Conf) when is_list(Conf) -> relation([{a,1},{a,2}])), ok. -no_elements_1(suite) -> []; -no_elements_1(doc) -> [""]; no_elements_1(Conf) when is_list(Conf) -> ?line 0 = no_elements(empty_set()), ?line 0 = no_elements(set([])), @@ -1444,8 +1376,6 @@ no_elements_1(Conf) when is_list(Conf) -> ?line {'EXIT', {function_clause, _}} = (catch no_elements(a)), ok. -image(suite) -> []; -image(doc) -> [""]; image(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1466,8 +1396,6 @@ image(Conf) when is_list(Conf) -> (catch image(from_term([{[a],1}]), set([[a]]))), ok. -inverse_image(suite) -> []; -inverse_image(doc) -> [""]; inverse_image(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1493,8 +1421,6 @@ inverse_image(Conf) when is_list(Conf) -> (catch inverse_image(converse(from_term([{[a],1}])), set([[a]]))), ok. -composite_1(suite) -> []; -composite_1(doc) -> [""]; composite_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = a_function([]), @@ -1545,8 +1471,6 @@ composite_1(Conf) when is_list(Conf) -> end, ok. -relative_product_1(suite) -> []; -relative_product_1(doc) -> [""]; relative_product_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1573,8 +1497,6 @@ relative_product_1(Conf) when is_list(Conf) -> from_term([{b,c}], [{d,r}]))), ok. -relative_product_2(suite) -> []; -relative_product_2(doc) -> [""]; relative_product_2(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1623,8 +1545,6 @@ relprod2(A1T, A2, R) -> eval(relative_product(A1T, A2), R), eval(relative_product(tuple_to_list(A1T), A2), R). -product_1(suite) -> []; -product_1(doc) -> [""]; product_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line eval(product(E, E), E), @@ -1651,8 +1571,6 @@ product_1(Conf) when is_list(Conf) -> ?line eval(product({relation([]), E}), E), ok. -partition_1(suite) -> []; -partition_1(doc) -> [""]; partition_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1697,8 +1615,6 @@ partition_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch partition(from_term([a]))), ok. -partition_3(suite) -> []; -partition_3(doc) -> [""]; partition_3(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1844,8 +1760,6 @@ partition_3(Conf) when is_list(Conf) -> lpartition(F, S1, S2) -> {restriction(F, S1, S2), drestriction(F, S1, S2)}. -multiple_relative_product(suite) -> []; -multiple_relative_product(doc) -> [""]; multiple_relative_product(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -1868,8 +1782,6 @@ multiple_relative_product(Conf) when is_list(Conf) -> (catch multiple_relative_product({T}, from_term([{{a}}]))), ok. -digraph(suite) -> []; -digraph(doc) -> [""]; digraph(Conf) when is_list(Conf) -> ?line T0 = ets:all(), ?line E = empty_set(), @@ -1931,8 +1843,6 @@ digraph_fail(ExitReason, Fail) -> {true,2} -> ok end. -constant_function(suite) -> []; -constant_function(doc) -> [""]; constant_function(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line C = from_term(3), @@ -1943,8 +1853,6 @@ constant_function(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch constant_function(set([]), foo)), ok. -misc(suite) -> []; -misc(doc) -> [""]; misc(Conf) when is_list(Conf) -> % find "relational" part of relation: ?line S = relation([{a,b},{b,c},{b,d},{c,d}]), @@ -1965,8 +1873,6 @@ relational_restriction(R) -> family_to_relation(family_specification(Fun, relation_to_family(R))). -family_specification(suite) -> []; -family_specification(doc) -> [""]; family_specification(Conf) when is_list(Conf) -> E = empty_set(), %% internal @@ -1997,8 +1903,6 @@ family_specification(Conf) when is_list(Conf) -> (catch family_specification({external, Fun3}, F3)), ok. -family_domain_1(suite) -> []; -family_domain_1(doc) -> [""]; family_domain_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]), @@ -2023,8 +1927,6 @@ family_domain_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch family_domain(set([{a,[b]}]))), ok. -family_range_1(suite) -> []; -family_range_1(doc) -> [""]; family_range_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]), @@ -2045,8 +1947,6 @@ family_range_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch family_range(set([{a,[b]}]))), ok. -family_to_relation_1(suite) -> []; -family_to_relation_1(doc) -> [""]; family_to_relation_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line ER = relation([]), @@ -2059,8 +1959,6 @@ family_to_relation_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch family_to_relation(set([a]))), ok. -union_of_family_1(suite) -> []; -union_of_family_1(doc) -> [""]; union_of_family_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]), @@ -2074,8 +1972,6 @@ union_of_family_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch union_of_family(set([a]))), ok. -intersection_of_family_1(suite) -> []; -intersection_of_family_1(doc) -> [""]; intersection_of_family_1(Conf) when is_list(Conf) -> ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]), ?line eval(intersection_of_family(EF), set([])), @@ -2088,8 +1984,6 @@ intersection_of_family_1(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch intersection_of_family(set([a]))), ok. -family_projection(suite) -> []; -family_projection(doc) -> [""]; family_projection(Conf) when is_list(Conf) -> SSType = [{atom,[[atom]]}], SRType = [{atom,[{atom,atom}]}], @@ -2149,8 +2043,6 @@ family_projection(Conf) when is_list(Conf) -> from_term([{1,a}])), ok. -family_difference(suite) -> []; -family_difference(doc) -> [""]; family_difference(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -2186,8 +2078,6 @@ family_difference(Conf) when is_list(Conf) -> from_term([{c,[d]}], [{i,[s]}]))), ok. -family_intersection_1(suite) -> []; -family_intersection_1(doc) -> [""]; family_intersection_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -2206,8 +2096,6 @@ family_intersection_1(Conf) when is_list(Conf) -> ?line eval(family_intersection(F3), family([{a,[2]},{c,[5,6]}])), ok. -family_intersection_2(suite) -> []; -family_intersection_2(doc) -> [""]; family_intersection_2(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -2237,8 +2125,6 @@ family_intersection_2(Conf) when is_list(Conf) -> ?line eval(intersection_of_family(F12), set([2,4])), ok. -family_union_1(suite) -> []; -family_union_1(doc) -> [""]; family_union_1(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -2252,8 +2138,6 @@ family_union_1(Conf) when is_list(Conf) -> family([{a,[1,2,3]},{b,[]},{c,[4]}])), ok. -family_union_2(suite) -> []; -family_union_2(doc) -> [""]; family_union_2(Conf) when is_list(Conf) -> ?line E = empty_set(), ?line EF = family([]), @@ -2281,8 +2165,6 @@ family_union_2(Conf) when is_list(Conf) -> from_term([{e,[{f}]}]))), ok. -partition_family(suite) -> []; -partition_family(doc) -> [""]; partition_family(Conf) when is_list(Conf) -> ?line E = empty_set(), diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 41176814db..be80e3e057 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -54,10 +54,7 @@ end_per_testcase(_Case, _Config) -> % % Test cases starts here. % -app_test(suite) -> - []; -app_test(doc) -> - ["Application consistency test."]; +%% Application consistency test. app_test(Config) when is_list(Config) -> test_server:app_test(stdlib), ok. @@ -160,10 +157,8 @@ check_appup([],_,_) -> -include_lib("stdlib/include/assert.hrl"). -include_lib("stdlib/include/assert.hrl"). % test repeated inclusion -assert_test(suite) -> - []; -assert_test(doc) -> - ["Assert macros test."]; + +%% Assert macros test. assert_test(_Config) -> ok = ?assert(true), {'EXIT',{{assert, _},_}} = (catch ?assert(false)), diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index 8a5759279b..60d341cd6d 100644 --- a/lib/stdlib/test/string_SUITE.erl +++ b/lib/stdlib/test/string_SUITE.erl @@ -72,10 +72,6 @@ end_per_testcase(_Case, _Config) -> % Test cases starts here. % -len(suite) -> - []; -len(doc) -> - []; len(Config) when is_list(Config) -> ?line 0 = string:len(""), ?line L = tuple_size(list_to_tuple(atom_to_list(?MODULE))), @@ -84,10 +80,6 @@ len(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:len({})), ok. -equal(suite) -> - []; -equal(doc) -> - []; equal(Config) when is_list(Config) -> ?line true = string:equal("", ""), ?line false = string:equal("", " "), @@ -97,10 +89,6 @@ equal(Config) when is_list(Config) -> ?line true = string:equal(2, 2), % not good, should crash ok. -concat(suite) -> - []; -concat(doc) -> - []; concat(Config) when is_list(Config) -> ?line "erlang rules" = string:concat("erlang ", "rules"), ?line "" = string:concat("", ""), @@ -110,10 +98,6 @@ concat(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:concat(hello, please)), ok. -chr_rchr(suite) -> - []; -chr_rchr(doc) -> - []; chr_rchr(Config) when is_list(Config) -> {_,_,X} = erlang:timestamp(), ?line 0 = string:chr("", (X rem (255-32)) + 32), @@ -134,10 +118,6 @@ chr_rchr(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:rchr("hello", h)), ok. -str_rstr(suite) -> - []; -str_rstr(doc) -> - []; str_rstr(Config) when is_list(Config) -> {_,_,X} = erlang:timestamp(), ?line 0 = string:str("", [(X rem (255-32)) + 32]), @@ -160,10 +140,6 @@ str_rstr(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:rstr("hello", he)), ok. -span_cspan(suite) -> - []; -span_cspan(doc) -> - []; span_cspan(Config) when is_list(Config) -> ?line 0 = string:span("", "1"), ?line 0 = string:span("1", ""), @@ -186,10 +162,6 @@ span_cspan(Config) when is_list(Config) -> ok. -substr(suite) -> - []; -substr(doc) -> - []; substr(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:substr("", 0)), ?line [] = string:substr("", 1), @@ -246,10 +218,6 @@ replace_sep(C, Seps, New) -> false -> C end. -chars(suite) -> - []; -chars(doc) -> - []; chars(Config) when is_list(Config) -> ?line [] = string:chars($., 0), ?line [] = string:chars($., 0, []), @@ -259,10 +227,6 @@ chars(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:chars($x, [])), ok. -copies(suite) -> - []; -copies(doc) -> - []; copies(Config) when is_list(Config) -> ?line "" = string:copies("", 10), ?line "" = string:copies(".", 0), @@ -273,10 +237,6 @@ copies(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:copies("hej", 2.0)), ok. -words(suite) -> - []; -words(doc) -> - []; words(Config) when is_list(Config) -> ?line 1 = string:words(""), ?line 1 = string:words("", $,), @@ -292,10 +252,6 @@ words(Config) when is_list(Config) -> ok. -strip(suite) -> - []; -strip(doc) -> - []; strip(Config) when is_list(Config) -> ?line "" = string:strip(""), ?line "" = string:strip("", both), @@ -313,10 +269,6 @@ strip(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:strip(" hej", left, " ")), % not good ok. -sub_word(suite) -> - []; -sub_word(doc) -> - []; sub_word(Config) when is_list(Config) -> ?line "" = string:sub_word("", 1), ?line "" = string:sub_word("", 1, $,), @@ -329,10 +281,6 @@ sub_word(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:sub_word("hello there", 1, "e")), ok. -left_right(suite) -> - []; -left_right(doc) -> - []; left_right(Config) when is_list(Config) -> ?line "" = string:left("", 0), ?line "" = string:left("hej", 0), @@ -356,10 +304,6 @@ left_right(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:right("hello", 5, ".")), ok. -sub_string(suite) -> - []; -sub_string(doc) -> - []; sub_string(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:sub_string("", 0)), ?line [] = string:sub_string("", 1), @@ -382,10 +326,6 @@ sub_string(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:sub_string("1234", "1")), ok. -centre(suite) -> - []; -centre(doc) -> - []; centre(Config) when is_list(Config) -> ?line "" = string:centre("", 0), ?line "" = string:centre("1", 0), @@ -401,10 +341,6 @@ centre(Config) when is_list(Config) -> ?line {'EXIT',_} = (catch string:centre(hello, 10)), ok. -to_integer(suite) -> - []; -to_integer(doc) -> - []; to_integer(Config) when is_list(Config) -> ?line {1,""} = test_to_integer("1"), ?line {1,""} = test_to_integer("+1"), @@ -434,10 +370,6 @@ test_to_integer(Str) -> Res end. -to_float(suite) -> - []; -to_float(doc) -> - []; to_float(Config) when is_list(Config) -> ?line {1.2,""} = test_to_float("1.2"), ?line {1.2,""} = test_to_float("1,2"), @@ -481,10 +413,6 @@ test_to_float(Str) -> Res end. -to_upper_to_lower(suite) -> - []; -to_upper_to_lower(doc) -> - []; to_upper_to_lower(Config) when is_list(Config) -> ?line "1234ABCDEFÅÄÖ=" = string:to_upper("1234abcdefåäö="), ?line "éèíúùòóåäöabc()" = string:to_lower("ÉÈÍÚÙÒÓÅÄÖabc()"), @@ -527,10 +455,6 @@ all_lower_latin1([H|T], C) when $A =< C, C =< $Z; all_lower_latin1(T, C+1); all_lower_latin1([], 256) -> ok. -join(suite) -> - []; -join(doc) -> - []; join(Config) when is_list(Config) -> ?line "erlang rules" = string:join(["erlang", "rules"], " "), ?line "a,-,b,-,c" = string:join(["a", "b", "c"], ",-,"), diff --git a/lib/stdlib/test/supervisor_bridge_SUITE.erl b/lib/stdlib/test/supervisor_bridge_SUITE.erl index be1bf82864..5cd28d00aa 100644 --- a/lib/stdlib/test/supervisor_bridge_SUITE.erl +++ b/lib/stdlib/test/supervisor_bridge_SUITE.erl @@ -55,7 +55,6 @@ end_per_group(_GroupName, Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -starting(suite) -> []; starting(Config) when is_list(Config) -> process_flag(trap_exit,true), @@ -65,12 +64,10 @@ starting(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -mini_terminate(suite) -> []; mini_terminate(Config) when is_list(Config) -> miniappl(1), ok. -mini_die(suite) -> []; mini_die(Config) when is_list(Config) -> miniappl(2), ok. @@ -172,8 +169,7 @@ terminate(_Reason, _State) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -badstart(suite) -> []; -badstart(doc) -> "Test various bad ways of starting a supervisor bridge."; +%% Test various bad ways of starting a supervisor bridge. badstart(Config) when is_list(Config) -> %% Various bad arguments. @@ -209,8 +205,7 @@ badstart(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% OTP-9212. Restart of global supervisor. -simple_global_supervisor(suite) -> []; -simple_global_supervisor(doc) -> "Globally registered supervisor."; +%% Globally registered supervisor. simple_global_supervisor(Config) when is_list(Config) -> Child = {child, {?MODULE,server9212,[]}, permanent, 2000, worker, []}, diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl index 581fb71a7b..e80c86562d 100644 --- a/lib/stdlib/test/sys_SUITE.erl +++ b/lib/stdlib/test/sys_SUITE.erl @@ -53,7 +53,6 @@ end_per_group(_GroupName, Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -log(suite) -> []; log(Config) when is_list(Config) -> {ok,_Server} = start(), ok = sys:log(?server,true), @@ -63,7 +62,6 @@ log(Config) when is_list(Config) -> stop(), ok. -log_to_file(suite) -> []; log_to_file(Config) when is_list(Config) -> TempName = test_server:temp_name(?config(priv_dir,Config) ++ "sys."), {ok,_Server} = start(), @@ -79,7 +77,6 @@ log_to_file(Config) when is_list(Config) -> stop(), ok. -stats(suite) -> []; stats(Config) when is_list(Config) -> Self = self(), {ok,_Server} = start(), @@ -95,7 +92,6 @@ stats(Config) when is_list(Config) -> stop(), ok. -trace(suite) -> []; trace(Config) when is_list(Config) -> {ok,_Server} = start(), ct:sleep(2000), @@ -111,7 +107,6 @@ trace(Config) when is_list(Config) -> stop(), ok. -suspend(suite) -> []; suspend(Config) when is_list(Config) -> ?line {ok,_Server} = start(), ?line sys:suspend(?server,1000), @@ -127,7 +122,6 @@ suspend(Config) when is_list(Config) -> ?line stop(), ok. -install(suite) -> []; install(Config) when is_list(Config) -> ?line {ok,_Server} = start(), ?line Master = self(), @@ -161,7 +155,6 @@ get_messages() -> after 1 -> [] end. -special_process(suite) -> []; special_process(Config) when is_list(Config) -> ok = spec_proc(sys_sp1), ok = spec_proc(sys_sp2). diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 6022854809..2584f9c01f 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -53,10 +53,9 @@ end_per_group(_GroupName, Config) -> Config. -borderline(doc) -> - ["Test creating, listing and extracting one file from an archive", - "multiple times with different file sizes. ", - "Also check that the file attributes of the extracted file has survived."]; +%% Test creating, listing and extracting one file from an archive, +%% multiple times with different file sizes. Also check that the file +%% attributes of the extracted file has survived. borderline(Config) when is_list(Config) -> %% Note: We cannot use absolute paths, because the pathnames will be @@ -198,11 +197,9 @@ random_byte_list(_X, 0, Result) -> next_random(X) -> (X*17059465+1) band 16#fffffffff. -atomic(doc) -> - ["Test the 'atomic' operations: create/extract/table, on compressed " - "and uncompressed archives." - "Also test the 'cooked' option."]; -atomic(suite) -> []; +%% Test the 'atomic' operations: create/extract/table, on compressed +%% and uncompressed archives. +%% Also test the 'cooked' option. atomic(Config) when is_list(Config) -> ?line ok = file:set_cwd(?config(priv_dir, Config)), ?line DataFiles = data_files(), @@ -279,9 +276,8 @@ create_files([{Name, Size, First}|Rest]) -> create_files([]) -> ok. -long_names(doc) -> - ["Test to extract an Unix tar file containing filenames longer than 100 ", - "characters and empty directories."]; +%% Test to extract an Unix tar file containing filenames longer than +%% 100 characters and empty directories. long_names(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line Long = filename:join(DataDir, "long_names.tar"), @@ -315,9 +311,8 @@ do_long_names(Long) -> ok. -create_long_names(doc) -> - ["Creates a tar file from a deep directory structure (filenames are ", - "longer than 100 characters)."]; +%% Creates a tar file from a deep directory structure (filenames are +%% longer than 100 characters). create_long_names(Config) when is_list(Config) -> run_in_short_tempdir(Config, fun create_long_names/0). @@ -359,8 +354,7 @@ make_dirs([Dir|Rest], Parent) -> make_dirs([], Dir) -> Dir. -bad_tar(doc) -> - ["Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files."]; +%% Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files. bad_tar(Config) when is_list(Config) -> ?line try_bad("bad_checksum", bad_header, Config), ?line try_bad("bad_octal", bad_header, Config), @@ -395,9 +389,8 @@ try_bad(Name0, Reason, Config) -> ct:fail({bad_return_value, Other1, Other2}) end. -errors(doc) -> - ["Tests that some common errors return correct error codes ", - "and that format_error/1 handles them correctly."]; +%% Tests that some common errors return correct error codes +%% and that format_error/1 handles them correctly. errors(Config) when is_list(Config) -> ?line PrivDir = ?config(priv_dir, Config), @@ -444,8 +437,7 @@ remove_prefix([C|Rest1], [C|Rest2]) -> remove_prefix(_, Result) -> Result. -extract_from_binary(doc) -> - "Test extracting a tar archive from a binary."; +%% Test extracting a tar archive from a binary. extract_from_binary(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line PrivDir = ?config(priv_dir, Config), @@ -501,8 +493,7 @@ extract_from_binary_compressed(Config) when is_list(Config) -> ok. -extract_from_open_file(doc) -> - "Test extracting a tar archive from an open file."; +%% Test extracting a tar archive from an open file. extract_from_open_file(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line PrivDir = ?config(priv_dir, Config), @@ -527,8 +518,7 @@ extract_from_open_file(Config) when is_list(Config) -> ok. -symlinks(doc) -> - "Test that archives containing symlinks can be created and extracted."; +%% Test that archives containing symlinks can be created and extracted. symlinks(Config) when is_list(Config) -> ?line PrivDir = ?config(priv_dir, Config), ?line Dir = filename:join(PrivDir, "symlinks"), @@ -700,9 +690,8 @@ cooked_compressed(Config) when is_list(Config) -> ?line delete_files([filename:join(PrivDir, "ddll_SUITE_data")]), ok. -memory(doc) -> - ["Test that an archive can be created directly from binaries and " - "that an archive can be extracted into binaries."]; +%% Test that an archive can be created directly from binaries and +%% that an archive can be extracted into binaries. memory(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl index 9b0c34435d..4b09b6ffff 100644 --- a/lib/stdlib/test/timer_simple_SUITE.erl +++ b/lib/stdlib/test/timer_simple_SUITE.erl @@ -89,27 +89,23 @@ init_per_testcase(_, Config) when is_list(Config) -> %% Testing timer interface!! -apply_after(doc) -> "Test of apply_after, with sending of message."; -apply_after(suite) -> []; +%% Test of apply_after, with sending of message. apply_after(Config) when is_list(Config) -> ?line timer:apply_after(500, ?MODULE, send, [self(), ok_apply]), ?line ok = get_mess(1000, ok_apply). -send_after1(doc) -> "Test of send_after with time = 0."; -send_after1(suite) -> []; +%% Test of send_after with time = 0. send_after1(Config) when is_list(Config) -> ?line timer:send_after(0, ok_send1), ?line ok = get_mess(1000, ok_send1). -send_after2(doc) -> "Test of send_after with time = 500."; -send_after2(suite) -> []; +%% Test of send_after with time = 500. send_after2(Config) when is_list(Config) -> ?line timer:send_after(500, self(), ok_send2), ?line ok = get_mess(2000, ok_send2). -send_after3(doc) -> "Test of send_after with time = 500, with receiver " - "a registered process. [OTP-2735]"; -send_after3(suite) -> []; +%% Test of send_after with time = 500, with receiver a registered +%% process. [OTP-2735] send_after3(Config) when is_list(Config) -> ?line Name = list_to_atom(pid_to_list(self())), ?line register(Name, self()), @@ -117,18 +113,15 @@ send_after3(Config) when is_list(Config) -> ?line ok = get_mess(2000, ok_send3), ?line unregister(Name). -exit_after1(doc) -> "Test of exit_after with time = 1000."; -exit_after1(suite) -> []; +%% Test of exit_after with time = 1000. exit_after1(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Pid = spawn_link(?MODULE, forever, []), ?line timer:exit_after(1000, Pid, exit_test1), ?line ok = get_mess(5000, {'EXIT', Pid, exit_test1}). -exit_after2(doc) -> "Test of exit_after with time = 1000. The process to " - "exit is the name of a registered process. " - "[OTP-2735]"; -exit_after2(suite) -> []; +%% Test of exit_after with time = 1000. The process to exit is the +%% name of a registered process. [OTP-2735] exit_after2(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Pid = spawn_link(?MODULE, forever, []), @@ -137,18 +130,15 @@ exit_after2(Config) when is_list(Config) -> ?line timer:exit_after(1000, Name, exit_test2), ?line ok = get_mess(2000, {'EXIT', Pid, exit_test2}). -kill_after1(doc) -> "Test of kill_after with time = 1000."; -kill_after1(suite) -> []; +%% Test of kill_after with time = 1000. kill_after1(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Pid = spawn_link(?MODULE, forever, []), ?line timer:kill_after(1000, Pid), ?line ok = get_mess(2000, {'EXIT', Pid, killed}). -kill_after2(doc) -> "Test of kill_after with time = 1000. The process to " - "exit is the name of a registered process. " - "[OTP-2735]"; -kill_after2(suite) -> []; +%% Test of kill_after with time = 1000. The process to exit is the +%% name of a registered process. [OTP-2735] kill_after2(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Pid = spawn_link(?MODULE, forever, []), @@ -157,10 +147,9 @@ kill_after2(Config) when is_list(Config) -> ?line timer:kill_after(1000, Name), ?line ok = get_mess(2000, {'EXIT', Pid, killed}). -apply_interval(doc) -> "Test of apply_interval by sending messages. Receive " - "3 messages, cancel the timer, and check that we do " - "not get any more messages."; -apply_interval(suite) -> []; +%% Test of apply_interval by sending messages. Receive +%% 3 messages, cancel the timer, and check that we do +%% not get any more messages. apply_interval(Config) when is_list(Config) -> ?line {ok, Ref} = timer:apply_interval(1000, ?MODULE, send, [self(), apply_int]), @@ -168,31 +157,25 @@ apply_interval(Config) when is_list(Config) -> ?line timer:cancel(Ref), ?line nor = get_mess(1000, apply_int). -send_interval1(doc) -> "Test of send_interval/2. Receive 5 messages, cancel " - "the timer, and check that we do not get any more " - "messages."; -send_interval1(suite) -> []; +%% Test of send_interval/2. Receive 5 messages, cancel the timer, and +%% check that we do not get any more messages. send_interval1(Config) when is_list(Config) -> {ok, Ref} = timer:send_interval(1000, send_int), ?line ok = get_mess(1500, send_int, 5), timer:cancel(Ref), ?line nor = get_mess(1000, send_int). % We should receive only five -send_interval2(doc) -> "Test of send_interval/3. Receive 2 messages, cancel " - "the timer, and check that we do not get any more " - "messages."; -send_interval2(suite) -> []; +%% Test of send_interval/3. Receive 2 messages, cancel the timer, and +%% check that we do not get any more messages. send_interval2(Config) when is_list(Config) -> {ok, Ref} = timer:send_interval(1000, self(), send_int2), ?line ok = get_mess(1500, send_int2, 2), timer:cancel(Ref), ?line nor = get_mess(1000, send_int2). % We should receive only two -send_interval3(doc) -> "Test of send_interval/3. Receive 2 messages, cancel " - "the timer, and check that we do not get any more " - "messages. The receiver is the name of a registered " - "process. [OTP-2735]"; -send_interval3(suite) -> []; +%% Test of send_interval/3. Receive 2 messages, cancel the timer, and +%% check that we do not get any more messages. The receiver is the +%% name of a registered process. [OTP-2735] send_interval3(Config) when is_list(Config) -> ?line process_flag(trap_exit, true), ?line Name = list_to_atom(pid_to_list(self())), @@ -203,9 +186,8 @@ send_interval3(Config) when is_list(Config) -> ?line nor = get_mess(1000, send_int3), % We should receive only two ?line unregister(Name). -send_interval4(doc) -> "Test that send interval stops sending msg when the " - "receiving process terminates."; -send_interval4(suite) -> []; +%% Test that send interval stops sending msg when the receiving +%% process terminates. send_interval4(Config) when is_list(Config) -> ?line timer:send_interval(500, one_time_only), receive @@ -217,20 +199,17 @@ send_interval4(Config) when is_list(Config) -> Msg -> Msg end. -cancel1(doc) -> "Test that we can cancel a timer."; -cancel1(suite) -> []; +%% Test that we can cancel a timer. cancel1(Config) when is_list(Config) -> ?line {ok, Ref} = timer:send_after(1000, this_should_be_canceled), ?line timer:cancel(Ref), ?line nor = get_mess(2000, this_should_be_canceled). % We should rec 0 msgs -cancel2(doc) -> "Test cancel/1 with bad argument."; -cancel2(suite) -> []; +%% Test cancel/1 with bad argument. cancel2(Config) when is_list(Config) -> ?line {error, badarg} = timer:cancel(no_reference). -tc(doc) -> "Test sleep/1 and tc/3."; -tc(suite) -> []; +%% Test sleep/1 and tc/3. tc(Config) when is_list(Config) -> %% This should test both sleep and tc/3 ?line {Res1, ok} = timer:tc(timer, sleep, [500]), @@ -284,11 +263,8 @@ tc(Config) when is_list(Config) -> ?line if MyRes == TimerRes -> ok end, ok. -unique_refs(doc) -> - "Tests that cancellations of one-shot timers do not accidentally " - "cancel interval timers [OTP-2771]."; -unique_refs(suite) -> - []; +%% Test that cancellations of one-shot timers do not accidentally +%% cancel interval timers. [OTP-2771]. unique_refs(Config) when is_list(Config) -> ?line ITimers = repeat_send_interval(10), % 10 interval timers ?line eat_refs(?MAXREF - ?REFMARG), @@ -359,7 +335,6 @@ forever() -> % -timer_perf(suite) -> []; timer_perf(Config) when is_list(Config) -> performance(timer). diff --git a/lib/stdlib/test/win32reg_SUITE.erl b/lib/stdlib/test/win32reg_SUITE.erl index c74f05637f..a0edf706a8 100644 --- a/lib/stdlib/test/win32reg_SUITE.erl +++ b/lib/stdlib/test/win32reg_SUITE.erl @@ -51,8 +51,7 @@ init_per_suite(Config) when is_list(Config) -> end_per_suite(Config) when is_list(Config) -> Config. - -long(doc) -> "Test long keys and entries (OTP-3446)."; +%% Test long keys and entries (OTP-3446). long(Config) when is_list(Config) -> LongKey = "software\\" ++ lists:flatten(lists:duplicate(10, "..\\software\\")) ++ diff --git a/lib/stdlib/test/y2k_SUITE.erl b/lib/stdlib/test/y2k_SUITE.erl index d80dd10631..fb95df9440 100644 --- a/lib/stdlib/test/y2k_SUITE.erl +++ b/lib/stdlib/test/y2k_SUITE.erl @@ -55,10 +55,7 @@ end_per_group(_GroupName, Config) -> Config. -date_1999_01_01(doc) -> - "#1 : 1999-01-01: test roll-over from 1998-12-31 to 1999-01-01."; -date_1999_01_01(suite) -> - []; +%% #1 : 1999-01-01: test roll-over from 1998-12-31 to 1999-01-01. date_1999_01_01(Config) when is_list(Config) -> ?line Date = {1998, 12, 31}, NextDate = {1999, 1, 1}, ?line match(next_date(Date), NextDate), @@ -78,29 +75,20 @@ date_1999_01_01(Config) when is_list(Config) -> ok end. -date_1999_02_28(doc) -> - "#2 : 1999-02-28: test roll-over from 1999-02-28 to 1999-03-01."; -date_1999_02_28(suite) -> - []; +%% #2 : 1999-02-28: test roll-over from 1999-02-28 to 1999-03-01. date_1999_02_28(Config) when is_list(Config) -> ?line Date = {1999, 2, 28}, NextDate = {1999, 3, 1}, ?line match(next_date(Date), NextDate), ?line match(tz_next_date(Date), NextDate). -date_1999_09_09(doc) -> - "#3 : 1999-09-09: test roll-over from 1999-09-08 to 1999-09-09."; -date_1999_09_09(suite) -> - []; +%% #3 : 1999-09-09: test roll-over from 1999-09-08 to 1999-09-09. date_1999_09_09(Config) when is_list(Config) -> ?line Date = {1999, 9, 8}, NextDate = {1999, 9, 9}, ?line match(next_date(Date), NextDate), ?line match(tz_next_date(Date), NextDate). -date_2000_01_01(doc) -> - "#4 : 2000-01-01: test roll-over from 1999-12-31 to 2000-01-01 to " - "2000-01-02."; -date_2000_01_01(suite) -> - []; +%% #4 : 2000-01-01: test roll-over from 1999-12-31 to 2000-01-01 to +%% 2000-01-02.; date_2000_01_01(Config) when is_list(Config) -> ?line Date = {1999, 12, 31}, NextDate = {2000, 1, 1}, ?line match(next_date(Date), NextDate), @@ -109,11 +97,8 @@ date_2000_01_01(Config) when is_list(Config) -> ?line match(next_date(NextDate), NextDate1), ?line match(tz_next_date(NextDate), NextDate1). -date_2000_02_29(doc) -> - "#5 : 2000-02-29: test roll-over from 2000-02-28 to 2000-02-29 to " - "2000-03-01."; -date_2000_02_29(suite) -> - []; +%% #5 : 2000-02-29: test roll-over from 2000-02-28 to 2000-02-29 to +%% 2000-03-01. date_2000_02_29(Config) when is_list(Config) -> ?line Date = {2000, 2, 28}, NextDate = {2000, 2, 29}, ?line match(next_date(Date), NextDate), @@ -122,29 +107,20 @@ date_2000_02_29(Config) when is_list(Config) -> ?line match(next_date(NextDate), NextDate1), ?line match(tz_next_date(NextDate), NextDate1). -date_2001_01_01(doc) -> - "#6 : 2001-01-01: test roll-over from 2000-12-31 to 2001-01-01."; -date_2001_01_01(suite) -> - []; +%% #6 : 2001-01-01: test roll-over from 2000-12-31 to 2001-01-01. date_2001_01_01(Config) when is_list(Config) -> ?line Date = {2000, 12, 31}, NextDate = {2001, 1, 1}, ?line match(next_date(Date), NextDate), ?line match(tz_next_date(Date), NextDate). -date_2001_02_29(doc) -> - "#7 : 2001-02-29: test roll-over from 2001-02-28 to 2001-03-01."; -date_2001_02_29(suite) -> - []; +%% #7 : 2001-02-29: test roll-over from 2001-02-28 to 2001-03-01. date_2001_02_29(Config) when is_list(Config) -> ?line Date = {2001, 2, 28}, NextDate = {2001, 3, 1}, ?line match(next_date(Date), NextDate), ?line match(tz_next_date(Date), NextDate). -date_2004_02_29(doc) -> - "#8 : 2004-02-29: test roll-over from 2004-02-28 to 2004-02-29 to " - "2004-03-01."; -date_2004_02_29(suite) -> - []; +%% #8 : 2004-02-29: test roll-over from 2004-02-28 to 2004-02-29 to +%% 2004-03-01. date_2004_02_29(Config) when is_list(Config) -> ?line Date = {2004, 2, 28}, NextDate = {2004, 2, 29}, ?line match(next_date(Date), NextDate), diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index 615c1a04a6..c1da498f49 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -56,10 +56,9 @@ end_per_group(_GroupName, Config) -> Config. -borderline(doc) -> - ["Test creating, listing and extracting one file from an archive " - "multiple times with different file sizes. Also check that the " - "modification date of the extracted file has survived."]; +%% Test creating, listing and extracting one file from an archive +%% multiple times with different file sizes. Also check that the +%% modification date of the extracted file has survived. borderline(Config) when is_list(Config) -> RootDir = ?config(priv_dir, Config), TempDir = filename:join(RootDir, "borderline"), @@ -215,10 +214,8 @@ random_byte_list(_X, 0, Result) -> next_random(X) -> (X*17059465+1) band 16#fffffffff. -atomic(doc) -> - ["Test the 'atomic' operations: zip/unzip/list_dir, on archives." - "Also test the 'cooked' option."]; -atomic(suite) -> []; +%% Test the 'atomic' operations: zip/unzip/list_dir, on archives. +%% Also test the 'cooked' option. atomic(Config) when is_list(Config) -> ok = file:set_cwd(?config(priv_dir, Config)), DataFiles = data_files(), @@ -243,10 +240,8 @@ atomic(Config) when is_list(Config) -> ok. -openzip_api(doc) -> - ["Test the openzip_open/2, openzip_get/1, openzip_get/2, openzip_close/1 " - "and openzip_list_dir/1 functions."]; -openzip_api(suite) -> []; +%% Test the openzip_open/2, openzip_get/1, openzip_get/2, openzip_close/1 +%% and openzip_list_dir/1 functions. openzip_api(Config) when is_list(Config) -> ok = file:set_cwd(?config(priv_dir, Config)), DataFiles = data_files(), @@ -282,10 +277,8 @@ openzip_api(Config) when is_list(Config) -> ok. -zip_api(doc) -> - ["Test the zip_open/2, zip_get/1, zip_get/2, zip_close/1 " - "and zip_list_dir/1 functions."]; -zip_api(suite) -> []; +%% Test the zip_open/2, zip_get/1, zip_get/2, zip_close/1, +%% and zip_list_dir/1 functions. zip_api(Config) when is_list(Config) -> ok = file:set_cwd(?config(priv_dir, Config)), DataFiles = data_files(), @@ -320,11 +313,9 @@ zip_api(Config) when is_list(Config) -> ok. -open_leak(doc) -> - ["Test that zip doesn't leak processes and ports where the " - "controlling process dies without closing an zip opened with " - "zip:zip_open/1."]; -open_leak(suite) -> []; +%% Test that zip doesn't leak processes and ports where the +%% controlling process dies without closing an zip opened with +%% zip:zip_open/1. open_leak(Config) when is_list(Config) -> %% Create a zip archive Zip = "zip.zip", @@ -358,10 +349,7 @@ spawned_zip_dead(ZipSrv) -> false end. -unzip_options(doc) -> - ["Test options for unzip, only cwd and file_list currently"]; -unzip_options(suite) -> - []; +%% Test options for unzip, only cwd and file_list currently. unzip_options(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -389,10 +377,7 @@ unzip_options(Config) when is_list(Config) -> ?line 0 = delete_files([Subdir]), ok. -unzip_jar(doc) -> - ["Test unzip a jar file (OTP-7382)"]; -unzip_jar(suite) -> - []; +%% Test unzip a jar file (OTP-7382). unzip_jar(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -418,10 +403,7 @@ unzip_jar(Config) when is_list(Config) -> ?line 0 = delete_files([Subdir]), ok. -zip_options(doc) -> - ["Test the options for unzip, only cwd currently"]; -zip_options(suite) -> - []; +%% Test the options for unzip, only cwd currently. zip_options(Config) when is_list(Config) -> PrivDir = ?config(priv_dir, Config), ok = file:set_cwd(PrivDir), @@ -459,10 +441,7 @@ zip_options(Config) when is_list(Config) -> ok. -list_dir_options(doc) -> - ["Test the options for list_dir... one day"]; -list_dir_options(suite) -> - []; +%% Test the options for list_dir... one day. list_dir_options(Config) when is_list(Config) -> ok. @@ -514,8 +493,7 @@ create_files([]) -> %% make_dirs([], Dir) -> %% Dir. -bad_zip(doc) -> - ["Try zip:unzip/1 on some corrupted zip files."]; +%% Try zip:unzip/1 on some corrupted zip files. bad_zip(Config) when is_list(Config) -> ok = file:set_cwd(?config(priv_dir, Config)), try_bad("bad_crc", {bad_crc, "abc.txt"}, Config), @@ -550,8 +528,7 @@ try_bad(Name0, Reason, What, Config) -> ct:fail({bad_return_value, Other}) end. -unzip_to_binary(doc) -> - ["Test extracting to binary with memory option."]; +%% Test extracting to binary with memory option. unzip_to_binary(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -573,8 +550,7 @@ unzip_to_binary(Config) when is_list(Config) -> ok. -zip_to_binary(doc) -> - ["Test compressing to binary with memory option."]; +%% Test compressing to binary with memory option. zip_to_binary(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -606,8 +582,7 @@ zip_to_binary(Config) when is_list(Config) -> ok. -aliases(doc) -> - ["Test using the aliases, extract/2, table/2 and create/3"]; +%% Test using the aliases, extract/2, table/2 and create/3. aliases(Config) when is_list(Config) -> {_, _, X0} = erlang:timestamp(), Size = 100, @@ -628,8 +603,7 @@ aliases(Config) when is_list(Config) -> -unzip_from_binary(doc) -> - ["Test extracting a zip archive from a binary."]; +%% Test extracting a zip archive from a binary. unzip_from_binary(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -698,9 +672,7 @@ do_delete_files([Item|Rest], Cnt) -> end, do_delete_files(Rest, Cnt + DelCnt). -compress_control(doc) -> - ["Test control of which files that should be compressed"]; -compress_control(suite) -> []; +%% Test control of which files that should be compressed. compress_control(Config) when is_list(Config) -> ok = file:set_cwd(?config(priv_dir, Config)), Dir = "compress_control", -- cgit v1.2.3