diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 1 | ||||
-rw-r--r-- | lib/stdlib/test/base64_SUITE.erl | 38 | ||||
-rw-r--r-- | lib/stdlib/test/error_logger_h_SUITE.erl | 400 | ||||
-rw-r--r-- | lib/stdlib/test/gen_event_SUITE.erl | 11 | ||||
-rw-r--r-- | lib/stdlib/test/id_transform_SUITE.erl | 53 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 213 | ||||
-rw-r--r-- | lib/stdlib/test/io_proto_SUITE.erl | 162 | ||||
-rw-r--r-- | lib/stdlib/test/lists_SUITE.erl | 163 | ||||
-rw-r--r-- | lib/stdlib/test/proc_lib_SUITE.erl | 228 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/test/rand_SUITE.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/test/re_SUITE.erl | 129 | ||||
-rw-r--r-- | lib/stdlib/test/zip_SUITE.erl | 20 |
13 files changed, 1088 insertions, 368 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index d4ab674486..e366c2b755 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -30,6 +30,7 @@ MODULES= \ erl_lint_SUITE \ erl_pp_SUITE \ erl_scan_SUITE \ + error_logger_h_SUITE \ escript_SUITE \ ets_SUITE \ ets_tough_SUITE \ diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl index cca9b967d5..75eebba6c6 100644 --- a/lib/stdlib/test/base64_SUITE.erl +++ b/lib/stdlib/test/base64_SUITE.erl @@ -30,7 +30,8 @@ %% Test cases must be exported. -export([base64_encode/1, base64_decode/1, base64_otp_5635/1, base64_otp_6279/1, big/1, illegal/1, mime_decode/1, - mime_decode_to_string/1, roundtrip/1]). + mime_decode_to_string/1, + roundtrip_1/1, roundtrip_2/1, roundtrip_3/1, roundtrip_4/1]). init_per_testcase(_, Config) -> Dog = test_server:timetrap(?t:minutes(4)), @@ -50,10 +51,11 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [base64_encode, base64_decode, base64_otp_5635, base64_otp_6279, big, illegal, mime_decode, mime_decode_to_string, - roundtrip]. + {group, roundtrip}]. groups() -> - []. + [{roundtrip, [parallel], + [roundtrip_1, roundtrip_2, roundtrip_3, roundtrip_4]}]. init_per_suite(Config) -> Config. @@ -242,21 +244,33 @@ mime_decode_to_string(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -roundtrip(Config) when is_list(Config) -> - Sizes = lists:seq(1, 255) ++ lists:seq(2400-5, 2440), - roundtrip_1(Sizes, []). +roundtrip_1(Config) when is_list(Config) -> + do_roundtrip(1). -roundtrip_1([NextSize|Sizes], Current) -> +roundtrip_2(Config) when is_list(Config) -> + do_roundtrip(2). + +roundtrip_3(Config) when is_list(Config) -> + do_roundtrip(3). + +roundtrip_4(Config) when is_list(Config) -> + do_roundtrip(4). + +do_roundtrip(Offset) -> + Sizes = lists:seq(Offset, 255, 4) ++ lists:seq(2400-6+Offset, 2440, 4), + do_roundtrip_1(Sizes, []). + +do_roundtrip_1([NextSize|Sizes], Current) -> Len = length(Current), io:format("~p", [Len]), - do_roundtrip(Current), + do_roundtrip_2(Current), Next = random_byte_list(NextSize - Len, Current), - roundtrip_1(Sizes, Next); -roundtrip_1([], Last) -> + do_roundtrip_1(Sizes, Next); +do_roundtrip_1([], Last) -> io:format("~p", [length(Last)]), - do_roundtrip(Last). + do_roundtrip_2(Last). -do_roundtrip(List) -> +do_roundtrip_2(List) -> Bin = list_to_binary(List), Base64Bin = base64:encode(List), Base64Bin = base64:encode(Bin), diff --git a/lib/stdlib/test/error_logger_h_SUITE.erl b/lib/stdlib/test/error_logger_h_SUITE.erl new file mode 100644 index 0000000000..b0b9c717a1 --- /dev/null +++ b/lib/stdlib/test/error_logger_h_SUITE.erl @@ -0,0 +1,400 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2015. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +-module(error_logger_h_SUITE). +-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, + init_per_group/2,end_per_group/2]). +-export([logfile/1,logfile_truncated/1,tty/1,tty_truncated/1]). + +%% Event handler exports. +-export([init/1,handle_event/2,terminate/2]). + +-include_lib("test_server/include/test_server.hrl"). + +suite() -> [{ct_hooks,[ts_install_cth]}]. + +all() -> + [logfile,logfile_truncated,tty,tty_truncated]. + +groups() -> + []. + +init_per_suite(Config) -> + Config. + +end_per_suite(_Config) -> + ok. + +init_per_group(_GroupName, Config) -> + Config. + +end_per_group(_GroupName, Config) -> + Config. + +logfile(Config) -> + PrivDir = ?config(priv_dir, Config), + LogDir = filename:join(PrivDir, ?MODULE), + Log = filename:join(LogDir, "logfile.log"), + ok = filelib:ensure_dir(Log), + + Ev = event_templates(), + + do_one_logfile(Log, Ev, unlimited), + + Pa = "-pa " ++ filename:dirname(code:which(?MODULE)), + {ok,Node} = start_node(logfile, Pa), + error_logger:logfile({open,Log}), + ok = rpc:call(Node, erlang, apply, [fun gen_events/1,[Ev]]), + AtNode = iolist_to_binary(["** at node ",atom_to_list(Node)," **"]), + error_logger:logfile(close), + analyse_events(Log, Ev, [AtNode], unlimited), + + test_server:stop_node(Node), + + cleanup(Log), + ok. + +logfile_truncated(Config) -> + PrivDir = ?config(priv_dir, Config), + LogDir = filename:join(PrivDir, ?MODULE), + Log = filename:join(LogDir, "logfile_truncated.log"), + ok = filelib:ensure_dir(Log), + + Ev = event_templates(), + + Depth = 20, + application:set_env(kernel, error_logger_format_depth, Depth), + try + do_one_logfile(Log, Ev, Depth) + after + application:unset_env(kernel, error_logger_format_depth) + end, + + cleanup(Log), + ok. + +do_one_logfile(Log, Ev, Depth) -> + error_logger:logfile({open,Log}), + gen_events(Ev), + error_logger:logfile(close), + analyse_events(Log, Ev, [], Depth). + +tty(Config) -> + PrivDir = ?config(priv_dir, Config), + LogDir = filename:join(PrivDir, ?MODULE), + Log = filename:join(LogDir, "tty.log"), + ok = filelib:ensure_dir(Log), + + Ev = event_templates(), + + do_one_tty(Log, Ev, unlimited), + + Pa = "-pa " ++ filename:dirname(code:which(?MODULE)), + {ok,Node} = start_node(logfile, Pa), + tty_log_open(Log), + ok = rpc:call(Node, erlang, apply, [fun gen_events/1,[Ev]]), + tty_log_close(), + AtNode = iolist_to_binary(["** at node ",atom_to_list(Node)," **"]), + analyse_events(Log, Ev, [AtNode], unlimited), + + test_server:stop_node(Node), + + cleanup(Log), + ok. + +tty_truncated(Config) -> + PrivDir = ?config(priv_dir, Config), + LogDir = filename:join(PrivDir, ?MODULE), + Log = filename:join(LogDir, "tty_truncated.log"), + ok = filelib:ensure_dir(Log), + + Ev = event_templates(), + + Depth = 20, + application:set_env(kernel, error_logger_format_depth, Depth), + try + do_one_tty(Log, Ev, Depth) + after + application:unset_env(kernel, error_logger_format_depth) + end, + + cleanup(Log), + ok. + +do_one_tty(Log, Ev, Depth) -> + tty_log_open(Log), + gen_events(Ev), + tty_log_close(), + analyse_events(Log, Ev, [], Depth). + +tty_log_open(Log) -> + {ok,Fd} = file:open(Log, [write]), + Depth = case application:get_env(kernel, error_logger_format_depth) of + {ok,D} -> D; + _ -> unlimited + end, + error_logger:add_report_handler(?MODULE, {Fd,Depth}), + Fd. + +tty_log_close() -> + error_logger:delete_report_handler(?MODULE), + ok. + +event_templates() -> + [{error_msg,["Pure error string\n",[]]}, + {error_msg,["Pure error string with error ~p\n",[]]}, + {error_msg,["Error string with ~p\n", [format]]}, + {error_msg,["Error string with bad format ~p\n", []]}, + + {error_report,[error_atom]}, + {error_report,["error string"]}, + {error_report,[[{error_tag,value},error_value]]}, + + {info_msg,["Pure info string\n",[]]}, + {info_msg,["Pure info string with error ~p\n",[]]}, + {info_msg,["Pure string with ~p\n", [format]]}, + {info_msg,["Pure string with bad format ~p\n", []]}, + + {info_report,[info_atom]}, + {info_report,["info string"]}, + {info_report,[[{info_tag,value},info_value]]}, + + {warning_msg,["Pure warning string\n",[]]}, + {warning_msg,["Pure warning string with error ~p\n",[]]}, + {warning_msg,["Warning string with ~p\n", [format]]}, + {warning_msg,["Warning string with bad format ~p\n", []]}, + + {warning_report,[warning_atom]}, + {warning_report,["warning string"]}, + {warning_report,[[{warning_tag,value},warning_value]]}, + + %% Bigger terms. + {error_msg,["fairly big: ~p\n",[lists:seq(1, 128)]]}, + {error_report,[list_to_tuple(lists:seq(1, 100))]}, + {error_report,[lists:seq(32, 126)]}, + {error_report,[[{tag,lists:seq(1, 64)}]]} + ]. + +gen_events(Ev) -> + io:format("node = ~p\n", [node()]), + io:format("group leader = ~p\n", [group_leader()]), + io:format("~p\n", [gen_event:which_handlers(error_logger)]), + call_error_logger(Ev), + + {Pid,Ref} = spawn_monitor(fun() -> error(ouch) end), + receive + {'DOWN',Ref,process,Pid,_} -> + ok + end, + + %% The following calls with a custom type will be ignored. + error_logger:error_report(ignored, value), + error_logger:warning_report(ignored, value), + error_logger:info_report(ignored, value), + receive after 100 -> ok end, + ok. + +analyse_events(Log, Ev, AtNode, Depth) -> + {ok,Bin} = file:read_file(Log), + + io:format("*** Contents of log file ***\n\n~s\n", [Bin]), + + Lines = binary:split(Bin, <<"\n">>, [global,trim_all]), + io:format("~p\n", [Lines]), + + Rest = match_output(Ev, Lines, AtNode, Depth), + io:format("~p\n", [Rest]), + + [] = match_emulator_error(Rest), + ok. + + +call_error_logger([{F,Args}|T]) -> + apply(error_logger, F, Args), + call_error_logger(T); +call_error_logger([]) -> ok. + + +match_emulator_error([Head,Second,Third,_|Lines]) -> + match_head(<<"ERROR">>, Head), + {match,[{0,_}]} = re:run(Second, + "^Error in process <\\d+[.]\\d+[.]\\d+> on " + "node [^ ]* with exit value:"), + {match,[{0,_}]} = re:run(Third, "^[{]ouch,"), + Lines. + +match_output([Item|T], Lines0, AtNode, Depth) -> + try match_item(Item, Lines0, AtNode, Depth) of + Lines -> + match_output(T, Lines, AtNode, Depth) + catch + C:E -> + Stk = erlang:get_stacktrace(), + io:format("ITEM: ~p", [Item]), + io:format("LINES: ~p", [Lines0]), + erlang:raise(C, E, Stk) + end; +match_output([], Lines, _, _) -> Lines. + +match_item(Item, Lines, AtNode, Depth) -> + case item_type(Item) of + {msg,Head,Args} -> + match_format(Head, Args, Lines, AtNode, Depth); + {report,Head,Args} -> + match_term(Head, Args, Lines, AtNode, Depth) + end. + +item_type({error_msg,Args}) -> + {msg,<<"ERROR">>,Args}; +item_type({info_msg,Args}) -> + {msg,<<"INFO">>,Args}; +item_type({warning_msg,Args}) -> + {msg,<<"WARNING">>,Args}; +item_type({error_report,Args}) -> + {report,<<"ERROR">>,Args}; +item_type({info_report,Args}) -> + {report,<<"INFO">>,Args}; +item_type({warning_report,Args}) -> + {report,<<"WARNING">>,Args}. + +match_format(Tag, [Format,Args], [Head|Lines], AtNode, Depth) -> + match_head(Tag, Head), + Bin = try dl_format(Depth, Format, Args) of + Str -> + iolist_to_binary(Str) + catch + _:_ -> + S = dl_format(Depth, "ERROR: ~p - ~p~n", [Format,Args]), + iolist_to_binary(S) + end, + Expected0 = binary:split(Bin, <<"\n">>, [global,trim]), + Expected = Expected0 ++ AtNode, + match_term_lines(Expected, Lines). + +match_term(Tag, [Arg], [Head|Lines], AtNode, Depth) -> + match_head(Tag, Head), + Expected0 = match_term_get_expected(Arg, Depth), + Expected = Expected0 ++ AtNode, + match_term_lines(Expected, Lines). + +match_term_get_expected(List, Depth) when is_list(List) -> + Bin = try iolist_to_binary(dl_format(Depth, "~s\n", [List])) of + Bin0 -> Bin0 + catch + _:_ -> + iolist_to_binary(format_rep(List, Depth)) + end, + binary:split(Bin, <<"\n">>, [global,trim]); +match_term_get_expected(Term, Depth) -> + S = dl_format(Depth, "~p\n", [Term]), + Bin = iolist_to_binary(S), + binary:split(Bin, <<"\n">>, [global,trim]). + +format_rep([{Tag,Data}|Rep], Depth) -> + [dl_format(Depth, " ~p: ~p\n", [Tag,Data])| + format_rep(Rep, Depth)]; +format_rep([Other|Rep], Depth) -> + [dl_format(Depth, " ~p\n", [Other])| + format_rep(Rep, Depth)]; +format_rep([], _Depth) -> []. + +match_term_lines([Line|T], [Line|Lines]) -> + match_term_lines(T, Lines); +match_term_lines([], Lines) -> Lines. + +match_head(Tag, Head) -> + Re = <<"^=",Tag/binary, + " REPORT==== \\d\\d?-[A-Z][a-z][a-z]-\\d{4}::" + "\\d\\d:\\d\\d:\\d\\d ===$">>, + {match,_} = re:run(Head, Re). + +start_node(Name, Args) -> + case test_server:start_node(Name, slave, [{args,Args}]) of + {ok,Node} -> + {ok,Node}; + Error -> + test_server:fail(Error) + end. + +cleanup(File) -> + %% The point of this test case is not to test file operations. + %% Therefore ignore any failures. + case file:delete(File) of + ok -> + ok; + {error,Error1} -> + io:format("file:delete(~s) failed with error ~p", + [File,Error1]) + end, + Dir = filename:dirname(File), + case file:del_dir(Dir) of + ok -> + ok; + {error,Error2} -> + io:format("file:del_dir(~s) failed with error ~p", + [Dir,Error2]) + end, + ok. + + +%% Depth-limited io_lib:format. Intentionally implemented here instead +%% of using io_lib:scan_format/2 to avoid using the same implementation +%% as in the error_logger handlers. + +dl_format(unlimited, Format, Args) -> + io_lib:format(Format, Args); +dl_format(Depth, Format0, Args0) -> + {Format,Args} = dl_format_1(Format0, Args0, Depth, [], []), + io_lib:format(Format, Args). + +dl_format_1("~p"++Fs, [A|As], Depth, Facc, Acc) -> + dl_format_1(Fs, As, Depth, [$P,$~|Facc], [Depth,A|Acc]); +dl_format_1("~w"++Fs, [A|As], Depth, Facc, Acc) -> + dl_format_1(Fs, As, Depth, [$W,$~|Facc], [Depth,A|Acc]); +dl_format_1("~s"++Fs, [A|As], Depth, Facc, Acc) -> + dl_format_1(Fs, As, Depth, [$s,$~|Facc], [A|Acc]); +dl_format_1([F|Fs], As, Depth, Facc, Aacc) -> + dl_format_1(Fs, As, Depth, [F|Facc], Aacc); +dl_format_1([], [], _, Facc, Aacc) -> + {lists:reverse(Facc),lists:reverse(Aacc)}. + +%%% +%%% Our own event handler. There is no way to intercept the output +%%% from error_logger_tty_h, but we can use the same code by +%%% calling error_logger_tty_h:write_event/2. +%%% + +init({_,_}=St) -> + {ok,St}. + +handle_event(Event, {Fd,Depth}=St) -> + case error_logger_tty_h:write_event(tag_event(Event), io_lib, Depth) of + ok -> + ok; + Str when is_list(Str) -> + io:put_chars(Fd, Str) + end, + {ok,St}. + +terminate(_Reason, {Fd,_}) -> + ok = file:close(Fd), + []. + +tag_event(Event) -> + {erlang:universaltime(),Event}. diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index 7a6fcba4e5..b019f98b69 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -412,7 +412,6 @@ notify(Config) when is_list(Config) -> ok end, ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:notify(my_dummy_handler, Event), ?line receive @@ -445,7 +444,6 @@ notify(Config) when is_list(Config) -> end, ?line ok = gen_event:notify(my_dummy_handler, {swap_event, {dummy1_h, 9}, swap}), - ?t:sleep(1000), ?line [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:notify(my_dummy_handler, Event), ?line receive @@ -485,7 +483,6 @@ notify(Config) when is_list(Config) -> ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:notify(my_dummy_handler, do_crash), @@ -496,7 +493,6 @@ notify(Config) when is_list(Config) -> ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), ?line ok = gen_event:notify(my_dummy_handler, {swap_event,dummy1_h,swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:notify(my_dummy_handler, delete_event), @@ -529,7 +525,6 @@ sync_notify(Config) when is_list(Config) -> end, ?line ok = gen_event:sync_notify(my_dummy_handler, {swap_event, dummy1_h, swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:sync_notify(my_dummy_handler, Event), ?line receive @@ -562,7 +557,6 @@ sync_notify(Config) when is_list(Config) -> end, ?line ok = gen_event:sync_notify(my_dummy_handler, {swap_event, {dummy1_h, 9}, swap}), - ?t:sleep(1000), ?line [{dummy1_h,9}] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:sync_notify(my_dummy_handler, Event), ?line receive @@ -603,7 +597,6 @@ sync_notify(Config) when is_list(Config) -> ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), ?line ok = gen_event:sync_notify(my_dummy_handler, {swap_event,dummy1_h,swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:sync_notify(my_dummy_handler, do_crash), @@ -615,7 +608,6 @@ sync_notify(Config) when is_list(Config) -> ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), ?line ok = gen_event:sync_notify(my_dummy_handler, {swap_event,dummy1_h,swap}), - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line ok = gen_event:sync_notify(my_dummy_handler, delete_event), @@ -789,7 +781,6 @@ info(Config) when is_list(Config) -> ok end, ?line my_dummy_handler ! {swap_info,dummy1_h,swap}, - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line my_dummy_handler ! Info, ?line receive @@ -821,7 +812,6 @@ info(Config) when is_list(Config) -> ok end, ?line my_dummy_handler ! {swap_info,{dummy1_h,2},swap}, - ?t:sleep(1000), ?line [{dummy1_h,2}] = gen_event:which_handlers(my_dummy_handler), ?line my_dummy_handler ! Info, ?line receive @@ -853,7 +843,6 @@ info(Config) when is_list(Config) -> ok end, ?line my_dummy_handler ! {swap_info,dummy1_h,swap}, - ?t:sleep(1000), ?line [dummy1_h] = gen_event:which_handlers(my_dummy_handler), ?line my_dummy_handler ! Info, ?line receive diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl index 41de016f8d..1cff990697 100644 --- a/lib/stdlib/test/id_transform_SUITE.erl +++ b/lib/stdlib/test/id_transform_SUITE.erl @@ -56,47 +56,26 @@ end_per_group(_GroupName, Config) -> id_transform(doc) -> "Test erl_id_trans."; id_transform(Config) when is_list(Config) -> - ?line File=filename:join([code:lib_dir(stdlib),"examples", - "erl_id_trans.erl"]), - ?line {ok,erl_id_trans,Bin}=compile:file(File,[binary]), - ?line {module,erl_id_trans}=code:load_binary(erl_id_trans,File,Bin), - ?line case test_server:purify_is_running() of - false -> - Dog = ct:timetrap(?t:hours(1)), - ?line Res = run_in_test_suite(), - ?t:timetrap_cancel(Dog), - Res; - true -> - {skip,"Purify (too slow)"} - end. + File = filename:join([code:lib_dir(stdlib),"examples", + "erl_id_trans.erl"]), + {ok,erl_id_trans,Bin} = compile:file(File,[binary]), + {module,erl_id_trans} = code:load_binary(erl_id_trans, File, Bin), + case test_server:purify_is_running() of + false -> + Dog = ct:timetrap(?t:hours(1)), + Res = run_in_test_suite(), + ?t:timetrap_cancel(Dog), + Res; + true -> + {skip,"Valgrind (too slow)"} + end. run_in_test_suite() -> - LibDir = code:lib_dir(), SuperDir = filename:dirname(filename:dirname(code:which(?MODULE))), TestDirs = filelib:wildcard(filename:join([SuperDir,"*_test"])), - {All,Res} = case LibDir of - "/clearcase/otp/erts/lib" -> - %% Only test_suites 'cause clearcase is too slow... - {false,run_list(TestDirs)}; - _ -> - {true,run_codepath_and(TestDirs)} - end, - Comment0 = case All of - true -> []; - false -> "Only testsuite directories traversed" - end, - case Res of - {error,Reason} when Comment0 =/= [] -> - {failed,Comment0++"; "++Reason}; - {error,Reason} -> - {failed,Reason}; - ok -> - {comment,Comment0} - end. - -run_codepath_and(DirList) -> AbsDirs = [filename:absname(X) || X <- code:get_path()], - run_list(ordsets:from_list([X || X <- AbsDirs] ++ DirList)). + Dirs = ordsets:from_list(AbsDirs ++ TestDirs), + run_list(Dirs). run_list(PathL) -> io:format("Where to search for beam files:\n~p\n", [PathL]), @@ -123,7 +102,7 @@ run_list(PathL) -> end, case length(SevereFailures) of 0 -> ok; - Len -> {error,integer_to_list(Len)++" failures"} + Len -> {failed,integer_to_list(Len)++" failures"} end. diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 5df09b6a79..0e897631ff 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -29,10 +29,11 @@ manpage/1, otp_6708/1, otp_7084/1, otp_7421/1, io_lib_collect_line_3_wb/1, cr_whitespace_in_string/1, io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1, - printable_range/1, + printable_range/1, bad_printable_range/1, io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1, otp_10836/1, io_lib_width_too_small/1, - io_with_huge_message_queue/1, format_string/1]). + io_with_huge_message_queue/1, format_string/1, + maps/1, coverage/1]). -export([pretty/2]). @@ -70,10 +71,10 @@ all() -> manpage, otp_6708, otp_7084, otp_7421, io_lib_collect_line_3_wb, cr_whitespace_in_string, io_fread_newlines, otp_8989, io_lib_fread_literal, - printable_range, + printable_range, bad_printable_range, io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836, io_lib_width_too_small, io_with_huge_message_queue, - format_string]. + format_string, maps, coverage]. groups() -> []. @@ -2062,8 +2063,6 @@ printable_range(Suite) when is_list(Suite) -> [{args, " +pclatin1 -pa " ++ Pa}]), unicode = rpc:call(UNode,io,printable_range,[]), latin1 = rpc:call(LNode,io,printable_range,[]), - {error, _} = test_server:start_node(printable_range_unnicode, slave, - [{args, " +pcunnicode -pa " ++ Pa}]), PrettyOptions = [{column,1}, {line_length,109}, {depth,30}, @@ -2071,48 +2070,69 @@ printable_range(Suite) when is_list(Suite) -> {record_print_fun, fun(_,_) -> no end}, {encoding,unicode}], - 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib_pretty,print, - [{hello, [1024,1025]}, - PrettyOptions]))), - 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib_pretty,print, - [{hello, [1024,1025]}, - PrettyOptions]))), - 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib_pretty,print, - [{hello, [1024,1025]}, - PrettyOptions]))), - 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib_pretty,print, - [{hello, <<1024/utf8,1025/utf8>>}, - PrettyOptions]))), - 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib_pretty,print, - [{hello, <<1024/utf8,1025/utf8>>}, - PrettyOptions]))), - 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib_pretty,print, - [{hello, <<1024/utf8,1025/utf8>>}, - PrettyOptions]))), + PrintableControls = "\t\v\b\f\e\r\n", + + 1025 = print_max(UNode, [{hello, [1024,1025]}, + PrettyOptions]), + 125 = print_max(LNode, [{hello, [1024,1025]}, + PrettyOptions]), + 125 = print_max(DNode, [{hello, [1024,1025]}, + PrettyOptions]), + 1025 = print_max(UNode, [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]), + 125 = print_max(LNode, [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]), + 125 = print_max(DNode, [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]), + $v = print_max(UNode, [PrintableControls,PrettyOptions]), + $v = print_max(LNode, [PrintableControls,PrettyOptions]), + $v = print_max(DNode, [PrintableControls,PrettyOptions]), + 16#10FFFF = print_max(UNode, + [<<16#10FFFF/utf8,"\t\v\b\f\e\r\n">>, + PrettyOptions]), + $> = print_max(LNode, + [<<16#10FFFF/utf8,"\t\v\b\f\e\r\n">>, + PrettyOptions]), + $> = print_max(DNode, + [<<16#10FFFF/utf8,"\t\v\b\f\e\r\n">>, + PrettyOptions]), - 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib,format, - ["~tp",[{hello, [1024,1025]}]]))), - 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib,format, - ["~tp",[{hello, [1024,1025]}]]))), - 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib,format, - ["~tp",[{hello, [1024,1025]}]]))), - 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib,format, - ["~tp", - [{hello, - <<1024/utf8,1025/utf8>>}]]))), - 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib,format, - ["~tp", - [{hello, - <<1024/utf8,1025/utf8>>}]]))), - 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib,format, - ["~tp", - [{hello, - <<1024/utf8,1025/utf8>>}]]))), + 1025 = format_max(UNode, ["~tp", [{hello, [1024,1025]}]]), + 125 = format_max(LNode, ["~tp", [{hello, [1024,1025]}]]), + 125 = format_max(DNode, ["~tp", [{hello, [1024,1025]}]]), + 1025 = format_max(UNode, ["~tp", [{hello, <<1024/utf8,1025/utf8>>}]]), + 125 = format_max(LNode, ["~tp", [{hello, <<1024/utf8,1025/utf8>>}]]), + 125 = format_max(DNode, ["~tp", [{hello, <<1024/utf8,1025/utf8>>}]]), + + $\e = format_max(UNode, ["~ts", [PrintableControls]]), + $\e = format_max(LNode, ["~ts", [PrintableControls]]), + $\e = format_max(DNode, ["~ts", [PrintableControls]]), + test_server:stop_node(UNode), test_server:stop_node(LNode), test_server:stop_node(DNode), ok. +print_max(Node, Args) -> + rpc_call_max(Node, io_lib_pretty, print, Args). + +format_max(Node, Args) -> + rpc_call_max(Node, io_lib, format, Args). + +rpc_call_max(Node, M, F, Args) -> + lists:max(lists:flatten(rpc:call(Node, M, F, Args))). + +%% Make sure that a bad specification for a printable range is rejected. +bad_printable_range(Config) when is_list(Config) -> + Cmd = lists:concat([lib:progname()," +pcunnnnnicode -run erlang halt"]), + case os:cmd(Cmd) of + "bad range of printable characters" ++ _ -> + ok; + String -> + io:format("~s\n", [String]), + ?t:fail() + end. + io_lib_print_binary_depth_one(doc) -> "Test binaries printed with a depth of one behave correctly"; io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> @@ -2225,7 +2245,7 @@ compile_file(File, Text, Config) -> after ok %file:delete(Fname) end. -io_lib_width_too_small(Config) -> +io_lib_width_too_small(_Config) -> "**" = lists:flatten(io_lib:format("~2.3w", [3.14])), "**" = lists:flatten(io_lib:format("~2.5w", [3.14])), ok. @@ -2271,8 +2291,113 @@ writes(N, F1) -> file:write(F1, "hello\n"), writes(N - 1, F1). -format_string(Config) -> +format_string(_Config) -> %% All but padding is tested by fmt/2. "xxxxxxsssx" = fmt("~10.4.xs", ["sss"]), "xxxxxxsssx" = fmt("~10.4.*s", [$x, "sss"]), ok. + +maps(_Config) -> + %% Note that order in which a map is printed is arbitrary. In + %% practice, small maps (non-HAMT) are printed in key order, but + %% the breakpoint for creating big maps (HAMT) is lower in the + %% debug-compiled run-time system than in the optimized run-time + %% system. + %% + %% Therefore, play it completely safe by not assuming any order + %% in a map with more than one element. + + "#{}" = fmt("~w", [#{}]), + "#{a=>b}" = fmt("~w", [#{a=>b}]), + re_fmt(<<"#\\{(a=>b|c=>d),[.][.][.]=>[.][.][.]\\}">>, + "~W", [#{a=>b,c=>d},2]), + re_fmt(<<"#\\{(a=>b|c=>d|e=>f),[.][.][.]=>[.][.][.],[.][.][.]\\}">>, + "~W", [#{a=>b,c=>d,e=>f},2]), + + "#{}" = fmt("~p", [#{}]), + "#{a => b}" = fmt("~p", [#{a=>b}]), + "#{...}" = fmt("~P", [#{a=>b},1]), + re_fmt(<<"#\\{(a => b|c => d),[.][.][.]\\}">>, + "~P", [#{a=>b,c=>d},2]), + re_fmt(<<"#\\{(a => b|c => d|e => f),[.][.][.]\\}">>, + "~P", [#{a=>b,c=>d,e=>f},2]), + + List = [{I,I*I} || I <- lists:seq(1, 20)], + Map = maps:from_list(List), + + "#{...}" = fmt("~P", [Map,1]), + + %% Print a map and parse it back to a map. + S = fmt("~p\n", [Map]), + io:format("~p\n", [S]), + Map = parse_map(S), + + %% Smoke test of a map as key. + MapAsKey = #{Map => "value"}, + io:format("~s\n", [fmt("~p", [MapAsKey])]), + ok. + +re_fmt(Pattern, Format, Args) -> + S = list_to_binary(fmt(Format, Args)), + case re:run(S, Pattern, [{capture,none}]) of + nomatch -> + io:format("Pattern: ~s", [Pattern]), + io:format("Result: ~s", [S]), + ?t:fail(); + match -> + ok + end. + +%% Parse a map consisting of integer keys and values. +parse_map(S0) -> + S1 = parse_expect(S0, "#{"), + {M,S2} = parse_map_1(S1), + S = parse_expect(S2, "}"), + S = "", + M. + +parse_map_1(S0) -> + {Key,S1} = parse_number(S0), + S2 = parse_expect(S1, "=>"), + {Val,S3} = parse_number(S2), + case S3 of + ","++S4 -> + S5 = parse_skip_ws(S4), + {Map,S} = parse_map_1(S5), + {Map#{Key=>Val},S}; + S -> + {#{Key=>Val},S} + end. + +parse_number(S) -> + parse_number(S, none). + +parse_number([C|S], Acc0) when $0 =< C, C =< $9 -> + Acc = case Acc0 of + none -> 0; + _ when is_integer(Acc0) -> Acc0 + end, + parse_number(S, Acc*10+C-$0); +parse_number(S, Acc) -> + {Acc,parse_skip_ws(S)}. + +parse_expect([H|T1], [H|T2]) -> + parse_expect(T1, T2); +parse_expect(S, []) -> + parse_skip_ws(S). + +parse_skip_ws([C|S]) when C =< $\s -> + parse_skip_ws(S); +parse_skip_ws(S) -> + S. + +%% Cover the last uncovered lines for completeness. +coverage(_Config) -> + S1 = io_lib_pretty:print({a,term}, fun(_, _) -> no end), + io:format("~s\n", [S1]), + + %% The tuple of arity three will be ignored. + S2 = io_lib_pretty:print(lists:seq(1, 100), [{depth,1,1}]), + io:format("~s\n", [S2]), + + ok. diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index 1337b7dde2..811c7ed7bb 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -1378,47 +1378,43 @@ rtnode(C,N) -> rtnode(Commands,Nodename,ErlPrefix) -> rtnode(Commands,Nodename,ErlPrefix,[]). rtnode(Commands,Nodename,ErlPrefix,Extra) -> - ?line case get_progs() of - {error,_Reason} -> - ?line {skip,"No runerl present"}; - {RunErl,ToErl,Erl} -> - ?line case create_tempdir() of - {error, Reason2} -> - ?line {skip, Reason2}; - Tempdir -> - ?line SPid = - start_runerl_node(RunErl,ErlPrefix++ - "\\\""++Erl++"\\\"", - Tempdir,Nodename, Extra), - ?line CPid = start_toerl_server(ToErl,Tempdir), - ?line erase(getline_skipped), - ?line Res = - (catch get_and_put(CPid, Commands,1)), - ?line case stop_runerl_node(CPid) of - {error,_} -> - ?line CPid2 = - start_toerl_server - (ToErl,Tempdir), - ?line erase(getline_skipped), - ?line ok = get_and_put - (CPid2, - [{putline,[7]}, - {sleep, - timeout(short)}, - {putline,""}, - {getline," -->"}, - {putline,"s"}, - {putline,"c"}, - {putline,""}],1), - ?line stop_runerl_node(CPid2); - _ -> - ?line ok - end, - ?line wait_for_runerl_server(SPid), - ?line ok = ?RM_RF(Tempdir), - ?line ok = Res - end - end. + case get_progs() of + {error,_Reason} -> + {skip,"No runerl present"}; + {RunErl,ToErl,Erl} -> + case create_tempdir() of + {error, Reason2} -> + {skip, Reason2}; + Tempdir -> + SPid = start_runerl_node(RunErl, ErlPrefix++ + "\\\""++Erl++"\\\"", + Tempdir, Nodename, Extra), + CPid = start_toerl_server(ToErl, Tempdir), + put(getline_skipped, []), + Res = (catch get_and_put(CPid, Commands, 1)), + case stop_runerl_node(CPid) of + {error,_} -> + CPid2 = start_toerl_server(ToErl, Tempdir), + put(getline_skipped, []), + ok = get_and_put + (CPid2, + [{putline,[7]}, + {sleep, + timeout(short)}, + {putline,""}, + {getline," -->"}, + {putline,"s"}, + {putline,"c"}, + {putline,""}], 1), + stop_runerl_node(CPid2); + _ -> + ok + end, + wait_for_runerl_server(SPid), + ok = ?RM_RF(Tempdir), + ok = Res + end + end. timeout(long) -> 2 * timeout(normal); @@ -1462,57 +1458,51 @@ get_and_put(CPid, [{sleep, X}|T],N) -> after X -> get_and_put(CPid,T,N+1) end; -get_and_put(CPid, [{getline, Match}|T],N) -> +get_and_put(CPid, [{getline_pred,Pred,Msg}|T]=T0, N) + when is_function(Pred) -> ?dbg({getline, Match}), CPid ! {self(), {get_line, timeout(normal)}}, receive {get_line, timeout} -> error_logger:error_msg("~p: getline timeout waiting for \"~s\" " "(command number ~p, skipped: ~p)~n", - [?MODULE, Match,N,get(getline_skipped)]), + [?MODULE,Msg,N,get(getline_skipped)]), {error, timeout}; {get_line, Data} -> ?dbg({data,Data}), - case lists:prefix(Match, Data) of - true -> - erase(getline_skipped), + case Pred(Data) of + yes -> + put(getline_skipped, []), get_and_put(CPid, T,N+1); - false -> - case get(getline_skipped) of - undefined -> - put(getline_skipped,[Data]); - List -> - put(getline_skipped,List ++ [Data]) - end, - get_and_put(CPid, [{getline, Match}|T],N) + no -> + error_logger:error_msg("~p: getline match failure " + "\"~s\" " + "(command number ~p)\n", + [?MODULE,Msg,N]), + {error, no_match}; + maybe -> + List = get(getline_skipped), + put(getline_skipped, List ++ [Data]), + get_and_put(CPid, T0, N) end end; +get_and_put(CPid, [{getline, Match}|T],N) -> + ?dbg({getline, Match}), + F = fun(Data) -> + case lists:prefix(Match, Data) of + true -> yes; + false -> maybe + end + end, + get_and_put(CPid, [{getline_pred,F,Match}|T], N); get_and_put(CPid, [{getline_re, Match}|T],N) -> - ?dbg({getline_re, Match}), - CPid ! {self(), {get_line, timeout(normal)}}, - receive - {get_line, timeout} -> - error_logger:error_msg("~p: getline_re timeout waiting for \"~s\" " - "(command number ~p, skipped: ~p)~n", - [?MODULE, Match,N,get(getline_skipped)]), - {error, timeout}; - {get_line, Data} -> - ?dbg({data,Data}), - case re:run(Data, Match,[{capture,none}]) of - match -> - erase(getline_skipped), - get_and_put(CPid, T,N+1); - _ -> - case get(getline_skipped) of - undefined -> - put(getline_skipped,[Data]); - List -> - put(getline_skipped,List ++ [Data]) - end, - get_and_put(CPid, [{getline_re, Match}|T],N) - end - end; - + F = fun(Data) -> + case re:run(Data, Match, [{capture,none}]) of + match -> yes; + _ -> maybe + end + end, + get_and_put(CPid, [{getline_pred,F,Match}|T], N); get_and_put(CPid, [{putline_raw, Line}|T],N) -> ?dbg({putline_raw, Line}), CPid ! {self(), {send_line, Line}}, @@ -1801,10 +1791,22 @@ get_data_within(Port, Timeout, Acc) -> end. get_default_shell() -> + Match = fun(Data) -> + case lists:prefix("undefined", Data) of + true -> + yes; + false -> + case re:run(Data, "<\\d+[.]\\d+[.]\\d+>", + [{capture,none}]) of + match -> no; + _ -> maybe + end + end + end, try rtnode([{putline,""}, {putline, "whereis(user_drv)."}, - {getline, "undefined"}],[]), + {getline_pred, Match, "matching of user_drv pid"}], []), old catch _E:_R -> ?dbg({_E,_R}), diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index e886a797f0..a0f7fd2744 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -38,13 +38,13 @@ % Test cases must be exported. -export([member/1, reverse/1, keymember/1, keysearch_keyfind/1, - keystore/1, keytake/1, + keystore/1, keytake/1, keyreplace/1, append_1/1, append_2/1, seq_loop/1, seq_2/1, seq_3/1, seq_2_e/1, seq_3_e/1, sublist_2/1, sublist_3/1, sublist_2_e/1, sublist_3_e/1, flatten_1/1, flatten_2/1, flatten_1_e/1, flatten_2_e/1, - dropwhile/1, + dropwhile/1, takewhile/1, sort_1/1, sort_stable/1, merge/1, rmerge/1, sort_rand/1, usort_1/1, usort_stable/1, umerge/1, rumerge/1,usort_rand/1, keymerge/1, rkeymerge/1, @@ -62,7 +62,7 @@ zip_unzip/1, zip_unzip3/1, zipwith/1, zipwith3/1, filter_partition/1, otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1, - suffix/1, subtract/1, droplast/1]). + suffix/1, subtract/1, droplast/1, hof/1]). %% Sort randomized lists until stopped. %% @@ -81,37 +81,51 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [{group, append}, reverse, member, keymember, - keysearch_keyfind, keystore, keytake, dropwhile, {group,sort}, - {group, usort}, {group, keysort}, {group, ukeysort}, - {group, funsort}, {group, ufunsort}, {group, sublist}, - {group, flatten}, {group, seq}, zip_unzip, zip_unzip3, - zipwith, zipwith3, filter_partition, {group, tickets}, - suffix, subtract]. + [{group, append}, + {group, key}, + {group,sort}, + {group, usort}, + {group, keysort}, + {group, ukeysort}, + {group, funsort}, + {group, ufunsort}, + {group, sublist}, + {group, flatten}, + {group, seq}, + {group, tickets}, + {group, zip}, + {group, misc}]. groups() -> - [{append, [], [append_1, append_2]}, - {usort, [], + [{append, [parallel], [append_1, append_2]}, + {usort, [parallel], [umerge, rumerge, usort_1, usort_rand, usort_stable]}, - {keysort, [], + {keysort, [parallel], [keymerge, rkeymerge, keysort_1, keysort_rand, keysort_i, keysort_stable, keysort_error]}, - {sort,[],[merge, rmerge, sort_1, sort_rand]}, - {ukeysort, [], + {key, [parallel], [keymember, keysearch_keyfind, keystore, + keytake, keyreplace]}, + {sort,[parallel],[merge, rmerge, sort_1, sort_rand]}, + {ukeysort, [parallel], [ukeymerge, rukeymerge, ukeysort_1, ukeysort_rand, ukeysort_i, ukeysort_stable, ukeysort_error]}, - {funsort, [], + {funsort, [parallel], [funmerge, rfunmerge, funsort_1, funsort_stable, funsort_error, funsort_rand]}, - {ufunsort, [], + {ufunsort, [parallel], [ufunmerge, rufunmerge, ufunsort_1, ufunsort_stable, ufunsort_error, ufunsort_rand]}, - {seq, [], [seq_loop, seq_2, seq_3, seq_2_e, seq_3_e]}, - {sublist, [], + {seq, [parallel], [seq_loop, seq_2, seq_3, seq_2_e, seq_3_e]}, + {sublist, [parallel], [sublist_2, sublist_3, sublist_2_e, sublist_3_e]}, - {flatten, [], + {flatten, [parallel], [flatten_1, flatten_2, flatten_1_e, flatten_2_e]}, - {tickets, [], [otp_5939, otp_6023, otp_6606, otp_7230]}]. + {tickets, [parallel], [otp_5939, otp_6023, otp_6606, otp_7230]}, + {zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3]}, + {misc, [parallel], [reverse, member, dropwhile, takewhile, + filter_partition, suffix, subtract, + hof]} + ]. init_per_suite(Config) -> Config. @@ -345,6 +359,33 @@ dropwhile(Config) when is_list(Config) -> ok. +takewhile(Config) when is_list(Config) -> + F = fun(C) -> C =/= $@ end, + + [] = lists:takewhile(F, []), + [a] = lists:takewhile(F, [a]), + [a,b] = lists:takewhile(F, [a,b]), + [a,b,c] = lists:takewhile(F, [a,b,c]), + + [] = lists:takewhile(F, [$@]), + [] = lists:takewhile(F, [$@,$@]), + [a] = lists:takewhile(F, [a,$@]), + + [$k] = lists:takewhile(F, [$k,$@]), + [$k,$l] = lists:takewhile(F, [$k,$l,$@,$@]), + [a] = lists:takewhile(F, [a,$@,$@,$@]), + + [] = lists:takewhile(F, [$@,a,$@,b]), + [] = lists:takewhile(F, [$@,$@,a,$@,b]), + [] = lists:takewhile(F, [$@,$@,$@,a,$@,b]), + + Long = lists:seq(1, 1024), + Shorter = lists:seq(1, 400), + + Shorter = lists:takewhile(fun(E) -> E =< 400 end, Long), + + ok. + keystore(doc) -> ["OTP-XXX."]; keystore(suite) -> []; @@ -382,6 +423,17 @@ keytake(Config) when is_list(Config) -> ?line false = lists:keytake(4, 2, L), ok. +%% Test lists:keyreplace/4. +keyreplace(Config) when is_list(Config) -> + [{new,42}] = lists:keyreplace(k, 1, [{k,1}], {new,42}), + [atom,{new,a,b}] = lists:keyreplace(k, 1, [atom,{k,1}], {new,a,b}), + [a,{x,y,z}] = lists:keyreplace(a, 5, [a,{x,y,z}], {no,use}), + + %% Error cases. + {'EXIT',_} = (catch lists:keyreplace(k, 1, [], not_tuple)), + {'EXIT',_} = (catch lists:keyreplace(k, 0, [], {a,b})), + ok. + merge(doc) -> ["merge functions"]; merge(suite) -> []; merge(Config) when is_list(Config) -> @@ -2326,19 +2378,25 @@ sublist_3_e(Config) when is_list(Config) -> -define(flatten_error1(X), ?line {'EXIT', _} = (catch lists:flatten(X))). -define(flatten_error2(X,Y), ?line {'EXIT', _} = (catch lists:flatten(X,Y))). -flatten_1(doc) -> ["flatten/1"]; -flatten_1(suite) -> []; +%% Test lists:flatten/1,2 and lists:flatlength/1. flatten_1(Config) when is_list(Config) -> - ?line [] = lists:flatten([]), - ?line [1,2] = lists:flatten([1,2]), - ?line [1,2] = lists:flatten([1,[2]]), - ?line [1,2] = lists:flatten([[1],2]), - ?line [1,2] = lists:flatten([[1],[2]]), - ?line [1,2] = lists:flatten([[1,2]]), - ?line [a,b,c,d] = lists:flatten([[a],[b,c,[d]]]), + [] = lists_flatten([]), + [1,2] = lists_flatten([1,2]), + [1,2] = lists_flatten([1,[2]]), + [1,2] = lists_flatten([[1],2]), + [1,2] = lists_flatten([[1],[2]]), + [1,2] = lists_flatten([[1,2]]), + [a,b,c,d] = lists_flatten([[a],[b,c,[d]]]), ok. +lists_flatten(List) -> + Flat = lists:flatten(List), + Flat = lists:flatten(List, []), + Len = lists:flatlength(List), + Len = length(Flat), + Flat. + flatten_1_e(doc) -> ["flatten/1 error cases"]; flatten_1_e(suite) -> []; flatten_1_e(Config) when is_list(Config) -> @@ -2351,11 +2409,11 @@ flatten_1_e(Config) when is_list(Config) -> %%% clear-cut. Right now, I think that any term should be allowed. %%% But I also wish this function didn't exist at all. -flatten_2(doc) -> ["flatten/2"]; -flatten_2(suite) -> []; +%% Test lists:flatten/2. flatten_2(Config) when is_list(Config) -> - ?line [] = lists:flatten([]), - ?line [a] = lists:flatten([a]), + [] = lists:flatten([], []), + [a] = lists:flatten([a], []), + [a,b,c,[no,flatten]] = lists:flatten([[a,[b,c]]], [[no,flatten]]), ok. flatten_2_e(doc) -> ["flatten/2 error cases"]; @@ -2651,3 +2709,40 @@ droplast(Config) when is_list(Config) -> ?line {'EXIT', {function_clause, _}} = (catch lists:droplast(x)), ok. + +%% Briefly test the common high-order functions to ensure they +%% are covered. +hof(Config) when is_list(Config) -> + L = [1,2,3], + [1,4,9] = lists:map(fun(N) -> N*N end, L), + [1,4,5,6] = lists:flatmap(fun(1) -> [1]; + (2) -> []; + (3) -> [4,5,6] + end, L), + [{1,[a]},{2,[b]},{3,[c]}] = + lists:keymap(fun(A) -> [A] end, 2, [{1,a},{2,b},{3,c}]), + + [1,3] = lists:filter(fun(N) -> N rem 2 =:= 1 end, L), + FilterMapFun = fun(1) -> true; + (2) -> {true,42}; + (3) -> false + end, + [1,42] = lists:filtermap(FilterMapFun, L), + [1,42] = lists:zf(FilterMapFun, L), + + [3,2,1] = lists:foldl(fun(E, A) -> [E|A] end, [], L), + [1,2,3] = lists:foldr(fun(E, A) -> [E|A] end, [], L), + {[1,4,9],[3,2,1]} = lists:mapfoldl(fun(E, A) -> + {E*E,[E|A]} + end, [], L), + {[1,4,9],[1,2,3]} = lists:mapfoldr(fun(E, A) -> + {E*E,[E|A]} + end, [], L), + + true = lists:any(fun(N) -> N =:= 2 end, L), + false = lists:any(fun(N) -> N =:= 42 end, L), + + true = lists:all(fun(N) -> is_integer(N) end, L), + false = lists:all(fun(N) -> N rem 2 =:= 0 end, L), + + ok. diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 36f009eec6..f7a6a38138 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -28,7 +28,7 @@ init_per_group/2,end_per_group/2, crash/1, sync_start_nolink/1, sync_start_link/1, spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, - hibernate/1, stop/1]). + hibernate/1, stop/1, t_format/1]). -export([ otp_6345/1, init_dont_hang/1]). -export([hib_loop/1, awaken/1]). @@ -51,7 +51,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [crash, {group, sync_start}, spawn_opt, hibernate, - {group, tickets}, stop]. + {group, tickets}, stop, t_format]. groups() -> [{tickets, [], [otp_6345, init_dont_hang]}, @@ -80,77 +80,123 @@ end_per_group(_GroupName, Config) -> crash(Config) when is_list(Config) -> error_logger:add_report_handler(?MODULE, self()), - Pid = proc_lib:spawn(?MODULE, sp1, []), - Pid ! die, - ?line Report = receive - {crash_report, Pid, Report0} -> Report0 - after 2000 -> test_server:fail(no_crash_report) - end, - ?line proc_lib:format(Report), - ?line [PidRep, []] = Report, - ?line {value, {initial_call,{?MODULE,sp1,[]}}} = - lists:keysearch(initial_call, 1, PidRep), - Self = self(), - ?line {value, {ancestors,[Self]}} = - lists:keysearch(ancestors, 1, PidRep), - ?line {value, {error_info,{exit,die,_StackTrace1}}} = - lists:keysearch(error_info, 1, PidRep), - - F = fun sp1/0, - Pid1 = proc_lib:spawn(node(), F), - Pid1 ! die, - ?line [PidRep1, []] = receive - {crash_report, Pid1, Report1} -> Report1 - after 2000 -> test_server:fail(no_crash_report) - end, - ?line {value, {initial_call,{Fmod,Fname,[]}}} = - lists:keysearch(initial_call, 1, PidRep1), - ?line {module,Fmod} = erlang:fun_info(F, module), - ?line {name,Fname} = erlang:fun_info(F, name), - ?line {value, {ancestors,[Self]}} = - lists:keysearch(ancestors, 1, PidRep1), - ?line {value, {error_info,{exit,die,_StackTrace2}}} = - lists:keysearch(error_info, 1, PidRep1), - - Pid2 = proc_lib:spawn(?MODULE, sp2, []), - test_server:sleep(100), - ?line {?MODULE,sp2,[]} = proc_lib:initial_call(Pid2), - ?line {?MODULE,sp2,0} = proc_lib:translate_initial_call(Pid2), - Pid2 ! die, - ?line [Pid2Rep, [{neighbour, LinkRep}]] = - receive - {crash_report, Pid2, Report2} -> Report2 - after 2000 -> test_server:fail(no_crash_report) - end, - ?line {value, {initial_call,{?MODULE,sp2,[]}}} = - lists:keysearch(initial_call, 1, Pid2Rep), - ?line {value, {ancestors,[Self]}} = - lists:keysearch(ancestors, 1, Pid2Rep), - ?line {value, {error_info,{exit,die,_StackTrace3}}} = - lists:keysearch(error_info, 1, Pid2Rep), - ?line {value, {initial_call,{?MODULE,sp1,[]}}} = - lists:keysearch(initial_call, 1, LinkRep), - %% Make sure that we don't get a crash report if a process %% terminates with reason 'shutdown' or reason {shutdown,Reason}. - ?line process_flag(trap_exit, true), - ?line Pid3 = proc_lib:spawn_link(erlang, apply, - [fun() -> exit(shutdown) end,[]]), + process_flag(trap_exit, true), + Pid0 = proc_lib:spawn_link(erlang, apply, + [fun() -> exit(shutdown) end,[]]), + Pid1 = proc_lib:spawn_link(erlang, apply, + [fun() -> exit({shutdown,{a,b,c}}) end,[]]), + + receive {'EXIT',Pid0,shutdown} -> ok end, + receive {'EXIT',Pid1,{shutdown,{a,b,c}}} -> ok end, + process_flag(trap_exit, false), + %% We expect any unexpected messages to be caught below, + %% so we don't have explicitly wait some time to be sure. + + %% Spawn export function. + Pid2 = proc_lib:spawn(?MODULE, sp1, []), + Pid2 ! die, + Exp2 = [{initial_call,{?MODULE,sp1,[]}}, + {ancestors,[self()]}, + {error_info,{exit,die,{stacktrace}}}], + analyse_crash(Pid2, Exp2, []), - ?line Pid4 = proc_lib:spawn_link(erlang, apply, - [fun() -> exit({shutdown,{a,b,c}}) end,[]]), + %% Spawn fun. + F = fun sp1/0, + Pid3 = proc_lib:spawn(node(), F), + Pid3 ! die, + {module,?MODULE} = erlang:fun_info(F, module), + {name,Fname} = erlang:fun_info(F, name), + Exp3 = [{initial_call,{?MODULE,Fname,[]}}, + {ancestors,[self()]}, + {error_info,{exit,die,{stacktrace}}}], + analyse_crash(Pid3, Exp3, []), - ?line receive {'EXIT',Pid3,shutdown} -> ok end, - ?line receive {'EXIT',Pid4,{shutdown,{a,b,c}}} -> ok end, - ?line process_flag(trap_exit, false), + %% Spawn function with neighbour. + Pid4 = proc_lib:spawn(?MODULE, sp2, []), + test_server:sleep(100), + {?MODULE,sp2,[]} = proc_lib:initial_call(Pid4), + {?MODULE,sp2,0} = proc_lib:translate_initial_call(Pid4), + Pid4 ! die, + Exp4 = [{initial_call,{?MODULE,sp2,[]}}, + {ancestors,[self()]}, + {error_info,{exit,die,{stacktrace}}}], + Links4 = [[{initial_call,{?MODULE,sp1,[]}}, + {ancestors,[Pid4,self()]}]], + analyse_crash(Pid4, Exp4, Links4), + + %% Make sure that we still get a crash report if the + %% process dictionary have been tampered with. + + Pid5 = proc_lib:spawn(erlang, apply, + [fun() -> + erase(), + exit(abnormal) + end,[]]), + Exp5 = [{initial_call,absent}, + {ancestors,[]}, + {error_info,{exit,abnormal,{stacktrace}}}], + analyse_crash(Pid5, Exp5, []), + + error_logger:delete_report_handler(?MODULE), + ok. +analyse_crash(Pid, Expected0, ExpLinks) -> + Expected = [{pid,Pid}|Expected0], receive - Any -> - ?line ?t:fail({unexpected_message,Any}) - after 2000 -> - ok - end. + {crash_report, Pid, Report} -> + _ = proc_lib:format(Report), %Smoke test. + [Crash,Links] = Report, + analyse_crash_1(Expected, Crash), + analyse_links(ExpLinks, Links); + Unexpected -> + io:format("~p\n", [Unexpected]), + test_server:fail(unexpected_message) + after 5000 -> + test_server:fail(no_crash_report) + end. +analyse_links([H|Es], [{neighbour,N}|Links]) -> + analyse_crash_1(H, N), + analyse_links(Es, Links); +analyse_links([], []) -> + ok. + +analyse_crash_1([{Key,absent}|T], Report) -> + false = lists:keymember(Key, 1, Report), + analyse_crash_1(T, Report); +analyse_crash_1([{Key,Pattern}|T], Report) -> + case lists:keyfind(Key, 1, Report) of + false -> + io:format("~p", [Report]), + test_server:fail({missing_key,Key}); + {Key,Info} -> + try + match_info(Pattern, Info) + catch + no_match -> + io:format("key: ~p", [Key]), + io:format("pattern: ~p", [Pattern]), + io:format("actual: ~p", [Report]), + test_server:fail(no_match) + end, + analyse_crash_1(T, Report) + end; +analyse_crash_1([], _Report) -> + []. + +match_info(T, T) -> + ok; +match_info({stacktrace}, Stk) when is_list(Stk) -> + ok; +match_info([H1|T1], [H2|T2]) -> + match_info(H1, H2), + match_info(T1, T2); +match_info(Tuple1, Tuple2) when tuple_size(Tuple1) =:= tuple_size(Tuple2) -> + match_info(tuple_to_list(Tuple1), tuple_to_list(Tuple2)); +match_info(_, _) -> + throw(no_match). sync_start_nolink(Config) when is_list(Config) -> _Pid = spawn_link(?MODULE, sp5, [self()]), @@ -301,6 +347,7 @@ hibernate(Config) when is_list(Config) -> ?line {value,{initial_call,{?MODULE,hib_loop,[_]}}} = lists:keysearch(initial_call, 1, Report), + error_logger:delete_report_handler(?MODULE), ok. hib_loop(LoopData) -> @@ -364,7 +411,7 @@ init_dont_hang(Config) when is_list(Config) -> end. init_dont_hang_init(_Parent) -> - 1 = 2. + error(bad_init). %% Test proc_lib:stop/1,3 stop(_Config) -> @@ -448,10 +495,55 @@ stop(_Config) -> ok. system_terminate(crash,_Parent,_Deb,_State) -> - 1 = 2; + error({badmatch,2}); system_terminate(Reason,_Parent,_Deb,_State) -> exit(Reason). + +t_format(_Config) -> + error_logger:tty(false), + try + t_format() + after + error_logger:tty(true) + end, + ok. + +t_format() -> + error_logger:add_report_handler(?MODULE, self()), + Pid = proc_lib:spawn(fun t_format_looper/0), + HugeData = gb_sets:from_list(lists:seq(1, 100)), + Pid ! {die,HugeData}, + Report = receive + {crash_report, Pid, Report0} -> Report0 + end, + Usz = do_test_format(Report, unlimited), + Tsz = do_test_format(Report, 20), + + if + Tsz >= Usz -> + ?t:fail(); + true -> + ok + end, + + ok. + +do_test_format(Report, Depth) -> + io:format("*** Depth = ~p", [Depth]), + S0 = proc_lib:format(Report, latin1, Depth), + S = lists:flatten(S0), + io:put_chars(S), + length(S). + +t_format_looper() -> + receive + {die,Data} -> + exit(Data); + _ -> + t_format_looper() + end. + %%----------------------------------------------------------------- %% The error_logger handler used. %%----------------------------------------------------------------- diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 72216bfa0d..52fdb69b73 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -74,6 +74,7 @@ otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1, otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1, otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1, otp_11758/1, + otp_12946/1, manpage/1, @@ -143,7 +144,7 @@ groups() -> {tickets, [], [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562, otp_6590, otp_6673, otp_6964, otp_7114, otp_7232, - otp_7238, otp_7552, otp_6674, otp_7714, otp_11758]}, + otp_7238, otp_7552, otp_6674, otp_7714, otp_11758, otp_12946]}, {compat, [], [backward, forward]}]. init_per_suite(Config) -> @@ -7154,6 +7155,18 @@ otp_6674(Config) when is_list(Config) -> ?line run(Config, Ts). +otp_12946(doc) -> + ["Syntax error."]; +otp_12946(suite) -> []; +otp_12946(Config) when is_list(Config) -> + Text = + <<"-export([init/0]). + init() -> + ok. + y">>, + {errors,[{4,erl_parse,_}],[]} = compile_file(Config, Text, []), + ok. + manpage(doc) -> "Examples from qlc(3)."; manpage(suite) -> []; diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index b03caebe91..111bf620de 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -25,7 +25,9 @@ ]). -export([interval_int/1, interval_float/1, seed/1, - api_eq/1, reference/1, basic_stats/1, + api_eq/1, reference/1, + basic_stats_uniform_1/1, basic_stats_uniform_2/1, + basic_stats_normal/1, plugin/1, measure/1 ]). @@ -51,11 +53,13 @@ all() -> [seed, interval_int, interval_float, api_eq, reference, - basic_stats, + {group, basic_stats}, plugin, measure ]. -groups() -> []. +groups() -> + [{basic_stats, [parallel], + [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]}]. init_per_suite(Config) -> Config. end_per_suite(_Config) -> ok. @@ -291,14 +295,19 @@ gen(_, _, Acc) -> lists:reverse(Acc). %% The algorithms must have good properties to begin with %% -basic_stats(doc) -> ["Check that the algorithms generate sound values."]; -basic_stats(suite) -> []; -basic_stats(Config) when is_list(Config) -> - io:format("Testing uniform~n",[]), +%% Check that the algorithms generate sound values. + +basic_stats_uniform_1(Config) when is_list(Config) -> [basic_uniform_1(?LOOP, rand:seed_s(Alg), 0.0, array:new([{default, 0}])) || Alg <- algs()], + ok. + +basic_stats_uniform_2(Config) when is_list(Config) -> [basic_uniform_2(?LOOP, rand:seed_s(Alg), 0, array:new([{default, 0}])) || Alg <- algs()], + ok. + +basic_stats_normal(Config) when is_list(Config) -> io:format("Testing normal~n",[]), [basic_normal_1(?LOOP, rand:seed_s(Alg), 0, 0) || Alg <- algs()], ok. diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index b8c20d9745..d78d6153da 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -28,7 +28,7 @@ pcre_compile_workspace_overflow/1,re_infinite_loop/1, re_backwards_accented/1,opt_dupnames/1,opt_all_names/1,inspect/1, opt_no_start_optimize/1,opt_never_utf/1,opt_ucp/1, - match_limit/1,sub_binaries/1]). + match_limit/1,sub_binaries/1,copt/1]). -include_lib("test_server/include/test_server.hrl"). -include_lib("kernel/include/file.hrl"). @@ -319,32 +319,26 @@ replace_return(doc) -> ["Tests return options of replace together with global searching"]; replace_return(Config) when is_list(Config) -> Dog = ?t:timetrap(?t:minutes(3)), - ?line {'EXIT',{badarg,_}} = (catch re:replace("na","(a","")), - ?line <<"nasse">> = re:replace(<<"nisse">>,"i","a",[{return,binary}]), - ?line <<"ABCÅXABCXA">> = re:replace("ABC\305abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary}]), - - ?line [<<"ABCÅ">>, - <<"X">>, - <<"ABC">>, - <<"X">> | - <<"A">> ] = - re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,iodata}]), - ?line "ABCÅXABCXA" = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,list},unicode]), - ?line <<65,66,67,195,133,88,65,66,67,88,65>> = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary},unicode]), - ?line <<65,66,67,195,133,88,65,66,67,97,98,99,100,65>> = re:replace("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[{return,binary},unicode]), - ?line <<"iXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\9X",[{return,binary}]), - ?line <<"jXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\10X",[{return,binary}]), - ?line <<"Xk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\11X",[{return,binary}]), - ?line <<"9X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g9X",[{return,binary}]), - ?line <<"0X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g10X",[{return,binary}]), - ?line <<"X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g11X",[{return,binary}]), - ?line <<"971">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{9}7",[{return,binary}]), - ?line <<"071">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{10}7",[{return,binary}]), - ?line <<"71">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{11}7",[{return,binary}]), - ?line "a\x{400}bcX" = re:replace("a\x{400}bcd","d","X",[global,{return,list},unicode]), - ?line <<"a",208,128,"bcX">> = re:replace("a\x{400}bcd","d","X",[global,{return,binary},unicode]), - ?line "a\x{400}bcd" = re:replace("a\x{400}bcd","Z","X",[global,{return,list},unicode]), - ?line <<"a",208,128,"bcd">> = re:replace("a\x{400}bcd","Z","X",[global,{return,binary},unicode]), + {'EXIT',{badarg,_}} = (catch re:replace("na","(a","")), + ok = replacetest(<<"nisse">>,"i","a",[{return,binary}],<<"nasse">>), + ok = replacetest("ABC\305abcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary}],<<"ABCÅXABCXA">>), + ok = replacetest("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,iodata}],[<<"ABCÅ">>,<<"X">>,<<"ABC">>,<<"X">>|<<"A">>]), + ok = replacetest("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,list},unicode],"ABCÅXABCXA"), + ok = replacetest("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[global,{return,binary},unicode],<<65,66,67,195,133,88,65,66,67,88,65>>), + ok = replacetest("ABCÅabcdABCabcdA","a(?<FOO>bcd)","X",[{return,binary},unicode],<<65,66,67,195,133,88,65,66,67,97,98,99,100,65>>), + ok = replacetest("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\9X",[{return,binary}],<<"iXk">>), + ok = replacetest("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\10X",[{return,binary}],<<"jXk">>), + ok = replacetest("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\11X",[{return,binary}],<<"Xk">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g9X",[{return,binary}],<<"9X1">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g10X",[{return,binary}],<<"0X1">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g11X",[{return,binary}],<<"X1">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{9}7",[{return,binary}],<<"971">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{10}7",[{return,binary}],<<"071">>), + ok = replacetest("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{11}7",[{return,binary}],<<"71">>), + ok = replacetest("a\x{400}bcd","d","X",[global,{return,list},unicode],"a\x{400}bcX"), + ok = replacetest("a\x{400}bcd","d","X",[global,{return,binary},unicode],<<"a",208,128,"bcX">>), + ok = replacetest("a\x{400}bcd","Z","X",[global,{return,list},unicode],"a\x{400}bcd"), + ok = replacetest("a\x{400}bcd","Z","X",[global,{return,binary},unicode],<<"a",208,128,"bcd">>), ?t:timetrap_cancel(Dog), ok. @@ -389,6 +383,35 @@ crtest(Subject,RE,Options,true,Result) -> error end. +replacetest(Subject,RE,Replacement,Options,Result) -> + Result = re:replace(Subject,RE,Replacement,Options), + {CompileOptions,ReplaceOptions} = lists:partition(fun copt/1, Options), + {ok,MP} = re:compile(RE,CompileOptions), + Result = re:replace(Subject,MP,Replacement,ReplaceOptions), + ok. + +splittest(Subject,RE,Options,Result) -> + Result = re:split(Subject,RE,Options), + {CompileOptions,SplitOptions} = lists:partition(fun copt/1, Options), + {ok,MP} = re:compile(RE,CompileOptions), + Result = re:split(Subject,MP,SplitOptions), + ok. + +copt(caseless) -> true; +copt(no_start_optimize) -> true; +copt(never_utf) -> true; +copt(ucp) -> true; +copt(dollar_endonly) -> true; +copt(dotall) -> true; +copt(extended) -> true; +copt(firstline) -> true; +copt(multiline) -> true; +copt(no_auto_capture) -> true; +copt(dupnames) -> true; +copt(ungreedy) -> true; +copt(unicode) -> true; +copt(_) -> false. + split_autogen(doc) -> ["Test split with autogenerated erlang module"]; split_autogen(Config) when is_list(Config) -> @@ -401,43 +424,23 @@ split_options(doc) -> ["Test special options to split."]; split_options(Config) when is_list(Config) -> Dog = ?t:timetrap(?t:minutes(1)), - ?line [[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]] = re:split("a b c ","( )",[group,trim]), - ?line [[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]] = re:split("a b c ","( )",[group,{parts,0}]), - ?line [[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<>>]] = - re:split("a b c ","( )",[{parts,infinity},group]), - ?line [[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<>>]] = - re:split("a b c ","( )",[group]), - ?line [[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>], - [<<"c">>,<<" ">>],[<<"d">>,<<" ">>]] = - re:split(" a b c d ","( +)",[group,trim]), - ?line [[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>], - [<<"c">>,<<" ">>],[<<"d">>,<<" ">>]] = - re:split(" a b c d ","( +)",[{parts,0},group]), - ?line [[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>], - [<<"c">>,<<" ">>],[<<"d">>,<<" ">>],[<<>>]] = - re:split(" a b c d ","( +)",[{parts,infinity},group]), - ?line [[<<"a">>,<<" ">>],[<<"b c d">>]] = - re:split("a b c d","( +)",[{parts,2},group]), - ?line [[[967]," "],["b c d"]] = - re:split([967]++" b c d","( +)", - [{parts,2},group,{return,list},unicode]), - ?line [[<<207,135>>,<<" ">>],[<<"b c d">>]] = - re:split([967]++" b c d","( +)", - [{parts,2},group,{return,binary},unicode]), - ?line {'EXIT',{badarg,_}} = - (catch re:split([967]++" b c d","( +)", - [{parts,2},group,{return,binary}])), - ?line {'EXIT',{badarg,_}} = - (catch re:split("a b c d","( +)",[{parts,-2}])), - ?line {'EXIT',{badarg,_}} = - (catch re:split("a b c d","( +)",[{parts,banan}])), - ?line {'EXIT',{badarg,_}} = - (catch re:split("a b c d","( +)",[{capture,all}])), - ?line {'EXIT',{badarg,_}} = - (catch re:split("a b c d","( +)",[{capture,[],binary}])), + ok = splittest("a b c ","( )",[group,trim],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]]), + ok = splittest("a b c ","( )",[group,{parts,0}],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>]]), + ok = splittest("a b c ","( )",[{parts,infinity},group],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<>>]]), + ok = splittest("a b c ","( )",[group],[[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<>>]]), + ok = splittest(" a b c d ","( +)",[group,trim],[[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<"d">>,<<" ">>]]), + ok = splittest(" a b c d ","( +)",[{parts,0},group],[[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<"d">>,<<" ">>]]), + ok = splittest(" a b c d ","( +)",[{parts,infinity},group],[[<<>>,<<" ">>],[<<"a">>,<<" ">>],[<<"b">>,<<" ">>],[<<"c">>,<<" ">>],[<<"d">>,<<" ">>],[<<>>]]), + ok = splittest("a b c d","( +)",[{parts,2},group],[[<<"a">>,<<" ">>],[<<"b c d">>]]), + ok = splittest([967]++" b c d","( +)",[{parts,2},group,{return,list},unicode],[[[967]," "],["b c d"]]), + ok = splittest([967]++" b c d","( +)",[{parts,2},group,{return,binary},unicode],[[<<207,135>>,<<" ">>],[<<"b c d">>]]), + {'EXIT',{badarg,_}} = (catch re:split([967]++" b c d","( +)",[{parts,2},group,{return,binary}])), + {'EXIT',{badarg,_}} = (catch re:split("a b c d","( +)",[{parts,-2}])), + {'EXIT',{badarg,_}} = (catch re:split("a b c d","( +)",[{parts,banan}])), + {'EXIT',{badarg,_}} = (catch re:split("a b c d","( +)",[{capture,all}])), + {'EXIT',{badarg,_}} = (catch re:split("a b c d","( +)",[{capture,[],binary}])), % Parts 0 is equal to no parts specification (implicit strip) - ?line ["a"," ","b"," ","c"," ","d"] = - re:split("a b c d","( *)",[{parts,0},{return,list}]), + ok = splittest("a b c d","( *)",[{parts,0},{return,list}],["a"," ","b"," ","c"," ","d"]), ?t:timetrap_cancel(Dog), ok. diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index 9d48d092cf..c275053691 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -556,9 +556,10 @@ unzip_to_binary(doc) -> unzip_to_binary(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), + WorkDir = filename:join(PrivDir, "unzip_to_binary"), + _ = file:make_dir(WorkDir), - delete_all_in(PrivDir), - file:set_cwd(PrivDir), + ok = file:set_cwd(WorkDir), Long = filename:join(DataDir, "abc.zip"), %% Unzip a zip file into a binary @@ -569,7 +570,7 @@ unzip_to_binary(Config) when is_list(Config) -> end, FBList), %% Make sure no files created in cwd - {ok,[]} = file:list_dir(PrivDir), + {ok,[]} = file:list_dir(WorkDir), ok. @@ -578,8 +579,10 @@ zip_to_binary(doc) -> zip_to_binary(Config) when is_list(Config) -> DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), - delete_all_in(PrivDir), - file:set_cwd(PrivDir), + WorkDir = filename:join(PrivDir, "zip_to_binary"), + _ = file:make_dir(WorkDir), + + file:set_cwd(WorkDir), FileName = "abc.txt", ZipName = "t.zip", FilePath = filename:join(DataDir, FileName), @@ -589,7 +592,7 @@ zip_to_binary(Config) when is_list(Config) -> {ok, {ZipName, ZipB}} = zip:zip(ZipName, [FileName], [memory]), %% Make sure no files created in cwd - {ok,[FileName]} = file:list_dir(PrivDir), + {ok,[FileName]} = file:list_dir(WorkDir), %% Zip to a file {ok, ZipName} = zip:zip(ZipName, [FileName]), @@ -696,11 +699,6 @@ do_delete_files([Item|Rest], Cnt) -> end, do_delete_files(Rest, Cnt + DelCnt). -delete_all_in(Dir) -> - {ok, Files} = file:list_dir(Dir), - delete_files(lists:map(fun(F) -> filename:join(Dir,F) end, - Files)). - compress_control(doc) -> ["Test control of which files that should be compressed"]; compress_control(suite) -> []; |