diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/array_SUITE.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/test/error_logger_h_SUITE.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 61 | ||||
-rw-r--r-- | lib/stdlib/test/gen_statem_SUITE.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/proc_lib_SUITE.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/rand_SUITE.erl | 82 | ||||
-rw-r--r-- | lib/stdlib/test/re_SUITE.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/test/string_SUITE.erl | 14 | ||||
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 30 | ||||
-rw-r--r-- | lib/stdlib/test/unicode_util_SUITE.erl | 52 | ||||
-rw-r--r-- | lib/stdlib/test/uri_string_SUITE.erl | 55 | ||||
-rw-r--r-- | lib/stdlib/test/zip_SUITE.erl | 3 |
12 files changed, 241 insertions, 90 deletions
diff --git a/lib/stdlib/test/array_SUITE.erl b/lib/stdlib/test/array_SUITE.erl index 5836f275ba..956582c4fd 100644 --- a/lib/stdlib/test/array_SUITE.erl +++ b/lib/stdlib/test/array_SUITE.erl @@ -141,10 +141,10 @@ t(What) -> io:format("Test ~p ~n",[T]), try ?MODULE:T([]) - catch _E:_R -> + catch _E:_R:_S -> Line = get(test_server_loc), io:format("Failed ~p:~p ~p ~p~n ~p~n", - [T,Line,_E,_R, erlang:get_stacktrace()]) + [T,Line,_E,_R,_S]) end end, What). @@ -161,8 +161,8 @@ extract_tests() -> end, [Call(Test) || Test <- Tests], io:format("Tests ~p~n", [Tests]) - catch _:Err -> - io:format("Error: ~p ~p~n", [Err, erlang:get_stacktrace()]) + catch _:Err:Stacktrace -> + io:format("Error: ~p ~p~n", [Err, Stacktrace]) end, file:close(In), file:close(Out). diff --git a/lib/stdlib/test/error_logger_h_SUITE.erl b/lib/stdlib/test/error_logger_h_SUITE.erl index 1f2a9fda0b..9dc04f27a1 100644 --- a/lib/stdlib/test/error_logger_h_SUITE.erl +++ b/lib/stdlib/test/error_logger_h_SUITE.erl @@ -257,8 +257,7 @@ match_output([Item|T], Lines0, AtNode, Depth) -> Lines -> match_output(T, Lines, AtNode, Depth) catch - C:E -> - Stk = erlang:get_stacktrace(), + C:E:Stk -> io:format("ITEM: ~p", [Item]), io:format("LINES: ~p", [Lines0]), erlang:raise(C, E, Stk) diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 07c8b60cbd..8b651f4b43 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -78,6 +78,7 @@ -export([ets_all/1]). -export([massive_ets_all/1]). -export([take/1]). +-export([whereis_table/1]). -export([init_per_testcase/2, end_per_testcase/2]). %% Convenience for manual testing @@ -137,7 +138,8 @@ all() -> otp_9423, ets_all, massive_ets_all, - take]. + take, + whereis_table]. groups() -> [{new, [], @@ -4099,6 +4101,7 @@ info_do(Opts) -> {value, {keypos, 2}} = lists:keysearch(keypos, 1, Res), {value, {protection, protected}} = lists:keysearch(protection, 1, Res), + {value, {id, Tab}} = lists:keysearch(id, 1, Res), true = ets:delete(Tab), undefined = ets:info(non_existing_table_xxyy), undefined = ets:info(non_existing_table_xxyy,type), @@ -5892,6 +5895,36 @@ take(Config) when is_list(Config) -> ets:delete(T3), ok. +whereis_table(Config) when is_list(Config) -> + %% Do we return 'undefined' when the named table doesn't exist? + undefined = ets:whereis(whereis_test), + + %% Does the tid() refer to the same table as the name? + whereis_test = ets:new(whereis_test, [named_table]), + Tid = ets:whereis(whereis_test), + + ets:insert(whereis_test, [{hello}, {there}]), + + [[{hello}],[{there}]] = ets:match(whereis_test, '$1'), + [[{hello}],[{there}]] = ets:match(Tid, '$1'), + + true = ets:delete_all_objects(Tid), + + [] = ets:match(whereis_test, '$1'), + [] = ets:match(Tid, '$1'), + + %% Does the name disappear when deleted through the tid()? + true = ets:delete(Tid), + undefined = ets:info(whereis_test), + {'EXIT',{badarg, _}} = (catch ets:match(whereis_test, '$1')), + + %% Is the old tid() broken when the table is re-created with the same + %% name? + whereis_test = ets:new(whereis_test, [named_table]), + [] = ets:match(whereis_test, '$1'), + {'EXIT',{badarg, _}} = (catch ets:match(Tid, '$1')), + + ok. %% %% Utility functions: @@ -6023,17 +6056,23 @@ etsmem() -> end}, {Mem,AllTabs}. -verify_etsmem({MemInfo,AllTabs}) -> + +verify_etsmem(MI) -> wait_for_test_procs(), + verify_etsmem(MI, 1). + +verify_etsmem({MemInfo,AllTabs}, Try) -> case etsmem() of {MemInfo,_} -> io:format("Ets mem info: ~p", [MemInfo]), - case MemInfo of - {ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined -> + case {MemInfo, Try} of + {{ErlMem,EtsAlloc},_} when ErlMem == notsup; EtsAlloc == undefined -> %% Use 'erl +Mea max' to do more complete memory leak testing. {comment,"Incomplete or no mem leak testing"}; - _ -> - ok + {_, 1} -> + ok; + _ -> + {comment, "Transient memory discrepancy"} end; {MemInfo2, AllTabs2} -> @@ -6041,7 +6080,15 @@ verify_etsmem({MemInfo,AllTabs}) -> io:format("Actual: ~p", [MemInfo2]), io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]), io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]), - ct:fail("Failed memory check") + case Try < 2 of + true -> + io:format("\nThis discrepancy could be caused by an " + "inconsistent memory \"snapshot\"" + "\nTry again...\n", []), + verify_etsmem({MemInfo, AllTabs}, Try+1); + false -> + ct:fail("Failed memory check") + end end. diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index c747db475a..7c8a386116 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -2040,9 +2040,9 @@ handle_event(Type, Event, State, Data) -> Result -> wrap_result(Result) catch - throw:Result -> + throw:Result:Stacktrace -> erlang:raise( - throw, wrap_result(Result), erlang:get_stacktrace()) + throw, wrap_result(Result), Stacktrace) end. unwrap_state([State]) -> diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 7686889360..fbdcb518b2 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -446,8 +446,8 @@ init_dont_hang(Config) when is_list(Config) -> StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000), StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000, []), ok - catch _:Error -> - io:format("Error ~p /= ~p ~n",[erlang:get_stacktrace(), StartLinkRes]), + catch _:Error:Stacktrace -> + io:format("Error ~p /= ~p ~n",[Stacktrace, StartLinkRes]), exit(Error) end. diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index 3d3241b33d..d753d929f5 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2017. All Rights Reserved. +%% Copyright Ericsson AB 2000-2018. 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. @@ -52,7 +52,9 @@ all() -> [seed, interval_int, interval_float, api_eq, reference, - {group, basic_stats}, uniform_real_conv, + {group, basic_stats}, + {group, distr_stats}, + uniform_real_conv, plugin, measure, {group, reference_jump} ]. @@ -60,8 +62,9 @@ all() -> groups() -> [{basic_stats, [parallel], [basic_stats_uniform_1, basic_stats_uniform_2, - basic_stats_standard_normal, - stats_standard_normal_box_muller, + basic_stats_standard_normal]}, + {distr_stats, [parallel], + [stats_standard_normal_box_muller, stats_standard_normal_box_muller_2, stats_standard_normal]}, {reference_jump, [parallel], @@ -70,6 +73,9 @@ groups() -> group(basic_stats) -> %% valgrind needs a lot of time [{timetrap,{minutes,10}}]; +group(distr_stats) -> + %% valgrind needs a lot of time + [{timetrap,{minutes,10}}]; group(reference_jump) -> %% valgrind needs a lot of time [{timetrap,{minutes,10}}]. @@ -82,9 +88,9 @@ test() -> try ok = ?MODULE:Test([]), io:format("~p: ok~n", [Test]) - catch _:Reason -> + catch _:Reason:Stacktrace -> io:format("Failed: ~p: ~p ~p~n", - [Test, Reason, erlang:get_stacktrace()]) + [Test, Reason, Stacktrace]) end end, Tests). @@ -98,8 +104,8 @@ seed(Config) when is_list(Config) -> Algs = algs(), Test = fun(Alg) -> try seed_1(Alg) - catch _:Reason -> - ct:fail({Alg, Reason, erlang:get_stacktrace()}) + catch _:Reason:Stacktrace -> + ct:fail({Alg, Reason, Stacktrace}) end end, [Test(Alg) || Alg <- Algs], @@ -437,7 +443,7 @@ stats_standard_normal_box_muller(Config) when is_list(Config) -> {Z, [S]} end, State = [rand:seed(exrop)], - stats_standard_normal(NormalS, State) + stats_standard_normal(NormalS, State, 3) catch error:_ -> {skip, "math:erfc/1 not supported"} end. @@ -462,7 +468,7 @@ stats_standard_normal_box_muller_2(Config) when is_list(Config) -> {Z, [S]} end, State = [rand:seed(exrop)], - stats_standard_normal(NormalS, State) + stats_standard_normal(NormalS, State, 3) catch error:_ -> {skip, "math:erfc/1 not supported"} end. @@ -472,21 +478,21 @@ stats_standard_normal(Config) when is_list(Config) -> try math:erfc(1.0) of _ -> stats_standard_normal( - fun rand:normal_s/1, rand:seed_s(exrop)) + fun rand:normal_s/1, rand:seed_s(exrop), 3) catch error:_ -> {skip, "math:erfc/1 not supported"} end. %% -stats_standard_normal(Fun, S) -> +stats_standard_normal(Fun, S, Retries) -> %%% %%% ct config: -%%% {rand_SUITE, [{stats_standard_normal,[{seconds, 8}, {std_devs, 4.2}]}]}. +%%% {rand_SUITE, [{stats_standard_normal,[{seconds, 8}, {std_devs, 4.0}]}]}. %%% Seconds = ct:get_config({?MODULE, ?FUNCTION_NAME, seconds}, 8), StdDevs = ct:get_config( {?MODULE, ?FUNCTION_NAME, std_devs}, - 4.2), % probability erfc(4.2/sqrt(2)) (1/37465) to fail a bucket + 4.0), % probability erfc(4.0/sqrt(2)) (1/15787) to fail a bucket %%% ct:timetrap({seconds, Seconds + 120}), %% Buckets is chosen to get a range where the the probability to land @@ -505,11 +511,11 @@ stats_standard_normal(Fun, S) -> P0 = math:erf(1 / W), Rounds = TargetHits * ceil(1.0 / P0), Histogram = array:new({default, 0}), - StopTime = erlang:monotonic_time(second) + Seconds, ct:pal( "Running standard normal test against ~w std devs for ~w seconds...", [StdDevs, Seconds]), - {PositiveHistogram, NegativeHistogram, Outlier, TotalRounds} = + StopTime = erlang:monotonic_time(second) + Seconds, + {PositiveHistogram, NegativeHistogram, Outlier, TotalRounds, NewS} = stats_standard_normal( InvDelta, Buckets, Histogram, Histogram, 0.0, Fun, S, Rounds, StopTime, Rounds, 0), @@ -522,16 +528,33 @@ stats_standard_normal(Fun, S) -> "Total rounds: ~w, tolerance: 1/~.2f..1/~.2f, " "outlier: ~.2f, probability 1/~.2f.", [TotalRounds, Precision, TopPrecision, Outlier, InvOP]), - {TotalRounds, [], []} = - {TotalRounds, + case + {bucket_error, TotalRounds, check_histogram( W, TotalRounds, StdDevs, PositiveHistogram, Buckets), check_histogram( - W, TotalRounds, StdDevs, NegativeHistogram, Buckets)}, - %% If the probability for getting this Outlier is lower than 1/50, - %% then this is fishy! - true = (1/50 =< OutlierProbability), - {comment, {tp, TopPrecision, op, InvOP}}. + W, TotalRounds, StdDevs, NegativeHistogram, Buckets)} + of + {_, _, [], []} when InvOP < 100 -> + {comment, {tp, TopPrecision, op, InvOP}}; + {_, _, [], []} -> + %% If the probability for getting this Outlier is lower than + %% 1/100, then this is fishy! + stats_standard_normal( + Fun, NewS, Retries, {outlier_fishy, InvOP}); + BucketErrors -> + stats_standard_normal( + Fun, NewS, Retries, BucketErrors) + end. +%% +stats_standard_normal(Fun, S, Retries, Failure) -> + case Retries - 1 of + 0 -> + ct:fail(Failure); + NewRetries -> + ct:pal("Retry due to TC glitch: ~p", [Failure]), + stats_standard_normal(Fun, S, NewRetries) + end. %% stats_standard_normal( InvDelta, Buckets, PositiveHistogram, NegativeHistogram, Outlier, @@ -544,7 +567,7 @@ stats_standard_normal( Fun, S, Rounds, StopTime, Rounds, TotalRounds + Rounds); _ -> {PositiveHistogram, NegativeHistogram, - Outlier, TotalRounds + Rounds} + Outlier, TotalRounds + Rounds, S} end; stats_standard_normal( InvDelta, Buckets, PositiveHistogram, NegativeHistogram, Outlier, @@ -571,9 +594,6 @@ increment_bucket(Bucket, Array) -> array:set(Bucket, array:get(Bucket, Array) + 1, Array). check_histogram(W, Rounds, StdDevs, Histogram, Buckets) -> - %%PrevBucket = 512, - %%Bucket = PrevBucket - 1, - %%P = 0.5 * math:erfc(PrevBucket / W), TargetP = 0.5 * math:erfc(Buckets / W), P = 0.0, N = 0, @@ -592,7 +612,7 @@ check_histogram( P = 0.5 * math:erfc(Bucket / W), BucketP = P - PrevP, if - TargetP =< BucketP -> + BucketP < TargetP -> check_histogram( W, Rounds, StdDevs, Histogram, TargetP, Bucket - 1, PrevBucket, PrevP, N); @@ -604,7 +624,7 @@ check_histogram( UpperLimit = ceil(Exp + Threshold), if N < LowerLimit; UpperLimit < N -> - [#{bucket => {Bucket, PrevBucket}, n => N, exp => Exp, + [#{bucket => {Bucket, PrevBucket}, n => N, lower => LowerLimit, upper => UpperLimit} | check_histogram( W, Rounds, StdDevs, Histogram, TargetP, @@ -722,12 +742,12 @@ uniform_real_conv_check(M, E, Gen) -> [["16#",integer_to_list(G,16),$\s]||G<-Gen]]), ct:fail({neq, FF, F}) catch - Error:Reason -> + Error:Reason:Stacktrace -> ct:pal( "~w:~p ~s: ~s~n", [Error, Reason, rand:float2str(F), [["16#",integer_to_list(G,16),$\s]||G<-Gen]]), - ct:fail({Error, Reason, F, erlang:get_stacktrace()}) + ct:fail({Error, Reason, F, Stacktrace}) end. diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index 71f86e32e5..7b82647416 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -894,10 +894,13 @@ match_limit(Config) when is_list(Config) -> %% 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}]), - 255 = binary:referenced_byte_size(B), - 255 = binary:referenced_byte_size(C), - {match,[D]}=re:run(Bin,"(a)",[{capture,[1],binary}]), - 255 = binary:referenced_byte_size(D), + %% The GC can auto-convert tiny sub-binaries to heap binaries, so we + %% extract large sequences to make the test more stable. + Bin = << <<I>> || I <- lists:seq(1, 4096) >>, + {match,[B,C]}=re:run(Bin,"a(.+)$",[{capture,all,binary}]), + true = byte_size(B) =/= byte_size(C), + 4096 = binary:referenced_byte_size(B), + 4096 = binary:referenced_byte_size(C), + {match,[D]}=re:run(Bin,"a(.+)$",[{capture,[1],binary}]), + 4096 = binary:referenced_byte_size(D), ok. diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index d02a6eac0a..fdff2d24b8 100644 --- a/lib/stdlib/test/string_SUITE.erl +++ b/lib/stdlib/test/string_SUITE.erl @@ -486,6 +486,10 @@ to_float(_) -> prefix(_) -> ?TEST("", ["a"], nomatch), ?TEST("a", [""], "a"), + ?TEST("a", [[[]]], "a"), + ?TEST("a", [<<>>], "a"), + ?TEST("a", [[<<>>]], "a"), + ?TEST("a", [[[<<>>]]], "a"), ?TEST("b", ["a"], nomatch), ?TEST("a", ["a"], ""), ?TEST("å", ["a"], nomatch), @@ -877,9 +881,9 @@ test_1(Line, Func, Str, Args, Exp) -> catch error:Exp -> ok; - error:Reason -> + error:Reason:Stacktrace -> io:format("~p:~p: Crash ~p ~p~n", - [?MODULE,Line, Reason, erlang:get_stacktrace()]), + [?MODULE,Line, Reason, Stacktrace]), exit({error, Func}) end. @@ -944,10 +948,10 @@ check_types(Line, Func, [Str|_], Res) -> io:format("Failed: ~p ~p: ~p ~p~n",[Line, Func, T1, T2]), io:format(" ~p => ~p~n", [Str, Res]), error; - _:Reason -> - io:format("Crash: ~p in~n ~p~n",[Reason, erlang:get_stacktrace()]), + _:Reason:Stacktrace -> + io:format("Crash: ~p in~n ~p~n",[Reason, Stacktrace]), io:format("Failed: ~p ~p: ~p => ~p~n", [Line, Func, Str, Res]), - exit({Reason, erlang:get_stacktrace()}) + exit({Reason, Stacktrace}) end. check_types_1(T, T) -> diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 4061008812..32a33283d1 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -28,7 +28,7 @@ extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1, memory/1,unicode/1,read_other_implementations/1, sparse/1, init/1, leading_slash/1, dotdot/1, - roundtrip_metadata/1]). + roundtrip_metadata/1, apply_file_info_opts/1]). -include_lib("common_test/include/ct.hrl"). -include_lib("kernel/include/file.hrl"). @@ -42,7 +42,8 @@ all() -> extract_filtered, symlinks, open_add_close, cooked_compressed, memory, unicode, read_other_implementations, - sparse,init,leading_slash,dotdot,roundtrip_metadata]. + sparse,init,leading_slash,dotdot,roundtrip_metadata, + apply_file_info_opts]. groups() -> []. @@ -989,6 +990,31 @@ do_roundtrip_metadata(Dir, File) -> ok end. +apply_file_info_opts(Config) when is_list(Config) -> + ok = file:set_cwd(proplists:get_value(priv_dir, Config)), + + ok = file:make_dir("empty_directory"), + ok = file:write_file("file", "contents"), + + Opts = [{atime, 0}, {mtime, 0}, {ctime, 0}, {uid, 0}, {gid, 0}], + TarFile = "reproducible.tar", + {ok, Tar} = erl_tar:open(TarFile, [write]), + ok = erl_tar:add(Tar, "file", Opts), + ok = erl_tar:add(Tar, "empty_directory", Opts), + ok = erl_tar:add(Tar, <<"contents">>, "memory_file", Opts), + erl_tar:close(Tar), + + ok = file:make_dir("extracted"), + erl_tar:extract(TarFile, [{cwd, "extracted"}]), + + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/empty_directory", [{time, posix}]), + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/file", [{time, posix}]), + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/memory_file", [{time, posix}]), + + ok. %% Delete the given list of files. delete_files([]) -> ok; diff --git a/lib/stdlib/test/unicode_util_SUITE.erl b/lib/stdlib/test/unicode_util_SUITE.erl index 632d9ae6e6..40b1c260a5 100644 --- a/lib/stdlib/test/unicode_util_SUITE.erl +++ b/lib/stdlib/test/unicode_util_SUITE.erl @@ -136,10 +136,10 @@ verify_gc(Line0, N, Acc) -> io:format("Expected: ~p~n", [Res]), io:format("Got: ~w~n", [Other]), Acc+1; - Cl:R -> + Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[N, Line, Str]), io:format("Expected: ~p~n", [Res]), - erlang:raise(Cl,R,erlang:get_stacktrace()) + erlang:raise(Cl,R,Stacktrace) end. gc_test_data([[247]|Rest], Str, [First|GCs]) -> @@ -175,29 +175,29 @@ verify_nfd(Data0, LineNo, _Acc) -> C3GC = fetch(C1, fun unicode_util:nfd/1), C3GC = fetch(C2, fun unicode_util:nfd/1), C3GC = fetch(C3, fun unicode_util:nfd/1) - catch _Cl:{badmatch, Other} = _R-> + catch _Cl:{badmatch, Other} = _R: Stacktrace -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C1, C1]), io:format("Expected: ~ts ~w~n", [C3GC, C3GC]), io:format("Got: ~ts ~w~n", [Other, Other]), - erlang:raise(_Cl,_R,erlang:get_stacktrace()); - Cl:R -> + erlang:raise(_Cl,_R,Stacktrace); + Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C3]), - erlang:raise(Cl,R,erlang:get_stacktrace()) + erlang:raise(Cl,R,Stacktrace) end, C5GC = fetch(C5, fun unicode_util:gc/1), try C5GC = fetch(C4, fun unicode_util:nfd/1), C5GC = fetch(C5, fun unicode_util:nfd/1) - catch _Cl2:{badmatch, Other2} = _R2-> + catch _Cl2:{badmatch, Other2} = _R2:Stacktrace2 -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C1, C1]), io:format("Expected: ~ts ~w~n", [C5GC, C5GC]), io:format("Got: ~ts ~w~n", [Other2, Other2]), - erlang:raise(_Cl2,_R2,erlang:get_stacktrace()); - Cl2:R2 -> + erlang:raise(_Cl2,_R2,Stacktrace2); + Cl2:R2:Stacktrace2 -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C5]), - erlang:raise(Cl2,R2,erlang:get_stacktrace()) + erlang:raise(Cl2,R2,Stacktrace2) end, ok. @@ -218,29 +218,29 @@ verify_nfc(Data0, LineNo, _Acc) -> C2GC = fetch(C1, fun unicode_util:nfc/1), C2GC = fetch(C2, fun unicode_util:nfc/1), C2GC = fetch(C3, fun unicode_util:nfc/1) - catch _Cl:{badmatch, Other} = _R-> + catch _Cl:{badmatch, Other} = _R:Stacktrace -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C1, C1]), io:format("Expected: ~ts ~w~n", [C2GC, C2GC]), io:format("Got: ~ts ~w~n", [Other, Other]), - erlang:raise(_Cl,_R,erlang:get_stacktrace()); - Cl:R -> + erlang:raise(_Cl,_R,Stacktrace); + Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C3]), - erlang:raise(Cl,R,erlang:get_stacktrace()) + erlang:raise(Cl,R,Stacktrace) end, C4GC = fetch(C4, fun unicode_util:gc/1), try C4GC = fetch(C4, fun unicode_util:nfc/1), C4GC = fetch(C5, fun unicode_util:nfc/1) - catch _Cl2:{badmatch, Other2} = _R2-> + catch _Cl2:{badmatch, Other2} = _R2:Stacktrace2 -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C1, C1]), io:format("Expected: ~ts ~w~n", [C4GC, C4GC]), io:format("Got: ~ts ~w~n", [Other2, Other2]), - erlang:raise(_Cl2,_R2,erlang:get_stacktrace()); - Cl2:R2 -> + erlang:raise(_Cl2,_R2,Stacktrace2); + Cl2:R2:Stacktrace2 -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C5]), - erlang:raise(Cl2,R2,erlang:get_stacktrace()) + erlang:raise(Cl2,R2,Stacktrace2) end, ok. @@ -263,15 +263,15 @@ verify_nfkd(Data0, LineNo, _Acc) -> C5GC = lists:flatten(fetch(C3, fun unicode_util:nfkd/1)), C5GC = lists:flatten(fetch(C4, fun unicode_util:nfkd/1)), C5GC = lists:flatten(fetch(C5, fun unicode_util:nfkd/1)) - catch _Cl:{badmatch, Other} = _R-> + catch _Cl:{badmatch, Other} = _R:Stacktrace -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C5, C5]), io:format("Expected: ~ts ~w~n", [C5GC, C5GC]), io:format("Got: ~ts ~w~n", [Other, Other]), - erlang:raise(_Cl,_R,erlang:get_stacktrace()); - Cl:R -> + erlang:raise(_Cl,_R,Stacktrace); + Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C3]), - erlang:raise(Cl,R,erlang:get_stacktrace()) + erlang:raise(Cl,R,Stacktrace) end, ok. @@ -296,15 +296,15 @@ verify_nfkc(Data0, LineNo, _Acc) -> C4GC = lists:flatten(fetch(C4, fun unicode_util:nfkc/1)), C4GC = lists:flatten(fetch(C5, fun unicode_util:nfkc/1)) - catch _Cl:{badmatch, Other} = _R-> + catch _Cl:{badmatch, Other} = _R:Stacktrace -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[LineNo, Data1, C4, C4]), io:format("Expected: ~ts ~w~n", [C4GC, C4GC]), io:format("Got: ~ts ~w~n", [Other, Other]), - erlang:raise(_Cl,_R,erlang:get_stacktrace()); - Cl:R -> + erlang:raise(_Cl,_R,Stacktrace); + Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[LineNo, Data1, C1]), io:format("Expected: ~p~n", [C3]), - erlang:raise(Cl,R,erlang:get_stacktrace()) + erlang:raise(Cl,R,Stacktrace) end, ok. diff --git a/lib/stdlib/test/uri_string_SUITE.erl b/lib/stdlib/test/uri_string_SUITE.erl index fef356355c..92f8bb3292 100644 --- a/lib/stdlib/test/uri_string_SUITE.erl +++ b/lib/stdlib/test/uri_string_SUITE.erl @@ -22,7 +22,7 @@ -include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0, - normalize/1, + normalize/1, normalize_map/1, normalize_return_map/1, normalize_negative/1, parse_binary_fragment/1, parse_binary_host/1, parse_binary_host_ipv4/1, parse_binary_host_ipv6/1, parse_binary_path/1, parse_binary_pct_encoded_fragment/1, parse_binary_pct_encoded_query/1, @@ -68,6 +68,9 @@ suite() -> all() -> [ normalize, + normalize_map, + normalize_return_map, + normalize_negative, parse_binary_scheme, parse_binary_userinfo, parse_binary_pct_encoded_userinfo, @@ -912,6 +915,56 @@ normalize(_Config) -> <<"tftp://localhost">> = uri_string:normalize(<<"tftp://localhost:69">>). +normalize_map(_Config) -> + "/a/g" = uri_string:normalize(#{path => "/a/b/c/./../../g"}), + <<"mid/6">> = uri_string:normalize(#{path => <<"mid/content=5/../6">>}), + "http://localhost-%C3%B6rebro/a/g" = + uri_string:normalize(#{scheme => "http",port => 80,path => "/a/b/c/./../../g", + host => "localhost-örebro"}), + <<"http://localhost-%C3%B6rebro/a/g">> = + uri_string:normalize(#{scheme => <<"http">>,port => 80, + path => <<"/a/b/c/./../../g">>, + host => <<"localhost-örebro"/utf8>>}), + <<"https://localhost/">> = + uri_string:normalize(#{scheme => <<"https">>,port => 443,path => <<>>, + host => <<"localhost">>}), + <<"https://localhost:445/">> = + uri_string:normalize(#{scheme => <<"https">>,port => 445,path => <<>>, + host => <<"localhost">>}), + <<"ftp://localhost">> = + uri_string:normalize(#{scheme => <<"ftp">>,port => 21,path => <<>>, + host => <<"localhost">>}), + <<"ssh://localhost">> = + uri_string:normalize(#{scheme => <<"ssh">>,port => 22,path => <<>>, + host => <<"localhost">>}), + <<"sftp://localhost">> = + uri_string:normalize(#{scheme => <<"sftp">>,port => 22,path => <<>>, + host => <<"localhost">>}), + <<"tftp://localhost">> = + uri_string:normalize(#{scheme => <<"tftp">>,port => 69,path => <<>>, + host => <<"localhost">>}). + +normalize_return_map(_Config) -> + #{scheme := "http",path := "/a/g",host := "localhost-örebro"} = + uri_string:normalize("http://localhos%74-%c3%b6rebro:80/a/b/c/./../../g", + [return_map]), + #{scheme := <<"http">>,path := <<"/a/g">>, host := <<"localhost-örebro"/utf8>>} = + uri_string:normalize(<<"http://localhos%74-%c3%b6rebro:80/a/b/c/./../../g">>, + [return_map]), + #{scheme := <<"https">>,path := <<"/">>, host := <<"localhost">>} = + uri_string:normalize(#{scheme => <<"https">>,port => 443,path => <<>>, + host => <<"localhost">>}, [return_map]). + +normalize_negative(_Config) -> + {error,invalid_uri,":"} = + uri_string:normalize("http://local>host"), + {error,invalid_uri,":"} = + uri_string:normalize(<<"http://local>host">>), + {error,invalid_uri,":"} = + uri_string:normalize("http://[192.168.0.1]", [return_map]), + {error,invalid_uri,":"} = + uri_string:normalize(<<"http://[192.168.0.1]">>, [return_map]). + interop_query_utf8(_Config) -> Q = uri_string:compose_query([{"foo bar","1"}, {"合", "2"}]), Uri = uri_string:recompose(#{path => "/", query => Q}), diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index 1dfcda4ed0..e5ba629c55 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -909,8 +909,7 @@ do_fd_leak(Bad, N) -> ok -> do_fd_leak(Bad, N + 1) catch - C:R -> - Stk = erlang:get_stacktrace(), + C:R:Stk -> io:format("Bad error after ~p attempts\n", [N]), erlang:raise(C, R, Stk) end. |