diff options
Diffstat (limited to 'lib/stdlib/test')
26 files changed, 776 insertions, 151 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index ae2e3d0e2b..bbe3cefa42 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -88,6 +88,7 @@ MODULES= \ unicode_SUITE \ unicode_util_SUITE \ uri_string_SUITE \ + uri_string_property_test_SUITE \ win32reg_SUITE \ y2k_SUITE \ select_SUITE \ @@ -152,6 +153,6 @@ release_tests_spec: make_emakefile $(INSTALL_DATA) stdlib.spec stdlib_bench.spec $(EMAKEFILE) \ $(ERL_FILES) $(COVERFILE) "$(RELSYSDIR)" chmod -R u+w "$(RELSYSDIR)" - @tar cf - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -) + @tar cf - *_SUITE_data property_test | (cd "$(RELSYSDIR)"; tar xf -) release_docs_spec: diff --git a/lib/stdlib/test/array_SUITE.erl b/lib/stdlib/test/array_SUITE.erl index 956582c4fd..df520ebb54 100644 --- a/lib/stdlib/test/array_SUITE.erl +++ b/lib/stdlib/test/array_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2016. All Rights Reserved. +%% Copyright Ericsson AB 2007-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. diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl index 73219f8fd8..3597d6d94b 100644 --- a/lib/stdlib/test/beam_lib_SUITE.erl +++ b/lib/stdlib/test/beam_lib_SUITE.erl @@ -78,7 +78,7 @@ normal(Conf) when is_list(Conf) -> BeamFile = Simple ++ ".beam", simple_file(Source), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), do_normal(Source, PrivDir, BeamFile, []), @@ -95,7 +95,7 @@ normal(Conf) when is_list(Conf) -> file:delete(BeamFile), file:delete(Source), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), true = (P0 == pps()), ok. @@ -173,7 +173,7 @@ error(Conf) when is_list(Conf) -> WrongFile = Simple ++ "foo.beam", simple_file(Source), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), {ok,_} = compile:file(Source, [{outdir,PrivDir},debug_info]), ACopy = filename:join(PrivDir, "a_copy.beam"), @@ -213,7 +213,7 @@ error(Conf) when is_list(Conf) -> %% we have eliminated them. ok = file:write_file(BeamFile, <<"FOR1",5:32,"BEAMfel">>), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), true = (P0 == pps()), file:delete(Source), file:delete(WrongFile), @@ -273,7 +273,7 @@ cmp(Conf) when is_list(Conf) -> {Source2D1, BeamFile2D1} = make_beam(Dir1, simple2, concat), {SourceD2, BeamFileD2} = make_beam(Dir2, simple, concat), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), %% cmp @@ -300,7 +300,7 @@ cmp(Conf) when is_list(Conf) -> ver(not_a_directory, beam_lib:diff_dirs(foo, bar)), true = (P0 == pps()), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), delete_files([SourceD1, BeamFileD1, Source2D1, BeamFile2D1, SourceD2, BeamFileD2]), @@ -321,7 +321,7 @@ cmp_literals(Conf) when is_list(Conf) -> {SourceD1, BeamFileD1} = make_beam(Dir1, simple, constant), {SourceD2, BeamFileD2} = make_beam(Dir2, simple, constant2), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), %% cmp @@ -334,7 +334,7 @@ cmp_literals(Conf) when is_list(Conf) -> ver(chunks_different, beam_lib:cmp(B1, B2)), true = (P0 == pps()), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), delete_files([SourceD1, BeamFileD1, SourceD2, BeamFileD2]), @@ -351,7 +351,7 @@ strip(Conf) when is_list(Conf) -> {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant), {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), %% strip binary @@ -392,7 +392,7 @@ strip(Conf) when is_list(Conf) -> (catch lines:t(atom)), true = (P0 == pps()), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), delete_files([SourceD1, BeamFileD1, Source2D1, BeamFile2D1, @@ -457,7 +457,7 @@ building(Conf) when is_list(Conf) -> {SourceD1, BeamFileD1} = make_beam(Dir1, building, member), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), %% read all chunks @@ -487,7 +487,7 @@ building(Conf) when is_list(Conf) -> end, ChunkIds), true = (P0 == pps()), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), delete_files([SourceD1, BeamFileD1, BeamFileD2]), file:del_dir(Dir1), @@ -535,7 +535,7 @@ encrypted_abstr_1(Conf) -> %% Avoid getting an extra port when crypto starts erl_ddll. erl_ddll:start(), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), Key = "#a_crypto_key", @@ -549,7 +549,7 @@ encrypted_abstr_1(Conf) -> ok = crypto:stop(), %To get rid of extra ets tables. file:delete(BeamFile), file:delete(Source), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), true = (P0 == pps()), ok. @@ -658,7 +658,7 @@ encrypted_abstr_file_1(Conf) -> %% Avoid getting an extra port when crypto starts erl_ddll. erl_ddll:start(), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), P0 = pps(), Key = "Long And niCe 99Krypto Key", @@ -676,7 +676,7 @@ encrypted_abstr_file_1(Conf) -> file:delete(filename:join(PrivDir, ".erlang.crypt")), file:delete(BeamFile), file:delete(Source), - NoOfTables = length(ets:all()), + NoOfTables = erlang:system_info(ets_count), true = (P0 == pps()), ok. diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl index f01988478c..bd84cdd228 100644 --- a/lib/stdlib/test/c_SUITE.erl +++ b/lib/stdlib/test/c_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2016. All Rights Reserved. +%% Copyright Ericsson AB 1998-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. diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 7d82790b82..fe324391af 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 9123bf2f28..a3e294ffea 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -28,7 +28,8 @@ otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1, otp_11728/1, encoding/1, extends/1, function_macro/1, - test_error/1, test_warning/1, otp_14285/1]). + test_error/1, test_warning/1, otp_14285/1, + test_if/1]). -export([epp_parse_erl_form/2]). @@ -69,7 +70,7 @@ all() -> overload_mac, otp_8388, otp_8470, otp_8562, otp_8665, otp_8911, otp_10302, otp_10820, otp_11728, encoding, extends, function_macro, test_error, test_warning, - otp_14285]. + otp_14285, test_if]. groups() -> [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]}, @@ -799,7 +800,8 @@ otp_8130(Config) when is_list(Config) -> PreDefMacs = macs(Epp), ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE', 'FUNCTION_ARITY','FUNCTION_NAME', - 'LINE','MACHINE','MODULE','MODULE_STRING'] = PreDefMacs, + 'LINE','MACHINE','MODULE','MODULE_STRING', + 'OTP_RELEASE'] = PreDefMacs, {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp), {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp), {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp), @@ -952,27 +954,7 @@ ifdef(Config) -> {define_c5, <<"-\ndefine a.\n">>, - {errors,[{{2,1},epp,{bad,define}}],[]}}, - - {define_c6, - <<"\n-if.\n" - "-endif.\n">>, - {errors,[{{2,2},epp,{'NYI','if'}}],[]}}, - - {define_c7, - <<"-ifndef(a).\n" - "-elif.\n" - "-endif.\n">>, - {errors,[{{2,2},epp,{'NYI',elif}}],[]}}, - - {define_c7, - <<"-ifndef(a).\n" - "-if.\n" - "-elif.\n" - "-endif.\n" - "-endif.\n" - "t() -> a.\n">>, - {errors,[{{2,2},epp,{'NYI','if'}}],[]}} + {errors,[{{2,1},epp,{bad,define}}],[]}} ], [] = compile(Config, Cs), @@ -1117,6 +1099,147 @@ test_warning(Config) -> [] = compile(Config, Cs), ok. +%% OTP-12847: Test the -if and -elif directives and the built-in +%% function defined(Symbol). +test_if(Config) -> + Cs = [{if_1c, + <<"-if.\n" + "-endif.\n" + "-if no_parentheses.\n" + "-endif.\n" + "-if(syntax error.\n" + "-endif.\n" + "-if(true).\n" + "-if(a+3).\n" + "syntax error not triggered here.\n" + "-endif.\n">>, + {errors,[{1,epp,{bad,'if'}}, + {3,epp,{bad,'if'}}, + {5,erl_parse,["syntax error before: ","error"]}, + {11,epp,{illegal,"unterminated",'if'}}], + []}}, + + {if_2c, %Bad guard expressions. + <<"-if(is_list(integer_to_list(42))).\n" %Not guard BIF. + "-endif.\n" + "-if(begin true end).\n" + "-endif.\n">>, + {errors,[{1,epp,{bad,'if'}}, + {3,epp,{bad,'if'}}], + []}}, + + {if_3c, %Invalid use of defined/1. + <<"-if defined(42).\n" + "-endif.\n">>, + {errors,[{1,epp,{bad,'if'}}],[]}}, + + {if_4c, + <<"-elif OTP_RELEASE > 18.\n">>, + {errors,[{1,epp,{illegal,"unbalanced",'elif'}}],[]}}, + + {if_5c, + <<"-ifdef(not_defined_today).\n" + "-else.\n" + "-elif OTP_RELEASE > 18.\n" + "-endif.\n">>, + {errors,[{3,epp,{illegal,"unbalanced",'elif'}}],[]}}, + + {if_6c, + <<"-if(defined(OTP_RELEASE)).\n" + "-else.\n" + "-elif(true).\n" + "-endif.\n">>, + {errors,[{3,epp,elif_after_else}],[]}}, + + {if_7c, + <<"-if(begin true end).\n" %Not a guard expression. + "-endif.\n">>, + {errors,[{1,epp,{bad,'if'}}],[]}} + + ], + [] = compile(Config, Cs), + + Ts = [{if_1, + <<"-if(?OTP_RELEASE > 18).\n" + "t() -> ok.\n" + "-else.\n" + "a bug.\n" + "-endif.\n">>, + ok}, + + {if_2, + <<"-if(false).\n" + "a bug.\n" + "-elif(?OTP_RELEASE > 18).\n" + "t() -> ok.\n" + "-else.\n" + "a bug.\n" + "-endif.\n">>, + ok}, + + {if_3, + <<"-if(true).\n" + "t() -> ok.\n" + "-elif(?OTP_RELEASE > 18).\n" + "a bug.\n" + "-else.\n" + "a bug.\n" + "-endif.\n">>, + ok}, + + {if_4, + <<"-define(a, 1).\n" + "-if(defined(a) andalso defined(OTP_RELEASE)).\n" + "t() -> ok.\n" + "-else.\n" + "a bug.\n" + "-endif.\n">>, + ok}, + + {if_5, + <<"-if(defined(a)).\n" + "a bug.\n" + "-else.\n" + "t() -> ok.\n" + "-endif.\n">>, + ok}, + + {if_6, + <<"-if(defined(not_defined_today)).\n" + " -if(true).\n" + " bug1.\n" + " -elif(true).\n" + " bug2.\n" + " -elif(true).\n" + " bug3.\n" + " -else.\n" + " bug4.\n" + " -endif.\n" + "-else.\n" + "t() -> ok.\n" + "-endif.\n">>, + ok}, + + {if_7, + <<"-if(not_builtin()).\n" + "a bug.\n" + "-else.\n" + "t() -> ok.\n" + "-endif.\n">>, + ok}, + + {if_8, + <<"-if(42).\n" %Not boolean. + "a bug.\n" + "-else.\n" + "t() -> ok.\n" + "-endif.\n">>, + ok} + ], + [] = run(Config, Ts), + + ok. + %% Advanced test on overloading macros. overload_mac(Config) when is_list(Config) -> Cs = [ diff --git a/lib/stdlib/test/error_logger_h_SUITE.erl b/lib/stdlib/test/error_logger_h_SUITE.erl index d533305939..bf9b6d9ad6 100644 --- a/lib/stdlib/test/error_logger_h_SUITE.erl +++ b/lib/stdlib/test/error_logger_h_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2015-2016. All Rights Reserved. +%% Copyright Ericsson AB 2015-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. diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 02211fa8df..7a48d1d55e 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. @@ -87,6 +87,7 @@ -export([t_select_reverse/1]). +-include_lib("stdlib/include/ms_transform.hrl"). % ets:fun2ms -include_lib("common_test/include/ct.hrl"). -define(m(A,B), assert_eq(A,B)). @@ -173,10 +174,12 @@ groups() -> init_per_suite(Config) -> erts_debug:set_internal_state(available_internal_state, true), + erts_debug:set_internal_state(ets_force_trap, true), Config. end_per_suite(_Config) -> stop_spawn_logger(), + erts_debug:set_internal_state(ets_force_trap, false), catch erts_debug:set_internal_state(available_internal_state, false), ok. @@ -812,7 +815,60 @@ t_delete_all_objects_do(Opts) -> 4000 = ets:info(T,size), true = ets:delete_all_objects(T), 0 = ets:info(T,size), - ets:delete(T). + ets:delete(T), + + %% Test delete_all_objects is atomic + T2 = ets:new(t_delete_all_objects, [public | Opts]), + Self = self(), + Inserters = [spawn_link(fun() -> inserter(T2, 100*1000, 1, Self) end) || _ <- [1,2,3,4]], + [receive {Ipid, running} -> ok end || Ipid <- Inserters], + + ets:delete_all_objects(T2), + erlang:yield(), + [Ipid ! stop || Ipid <- Inserters], + Result = [receive {Ipid, stopped, Highest} -> {Ipid,Highest} end || Ipid <- Inserters], + + %% Verify unbroken sequences of objects inserted _after_ ets:delete_all_objects. + Sum = lists:foldl(fun({Ipid, Highest}, AccSum) -> + %% ets:fun2ms(fun({{K,Ipid}}) when K =< Highest -> true end), + AliveMS = [{{{'$1',Ipid}},[{'=<','$1',{const,Highest}}],[true]}], + Alive = ets:select_count(T2, AliveMS), + Lowest = Highest - (Alive-1), + + %% ets:fun2ms(fun({{K,Ipid}}) when K < Lowest -> true end) + DeletedMS = [{{{'$1',Ipid}},[{'<','$1',{const,Lowest}}],[true]}], + 0 = ets:select_count(T2, DeletedMS), + AccSum + Alive + end, + 0, + Result), + ok = case ets:info(T2, size) of + Sum -> ok; + Size -> + io:format("Sum = ~p\nSize = ~p\n", [Sum, Size]), + {Sum,Size} + end, + + ets:delete(T2). + +inserter(_, 0, _, _) -> + ok; +inserter(T, N, Next, Papa) -> + case Next of + 10*1000 -> + Papa ! {self(), running}; + _ -> + ok + end, + + ets:insert(T, {{Next, self()}}), + receive + stop -> + Papa ! {self(), stopped, Next}, + ok + after 0 -> + inserter(T, N-1, Next+1, Papa) + end. %% Test ets:delete_object/2. @@ -6153,20 +6209,23 @@ spawn_logger(Procs) -> ok; (Proc) -> Mon = erlang:monitor(process, Proc), - receive + ok = receive {'DOWN', Mon, _, _, _} -> ok after 0 -> case Kill of true -> exit(Proc, kill); - _ -> - erlang:display({"Waiting for 'DOWN' from", Proc, - process_info(Proc), - pid_status(Proc)}) + _ -> ok end, receive {'DOWN', Mon, _, _, _} -> ok + after 5000 -> + io:format("Waiting for 'DOWN' from ~w, status=~w\n" + "info = ~p\n", [Proc, + pid_status(Proc), + process_info(Proc)]), + timeout end end end, Procs), diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl index 186df41d3f..0addf09461 100644 --- a/lib/stdlib/test/id_transform_SUITE.erl +++ b/lib/stdlib/test/id_transform_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2016. All Rights Reserved. +%% Copyright Ericsson AB 2003-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. diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 9f48fbf5e3..79cee54335 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -31,7 +31,8 @@ otp_10836/1, io_lib_width_too_small/1, io_with_huge_message_queue/1, format_string/1, maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1, - otp_14285/1, limit_term/1, otp_14983/1]). + otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, + otp_15159/1]). -export([pretty/2, trf/3]). @@ -63,7 +64,7 @@ all() -> io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836, io_lib_width_too_small, io_with_huge_message_queue, format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175, - otp_14285, limit_term, otp_14983]. + otp_14285, limit_term, otp_14983, otp_15103, otp_15159]. %% Error cases for output. error_1(Config) when is_list(Config) -> @@ -1808,7 +1809,7 @@ rpc_call_max(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"]), + Cmd = ct:get_progname() ++ " +pcunnnnnicode -run erlang halt", P = open_port({spawn, Cmd}, [stderr_to_stdout, {line, 200}]), ok = receive {P, {data, {eol , "bad range of printable characters" ++ _}}} -> @@ -2615,3 +2616,26 @@ trf(Format, Args, T) -> trf(Format, Args, T, Opts) -> lists:flatten(io_lib:format(Format, Args, [{chars_limit, T}|Opts])). + +otp_15103(_Config) -> + T = lists:duplicate(5, {a,b,c}), + + S1 = io_lib:format("~0p", [T]), + "[{a,b,c},{a,b,c},{a,b,c},{a,b,c},{a,b,c}]" = lists:flatten(S1), + S2 = io_lib:format("~-0p", [T]), + "[{a,b,c},{a,b,c},{a,b,c},{a,b,c},{a,b,c}]" = lists:flatten(S2), + S3 = io_lib:format("~1p", [T]), + "[{a,\n b,\n c},\n {a,\n b,\n c},\n {a,\n b,\n c},\n {a,\n b,\n" + " c},\n {a,\n b,\n c}]" = lists:flatten(S3), + + S4 = io_lib:format("~0P", [T, 5]), + "[{a,b,c},{a,b,...},{a,...},{...}|...]" = lists:flatten(S4), + S5 = io_lib:format("~1P", [T, 5]), + "[{a,\n b,\n c},\n {a,\n b,...},\n {a,...},\n {...}|...]" = + lists:flatten(S5), + ok. + +otp_15159(_Config) -> + "[atom]" = + lists:flatten(io_lib:format("~p", [[atom]], [{chars_limit,5}])), + ok. diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl index a75751b31d..6f3cd8bf1b 100644 --- a/lib/stdlib/test/maps_SUITE.erl +++ b/lib/stdlib/test/maps_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2016. All Rights Reserved. +%% Copyright Ericsson AB 1997-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. @@ -108,6 +108,8 @@ t_without_2(_Config) -> %% error case ?badmap(a,without,[[a,b],a]) = (catch maps:without([a,b],id(a))), ?badmap(a,without,[{a,b},a]) = (catch maps:without({a,b},id(a))), + ?badmap({0,<<>>,97},without,[[],{0,<<>>,97}]) = (catch maps:without([], {0,<<>>,97})), + ?badmap({0,<<>>,97},without,[[false, -20, -8],{0,<<>>,97}]) = (catch maps:without([false, -20, -8], {0, <<>>, 97})), ?badarg(without,[a,#{}]) = (catch maps:without(a,#{})), ok. @@ -120,6 +122,8 @@ t_with_2(_Config) -> %% error case ?badmap(a,with,[[a,b],a]) = (catch maps:with([a,b],id(a))), ?badmap(a,with,[{a,b},a]) = (catch maps:with({a,b},id(a))), + ?badmap({0,<<>>,97},with,[[],{0,<<>>,97}]) = (catch maps:with([], {0,<<>>,97})), + ?badmap({0,<<>>,97},with,[[false, -20, -8],{0,<<>>,97}]) = (catch maps:with([false, -20, -8], {0, <<>>, 97})), ?badarg(with,[a,#{}]) = (catch maps:with(a,#{})), ok. diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 81bf9020b8..127b1317e4 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. @@ -542,13 +542,14 @@ system_terminate(Reason,_Parent,_Deb,_State) -> t_format(_Config) -> - logger:add_handler_filter(logger_std_h,stop_all,{fun(_,_) -> stop end,ok}), + {ok,#{level:=Level}} = logger:get_handler_config(default), + logger:set_handler_config(default,level,none), error_logger:add_report_handler(?MODULE, self()), try t_format() after error_logger:delete_report_handler(?MODULE), - logger:remove_handler_filter(logger_std_h,stop_all) + logger:set_handler_config(default,level,Level) end, ok. @@ -585,11 +586,12 @@ t_format() -> ok. t_format_arbitrary(_Config) -> - logger:add_handler_filter(logger_std_h,stop_all,{fun(_,_) -> stop end,ok}), + {ok,#{level:=Level}} = logger:get_handler_config(default), + logger:set_handler_config(default,level,none), try t_format_arbitrary() after - logger:remove_handler_filter(logger_std_h,stop_all) + logger:set_handler_config(default,level,Level) end, ok. diff --git a/lib/stdlib/test/property_test/uri_string_recompose.erl b/lib/stdlib/test/property_test/uri_string_recompose.erl index e51a671172..39fadf23c2 100644 --- a/lib/stdlib/test/property_test/uri_string_recompose.erl +++ b/lib/stdlib/test/property_test/uri_string_recompose.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2017. All Rights Reserved. +%% Copyright Ericsson AB 2008-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. @@ -65,15 +65,29 @@ -define(QUERY, {query, query_map()}). -define(FRAGMENT, {fragment, fragment_map()}). +%% Non-unicode +-define(USER_NU, {userinfo, non_unicode()}). +-define(HOST_NU, {host, host_map_nu()}). +-define(PATH_ABE_NU, {path, path_abempty_map_nu()}). +-define(PATH_ABS_NU, {path, path_absolute_map_nu()}). +-define(PATH_NOS_NU, {path, path_noscheme_map_nu()}). +-define(PATH_ROO_NU, {path, path_rootless_map_nu()}). +-define(QUERY_NU, {query, query_map_nu()}). +-define(FRAGMENT_NU, {fragment, fragment_map_nu()}). %%%======================================================================== %%% Properties %%%======================================================================== prop_recompose() -> + ?FORALL(Map, map_no_unicode(), + Map =:= uri_string:parse(uri_string:recompose(Map))). + +prop_normalize() -> ?FORALL(Map, map(), - Map =:= uri_string:parse(uri_string:recompose(Map)) - ). + uri_string:normalize(Map, [return_map]) =:= + uri_string:normalize(uri_string:parse(uri_string:recompose(Map)), + [return_map])). %% Stats prop_map_key_length_collect() -> @@ -96,6 +110,9 @@ prop_scheme_collect() -> map() -> ?LET(Gen, comp_proplist(), proplist_to_map(Gen)). +map_no_unicode() -> + ?LET(Gen, comp_proplist_nu(), proplist_to_map(Gen)). + comp_proplist() -> frequency([ {2, [?SCHEME,?PATH_ABS]}, @@ -166,6 +183,76 @@ comp_proplist() -> {2, [?USER,?HOST,?PORT,?PATH_ABE,?QUERY,?FRAGMENT]} ]). +comp_proplist_nu() -> + frequency([ + {2, [?SCHEME,?PATH_ABS_NU]}, + {2, [?SCHEME,?PATH_ROO_NU]}, + {2, [?SCHEME,?PATH_EMP]}, + {2, [?SCHEME,?HOST_NU,?PATH_ABE_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PATH_ABE_NU]}, + {2, [?SCHEME,?HOST_NU,?PORT,?PATH_ABE_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU]}, + + {2, [?PATH_ABS_NU]}, + {2, [?PATH_NOS_NU]}, + {2, [?PATH_EMP]}, + {2, [?HOST_NU,?PATH_ABE_NU]}, + {2, [?USER_NU,?HOST_NU,?PATH_ABE_NU]}, + {2, [?HOST_NU,?PORT,?PATH_ABE_NU]}, + {2, [?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU]}, + + + {2, [?SCHEME,?PATH_ABS_NU,?QUERY_NU]}, + {2, [?SCHEME,?PATH_ROO_NU,?QUERY_NU]}, + {2, [?SCHEME,?PATH_EMP,?QUERY_NU]}, + {2, [?SCHEME,?HOST_NU,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?SCHEME,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU]}, + + {2, [?PATH_ABS_NU,?QUERY_NU]}, + {2, [?PATH_NOS_NU,?QUERY_NU]}, + {2, [?PATH_EMP,?QUERY_NU]}, + {2, [?HOST_NU,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?USER_NU,?HOST_NU,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU]}, + {2, [?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU]}, + + + {2, [?SCHEME,?PATH_ABS_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?PATH_ROO_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?PATH_EMP,?FRAGMENT_NU]}, + {2, [?SCHEME,?HOST_NU,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?HOST_NU,?PORT,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?FRAGMENT_NU]}, + + {2, [?PATH_ABS_NU,?FRAGMENT_NU]}, + {2, [?PATH_NOS_NU,?FRAGMENT_NU]}, + {2, [?PATH_EMP,?FRAGMENT_NU]}, + {2, [?HOST_NU,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?USER_NU,?HOST_NU,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?HOST_NU,?PORT,?PATH_ABE_NU,?FRAGMENT_NU]}, + {2, [?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?FRAGMENT_NU]}, + + + {2, [?SCHEME,?PATH_ABS_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?PATH_ROO_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?PATH_EMP,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?HOST_NU,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?SCHEME,?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + + {2, [?PATH_ABS_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?PATH_NOS_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?PATH_EMP,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?HOST_NU,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?USER_NU,?HOST_NU,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]}, + {2, [?USER_NU,?HOST_NU,?PORT,?PATH_ABE_NU,?QUERY_NU,?FRAGMENT_NU]} + ]). + %%------------------------------------------------------------------------- %% Path @@ -174,6 +261,11 @@ path_abempty_map() -> frequency([{90, path_abe_map()}, {10, path_empty_map()}]). +path_abempty_map_nu() -> + frequency([{90, path_abe_map_nu()}, + {10, path_empty_map()}]). + + path_abe_map() -> ?SIZED(Length, path_abe_map(Length, [])). %% @@ -182,6 +274,14 @@ path_abe_map(0, Segments) -> path_abe_map(N, Segments) -> path_abe_map(N-1, [slash(),segment()|Segments]). +path_abe_map_nu() -> + ?SIZED(Length, path_abe_map_nu(Length, [])). +%% +path_abe_map_nu(0, Segments) -> + ?LET(Gen, Segments, lists:append(Gen)); +path_abe_map_nu(N, Segments) -> + path_abe_map_nu(N-1, [slash(),segment_nu()|Segments]). + path_absolute_map() -> ?SIZED(Length, path_absolute_map(Length, [])). @@ -191,6 +291,14 @@ path_absolute_map(0, Segments) -> path_absolute_map(N, Segments) -> path_absolute_map(N-1, [slash(),segment()|Segments]). +path_absolute_map_nu() -> + ?SIZED(Length, path_absolute_map_nu(Length, [])). +%% +path_absolute_map_nu(0, Segments) -> + ?LET(Gen, [slash(),segment_nz_nu()|Segments], lists:append(Gen)); +path_absolute_map_nu(N, Segments) -> + path_absolute_map_nu(N-1, [slash(),segment_nu()|Segments]). + path_noscheme_map() -> ?SIZED(Length, path_noscheme_map(Length, [])). @@ -200,6 +308,15 @@ path_noscheme_map(0, Segments) -> path_noscheme_map(N, Segments) -> path_noscheme_map(N-1, [slash(),segment()|Segments]). +path_noscheme_map_nu() -> + ?SIZED(Length, path_noscheme_map_nu(Length, [])). +%% +path_noscheme_map_nu(0, Segments) -> + ?LET(Gen, [segment_nz_nc_nu()|Segments], lists:append(Gen)); +path_noscheme_map_nu(N, Segments) -> + path_noscheme_map_nu(N-1, [slash(),segment_nu()|Segments]). + + path_rootless_map() -> ?SIZED(Length, path_rootless_map(Length, [])). %% @@ -208,24 +325,59 @@ path_rootless_map(0, Segments) -> path_rootless_map(N, Segments) -> path_rootless_map(N-1, [slash(),segment()|Segments]). +path_rootless_map_nu() -> + ?SIZED(Length, path_rootless_map_nu(Length, [])). +%% +path_rootless_map_nu(0, Segments) -> + ?LET(Gen, [segment_nz_nu()|Segments], lists:append(Gen)); +path_rootless_map_nu(N, Segments) -> + path_rootless_map_nu(N-1, [slash(),segment_nu()|Segments]). + segment_nz() -> non_empty(segment()). -segment_nz_nc() -> - non_empty(list(frequency([{30, unreserved()}, - {10, sub_delims()}, - {10, unicode_char()}, - {5, oneof([$@])} - ]))). +segment_nz_nu() -> + non_empty(segment_nu()). +segment_nz_nc() -> + ?LET(Gen, + non_empty(list(frequency([{30, unreserved()}, + {10, ptc_encoded_reserved()}, + {10, sub_delims()}, + {10, unicode_char()}, + {5, oneof([$@])} + ]))), + lists:flatten(Gen)). + +segment_nz_nc_nu() -> + ?LET(Gen, + non_empty(list(frequency([{30, unreserved()}, + {10, ptc_encoded_reserved()}, + {10, sub_delims()}, + {5, oneof([$@])} + ]))), + lists:flatten(Gen)). + segment() -> - list(frequency([{30, unreserved()}, - {10, sub_delims()}, - {10, unicode_char()}, - {5, oneof([$:, $@])} - ])). + ?LET(Gen, + list(frequency([{30, unreserved()}, + {10, ptc_encoded_reserved()}, + {10, sub_delims()}, + {10, unicode_char()}, + {5, oneof([$:, $@])} + ])), + lists:flatten(Gen)). + +segment_nu() -> + ?LET(Gen, + list(frequency([{30, unreserved()}, + {10, ptc_encoded_reserved()}, + {10, sub_delims()}, + {5, oneof([$:, $@])} + ])), + lists:flatten(Gen)). slash() -> "/". @@ -235,19 +387,35 @@ path_empty_map() -> %%------------------------------------------------------------------------- -%% Path +%% Host %%------------------------------------------------------------------------- host_map() -> frequency([{30, reg_name()}, {30, ip_address()} ]). +host_map_nu() -> + frequency([{30, reg_name_nu()}, + {30, ip_address()} + ]). reg_name() -> - list(frequency([{30, alpha()}, - {10, sub_delims()}, - {10, unicode_char()} - ])). + ?LET(Gen, + list(frequency([{30, alpha()}, + {10, sub_delims()}, + {10, ptc_encoded_reserved()}, + {10, unicode_char()} + ])), + lists:flatten(Gen)). + +reg_name_nu() -> + ?LET(Gen, + list(frequency([{30, alpha()}, + {10, sub_delims()}, + {10, ptc_encoded_reserved()} + ])), + lists:flatten(Gen)). + ip_address() -> oneof(["127.0.0.1", "::127.0.0.1", @@ -258,10 +426,13 @@ ip_address() -> %% Generating only reg-names host_uri() -> - non_empty(list(frequency([{30, unreserved()}, - {10, sub_delims()}, - {10, pct_encoded()} - ]))). + ?LET(Gen, + non_empty(list(frequency([{30, unreserved()}, + {10, sub_delims()}, + {10, ptc_encoded_reserved()}, + {10, pct_encoded()} + ]))), + lists:flatten(Gen)). %%------------------------------------------------------------------------- %% Port, Query, Fragment @@ -274,6 +445,9 @@ port() -> query_map() -> unicode(). +query_map_nu() -> + non_unicode(). + query_uri() -> [$?| non_empty(list(frequency([{20, pchar()}, @@ -283,6 +457,10 @@ query_uri() -> fragment_map() -> unicode(). +fragment_map_nu() -> + non_unicode(). + + fragment_uri() -> [$?| non_empty(list(frequency([{20, pchar()}, {5, oneof([$/, $?])} % punctuation @@ -311,9 +489,14 @@ scheme(N, L) -> %%------------------------------------------------------------------------- unicode() -> list(frequency([{20, alpha()}, % alpha - {10, digit()}, % digit - {10, unicode_char()} % unicode - ])). + {10, digit()}, % digit + {10, unicode_char()} % unicode + ])). + +non_unicode() -> + list(frequency([{20, alpha()}, % alpha + {10, digit()} % digit + ])). scheme_char() -> frequency([{20, alpha()}, % alpha @@ -327,6 +510,7 @@ sub_delims() -> pchar() -> frequency([{20, unreserved()}, + {5, ptc_encoded_reserved()}, {5, pct_encoded()}, {5, sub_delims()}, {1, oneof([$:, $@])} % punctuation @@ -351,6 +535,22 @@ digit() -> pct_encoded() -> oneof(["%C3%A4", "%C3%A5", "%C3%B6"]). +%%------------------------------------------------------------------------- +%% [RFC 3986, Chapter 2.2. Reserved Characters] +%% +%% reserved = gen-delims / sub-delims +%% +%% gen-delims = ":" / "/" / "?" / "#" / "[" / "]" / "@" +%% 3A 2F 3F 23 5B 5D 40 +%% sub-delims = "!" / "$" / "&" / "'" / "(" / ")" +%% 21 24 26 27 28 29 +%% / "*" / "+" / "," / ";" / "=" +%% 2A 2B 2C 3B 3D +%%------------------------------------------------------------------------- +ptc_encoded_reserved() -> + oneof(["%3A","%2F","%3F","%23","%5B","%5D","%40", + "%21","%24","%26","%27","%28","%29", + "%2A","%2B","%2C","%3B","3D"]). %%%======================================================================== %%% Helpers @@ -359,3 +559,13 @@ proplist_to_map(L) -> lists:foldl(fun({K,V},M) -> M#{K => V}; (_,M) -> M end, #{}, L). + +map_scheme_host_to_lower(Map) -> + Fun = fun (scheme,V) -> + string:to_lower(V); + (host,V) -> + string:to_lower(V); + (_,V) -> + V + end, + maps:map(Fun, Map). diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 8f8a0f6e73..d7354438f9 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2017. All Rights Reserved. +%% Copyright Ericsson AB 2004-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. @@ -7468,7 +7468,7 @@ strip_qlc_call(H) -> strip_qlc_call2(H) -> S = qlc:info(H, {flat, false}), {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), - {ok, [Expr], Bs} = lib:extended_parse_exprs(Tokens), + {ok, [Expr], Bs} = erl_eval:extended_parse_exprs(Tokens), {case Expr of {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} -> {qlc, lists:flatten([erl_pp:expr(LC), "."]), []}; @@ -7489,7 +7489,7 @@ strip_qlc_call2(H) -> join_info_count(H) -> S = qlc:info(H, {flat, false}), {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), - {ok, [Expr], _Bs} = lib:extended_parse_exprs(Tokens), + {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens), #ji{nmerge = Nmerge, nlookup = Nlookup, nkeysort = NKeysort, nnested_loop = Nnested_loop} = ji(Expr, #ji{}), @@ -7533,7 +7533,7 @@ lookup_keys({generate,_,Q}, L) -> lookup_keys(Q, L); lookup_keys({table,Chars}, L) when is_list(Chars) -> {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]), - {ok, [Expr], _Bs} = lib:extended_parse_exprs(Tokens), + {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens), case Expr of {call,_,_,[_fun,AKs]} -> case erl_parse:normalise(AKs) of diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index 7b82647416..c9ef9da990 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2017. All Rights Reserved. +%% Copyright Ericsson AB 2008-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. diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl index 7066d07e19..2c1b388d52 100644 --- a/lib/stdlib/test/sets_SUITE.erl +++ b/lib/stdlib/test/sets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2016. All Rights Reserved. +%% Copyright Ericsson AB 2004-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. diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl index 93d027704b..e4d476ba54 100644 --- a/lib/stdlib/test/sets_test_lib.erl +++ b/lib/stdlib/test/sets_test_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2015. All Rights Reserved. +%% Copyright Ericsson AB 2004-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. diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index ca85314775..22136d687c 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2780,7 +2780,7 @@ otp_10302(Config) when is_list(Config) -> rpc:call(Node,shell, prompt_func, [default]), _ = shell:prompt_func(default), - %% Test lib:format_exception() (cf. OTP-6554) + %% Test erl_error:format_exception() (cf. OTP-6554) Test6 = <<"begin A = <<\"\\xaa\">>, @@ -2967,10 +2967,10 @@ otp_14296(Config) when is_list(Config) -> R = t(S) end(), - %% Test lib:extended_parse_term/1 + %% Test erl_eval:extended_parse_term/1 TF = fun(S) -> {ok, Ts, _} = erl_scan:string(S++".", 1, [text]), - case lib:extended_parse_term(Ts) of + case erl_eval:extended_parse_term(Ts) of {ok, Term} -> Term; {error, _}=Error -> Error end diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index fdff2d24b8..251e09121c 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-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. @@ -409,8 +409,8 @@ 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"), @@ -423,8 +423,8 @@ 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"), @@ -449,8 +449,8 @@ 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"), @@ -810,6 +810,18 @@ 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]], diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl index c3ccacc587..0d3dc67d3b 100644 --- a/lib/stdlib/test/supervisor_1.erl +++ b/lib/stdlib/test/supervisor_1.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index 761df8eb40..ed7dd04171 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl index 439a23d82d..3278eb0eb0 100644 --- a/lib/stdlib/test/sys_SUITE.erl +++ b/lib/stdlib/test/sys_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-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. diff --git a/lib/stdlib/test/unicode_util_SUITE.erl b/lib/stdlib/test/unicode_util_SUITE.erl index 40b1c260a5..962b307b07 100644 --- a/lib/stdlib/test/unicode_util_SUITE.erl +++ b/lib/stdlib/test/unicode_util_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2017. All Rights Reserved. +%% Copyright Ericsson AB 2017-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. diff --git a/lib/stdlib/test/uri_string_SUITE.erl b/lib/stdlib/test/uri_string_SUITE.erl index 92f8bb3292..4fc0d76be8 100644 --- a/lib/stdlib/test/uri_string_SUITE.erl +++ b/lib/stdlib/test/uri_string_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2017. All Rights Reserved. +%% Copyright Ericsson AB 2008-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. @@ -23,6 +23,12 @@ -export([all/0, suite/0,groups/0, normalize/1, normalize_map/1, normalize_return_map/1, normalize_negative/1, + normalize_binary_pct_encoded_userinfo/1, + normalize_binary_pct_encoded_query/1, + normalize_binary_pct_encoded_fragment/1, + normalize_pct_encoded_userinfo/1, + normalize_pct_encoded_query/1, + normalize_pct_encoded_fragment/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, @@ -41,7 +47,8 @@ transcode_basic/1, transcode_options/1, transcode_mixed/1, transcode_negative/1, compose_query/1, compose_query_latin1/1, compose_query_negative/1, dissect_query/1, dissect_query_negative/1, - interop_query_latin1/1, interop_query_utf8/1 + interop_query_latin1/1, interop_query_utf8/1, + regression_parse/1, regression_recompose/1, regression_normalize/1 ]). @@ -71,6 +78,12 @@ all() -> normalize_map, normalize_return_map, normalize_negative, + normalize_binary_pct_encoded_userinfo, + normalize_binary_pct_encoded_query, + normalize_binary_pct_encoded_fragment, + normalize_pct_encoded_userinfo, + normalize_pct_encoded_query, + normalize_pct_encoded_fragment, parse_binary_scheme, parse_binary_userinfo, parse_binary_pct_encoded_userinfo, @@ -120,7 +133,10 @@ all() -> dissect_query, dissect_query_negative, interop_query_latin1, - interop_query_utf8 + interop_query_utf8, + regression_parse, + regression_recompose, + regression_normalize ]. groups() -> @@ -338,20 +354,23 @@ parse_binary_userinfo(_Config) -> uri_string:parse(<<"foo://user:password@localhost">>). parse_binary_pct_encoded_userinfo(_Config) -> - #{scheme := <<"user">>, path := <<"合@気道"/utf8>>} = + #{scheme := <<"user">>, path := <<"%E5%90%88@%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"user:%E5%90%88@%E6%B0%97%E9%81%93">>), - #{path := <<"合気道@"/utf8>>} = uri_string:parse(<<"%E5%90%88%E6%B0%97%E9%81%93@">>), - #{path := <<"/合気道@"/utf8>>} = uri_string:parse(<<"/%E5%90%88%E6%B0%97%E9%81%93@">>), - #{path := <<"合@気道"/utf8>>} = uri_string:parse(<<"%E5%90%88@%E6%B0%97%E9%81%93">>), - #{userinfo := <<"合"/utf8>>, host := <<"気道"/utf8>>} = + #{path := <<"%E5%90%88%E6%B0%97%E9%81%93@">>} = + uri_string:parse(<<"%E5%90%88%E6%B0%97%E9%81%93@">>), + #{path := <<"/%E5%90%88%E6%B0%97%E9%81%93@">>} = + uri_string:parse(<<"/%E5%90%88%E6%B0%97%E9%81%93@">>), + #{path := <<"%E5%90%88@%E6%B0%97%E9%81%93">>} = + uri_string:parse(<<"%E5%90%88@%E6%B0%97%E9%81%93">>), + #{userinfo := <<"%E5%90%88">>, host := <<"%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"//%E5%90%88@%E6%B0%97%E9%81%93">>), - #{userinfo := <<"合:気"/utf8>>, host := <<"道"/utf8>>} = + #{userinfo := <<"%E5%90%88:%E6%B0%97">>, host := <<"%E9%81%93">>} = uri_string:parse(<<"//%E5%90%88:%E6%B0%97@%E9%81%93">>), - #{scheme := <<"foo">>, path := <<"/合気道@"/utf8>>} = + #{scheme := <<"foo">>, path := <<"/%E5%90%88%E6%B0%97%E9%81%93@">>} = uri_string:parse(<<"foo:/%E5%90%88%E6%B0%97%E9%81%93@">>), - #{scheme := <<"foo">>, userinfo := <<"合"/utf8>>, host := <<"気道"/utf8>>} = + #{scheme := <<"foo">>, userinfo := <<"%E5%90%88">>, host := <<"%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"foo://%E5%90%88@%E6%B0%97%E9%81%93">>), - #{scheme := <<"foo">>, userinfo := <<"合:気"/utf8>>, host := <<"道"/utf8>>} = + #{scheme := <<"foo">>, userinfo := <<"%E5%90%88:%E6%B0%97">>, host := <<"%E9%81%93">>} = uri_string:parse(<<"foo://%E5%90%88:%E6%B0%97@%E9%81%93">>), {error,invalid_uri,"@"} = uri_string:parse(<<"//%E5%90%88@%E6%B0%97%E9%81%93@">>), {error,invalid_uri,":"} = uri_string:parse(<<"foo://%E5%90%88@%E6%B0%97%E9%81%93@">>). @@ -369,8 +388,8 @@ parse_binary_host_ipv4(_Config) -> #{host := <<"127.0.0.1">>, query := <<"name=ferret">>} = uri_string:parse(<<"//127.0.0.1?name=ferret">>), #{host := <<"127.0.0.1">>, fragment := <<"nose">>} = uri_string:parse(<<"//127.0.0.1#nose">>), - {error,invalid_uri,"x"} = uri_string:parse(<<"//127.0.0.x">>), - {error,invalid_uri,"1227.0.0.1"} = uri_string:parse(<<"//1227.0.0.1">>). + #{host := <<"127.0.0.x">>,path := <<>>} = uri_string:parse(<<"//127.0.0.x">>), + #{host := <<"1227.0.0.1">>,path := <<>>} = uri_string:parse(<<"//1227.0.0.1">>). parse_binary_host_ipv6(_Config) -> #{host := <<"::127.0.0.1">>} = uri_string:parse(<<"//[::127.0.0.1]">>), @@ -439,9 +458,9 @@ parse_binary_query(_Config) -> parse_binary_pct_encoded_query(_Config) -> #{scheme := <<"foo">>, host := <<"example.com">>, path := <<"/">>, - query := <<"name=合気道"/utf8>>} = + query := <<"name=%E5%90%88%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"foo://example.com/?name=%E5%90%88%E6%B0%97%E9%81%93">>), - #{host := <<"example.com">>, path := <<"/">>, query := <<"name=合気道"/utf8>>} = + #{host := <<"example.com">>, path := <<"/">>, query := <<"name=%E5%90%88%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"//example.com/?name=%E5%90%88%E6%B0%97%E9%81%93">>). parse_binary_fragment(_Config) -> @@ -472,9 +491,11 @@ parse_binary_fragment(_Config) -> uri_string:parse(<<"//example.com/#nose">>). parse_binary_pct_encoded_fragment(_Config) -> - #{scheme := <<"foo">>, host := <<"example.com">>, fragment := <<"合気道"/utf8>>} = + #{scheme := <<"foo">>, host := <<"example.com">>, + fragment := <<"%E5%90%88%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"foo://example.com#%E5%90%88%E6%B0%97%E9%81%93">>), - #{host := <<"example.com">>, path := <<"/">>, fragment := <<"合気道"/utf8>>} = + #{host := <<"example.com">>, path := <<"/">>, + fragment := <<"%E5%90%88%E6%B0%97%E9%81%93">>} = uri_string:parse(<<"//example.com/#%E5%90%88%E6%B0%97%E9%81%93">>). parse_scheme(_Config) -> @@ -506,25 +527,27 @@ parse_userinfo(_Config) -> uri_string:parse("foo://user:password@localhost"). parse_pct_encoded_userinfo(_Config) -> - #{scheme := "user", path := "合@気道"} = + #{scheme := "user", path := "%E5%90%88@%E6%B0%97%E9%81%93"} = uri_string:parse("user:%E5%90%88@%E6%B0%97%E9%81%93"), - #{path := "合気道@"} = uri_string:parse("%E5%90%88%E6%B0%97%E9%81%93@"), - #{path := "/合気道@"} = uri_string:parse("/%E5%90%88%E6%B0%97%E9%81%93@"), - #{path := "合@気道"} = uri_string:parse("%E5%90%88@%E6%B0%97%E9%81%93"), - #{userinfo := "合", host := "気道"} = + #{path := "%E5%90%88%E6%B0%97%E9%81%93@"} = + uri_string:parse("%E5%90%88%E6%B0%97%E9%81%93@"), + #{path := "/%E5%90%88%E6%B0%97%E9%81%93@"} = + uri_string:parse("/%E5%90%88%E6%B0%97%E9%81%93@"), + #{path := "%E5%90%88@%E6%B0%97%E9%81%93"} = + uri_string:parse("%E5%90%88@%E6%B0%97%E9%81%93"), + #{userinfo := "%E5%90%88", host := "%E6%B0%97%E9%81%93"} = uri_string:parse("//%E5%90%88@%E6%B0%97%E9%81%93"), - #{userinfo := "合:気", host := "道"} = + #{userinfo := "%E5%90%88:%E6%B0%97", host := "%E9%81%93"} = uri_string:parse("//%E5%90%88:%E6%B0%97@%E9%81%93"), - #{scheme := "foo", path := "/合気道@"} = + #{scheme := "foo", path := "/%E5%90%88%E6%B0%97%E9%81%93@"} = uri_string:parse("foo:/%E5%90%88%E6%B0%97%E9%81%93@"), - #{scheme := "foo", userinfo := "合", host := "気道"} = + #{scheme := "foo", userinfo := "%E5%90%88", host := "%E6%B0%97%E9%81%93"} = uri_string:parse("foo://%E5%90%88@%E6%B0%97%E9%81%93"), - #{scheme := "foo", userinfo := "合:気", host := "道"} = + #{scheme := "foo", userinfo := "%E5%90%88:%E6%B0%97", host := "%E9%81%93"} = uri_string:parse("foo://%E5%90%88:%E6%B0%97@%E9%81%93"), {error,invalid_uri,"@"} = uri_string:parse("//%E5%90%88@%E6%B0%97%E9%81%93@"), {error,invalid_uri,":"} = uri_string:parse("foo://%E5%90%88@%E6%B0%97%E9%81%93@"). - parse_host(_Config) -> #{host := "hostname"} = uri_string:parse("//hostname"), #{host := "hostname",scheme := "foo"} = uri_string:parse("foo://hostname"), @@ -538,8 +561,8 @@ parse_host_ipv4(_Config) -> #{host := "127.0.0.1", path := "/over/there"} = uri_string:parse("//127.0.0.1/over/there"), #{host := "127.0.0.1", query := "name=ferret"} = uri_string:parse("//127.0.0.1?name=ferret"), #{host := "127.0.0.1", fragment := "nose"} = uri_string:parse("//127.0.0.1#nose"), - {error,invalid_uri,"x"} = uri_string:parse("//127.0.0.x"), - {error,invalid_uri,"1227.0.0.1"} = uri_string:parse("//1227.0.0.1"). + #{host := "127.0.0.x",path := []} = uri_string:parse("//127.0.0.x"), + #{host := "1227.0.0.1",path := []} = uri_string:parse("//1227.0.0.1"). parse_host_ipv6(_Config) -> #{host := "::127.0.0.1"} = uri_string:parse("//[::127.0.0.1]"), @@ -602,9 +625,9 @@ parse_query(_Config) -> parse_pct_encoded_query(_Config) -> #{scheme := "foo", host := "example.com", path := "/", - query := "name=合気道"} = + query := "name=%E5%90%88%E6%B0%97%E9%81%93"} = uri_string:parse("foo://example.com/?name=%E5%90%88%E6%B0%97%E9%81%93"), - #{host := "example.com", path := "/", query := "name=合気道"} = + #{host := "example.com", path := "/", query := "name=%E5%90%88%E6%B0%97%E9%81%93"} = uri_string:parse("//example.com/?name=%E5%90%88%E6%B0%97%E9%81%93"). parse_fragment(_Config) -> @@ -635,9 +658,11 @@ parse_fragment(_Config) -> uri_string:parse("//example.com/#nose"). parse_pct_encoded_fragment(_Config) -> - #{scheme := "foo", host := "example.com", fragment := "合気道"} = + #{scheme := "foo", host := "example.com", + fragment := "%E5%90%88%E6%B0%97%E9%81%93"} = uri_string:parse("foo://example.com#%E5%90%88%E6%B0%97%E9%81%93"), - #{host := "example.com", path := "/", fragment := "合気道"} = + #{host := "example.com", path := "/", + fragment := "%E5%90%88%E6%B0%97%E9%81%93"} = uri_string:parse("//example.com/#%E5%90%88%E6%B0%97%E9%81%93"). parse_list(_Config) -> @@ -711,9 +736,7 @@ parse_negative(_Config) -> {error,invalid_uri,":"} = uri_string:parse("foo://usär@host"), {error,invalid_uri,"ö"} = uri_string:parse("//host/path?foö=bar"), {error,invalid_uri,"ö"} = uri_string:parse("//host/path#foö"), - {error,invalid_uri,"127.256.0.1"} = uri_string:parse("//127.256.0.1"), {error,invalid_uri,":::127.0.0.1"} = uri_string:parse("//[:::127.0.0.1]"), - {error,invalid_utf8,<<0,0,0,246>>} = uri_string:parse("//%00%00%00%F6"), {error,invalid_uri,"A"} = uri_string:parse("//localhost:A8"). @@ -913,7 +936,9 @@ normalize(_Config) -> <<"sftp://localhost">> = uri_string:normalize(<<"sftp://localhost:22">>), <<"tftp://localhost">> = - uri_string:normalize(<<"tftp://localhost:69">>). + uri_string:normalize(<<"tftp://localhost:69">>), + <<"/foo/%2F/bar">> = + uri_string:normalize(<<"/foo/%2f/%62ar">>). normalize_map(_Config) -> "/a/g" = uri_string:normalize(#{path => "/a/b/c/./../../g"}), @@ -942,7 +967,9 @@ normalize_map(_Config) -> host => <<"localhost">>}), <<"tftp://localhost">> = uri_string:normalize(#{scheme => <<"tftp">>,port => 69,path => <<>>, - host => <<"localhost">>}). + host => <<"localhost">>}), + "/foo/%2F/bar" = + uri_string:normalize(#{path => "/foo/%2f/%62ar"}). normalize_return_map(_Config) -> #{scheme := "http",path := "/a/g",host := "localhost-örebro"} = @@ -963,7 +990,82 @@ normalize_negative(_Config) -> {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]). + uri_string:normalize(<<"http://[192.168.0.1]">>, [return_map]), + {error,invalid_utf8,<<0,0,0,246>>} = uri_string:normalize("//%00%00%00%F6"). + +normalize_binary_pct_encoded_userinfo(_Config) -> + #{scheme := <<"user">>, path := <<"合@気道"/utf8>>} = + uri_string:normalize(<<"user:%E5%90%88@%E6%B0%97%E9%81%93">>, [return_map]), + #{path := <<"合気道@"/utf8>>} = + uri_string:normalize(<<"%E5%90%88%E6%B0%97%E9%81%93@">>, [return_map]), + #{path := <<"/合気道@"/utf8>>} = + uri_string:normalize(<<"/%E5%90%88%E6%B0%97%E9%81%93@">>, [return_map]), + #{path := <<"合@気道"/utf8>>} = + uri_string:normalize(<<"%E5%90%88@%E6%B0%97%E9%81%93">>, [return_map]), + #{userinfo := <<"合"/utf8>>, host := <<"気道"/utf8>>} = + uri_string:normalize(<<"//%E5%90%88@%E6%B0%97%E9%81%93">>, [return_map]), + #{userinfo := <<"合:気"/utf8>>, host := <<"道"/utf8>>} = + uri_string:normalize(<<"//%E5%90%88:%E6%B0%97@%E9%81%93">>, [return_map]), + #{scheme := <<"foo">>, path := <<"/合気道@"/utf8>>} = + uri_string:normalize(<<"foo:/%E5%90%88%E6%B0%97%E9%81%93@">>, [return_map]), + #{scheme := <<"foo">>, userinfo := <<"合"/utf8>>, host := <<"気道"/utf8>>} = + uri_string:normalize(<<"foo://%E5%90%88@%E6%B0%97%E9%81%93">>, [return_map]), + #{scheme := <<"foo">>, userinfo := <<"合:気"/utf8>>, host := <<"道"/utf8>>} = + uri_string:normalize(<<"foo://%E5%90%88:%E6%B0%97@%E9%81%93">>, [return_map]), + {error,invalid_uri,"@"} = + uri_string:normalize(<<"//%E5%90%88@%E6%B0%97%E9%81%93@">>, [return_map]), + {error,invalid_uri,":"} = + uri_string:normalize(<<"foo://%E5%90%88@%E6%B0%97%E9%81%93@">>, [return_map]). + +normalize_binary_pct_encoded_query(_Config) -> + #{scheme := <<"foo">>, host := <<"example.com">>, path := <<"/">>, + query := <<"name=合気道"/utf8>>} = + uri_string:normalize(<<"foo://example.com/?name=%E5%90%88%E6%B0%97%E9%81%93">>, [return_map]), + #{host := <<"example.com">>, path := <<"/">>, query := <<"name=合気道"/utf8>>} = + uri_string:normalize(<<"//example.com/?name=%E5%90%88%E6%B0%97%E9%81%93">>, [return_map]). + +normalize_binary_pct_encoded_fragment(_Config) -> + #{scheme := <<"foo">>, host := <<"example.com">>, fragment := <<"合気道"/utf8>>} = + uri_string:normalize(<<"foo://example.com#%E5%90%88%E6%B0%97%E9%81%93">>, [return_map]), + #{host := <<"example.com">>, path := <<"/">>, fragment := <<"合気道"/utf8>>} = + uri_string:normalize(<<"//example.com/#%E5%90%88%E6%B0%97%E9%81%93">>, [return_map]). + +normalize_pct_encoded_userinfo(_Config) -> + #{scheme := "user", path := "合@気道"} = + uri_string:normalize("user:%E5%90%88@%E6%B0%97%E9%81%93", [return_map]), + #{path := "合気道@"} = + uri_string:normalize("%E5%90%88%E6%B0%97%E9%81%93@", [return_map]), + #{path := "/合気道@"} = + uri_string:normalize("/%E5%90%88%E6%B0%97%E9%81%93@", [return_map]), + #{path := "合@気道"} = + uri_string:normalize("%E5%90%88@%E6%B0%97%E9%81%93", [return_map]), + #{userinfo := "合", host := "気道"} = + uri_string:normalize("//%E5%90%88@%E6%B0%97%E9%81%93", [return_map]), + #{userinfo := "合:気", host := "道"} = + uri_string:normalize("//%E5%90%88:%E6%B0%97@%E9%81%93", [return_map]), + #{scheme := "foo", path := "/合気道@"} = + uri_string:normalize("foo:/%E5%90%88%E6%B0%97%E9%81%93@", [return_map]), + #{scheme := "foo", userinfo := "合", host := "気道"} = + uri_string:normalize("foo://%E5%90%88@%E6%B0%97%E9%81%93", [return_map]), + #{scheme := "foo", userinfo := "合:気", host := "道"} = + uri_string:normalize("foo://%E5%90%88:%E6%B0%97@%E9%81%93", [return_map]), + {error,invalid_uri,"@"} = + uri_string:normalize("//%E5%90%88@%E6%B0%97%E9%81%93@", [return_map]), + {error,invalid_uri,":"} = + uri_string:normalize("foo://%E5%90%88@%E6%B0%97%E9%81%93@", [return_map]). + +normalize_pct_encoded_query(_Config) -> + #{scheme := "foo", host := "example.com", path := "/", + query := "name=合気道"} = + uri_string:normalize("foo://example.com/?name=%E5%90%88%E6%B0%97%E9%81%93", [return_map]), + #{host := "example.com", path := "/", query := "name=合気道"} = + uri_string:normalize("//example.com/?name=%E5%90%88%E6%B0%97%E9%81%93", [return_map]). + +normalize_pct_encoded_fragment(_Config) -> + #{scheme := "foo", host := "example.com", fragment := "合気道"} = + uri_string:normalize("foo://example.com#%E5%90%88%E6%B0%97%E9%81%93", [return_map]), + #{host := "example.com", path := "/", fragment := "合気道"} = + uri_string:normalize("//example.com/#%E5%90%88%E6%B0%97%E9%81%93", [return_map]). interop_query_utf8(_Config) -> Q = uri_string:compose_query([{"foo bar","1"}, {"合", "2"}]), @@ -977,3 +1079,86 @@ interop_query_latin1(_Config) -> Uri1 = uri_string:transcode(Uri, [{in_encoding, latin1}]), #{query := Q1} = uri_string:parse(Uri1), [{"foo bar","1"}, {"合", "2"}] = uri_string:dissect_query(Q1). + +regression_parse(_Config) -> + #{host := "Bar",path := [],scheme := "FOo"} = + uri_string:parse("FOo://Bar"), + #{host := "bar",path := [],scheme := "foo"} = + uri_string:parse("foo://bar"), + #{host := "A%2f",path := "/%62ar",scheme := "foo"} = + uri_string:parse("foo://A%2f/%62ar"), + #{host := "a%2F",path := "/bar",scheme := "foo"} = + uri_string:parse("foo://a%2F/bar"), + #{host := "%C3%B6",path := [],scheme := "FOo"} = + uri_string:parse("FOo://%C3%B6"). + +regression_recompose(_Config) -> + "FOo://Bar" = + uri_string:recompose(#{host => "Bar",path => [],scheme => "FOo"}), + "foo://bar" = + uri_string:recompose(#{host => "bar",path => [],scheme => "foo"}), + "foo://A%2f/%62ar" = + uri_string:recompose(#{host => "A%2f",path => "/%62ar",scheme => "foo"}), + "foo://a%2F/bar" = + uri_string:recompose(#{host => "a%2F",path => "/bar",scheme => "foo"}), + "FOo://%C3%B6" = + uri_string:recompose(#{host => "%C3%B6",path => [],scheme => "FOo"}), + "FOo://%C3%B6" = + uri_string:recompose(#{host => "ö",path => [],scheme => "FOo"}). + +regression_normalize(_Config) -> + "foo://bar" = + uri_string:normalize("FOo://Bar"), + #{host := "bar",path := [],scheme := "foo"} = + uri_string:normalize("FOo://Bar", [return_map]), + + "foo://bar" = + uri_string:normalize("foo://bar"), + #{host := "bar",path := [],scheme := "foo"} = + uri_string:normalize("foo://bar", [return_map]), + + "foo://a%2F/bar" = + uri_string:normalize("foo://A%2f/%62ar"), + #{host := "a%2F",path := "/bar",scheme := "foo"} = + uri_string:normalize("foo://A%2f/%62ar", [return_map]), + + "foo://a%2F/bar" = + uri_string:normalize("foo://a%2F/bar"), + #{host := "a%2F",path := "/bar",scheme := "foo"} = + uri_string:normalize("foo://a%2F/bar", [return_map]), + + "foo://%C3%B6" = + uri_string:normalize("FOo://%C3%B6"), + #{host := "ö",path := [],scheme := "foo"} = + uri_string:normalize("FOo://%C3%B6", [return_map]), + + + "foo://bar" = + uri_string:normalize(#{host => "Bar",path => [],scheme => "FOo"}), + #{host := "bar",path := [],scheme := "foo"} = + uri_string:normalize(#{host => "Bar",path => [],scheme => "FOo"}, [return_map]), + + "foo://bar" = + uri_string:normalize(#{host => "bar",path => [],scheme => "foo"}), + #{host := "bar",path := [],scheme := "foo"} = + uri_string:normalize(#{host => "bar",path => [],scheme => "foo"}, [return_map]), + + "foo://a%2F/bar" = + uri_string:normalize(#{host => "A%2f",path => "/%62ar",scheme => "foo"}), + #{host := "a%2F",path := "/bar",scheme := "foo"} = + uri_string:normalize(#{host => "A%2f",path => "/%62ar",scheme => "foo"}, [return_map]), + + "foo://a%2F/bar" = + uri_string:normalize(#{host => "a%2F",path => "/bar",scheme => "foo"}), + #{host := "a%2F",path := "/bar",scheme := "foo"} = + uri_string:normalize(#{host => "a%2F",path => "/bar",scheme => "foo"}, [return_map]), + + "foo://%C3%B6" = + uri_string:normalize(#{host => "%C3%B6",path => [],scheme => "FOo"}), + #{host := "ö",path := [],scheme := "foo"} = + uri_string:normalize(#{host => "%C3%B6",path => [],scheme => "FOo"}, [return_map]), + + "foo://%C3%B6" = + uri_string:normalize(#{host => "ö",path => [],scheme => "FOo"}), + #{host := "ö",path := [],scheme := "foo"} = + uri_string:normalize(#{host => "ö",path => [],scheme => "FOo"}, [return_map]). diff --git a/lib/stdlib/test/uri_string_property_test_SUITE.erl b/lib/stdlib/test/uri_string_property_test_SUITE.erl index ae2c61c7aa..f1d27924db 100644 --- a/lib/stdlib/test/uri_string_property_test_SUITE.erl +++ b/lib/stdlib/test/uri_string_property_test_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2017. All Rights Reserved. +%% Copyright Ericsson AB 2008-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. @@ -22,7 +22,7 @@ -include_lib("common_test/include/ct.hrl"). -compile(export_all). -all() -> [recompose]. +all() -> [recompose, normalize]. init_per_suite(Config) -> ct_property_test:init_per_suite(Config). @@ -37,3 +37,8 @@ recompose(Config) -> ct_property_test:quickcheck( uri_string_recompose:prop_recompose(), Config). + +normalize(Config) -> + ct_property_test:quickcheck( + uri_string_recompose:prop_normalize(), + Config). diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index e5ba629c55..081bffa7cb 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2017. All Rights Reserved. +%% Copyright Ericsson AB 2006-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. |