diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/beam_lib_SUITE.erl | 40 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 24 | ||||
-rw-r--r-- | lib/stdlib/test/rand_SUITE.erl | 106 |
3 files changed, 129 insertions, 41 deletions
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl index 1baf7d0a94..93d51d17b3 100644 --- a/lib/stdlib/test/beam_lib_SUITE.erl +++ b/lib/stdlib/test/beam_lib_SUITE.erl @@ -85,6 +85,8 @@ normal(Conf) when is_list(Conf) -> do_normal(Source, PrivDir, BeamFile, [no_utf8_atoms]), {ok,_} = compile:file(Source, [{outdir,PrivDir}, no_debug_info]), + {ok, {simple, [{debug_info, {debug_info_v1, erl_abstract_code, {none, _}}}]}} = + beam_lib:chunks(BeamFile, [debug_info]), {ok, {simple, [{abstract_code, no_abstract_code}]}} = beam_lib:chunks(BeamFile, [abstract_code]), @@ -130,8 +132,10 @@ do_normal(BeamFile, Opts) -> {ok, {simple, [{labeled_locals, _LLocals}]}} = beam_lib:chunks(BeamFile, [labeled_locals]), {ok, {simple, [_Vsn]}} = beam_lib:version(BeamFile), - {ok, {simple, [{abstract_code, _}]}} = + {ok, {simple, [{abstract_code, {_, _}}]}} = beam_lib:chunks(BeamFile, [abstract_code]), + {ok, {simple, [{debug_info, {debug_info_v1, erl_abstract_code, _}}]}} = + beam_lib:chunks(BeamFile, [debug_info]), %% Test reading optional chunks. All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT", "AtU8"], @@ -197,11 +201,11 @@ error(Conf) when is_list(Conf) -> LastChunk = last_chunk(Binary), verify(chunk_too_big, beam_lib:chunks(Binary1, [LastChunk])), Chunks = chunk_info(Binary), - {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks), - {Binary2, _} = split_binary(Binary, AbstractStart), - verify(chunk_too_big, beam_lib:chunks(Binary2, ["Abst"])), - {Binary3, _} = split_binary(Binary, AbstractStart-4), - verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Abst"])), + {value, {_, DebugInfoStart, _}} = lists:keysearch("Dbgi", 1, Chunks), + {Binary2, _} = split_binary(Binary, DebugInfoStart), + verify(chunk_too_big, beam_lib:chunks(Binary2, ["Dbgi"])), + {Binary3, _} = split_binary(Binary, DebugInfoStart-4), + verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Dbgi"])), %% Instead of the 5:32 field below, there used to be control characters %% (including zero bytes) directly in the string. Because inferior programs @@ -228,7 +232,7 @@ do_error(BeamFile, ACopy) -> Chunks = chunk_info(BeamFile), {value, {_, AtomStart, _}} = lists:keysearch("AtU8", 1, Chunks), {value, {_, ImportStart, _}} = lists:keysearch("ImpT", 1, Chunks), - {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks), + {value, {_, DebugInfoStart, _}} = lists:keysearch("Dbgi", 1, Chunks), {value, {_, AttributesStart, _}} = lists:keysearch("Attr", 1, Chunks), {value, {_, CompileInfoStart, _}} = @@ -238,8 +242,8 @@ do_error(BeamFile, ACopy) -> verify(invalid_chunk, beam_lib:chunks(BF2, [imports])), BF3 = set_byte(ACopy, BeamFile, AtomStart-6, 17), verify(missing_chunk, beam_lib:chunks(BF3, [imports])), - BF4 = set_byte(ACopy, BeamFile, AbstractStart+10, 17), - verify(invalid_chunk, beam_lib:chunks(BF4, [abstract_code])), + BF4 = set_byte(ACopy, BeamFile, DebugInfoStart+10, 17), + verify(invalid_chunk, beam_lib:chunks(BF4, [debug_info])), BF5 = set_byte(ACopy, BeamFile, AttributesStart+8, 17), verify(invalid_chunk, beam_lib:chunks(BF5, [attributes])), @@ -550,11 +554,11 @@ encrypted_abstr_1(Conf) -> ok. do_encrypted_abstr(Beam, Key) -> - verify(key_missing_or_invalid, beam_lib:chunks(Beam, [abstract_code])), + verify(key_missing_or_invalid, beam_lib:chunks(Beam, [debug_info])), - %% The raw chunk "Abst" can still be read even without a key. - {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]), - <<0:8,8:8,"des3_cbc",_/binary>> = Abst, + %% The raw chunk "Dbgi" can still be read even without a key. + {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]), + <<0:8,8:8,"des3_cbc",_/binary>> = Dbgi, %% Try som invalid funs. bad_fun(badfun, fun() -> ok end), @@ -585,7 +589,7 @@ do_encrypted_abstr(Beam, Key) -> {ok,_} = beam_lib:clear_crypto_key_fun(), ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)), verify_abstract(Beam), - {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]), + {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]), %% Installing a new key fun is not possible without clearing the old. verify(exists, beam_lib:crypto_key_fun(ets_crypto_fun(Key))), @@ -594,7 +598,7 @@ do_encrypted_abstr(Beam, Key) -> {ok,_} = beam_lib:clear_crypto_key_fun(), ok = beam_lib:crypto_key_fun(ets_crypto_fun(Key)), verify_abstract(Beam), - {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]), + {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]), {ok,cleared} = beam_lib:clear_crypto_key_fun(), @@ -617,10 +621,10 @@ bad_fun(F) -> bad_fun(S, F) -> verify(S, beam_lib:crypto_key_fun(F)). - verify_abstract(Beam) -> - {ok,{simple,[Chunk]}} = beam_lib:chunks(Beam, [abstract_code]), - {abstract_code,{raw_abstract_v1,_}} = Chunk. + {ok,{simple,[Abst, Dbgi]}} = beam_lib:chunks(Beam, [abstract_code, debug_info]), + {abstract_code,{raw_abstract_v1,_}} = Abst, + {debug_info,{debug_info_v1,erl_abstract_code,_}} = Dbgi. simple_crypto_fun(Key) -> fun(init) -> ok; diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index b2754e47ba..ef3f0be5d7 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -2348,4 +2348,28 @@ otp_14285(_Config) -> L1 = [S || C <- Chars, S <- io_lib:write_atom(list_to_atom([C])), not is_latin1(S)], L1 = lists:seq(256, 512), + + latin1_fmt("~w", ['кирилли́ческий атом']), + latin1_fmt("~w", ['\x{10FFFF}']), + "'кирилли́ческий атом'" = fmt("~tw", ['кирилли́ческий атом']), + [$',16#10FFFF,$'] = fmt("~tw", ['\x{10FFFF}']), + + latin1_fmt("~W", ['кирилли́ческий атом', 13]), + latin1_fmt("~W", ['\x{10FFFF}', 13]), + "'кирилли́ческий атом'" = fmt("~tW", ['кирилли́ческий атом', 13]), + [$',16#10FFFF,$'] = fmt("~tW", ['\x{10FFFF}', 13]), + + {ok, [an_atom],[]} = io_lib:fread("~a", "an_atom"), + {ok, [an_atom],[]} = io_lib:fread("~ta", "an_atom"), + Str = "\"ab" ++ [1089] ++ "cd\"", + {ok, ["\"ab"], [1089]++"cd\""} = io_lib:fread("~s", Str), + {ok, ['\"ab'], [1089]++"cd\""} = io_lib:fread("~a", Str), + {ok,[Str], []} = io_lib:fread("~ts", Str), + {ok,[Atom],[]} = io_lib:fread("~ta", Str), + Str = atom_to_list(Atom), + ok. + +latin1_fmt(Fmt, Args) -> + L = fmt(Fmt, Args), + true = lists:all(fun is_latin1/1, L). diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index 36bc283aec..2ccd89a59f 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -324,8 +324,9 @@ basic_stats_normal(Config) when is_list(Config) -> ct:timetrap({minutes, 6 * length(IntendedMeanVariancePairs)}), %% valgrind needs a lot of time lists:foreach( fun ({IntendedMean, IntendedVariance}) -> - io:format("Testing normal(~.2f, ~.2f)~n", - [float(IntendedMean), float(IntendedVariance)]), + ct:pal( + "Testing normal(~.2f, ~.2f)~n", + [float(IntendedMean), float(IntendedVariance)]), [basic_normal_1(?LOOP, IntendedMean, IntendedVariance, rand:seed_s(Alg), 0, 0) || Alg <- algs()] @@ -485,12 +486,12 @@ do_measure(_Config) -> {int, rand:uniform_s(Range, State)} end) || Algo <- Algos], %% - ct:pal("~nRNG uniform integer 2^(N-1) performance~n",[]), - RangeTwoPowFun = fun (State) -> quart_range(State) bsl 1 end, + ct:pal("~nRNG uniform integer half range performance~n",[]), + HalfRangeFun = fun (State) -> half_range(State) end, TMark2 = measure_1( random, - RangeTwoPowFun, + HalfRangeFun, undefined, fun (Range, State) -> {int, random:uniform_s(Range, State)} @@ -498,18 +499,18 @@ do_measure(_Config) -> _ = [measure_1( Algo, - RangeTwoPowFun, + HalfRangeFun, TMark2, fun (Range, State) -> {int, rand:uniform_s(Range, State)} end) || Algo <- Algos], %% - ct:pal("~nRNG uniform integer 3*2^(N-2)+1 performance~n",[]), - RangeLargeFun = fun (State) -> 3 * quart_range(State) + 1 end, + ct:pal("~nRNG uniform integer half range + 1 performance~n",[]), + HalfRangePlus1Fun = fun (State) -> half_range(State) + 1 end, TMark3 = measure_1( random, - RangeLargeFun, + HalfRangePlus1Fun, undefined, fun (Range, State) -> {int, random:uniform_s(Range, State)} @@ -517,17 +518,18 @@ do_measure(_Config) -> _ = [measure_1( Algo, - RangeLargeFun, + HalfRangePlus1Fun, TMark3, fun (Range, State) -> {int, rand:uniform_s(Range, State)} end) || Algo <- Algos], %% - ct:pal("~nRNG uniform integer 2^128 performance~n",[]), + ct:pal("~nRNG uniform integer full range - 1 performance~n",[]), + FullRangeMinus1Fun = fun (State) -> (half_range(State) bsl 1) - 1 end, TMark4 = measure_1( random, - fun (_) -> 1 bsl 128 end, + FullRangeMinus1Fun, undefined, fun (Range, State) -> {int, random:uniform_s(Range, State)} @@ -535,17 +537,18 @@ do_measure(_Config) -> _ = [measure_1( Algo, - fun (_) -> 1 bsl 128 end, + FullRangeMinus1Fun, TMark4, fun (Range, State) -> {int, rand:uniform_s(Range, State)} end) || Algo <- Algos], %% - ct:pal("~nRNG uniform integer 2^128 + 1 performance~n",[]), + ct:pal("~nRNG uniform integer full range performance~n",[]), + FullRangeFun = fun (State) -> half_range(State) bsl 1 end, TMark5 = measure_1( random, - fun (_) -> (1 bsl 128) + 1 end, + FullRangeFun, undefined, fun (Range, State) -> {int, random:uniform_s(Range, State)} @@ -553,16 +556,73 @@ do_measure(_Config) -> _ = [measure_1( Algo, - fun (_) -> (1 bsl 128) + 1 end, + FullRangeFun, TMark5, fun (Range, State) -> {int, rand:uniform_s(Range, State)} end) || Algo <- Algos], %% - ct:pal("~nRNG uniform float performance~n",[]), + ct:pal("~nRNG uniform integer full range + 1 performance~n",[]), + FullRangePlus1Fun = fun (State) -> (half_range(State) bsl 1) + 1 end, TMark6 = measure_1( random, + FullRangePlus1Fun, + undefined, + fun (Range, State) -> + {int, random:uniform_s(Range, State)} + end), + _ = + [measure_1( + Algo, + FullRangePlus1Fun, + TMark6, + fun (Range, State) -> + {int, rand:uniform_s(Range, State)} + end) || Algo <- Algos], + %% + ct:pal("~nRNG uniform integer double range performance~n",[]), + DoubleRangeFun = fun (State) -> half_range(State) bsl 2 end, + TMark7 = + measure_1( + random, + DoubleRangeFun, + undefined, + fun (Range, State) -> + {int, random:uniform_s(Range, State)} + end), + _ = + [measure_1( + Algo, + DoubleRangeFun, + TMark7, + fun (Range, State) -> + {int, rand:uniform_s(Range, State)} + end) || Algo <- Algos], + %% + ct:pal("~nRNG uniform integer double range + 1 performance~n",[]), + DoubleRangePlus1Fun = fun (State) -> (half_range(State) bsl 2) + 1 end, + TMark8 = + measure_1( + random, + DoubleRangePlus1Fun, + undefined, + fun (Range, State) -> + {int, random:uniform_s(Range, State)} + end), + _ = + [measure_1( + Algo, + DoubleRangePlus1Fun, + TMark8, + fun (Range, State) -> + {int, rand:uniform_s(Range, State)} + end) || Algo <- Algos], + %% + ct:pal("~nRNG uniform float performance~n",[]), + TMark9 = + measure_1( + random, fun (_) -> 0 end, undefined, fun (_, State) -> @@ -572,7 +632,7 @@ do_measure(_Config) -> [measure_1( Algo, fun (_) -> 0 end, - TMark6, + TMark9, fun (_, State) -> {uniform, rand:uniform_s(State)} end) || Algo <- Algos], @@ -582,7 +642,7 @@ do_measure(_Config) -> _ = [measure_1( Algo, fun (_) -> 0 end, - TMark6, + TMark9, fun (_, State) -> {normal, rand:normal_s(State)} end) || Algo <- Algos], @@ -1043,7 +1103,7 @@ range({#{max:=Max}, _}) -> Max; %% Old incorrect range range({_, _, _}) -> 51. % random -quart_range({#{bits:=Bits}, _}) -> 1 bsl (Bits - 2); -quart_range({#{max:=Max}, _}) -> (Max bsr 2) + 1; -quart_range({#{}, _}) -> 1 bsl 62; % crypto -quart_range({_, _, _}) -> 1 bsl 49. % random +half_range({#{bits:=Bits}, _}) -> 1 bsl (Bits - 1); +half_range({#{max:=Max}, _}) -> (Max bsr 1) + 1; +half_range({#{}, _}) -> 1 bsl 63; % crypto +half_range({_, _, _}) -> 1 bsl 50. % random |