diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 3 | ||||
-rw-r--r-- | lib/stdlib/test/dets_SUITE.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/test/erl_eval_SUITE.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 27 | ||||
-rw-r--r-- | lib/stdlib/test/filelib_SUITE.erl | 144 | ||||
-rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 39 | ||||
-rw-r--r-- | lib/stdlib/test/gen_server_SUITE.erl | 41 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/test/maps_SUITE.erl | 69 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_SUITE.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 66 |
12 files changed, 401 insertions, 28 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index 39f6ce423a..a271229c59 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -85,7 +85,8 @@ MODULES= \ zip_SUITE \ random_unicode_list \ random_iolist \ - error_logger_forwarder + error_logger_forwarder \ + maps_SUITE ERL_FILES= $(MODULES:%=%.erl) diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 6be37cbecf..119b4dc7cb 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -2032,6 +2032,12 @@ match(Config, Version) -> CrashPos = if Version =:= 8 -> 5; Version =:= 9 -> 1 end, crash(Fname, ObjPos2+CrashPos), {ok, _} = dets:open_file(T, Args), + case dets:insert_new(T, Obj) of % OTP-12024 + ok -> + bad_object(dets:sync(T), Fname); + Else3 -> + bad_object(Else3, Fname) + end, io:format("Expect corrupt table:~n"), case ins(T, N) of ok -> diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index b91d14b5b8..b55324161b 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -1451,6 +1451,13 @@ eep43(Config) when is_list(Config) -> " {Map#{a := B},Map#{a => c},Map#{d => e}} " "end.", {#{a => b},#{a => c},#{a => b,d => e}}), + check(fun () -> + lists:map(fun (X) -> X#{price := 0} end, + [#{hello => 0, price => nil}]) + end, + "lists:map(fun (X) -> X#{price := 0} end, + [#{hello => 0, price => nil}]).", + [#{hello => 0, price => 0}]), error_check("[camembert]#{}.", {badarg,[camembert]}), error_check("#{} = 1.", {badmatch,1}), ok. diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index d9512c0ef4..ea61b2082b 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -52,7 +52,7 @@ guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1, otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1, otp_5917/1, otp_6585/1, otp_6885/1, otp_10436/1, otp_11254/1, - otp_11772/1, otp_11771/1, + otp_11772/1, otp_11771/1, otp_11872/1, export_all/1, bif_clash/1, behaviour_basic/1, behaviour_multiple/1, @@ -88,7 +88,7 @@ all() -> otp_4886, otp_4988, otp_5091, otp_5276, otp_5338, otp_5362, otp_5371, otp_7227, otp_5494, otp_5644, otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, otp_11254, - otp_11772, otp_11771, export_all, + otp_11772, otp_11771, otp_11872, export_all, bif_clash, behaviour_basic, behaviour_multiple, otp_7550, otp_8051, format_warn, {group, on_load}, too_many_arguments, basic_errors, bin_syntax_errors, predef, @@ -2630,6 +2630,29 @@ otp_11771(Config) when is_list(Config) -> []} = run_test2(Config, Ts, []), ok. +otp_11872(doc) -> + "OTP-11872. The type map() undefined when exported."; +otp_11872(suite) -> []; +otp_11872(Config) when is_list(Config) -> + Ts = <<" + -module(map). + + -compile(export_all). + + -export_type([map/0, product/0]). + + -opaque map() :: dict(). + + -spec t() -> map(). + + t() -> + 1. + ">>, + {error,[{6,erl_lint,{undefined_type,{product,0}}}], + [{8,erl_lint,{new_var_arity_type,map}}]} = + run_test2(Config, Ts, []), + ok. + export_all(doc) -> "OTP-7392. Warning for export_all."; export_all(Config) when is_list(Config) -> diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 4a67d68428..040ae1effc 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2005-2013. All Rights Reserved. +%% Copyright Ericsson AB 2005-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -23,7 +23,8 @@ init_per_group/2,end_per_group/2, init_per_testcase/2,end_per_testcase/2, wildcard_one/1,wildcard_two/1,wildcard_errors/1, - fold_files/1,otp_5960/1,ensure_dir_eexist/1]). + fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1, + wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1]). -import(lists, [foreach/2]). @@ -43,7 +44,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [wildcard_one, wildcard_two, wildcard_errors, - fold_files, otp_5960, ensure_dir_eexist]. + fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink, + wildcard_symlink, is_file_symlink, file_props_symlink]. groups() -> []. @@ -366,3 +368,139 @@ ensure_dir_eexist(Config) when is_list(Config) -> ?line {error, eexist} = filelib:ensure_dir(NeedFile), ?line {error, eexist} = filelib:ensure_dir(NeedFileB), ok. + +ensure_dir_symlink(Config) when is_list(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, "ensure_dir_symlink"), + Name = filename:join(Dir, "same_name_as_file_and_dir"), + ok = filelib:ensure_dir(Name), + ok = file:write_file(Name, <<"some string\n">>), + %% With a symlink to the directory. + Symlink = filename:join(PrivDir, "ensure_dir_symlink_link"), + case file:make_symlink(Dir, Symlink) of + {error,enotsup} -> + {skip,"Symlinks not supported on this platform"}; + {error,eperm} -> + {win32,_} = os:type(), + {skip,"Windows user not privileged to create symlinks"}; + ok -> + SymlinkedName = filename:join(Symlink, "same_name_as_file_and_dir"), + ok = filelib:ensure_dir(SymlinkedName) + end. + +wildcard_symlink(Config) when is_list(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_wildcard_symlink"), + SubDir = filename:join(Dir, "sub"), + AFile = filename:join(SubDir, "a_file"), + Alias = filename:join(Dir, "symlink"), + ok = file:make_dir(Dir), + ok = file:make_dir(SubDir), + ok = file:write_file(AFile, "not that big\n"), + case file:make_symlink(AFile, Alias) of + {error, enotsup} -> + {skip, "Links not supported on this platform"}; + {error, eperm} -> + {win32,_} = os:type(), + {skip, "Windows user not privileged to create symlinks"}; + ok -> + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + erl_prim_loader)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + erl_prim_loader)), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + prim_file)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + prim_file)), + ok = file:delete(AFile), + %% The symlink should still be visible even when its target + %% has been deleted. + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + erl_prim_loader)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + erl_prim_loader)), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + prim_file)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + prim_file)), + ok + end. + +basenames(Dir, Files) -> + [begin + Dir = filename:dirname(F), + filename:basename(F) + end || F <- Files]. + +is_file_symlink(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_is_file_symlink"), + SubDir = filename:join(Dir, "sub"), + AFile = filename:join(SubDir, "a_file"), + DirAlias = filename:join(Dir, "dir_symlink"), + FileAlias = filename:join(Dir, "file_symlink"), + ok = file:make_dir(Dir), + ok = file:make_dir(SubDir), + ok = file:write_file(AFile, "not that big\n"), + case file:make_symlink(SubDir, DirAlias) of + {error, enotsup} -> + {skip, "Links not supported on this platform"}; + {error, eperm} -> + {win32,_} = os:type(), + {skip, "Windows user not privileged to create symlinks"}; + ok -> + true = filelib:is_dir(DirAlias), + true = filelib:is_dir(DirAlias, erl_prim_loader), + true = filelib:is_dir(DirAlias, prim_file), + true = filelib:is_file(DirAlias), + true = filelib:is_file(DirAlias, erl_prim_loader), + true = filelib:is_file(DirAlias, prim_file), + ok = file:make_symlink(AFile,FileAlias), + true = filelib:is_file(FileAlias), + true = filelib:is_file(FileAlias, erl_prim_loader), + true = filelib:is_file(FileAlias, prim_file), + true = filelib:is_regular(FileAlias), + true = filelib:is_regular(FileAlias, erl_prim_loader), + true = filelib:is_regular(FileAlias, prim_file), + ok + end. + +file_props_symlink(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_file_props_symlink"), + AFile = filename:join(Dir, "a_file"), + Alias = filename:join(Dir, "symlink"), + ok = file:make_dir(Dir), + ok = file:write_file(AFile, "not that big\n"), + case file:make_symlink(AFile, Alias) of + {error, enotsup} -> + {skip, "Links not supported on this platform"}; + {error, eperm} -> + {win32,_} = os:type(), + {skip, "Windows user not privileged to create symlinks"}; + ok -> + {_,_} = LastMod = filelib:last_modified(AFile), + LastMod = filelib:last_modified(Alias), + LastMod = filelib:last_modified(Alias, erl_prim_loader), + LastMod = filelib:last_modified(Alias, prim_file), + FileSize = filelib:file_size(AFile), + FileSize = filelib:file_size(Alias), + FileSize = filelib:file_size(Alias, erl_prim_loader), + FileSize = filelib:file_size(Alias, prim_file) + end. diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index 8aeec07ae8..336065b258 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -31,7 +31,9 @@ -export([shutdown/1]). --export([ sys1/1, call_format_status/1, error_format_status/1, get_state/1, replace_state/1]). +-export([ sys1/1, + call_format_status/1, error_format_status/1, terminate_crash_format/1, + get_state/1, replace_state/1]). -export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]). @@ -66,7 +68,8 @@ groups() -> start8, start9, start10, start11, start12]}, {abnormal, [], [abnormal1, abnormal2]}, {sys, [], - [sys1, call_format_status, error_format_status, get_state, replace_state]}]. + [sys1, call_format_status, error_format_status, terminate_crash_format, + get_state, replace_state]}]. init_per_suite(Config) -> Config. @@ -403,7 +406,7 @@ error_format_status(Config) when is_list(Config) -> receive {error,_GroupLeader,{Pid, "** State machine"++_, - [Pid,{_,_,badreturn},idle,StateData,_]}} -> + [Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), @@ -413,6 +416,29 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +terminate_crash_format(Config) when is_list(Config) -> + error_logger_forwarder:register(), + OldFl = process_flag(trap_exit, true), + StateData = crash_terminate, + {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []), + stop_it(Pid), + receive + {error,_GroupLeader,{Pid, + "** State machine"++_, + [Pid,{_,_,_},idle,{formatted, StateData},_]}} -> + ok; + Other -> + io:format("Unexpected: ~p", [Other]), + ?t:fail() + after 5000 -> + io:format("Timeout: expected error logger msg", []), + ?t:fail() + end, + [] = ?t:messages_get(), + process_flag(trap_exit, OldFl), + ok. + + get_state(Config) when is_list(Config) -> State = self(), {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []), @@ -867,7 +893,8 @@ init({state_data, StateData}) -> init(_) -> {ok, idle, state_data}. - +terminate(_, _State, crash_terminate) -> + exit({crash, terminate}); terminate({From, stopped}, State, _Data) -> From ! {self(), {stopped, State}}, ok; @@ -1005,6 +1032,6 @@ handle_sync_event({get, _Pid}, _From, State, Data) -> {reply, {state, State, Data}, State, Data}. format_status(terminate, [_Pdict, StateData]) -> - StateData; + {formatted, StateData}; format_status(normal, [_Pdict, _StateData]) -> [format_status_called]. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 960e7f60e7..42694d8b5d 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -32,7 +32,8 @@ spec_init_local_registered_parent/1, spec_init_global_registered_parent/1, otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1, - error_format_status/1, get_state/1, replace_state/1, call_with_huge_message_queue/1 + error_format_status/1, terminate_crash_format/1, + get_state/1, replace_state/1, call_with_huge_message_queue/1 ]). % spawn export @@ -56,7 +57,8 @@ all() -> call_remote_n3, spec_init, spec_init_local_registered_parent, spec_init_global_registered_parent, otp_5854, hibernate, - otp_7669, call_format_status, error_format_status, + otp_7669, + call_format_status, error_format_status, terminate_crash_format, get_state, replace_state, call_with_huge_message_queue]. @@ -273,7 +275,7 @@ crash(Config) when is_list(Config) -> receive {error,_GroupLeader4,{Pid4, "** Generic server"++_, - [Pid4,crash,state4,crashed]}} -> + [Pid4,crash,{formatted, state4},crashed]}} -> ok; Other4a -> ?line io:format("Unexpected: ~p", [Other4a]), @@ -1024,7 +1026,7 @@ error_format_status(Config) when is_list(Config) -> receive {error,_GroupLeader,{Pid, "** Generic server"++_, - [Pid,crash,State,crashed]}} -> + [Pid,crash,{formatted, State},crashed]}} -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), @@ -1034,6 +1036,31 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +%% Verify that error when terminating correctly calls our format_status/2 fun +%% +terminate_crash_format(Config) when is_list(Config) -> + error_logger_forwarder:register(), + OldFl = process_flag(trap_exit, true), + State = crash_terminate, + {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []), + gen_server:call(Pid, stop), + receive {'EXIT', Pid, {crash, terminate}} -> ok end, + receive + {error,_GroupLeader,{Pid, + "** Generic server"++_, + [Pid,stop, {formatted, State},{crash, terminate}]}} -> + ok; + Other -> + io:format("Unexpected: ~p", [Other]), + ?t:fail() + after 5000 -> + io:format("Timeout: expected error logger msg", []), + ?t:fail() + end, + ?t:messages_get(), + process_flag(trap_exit, OldFl), + ok. + %% Verify that sys:get_state correctly returns gen_server state %% get_state(suite) -> @@ -1323,10 +1350,12 @@ terminate({From, stopped}, _State) -> terminate({From, stopped_info}, _State) -> From ! {self(), stopped_info}, ok; +terminate(_, crash_terminate) -> + exit({crash, terminate}); terminate(_Reason, _State) -> ok. format_status(terminate, [_PDict, State]) -> - State; + {formatted, State}; format_status(normal, [_PDict, _State]) -> format_status_called. diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 5a8971c071..3a76275f31 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -30,7 +30,7 @@ io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1, printable_range/1, io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1, - otp_10836/1]). + otp_10836/1, io_lib_width_too_small/1]). -export([pretty/2]). @@ -69,7 +69,8 @@ all() -> io_lib_collect_line_3_wb, cr_whitespace_in_string, io_fread_newlines, otp_8989, io_lib_fread_literal, printable_range, - io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836]. + io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836, + io_lib_width_too_small]. groups() -> []. @@ -2213,3 +2214,8 @@ compile_file(File, Text, Config) -> try compile:file(Fname, [return]) after ok %file:delete(Fname) end. + +io_lib_width_too_small(Config) -> + "**" = lists:flatten(io_lib:format("~2.3w", [3.14])), + "**" = lists:flatten(io_lib:format("~2.5w", [3.14])), + ok. diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl new file mode 100644 index 0000000000..c826ee731a --- /dev/null +++ b/lib/stdlib/test/maps_SUITE.erl @@ -0,0 +1,69 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1997-2014. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%%%---------------------------------------------------------------- +%%% Purpose: Test suite for the 'maps' module. +%%%----------------------------------------------------------------- + +-module(maps_SUITE). + +-include_lib("test_server/include/test_server.hrl"). + +% Default timetrap timeout (set in init_per_testcase). +% This should be set relatively high (10-15 times the expected +% max testcasetime). +-define(default_timeout, ?t:minutes(4)). + +% Test server specific exports +-export([all/0]). +-export([suite/0]). +-export([init_per_suite/1]). +-export([end_per_suite/1]). +-export([init_per_testcase/2]). +-export([end_per_testcase/2]). + +-export([get3/1]). + +suite() -> + [{ct_hooks, [ts_install_cth]}]. + +all() -> + [get3]. + +init_per_suite(Config) -> + Config. + +end_per_suite(_Config) -> + ok. + +init_per_testcase(_Case, Config) -> + ?line Dog=test_server:timetrap(?default_timeout), + [{watchdog, Dog}|Config]. + +end_per_testcase(_Case, Config) -> + Dog=?config(watchdog, Config), + test_server:timetrap_cancel(Dog), + ok. + +get3(Config) when is_list(Config) -> + Map = #{ key1 => value1, key2 => value2 }, + DefaultValue = "Default value", + ?line value1 = maps:get(key1, Map, DefaultValue), + ?line value2 = maps:get(key2, Map, DefaultValue), + ?line DefaultValue = maps:get(key3, Map, DefaultValue), + ok. diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index e016432f4d..f841e2c4a6 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2532,6 +2532,11 @@ otp_6554(Config) when is_list(Config) -> "\n end.\nok.\n" = t(<<"begin F = fun() -> foo end, 1 end. B = F(). C = 17. b().">>), + ?line "3: command not found" = comm_err(<<"#{v(3) => v}.">>), + ?line "3: command not found" = comm_err(<<"#{k => v(3)}.">>), + ?line "3: command not found" = comm_err(<<"#{v(3) := v}.">>), + ?line "3: command not found" = comm_err(<<"#{k := v(3)}.">>), + ?line "3: command not found" = comm_err(<<"(v(3))#{}.">>), %% Tests I'd like to do: (you should try them manually) %% "catch spawn_link(fun() -> timer:sleep(1000), exit(foo) end)." %% "** exception error: foo" should be output after 1 second diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 53a34511d9..59821220b4 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -94,10 +94,10 @@ appup_tests(App,{OkVsns,NokVsns}) -> ok. create_test_vsns(App) -> - This = erlang:system_info(otp_release), - FirstMajor = previous_major(This), + ThisMajor = erlang:system_info(otp_release), + FirstMajor = previous_major(ThisMajor), SecondMajor = previous_major(FirstMajor), - Ok = app_vsn(App,[FirstMajor]), + Ok = app_vsn(App,[ThisMajor,FirstMajor]), Nok0 = app_vsn(App,[SecondMajor]), Nok = case Ok of [Ok1|_] -> @@ -108,9 +108,9 @@ create_test_vsns(App) -> {Ok,Nok}. previous_major("17") -> - "r16"; -previous_major("r"++Rel) -> - "r"++previous_major(Rel); + "r16b"; +previous_major("r16b") -> + "r15b"; previous_major(Rel) -> integer_to_list(list_to_integer(Rel)-1). diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 5bc34e35af..6349139925 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -23,7 +23,7 @@ create_long_names/1, bad_tar/1, errors/1, extract_from_binary/1, extract_from_binary_compressed/1, extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1, - memory/1]). + memory/1,unicode/1]). -include_lib("test_server/include/test_server.hrl"). -include_lib("kernel/include/file.hrl"). @@ -34,7 +34,7 @@ all() -> [borderline, atomic, long_names, create_long_names, bad_tar, errors, extract_from_binary, extract_from_binary_compressed, extract_from_open_file, - symlinks, open_add_close, cooked_compressed, memory]. + symlinks, open_add_close, cooked_compressed, memory, unicode]. groups() -> []. @@ -73,6 +73,7 @@ borderline(Config) when is_list(Config) -> ?line lists:foreach(fun(Size) -> borderline_test(Size, TempDir) end, [0, 1, 10, 13, 127, 333, Record-1, Record, Record+1, + Block-2*Record-1, Block-2*Record, Block-2*Record+1, Block-Record-1, Block-Record, Block-Record+1, Block-1, Block, Block+1, Block+Record-1, Block+Record, Block+Record+1]), @@ -726,6 +727,56 @@ memory(Config) when is_list(Config) -> ?line ok = delete_files([Name1,Name2]), ok. +%% Test filenames with characters outside the US ASCII range. +unicode(Config) when is_list(Config) -> + PrivDir = ?config(priv_dir, Config), + do_unicode(PrivDir), + case has_transparent_naming() of + true -> + Pa = filename:dirname(code:which(?MODULE)), + Node = start_node(unicode, "+fnl -pa "++Pa), + ok = rpc:call(Node, erlang, apply, + [fun() -> do_unicode(PrivDir) end,[]]), + true = test_server:stop_node(Node), + ok; + false -> + ok + end. + +has_transparent_naming() -> + case os:type() of + {unix,darwin} -> false; + {unix,_} -> true; + _ -> false + end. + +do_unicode(PrivDir) -> + ok = file:set_cwd(PrivDir), + ok = file:make_dir("unicöde"), + + Names = unicode_create_files(), + Tar = "unicöde.tar", + ok = erl_tar:create(Tar, ["unicöde"], []), + {ok,Names} = erl_tar:table(Tar, []), + _ = [ok = file:delete(Name) || Name <- Names], + ok = erl_tar:extract(Tar), + _ = [{ok,_} = file:read_file(Name) || Name <- Names], + _ = [ok = file:delete(Name) || Name <- Names], + ok = file:del_dir("unicöde"), + ok. + +unicode_create_files() -> + FileA = "unicöde/smörgåsbord", + ok = file:write_file(FileA, "yum!\n"), + [FileA|case file:native_name_encoding() of + utf8 -> + FileB = "unicöde/Хороший файл!", + ok = file:write_file(FileB, "But almost empty.\n"), + [FileB]; + latin1 -> + [] + end]. + %% Delete the given list of files. delete_files([]) -> ok; delete_files([Item|Rest]) -> @@ -791,3 +842,14 @@ make_temp_dir(Base, I) -> ok -> Name; {error,eexist} -> make_temp_dir(Base, I+1) end. + +start_node(Name, Args) -> + [_,Host] = string:tokens(atom_to_list(node()), "@"), + ct:log("Trying to start ~w@~s~n", [Name,Host]), + case test_server:start_node(Name, peer, [{args,Args}]) of + {error,Reason} -> + test_server:fail(Reason); + {ok,Node} -> + ct:log("Node ~p started~n", [Node]), + Node + end. |