diff options
Diffstat (limited to 'lib/stdlib/test')
| -rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 35 | ||||
| -rw-r--r-- | lib/stdlib/test/lists_SUITE.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/stdlib.spec | 2 | ||||
| -rw-r--r-- | lib/stdlib/test/stdlib_bench_SUITE.erl | 67 | ||||
| -rw-r--r-- | lib/stdlib/test/uri_string_SUITE.erl | 10 | 
7 files changed, 59 insertions, 61 deletions
| diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index a3e294ffea..10e1b75e0f 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1372,7 +1372,7 @@ otp_8562(Config) when is_list(Config) ->  otp_8911(Config) when is_list(Config) ->      case test_server:is_cover() of  	true -> -	    {skip, "Testing cover, so can not run when cover is already running"}; +	    {skip, "Testing cover, so cannot run when cover is already running"};  	false ->  	    do_otp_8911(Config)      end. diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index f9ab83a120..c1613a7273 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2730,7 +2730,7 @@ bif_clash(Config) when is_list(Config) ->             [],  	   {errors,[{2,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}}, -	  %% Verify that warnings can not be turned off in the old way. +	  %% Verify that warnings cannot be turned off in the old way.  	  {clash2,             <<"-export([t/1,size/1]).                t(X) -> diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 7a48d1d55e..fee8b204f4 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -6112,40 +6112,11 @@ etsmem() ->  				   ets:info(T,memory),ets:info(T,type)}  			end, ets:all()), -    EtsAllocInfo = erlang:system_info({allocator,ets_alloc}), +    EtsAllocSize = erts_debug:alloc_blocks_size(ets_alloc),      ErlangMemoryEts = try erlang:memory(ets) catch error:notsup -> notsup end, -    Mem = -	{ErlangMemoryEts, -	 case EtsAllocInfo of -	     false -> undefined; -	     MemInfo -> -		 CS = lists:foldl( -			fun ({instance, _, L}, Acc) -> -				{value,{mbcs,MBCS}} = lists:keysearch(mbcs, 1, L), -				{value,{sbcs,SBCS}} = lists:keysearch(sbcs, 1, L), -				NewAcc = [MBCS, SBCS | Acc], -				case lists:keysearch(mbcs_pool, 1, L) of -				    {value,{mbcs_pool, MBCS_POOL}} -> -					[MBCS_POOL|NewAcc]; -				    _ -> NewAcc -				end -			end, -			[], -			MemInfo), -		 lists:foldl( -		   fun(L, {Bl0,BlSz0}) -> -			   {value,BlTup} = lists:keysearch(blocks, 1, L), -			   blocks = element(1, BlTup), -			   Bl = element(2, BlTup), -			   {value,BlSzTup} = lists:keysearch(blocks_size, 1, L), -			   blocks_size = element(1, BlSzTup), -			   BlSz = element(2, BlSzTup), -			   {Bl0+Bl,BlSz0+BlSz} -		   end, {0,0}, CS) -	 end}, -    {Mem,AllTabs}. - +    Mem = {ErlangMemoryEts, EtsAllocSize}, +    {Mem, AllTabs}.  verify_etsmem(MI) ->      wait_for_test_procs(), diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index 837ab4e97e..af94fc79bc 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -1679,7 +1679,7 @@ make_fun() ->      receive {Pid, Fun} -> Fun end.  make_fun(Pid) -> -    Pid ! {self(), fun make_fun/1}. +    Pid ! {self(), fun (X) -> {X, Pid} end}.  fun_pid(Fun) ->      erlang:fun_info(Fun, pid). diff --git a/lib/stdlib/test/stdlib.spec b/lib/stdlib/test/stdlib.spec index 9c625091a8..4de7c1a0eb 100644 --- a/lib/stdlib/test/stdlib.spec +++ b/lib/stdlib/test/stdlib.spec @@ -1,4 +1,4 @@  {suites,"../stdlib_test",all}.  {skip_groups,"../stdlib_test",stdlib_bench_SUITE, -             [base64,gen_server,gen_statem,unicode], +             [binary,base64,gen_server,gen_statem,unicode],               "Benchmark only"}. diff --git a/lib/stdlib/test/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl index 2364e8376f..b937eeb06a 100644 --- a/lib/stdlib/test/stdlib_bench_SUITE.erl +++ b/lib/stdlib/test/stdlib_bench_SUITE.erl @@ -29,7 +29,7 @@ suite() -> [{ct_hooks,[{ts_install_cth,[{nodenames,2}]}]}].  all() -> -    [{group,unicode},{group,base64}, +    [{group,unicode},{group,base64},{group,binary},       {group,gen_server},{group,gen_statem},       {group,gen_server_comparison},{group,gen_statem_comparison}]. @@ -38,6 +38,11 @@ groups() ->        [norm_nfc_list, norm_nfc_deep_l, norm_nfc_binary,         string_lexemes_list, string_lexemes_binary        ]}, +     {binary, [{repeat, 5}], +      [match_single_pattern_no_match, +       matches_single_pattern_no_match, +       matches_single_pattern_eventual_match, +       matches_single_pattern_frequent_match]},       {base64,[{repeat,5}],        [decode_binary, decode_binary_to_string,         decode_list, decode_list_to_string, @@ -157,41 +162,59 @@ norm_data(Config) ->  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +match_single_pattern_no_match(_Config) -> +    Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000), +    comment(test(binary, match, [Binary, <<"o">>])). + +matches_single_pattern_no_match(_Config) -> +    Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000), +    comment(test(binary, matches, [Binary, <<"o">>])). + +matches_single_pattern_eventual_match(_Config) -> +    Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsal\n">>, 1000000), +    comment(test(binary, matches, [Binary, <<"\n">>])). + +matches_single_pattern_frequent_match(_Config) -> +    Binary = binary:copy(<<"abc\n">>, 1000000), +    comment(test(binary, matches, [Binary, <<"abc">>])). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +  decode_binary(_Config) -> -    comment(test(decode, encoded_binary())). +    comment(test(base64, decode, [encoded_binary()])).  decode_binary_to_string(_Config) -> -    comment(test(decode_to_string, encoded_binary())). +    comment(test(base64, decode_to_string, [encoded_binary()])).  decode_list(_Config) -> -    comment(test(decode, encoded_list())). +    comment(test(base64, decode, [encoded_list()])).  decode_list_to_string(_Config) -> -    comment(test(decode_to_string, encoded_list())). +    comment(test(base64, decode_to_string, [encoded_list()])).  encode_binary(_Config) -> -    comment(test(encode, binary())). +    comment(test(base64, encode, [binary()])).  encode_binary_to_string(_Config) -> -    comment(test(encode_to_string, binary())). +    comment(test(base64, encode_to_string, [binary()])).  encode_list(_Config) -> -    comment(test(encode, list())). +    comment(test(base64, encode, [list()])).  encode_list_to_string(_Config) -> -    comment(test(encode_to_string, list())). +    comment(test(base64, encode_to_string, [list()])).  mime_binary_decode(_Config) -> -    comment(test(mime_decode, encoded_binary())). +    comment(test(base64, mime_decode, [encoded_binary()])).  mime_binary_decode_to_string(_Config) -> -    comment(test(mime_decode_to_string, encoded_binary())). +    comment(test(base64, mime_decode_to_string, [encoded_binary()])).  mime_list_decode(_Config) -> -    comment(test(mime_decode, encoded_list())). +    comment(test(base64, mime_decode, [encoded_list()])).  mime_list_decode_to_string(_Config) -> -    comment(test(mime_decode_to_string, encoded_list())). +    comment(test(base64, mime_decode_to_string, [encoded_list()])).  -define(SIZE, 10000).  -define(N, 1000). @@ -209,15 +232,15 @@ binary() ->  list() ->      random_byte_list(?SIZE). -test(Func, Data) -> -    F = fun() -> loop(?N, Func, Data) end, +test(Mod, Fun, Args) -> +    F = fun() -> loop(?N, Mod, Fun, Args) end,      {Time, ok} = timer:tc(fun() -> lspawn(F) end), -    report_base64(Time). +    report_mfa(Time, Mod). -loop(0, _F, _D) -> garbage_collect(), ok; -loop(N, F, D) -> -    _ = base64:F(D), -    loop(N - 1, F, D). +loop(0, _M, _F, _A) -> garbage_collect(), ok; +loop(N, M, F, A) -> +    _ = apply(M, F, A), +    loop(N - 1, M, F, A).  lspawn(Fun) ->      {Pid, Ref} = spawn_monitor(fun() -> exit(Fun()) end), @@ -225,10 +248,10 @@ lspawn(Fun) ->          {'DOWN', Ref, process, Pid, Rep} -> Rep      end. -report_base64(Time) -> +report_mfa(Time, Mod) ->      Tps = round((?N*1000000)/Time),      ct_event:notify(#event{name = benchmark_data, -                           data = [{suite, "stdlib_base64"}, +                           data = [{suite, "stdlib_" ++ atom_to_list(Mod)},                                     {value, Tps}]}),      Tps. diff --git a/lib/stdlib/test/uri_string_SUITE.erl b/lib/stdlib/test/uri_string_SUITE.erl index 4fc0d76be8..ddaead9c7c 100644 --- a/lib/stdlib/test/uri_string_SUITE.erl +++ b/lib/stdlib/test/uri_string_SUITE.erl @@ -862,9 +862,11 @@ transcode_negative(_Config) ->  compose_query(_Config) ->      [] = uri_string:compose_query([]),      "foo=1&bar=2" = uri_string:compose_query([{<<"foo">>,"1"}, {"bar", "2"}]), +    "foo=1&bar" = uri_string:compose_query([{<<"foo">>,"1"}, {"bar", true}]),      "foo=1&b%C3%A4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,utf8}]),      "foo=1&b%C3%A4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,unicode}]),      "foo=1&b%E4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,latin1}]), +    "foo&b%E4r=2" = uri_string:compose_query([{"foo",true}, {"bär", "2"}],[{encoding,latin1}]),      "foo+bar=1&%E5%90%88=2" = uri_string:compose_query([{"foo bar","1"}, {"合", "2"}]),      "foo+bar=1&%26%2321512%3B=2" =          uri_string:compose_query([{"foo bar","1"}, {"合", "2"}],[{encoding,latin1}]), @@ -906,11 +908,13 @@ dissect_query(_Config) ->      [{"föo bar","1"},{"ö","2"}] =          uri_string:dissect_query("föo+bar=1&%C3%B6=2"),      [{<<"föo bar"/utf8>>,<<"1">>},{<<"ö"/utf8>>,<<"2">>}] = -        uri_string:dissect_query(<<"föo+bar=1&%C3%B6=2"/utf8>>). +        uri_string:dissect_query(<<"föo+bar=1&%C3%B6=2"/utf8>>), +    [{"foo1",true},{"bar","2"}] = +        uri_string:dissect_query("foo1&bar=2"), +    [{<<"foo1">>,<<"1">>},{<<"bar">>,true}] = +        uri_string:dissect_query(<<"foo1=1&bar">>).  dissect_query_negative(_Config) -> -    {error,missing_value,"&"} = -        uri_string:dissect_query("foo1&bar=2"),      {error,invalid_percent_encoding,"%XX%B6"} = uri_string:dissect_query("foo=%XX%B6&bar=2"),      {error,invalid_input,[153]} =          uri_string:dissect_query("foo=%99%B6&bar=2"), | 
