diff options
Diffstat (limited to 'lib/stdlib/test/string_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/string_SUITE.erl | 159 |
1 files changed, 131 insertions, 28 deletions
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index 17714b8d4d..c9aadd7f10 100644 --- a/lib/stdlib/test/string_SUITE.erl +++ b/lib/stdlib/test/string_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2017. All Rights Reserved. +%% Copyright Ericsson AB 2004-2019. 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. @@ -47,7 +47,8 @@ -export([to_upper_to_lower/1]). %% Run tests when debugging them --export([debug/0]). +-export([debug/0, time_func/4]). +-compile([nowarn_deprecated_function]). suite() -> [{ct_hooks,[ts_install_cth]}, @@ -102,6 +103,15 @@ debug() -> test(?LINE,?FUNCTION_NAME,B,C,D, false), test(?LINE,?FUNCTION_NAME,hd(C),[B|tl(C)],D, false)). +-define(TRY(Exp), + fun() -> + try Exp + catch _E:Reason:_ST -> + %% io:format("~p:~w: ~p: ~.0p ~p~n", + %% [?FUNCTION_NAME, ?LINE,_E,Reason, hd(_ST)]), + {'EXIT', Reason} + end + end()). is_empty(_) -> ?TEST("", [], true), @@ -125,6 +135,10 @@ length(_) -> ?TEST(["abc"|<<"abc">>], [], 6), ?TEST(["abc",["def"]], [], 6), ?TEST([<<97/utf8, 778/utf8, 98/utf8>>, [776,111,776]], [], 3), %% åäö in nfd + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:length(InvalidUTF8)), + {'EXIT', {badarg, _}} = ?TRY(string:length(<<$a, InvalidUTF8/binary, $z>>)), ok. equal(_) -> @@ -225,6 +239,8 @@ to_graphemes(_) -> true = erlang:length(GCs) =:= erlang:length(string:to_graphemes(NFD)), true = erlang:length(GCs) =:= erlang:length(string:to_graphemes(unicode:characters_to_nfc_list(String))), + + {'EXIT', {badarg, _}} = ?TRY(string:to_graphemes(<<$a,192,192,$z>>)), ok. reverse(_) -> @@ -237,6 +253,11 @@ reverse(_) -> ?TEST(Str2, [], lists:reverse(Str2)), ?TEST(Str3, [], lists:reverse(Str3)), true = string:reverse(Str3) =:= lists:reverse(string:to_graphemes(Str3)), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:reverse(InvalidUTF8)), + {'EXIT', {badarg, _}} = ?TRY(string:reverse(<<$a, InvalidUTF8/binary, $z>>)), + ok. slice(_) -> @@ -257,6 +278,14 @@ slice(_) -> ?TEST([<<"aå"/utf8>>,"äöbcd"], [3,3], "öbc"), ?TEST([<<"aåä"/utf8>>,"öbcd"], [3,10], "öbcd"), + InvalidUTF8 = <<192,192>>, + [$b, $c|InvalidUTF8] = string:slice(["abc", InvalidUTF8], 1), + InvalidUTF8 = string:slice(["abc", InvalidUTF8], 3), + {'EXIT', {badarg, _}} = ?TRY(string:slice(["abc", InvalidUTF8], 1, 5)), + BadUtf8 = <<$a, InvalidUTF8/binary, "teststring">>, + {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 2)), + {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 1, 5)), + {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 0, 5)), ok. pad(_) -> @@ -269,6 +298,10 @@ pad(_) -> ?TEST(Str, [10, trailing, $.], "Hallå....."), ?TEST(Str++["f"], [10, trailing, $.], "Hallåf...."), ?TEST(Str++[" flåwer"], [10, trailing, $.], "Hallå flåwer"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:pad(InvalidUTF8, 10, both, $.)), + {'EXIT', {badarg, _}} = ?TRY(string:pad(<<$a, InvalidUTF8/binary, $z>>, 10, both, $.)), ok. trim(_) -> @@ -299,6 +332,11 @@ trim(_) -> ?TEST([[<<"!v">>|<<204,128,$v,204,129>>]],[trailing, [[$v,769]]], [$!,$v,768]), ?TEST([[[<<"v">>|<<204,129,118,204,128,118>>],769,118,769]], [trailing, [[118,769]]], [$v,769,$v,768]), ?TEST([<<"vv">>|<<204,128,118,204,128>>], [trailing, [[118,768]]], "v"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:trim(InvalidUTF8, both, "az")), + %% Not checked (using binary search) + %% {'EXIT', {badarg, _}} = ?TRY(string:trim(<<$a, $b, InvalidUTF8/binary, $z>>, both, "az")), ok. chomp(_) -> @@ -399,6 +437,13 @@ take(_) -> ?TEST([<<"e">>,778,"åäöe", <<778/utf8>>, $e, 779], [[[$e,778]], true, trailing], {[$e,778]++"åäöe"++[778], [$e,779]}), + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], false, leading)), + %% Not checked (using binary search) + %% {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], true, leading)), + %% {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], false, trailing)), + {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], true, trailing)), + ok. @@ -408,13 +453,18 @@ uppercase(_) -> ?TEST("abc", [], "ABC"), ?TEST("ABC", [], "ABC"), ?TEST("abcdefghiljklmnopqrstvxyzåäö",[], "ABCDEFGHILJKLMNOPQRSTVXYZÅÄÖ"), - ?TEST("åäö", [], "ÅÄÖ"), - ?TEST("ÅÄÖ", [], "ÅÄÖ"), + ?TEST("åäö ", [], "ÅÄÖ "), + ?TEST("ÅÄÖ ", [], "ÅÄÖ "), ?TEST("Michał", [], "MICHAŁ"), ?TEST(["Mic",<<"hał"/utf8>>], [], "MICHAŁ"), ?TEST("ljLJ", [], "LJLJ"), ?TEST("LJlj", [], "LJLJ"), ?TEST("ß sharp s", [], "SS SHARP S"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:uppercase(InvalidUTF8)), + {'EXIT', {badarg, _}} = ?TRY(string:uppercase(<<$a, InvalidUTF8/binary, $z>>)), + ok. lowercase(_) -> @@ -422,12 +472,16 @@ lowercase(_) -> ?TEST("123", [], "123"), ?TEST("abc", [], "abc"), ?TEST("ABC", [], "abc"), - ?TEST("åäö", [], "åäö"), - ?TEST("ÅÄÖ", [], "åäö"), + ?TEST("åäö ", [], "åäö "), + ?TEST("ÅÄÖ ", [], "åäö "), ?TEST("MICHAŁ", [], "michał"), ?TEST(["Mic",<<"HAŁ"/utf8>>], [], "michał"), ?TEST("ß SHARP S", [], "ß sharp s"), ?TEST("İ I WITH DOT ABOVE", [], "i̇ i with dot above"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:lowercase(InvalidUTF8)), + {'EXIT', {badarg, _}} = ?TRY(string:lowercase(<<$a, InvalidUTF8/binary, $z>>)), ok. titlecase(_) -> @@ -441,6 +495,10 @@ titlecase(_) -> ?TEST("ljLJ", [], "LjLJ"), ?TEST("LJlj", [], "Ljlj"), ?TEST("ß sharp s", [], "Ss sharp s"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:titlecase(InvalidUTF8)), + <<$A, _/binary>> = ?TRY(string:titlecase(<<$a, InvalidUTF8/binary, $z>>)), ok. casefold(_) -> @@ -448,13 +506,17 @@ casefold(_) -> ?TEST("123", [], "123"), ?TEST("abc", [], "abc"), ?TEST("ABC", [], "abc"), - ?TEST("åäö", [], "åäö"), - ?TEST("ÅÄÖ", [], "åäö"), + ?TEST("åäö ", [], "åäö "), + ?TEST("ÅÄÖ ", [], "åäö "), ?TEST("MICHAŁ", [], "michał"), ?TEST(["Mic",<<"HAŁ"/utf8>>], [], "michał"), ?TEST("ß SHARP S", [], "ss sharp s"), ?TEST("ẞ SHARP S", [], "ss sharp s"), ?TEST("İ I WITH DOT ABOVE", [], "i̇ i with dot above"), + + InvalidUTF8 = <<192,192>>, + {'EXIT', {badarg, _}} = ?TRY(string:casefold(InvalidUTF8)), + {'EXIT', {badarg, _}} = ?TRY(string:casefold(<<$a, InvalidUTF8/binary, $z>>)), ok. @@ -739,7 +801,7 @@ meas(Config) -> _ -> % No scaling, run at most 1.5 min Tester = spawn(Exec), receive {test_done, Tester} -> ok - after 90000 -> + after 118000 -> io:format("Timelimit reached stopping~n",[]), exit(Tester, die) end, @@ -752,20 +814,23 @@ do_measure(DataDir) -> {ok, Bin} = file:read_file(File), io:format("~p~n",[byte_size(Bin)]), Do = fun(Name, Func, Mode) -> - {N, Mean, Stddev, _} = time_func(Func, Mode, Bin), - io:format("~15w ~6w ~6.2fms ±~5.2fms #~.2w gc included~n", + {N, Mean, Stddev, _} = time_func(Func, Mode, Bin, 20), + io:format("~15w ~15w ~8.2fms ±~6.2fms #~.2w gc included~n", [Name, Mode, Mean/1000, Stddev/1000, N]) end, Do2 = fun(Name, Func, Mode) -> - {N, Mean, Stddev, _} = time_func(Func, binary, <<>>), - io:format("~15w ~6w ~6.2fms ±~5.2fms #~.2w gc included~n", + {N, Mean, Stddev, _} = time_func(Func, binary, <<>>, 20), + io:format("~15w ~15w ~8.2fms ±~6.2fms #~.2w gc included~n", [Name, Mode, Mean/1000, Stddev/1000, N]) end, + %% lefty_list means a list balanced to the left, like + %% [[[30],31],32]. Only some functions check such lists. + Modes = [list, lefty_list, binary, {many_lists,1}, {many_lists, 4}], io:format("----------------------~n"), Do(old_tokens, fun(Str) -> string:tokens(Str, [$\n,$\r]) end, list), Tokens = {lexemes, fun(Str) -> string:lexemes(Str, [$\n,$\r]) end}, - [Do(Name,Fun,Mode) || {Name,Fun} <- [Tokens], Mode <- [list, binary]], + [Do(Name,Fun,Mode) || {Name,Fun} <- [Tokens], Mode <- Modes], S0 = "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxy.....", S0B = <<"xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxy.....">>, @@ -809,19 +874,31 @@ do_measure(DataDir) -> Do2(slice, repeat(fun() -> string:slice(S0, 20, 15) end), list), Do2(slice, repeat(fun() -> string:slice(S0B, 20, 15) end), binary), + LCase = "areaa reare rerar earea reare reare", + LCaseB = unicode:characters_to_binary(LCase), + UCase = string:uppercase(LCase), + UCaseB = unicode:characters_to_binary(UCase), + + Do2(to_upper_0, repeat(fun() -> string:to_upper(UCase) end), list), + Do2(uppercase_0, repeat(fun() -> string:uppercase(UCase) end), list), + Do2(uppercase_0, repeat(fun() -> string:uppercase(UCaseB) end), binary), + Do2(to_upper_a, repeat(fun() -> string:to_upper(LCase) end), list), + Do2(uppercase_a, repeat(fun() -> string:uppercase(LCase) end), list), + Do2(uppercase_a, repeat(fun() -> string:uppercase(LCaseB) end), binary), + io:format("--~n",[]), NthTokens = {nth_lexemes, fun(Str) -> string:nth_lexeme(Str, 18000, [$\n,$\r]) end}, - [Do(Name,Fun,Mode) || {Name,Fun} <- [NthTokens], Mode <- [list, binary]], + [Do(Name,Fun,Mode) || {Name,Fun} <- [NthTokens], Mode <- Modes], Do2(take_t, repeat(fun() -> string:take(S0, [$.,$y], false, trailing) end), list), Do2(take_t, repeat(fun() -> string:take(S0B, [$.,$y], false, trailing) end), binary), Do2(take_tc, repeat(fun() -> string:take(S0, [$x], true, trailing) end), list), Do2(take_tc, repeat(fun() -> string:take(S0B, [$x], true, trailing) end), binary), Length = {length, fun(Str) -> string:length(Str) end}, - [Do(Name,Fun,Mode) || {Name,Fun} <- [Length], Mode <- [list, binary]], + [Do(Name,Fun,Mode) || {Name,Fun} <- [Length], Mode <- Modes], Reverse = {reverse, fun(Str) -> string:reverse(Str) end}, - [Do(Name,Fun,Mode) || {Name,Fun} <- [Reverse], Mode <- [list, binary]], + [Do(Name,Fun,Mode) || {Name,Fun} <- [Reverse], Mode <- Modes], ok. @@ -880,9 +957,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. @@ -947,10 +1024,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) -> @@ -1033,25 +1110,51 @@ needs_check(_) -> true. %%%% Timer stuff -time_func(Fun, Mode, Bin) -> +time_func(Fun, Mode, Bin, Repeat) -> timer:sleep(100), %% Let emulator catch up and clean things before test runs Self = self(), Pid = spawn_link(fun() -> Str = mode(Mode, Bin), - Self ! {self(),time_func(0,0,0, Fun, Str, undefined)} + Self ! {self(),time_func(0,0,0, Fun, Str, undefined, Repeat)} end), receive {Pid,Msg} -> Msg end. -time_func(N,Sum,SumSq, Fun, Str, _) when N < 20 -> +time_func(N,Sum,SumSq, Fun, Str, _, Repeat) when N < Repeat -> {Time, Res} = timer:tc(fun() -> Fun(Str) end), - time_func(N+1,Sum+Time,SumSq+Time*Time, Fun, Str, Res); -time_func(N,Sum,SumSq, _, _, Res) -> + time_func(N+1,Sum+Time,SumSq+Time*Time, Fun, Str, Res, Repeat); +time_func(N,Sum,SumSq, _, _, Res, _) -> Mean = round(Sum / N), Stdev = round(math:sqrt((SumSq - (Sum*Sum/N))/(N - 1))), {N, Mean, Stdev, Res}. mode(binary, Bin) -> Bin; -mode(list, Bin) -> unicode:characters_to_list(Bin). +mode(list, Bin) -> unicode:characters_to_list(Bin); +mode(lefty_list, Bin) -> + L = unicode:characters_to_list(Bin), + to_left(L); +mode({many_lists, N}, Bin) -> + group(unicode:characters_to_list(Bin), N). + +group([], _N) -> + []; +group(L, N) -> + try lists:split(N, L) of + {L1, L2} -> + [L1 | group(L2, N)] + catch + _:_ -> + [L] + end. + +to_left([]) -> + []; +to_left([H|L]) -> + to_left([H], L). + +to_left(V, []) -> + V; +to_left(V, [H|L]) -> + to_left([V,H], L). %% %% Old string lists Test cases starts here. |