diff options
Diffstat (limited to 'lib/stdlib/test/tar_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 944 |
1 files changed, 602 insertions, 342 deletions
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 6da017f818..32a33283d1 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2011. All Rights Reserved. +%% Copyright Ericsson AB 1997-2017. 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. @@ -20,13 +20,17 @@ -module(tar_SUITE). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, - init_per_group/2,end_per_group/2, borderline/1, atomic/1, long_names/1, + init_per_group/2, end_per_group/2, + init_per_testcase/2, + borderline/1, atomic/1, long_names/1, create_long_names/1, bad_tar/1, errors/1, extract_from_binary/1, - extract_from_binary_compressed/1, + extract_from_binary_compressed/1, extract_filtered/1, extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1, - memory/1,unicode/1]). + memory/1,unicode/1,read_other_implementations/1, + sparse/1, init/1, leading_slash/1, dotdot/1, + roundtrip_metadata/1, apply_file_info_opts/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -include_lib("kernel/include/file.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -35,7 +39,11 @@ 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, unicode]. + extract_filtered, + symlinks, open_add_close, cooked_compressed, memory, unicode, + read_other_implementations, + sparse,init,leading_slash,dotdot,roundtrip_metadata, + apply_file_info_opts]. groups() -> []. @@ -52,11 +60,13 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. +init_per_testcase(_Case, Config) -> + Ports = ordsets:from_list(erlang:ports()), + [{ports,Ports}|Config]. -borderline(doc) -> - ["Test creating, listing and extracting one file from an archive", - "multiple times with different file sizes. ", - "Also check that the file attributes of the extracted file has survived."]; +%% Test creating, listing and extracting one file from an archive, +%% multiple times with different file sizes. Also check that the file +%% attributes of the extracted file has survived. borderline(Config) when is_list(Config) -> %% Note: We cannot use absolute paths, because the pathnames will be @@ -64,47 +74,65 @@ borderline(Config) when is_list(Config) -> %% Therefore, strip off the current working directory from the front %% of the private directory path. - ?line {ok, Cwd} = file:get_cwd(), - ?line RootDir = ?config(priv_dir, Config), - ?line TempDir = remove_prefix(Cwd++"/", filename:join(RootDir, "borderline")), - ?line ok = file:make_dir(TempDir), + {ok, Cwd} = file:get_cwd(), + RootDir = proplists:get_value(priv_dir, Config), + TempDir = remove_prefix(Cwd++"/", filename:join(RootDir, "borderline")), + ok = file:make_dir(TempDir), - ?line Record = 512, - ?line Block = 20 * Record, + Record = 512, + Block = 20 * Record, - ?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]), + 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]), %% Clean up. - ?line delete_files([TempDir]), + delete_files([TempDir]), - ok. + verify_ports(Config). borderline_test(Size, TempDir) -> - ?line Archive = filename:join(TempDir, "ar_"++integer_to_list(Size)++".tar"), - ?line Name = filename:join(TempDir, "file_"++integer_to_list(Size)), - ?line io:format("Testing size ~p", [Size]), + io:format("Testing size ~p", [Size]), + borderline_test(Size, TempDir, true), + borderline_test(Size, TempDir, false), + ok. + +borderline_test(Size, TempDir, IsUstar) -> + Prefix = case IsUstar of + true -> + "file_"; + false -> + lists:duplicate(100, $f) ++ "ile_" + end, + SizeList = integer_to_list(Size), + Archive = filename:join(TempDir, "ar_"++ SizeList ++".tar"), + Name = filename:join(TempDir, Prefix++SizeList), %% Create a file and archive it. X0 = erlang:monotonic_time(), - ?line file:write_file(Name, random_byte_list(X0, Size)), - ?line ok = erl_tar:create(Archive, [Name]), - ?line ok = file:delete(Name), + ok = file:write_file(Name, random_byte_list(X0, Size)), + ok = erl_tar:create(Archive, [Name]), + ok = file:delete(Name), %% Verify listing and extracting. - ?line {ok, [Name]} = erl_tar:table(Archive), - ?line ok = erl_tar:extract(Archive, [verbose]), + IsUstar = is_ustar(Archive), + {ok, [Name]} = erl_tar:table(Archive), + ok = erl_tar:extract(Archive, [verbose]), %% Verify contents of extracted file. - ?line {ok, Bin} = file:read_file(Name), - ?line true = match_byte_list(X0, binary_to_list(Bin)), + {ok, Bin} = file:read_file(Name), + true = match_byte_list(X0, binary_to_list(Bin)), %% Verify that Unix tar can read it. - ?line tar_tf(Archive, Name), + case IsUstar of + true -> + tar_tf(Archive, Name); + false -> + ok + end, ok. @@ -117,20 +145,20 @@ tar_tf(Archive, Name) -> end. tar_tf1(Archive, Name) -> - ?line Expect = Name ++ "\n", - ?line cmd_expect("tar tf " ++ Archive, Expect). + Expect = Name ++ "\n", + cmd_expect("tar tf " ++ Archive, Expect). %% We can't use os:cmd/1, because Unix 'tar tf Name' on Solaris never %% terminates when given an archive of a size it doesn't like. cmd_expect(Cmd, Expect) -> - ?line Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]), - ?line get_data(Port, Expect). + Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]), + get_data(Port, Expect). get_data(Port, Expect) -> receive {Port, {data, Bytes}} -> - ?line get_data(Port, match_output(Bytes, Expect, Port)); + get_data(Port, match_output(Bytes, Expect, Port)); {Port, eof} -> Port ! {self(), close}, receive @@ -143,26 +171,26 @@ get_data(Port, Expect) -> after 1 -> % force context switch ok end, - ?line match_output(eof, Expect, Port) + match_output(eof, Expect, Port) end. match_output([C|Output], [C|Expect], Port) -> - ?line match_output(Output, Expect, Port); + match_output(Output, Expect, Port); match_output([_|_], [_|_], Port) -> - ?line kill_port_and_fail(Port, badmatch); + kill_port_and_fail(Port, badmatch); match_output([X|Output], [], Port) -> - ?line kill_port_and_fail(Port, {too_much_data, [X|Output]}); + kill_port_and_fail(Port, {too_much_data, [X|Output]}); match_output([], Expect, _Port) -> Expect; match_output(eof, [], _Port) -> []; match_output(eof, _Expect, Port) -> - ?line kill_port_and_fail(Port, unexpected_end_of_input). + kill_port_and_fail(Port, unexpected_end_of_input). kill_port_and_fail(Port, Reason) -> unlink(Port), exit(Port, die), - test_server:fail(Reason). + ct:fail(Reason). make_cmd(Cmd) -> case os:type() of @@ -198,60 +226,58 @@ random_byte_list(_X, 0, Result) -> next_random(X) -> (X*17059465+1) band 16#fffffffff. -atomic(doc) -> - ["Test the 'atomic' operations: create/extract/table, on compressed " - "and uncompressed archives." - "Also test the 'cooked' option."]; -atomic(suite) -> []; +%% Test the 'atomic' operations: create/extract/table, on compressed +%% and uncompressed archives. +%% Also test the 'cooked' option. atomic(Config) when is_list(Config) -> - ?line ok = file:set_cwd(?config(priv_dir, Config)), - ?line DataFiles = data_files(), - ?line Names = [Name || {Name,_,_} <- DataFiles], + ok = file:set_cwd(proplists:get_value(priv_dir, Config)), + DataFiles = data_files(), + Names = [Name || {Name,_,_} <- DataFiles], io:format("Names: ~p", [Names]), %% Create an uncompressed archive. The compressed flag should still be %% allowed when listing contents or extracting. - ?line Tar1 = "uncompressed.tar", - ?line erl_tar:create(Tar1, Names, []), - ?line {ok, Names} = erl_tar:table(Tar1, []), - ?line {ok, Names} = erl_tar:table(Tar1, [compressed]), - ?line {ok, Names} = erl_tar:table(Tar1, [cooked]), - ?line {ok, Names} = erl_tar:table(Tar1, [compressed,cooked]), - + Tar1 = "uncompressed.tar", + erl_tar:create(Tar1, Names, []), + {ok, Names} = erl_tar:table(Tar1, []), + {ok, Names} = erl_tar:table(Tar1, [compressed]), + {ok, Names} = erl_tar:table(Tar1, [cooked]), + {ok, Names} = erl_tar:table(Tar1, [compressed,cooked]), + %% Create a compressed archive. - ?line Tar2 = "compressed.tar", - ?line erl_tar:create(Tar2, Names, [compressed]), - ?line {ok, Names} = erl_tar:table(Tar2, [compressed]), - ?line {error, Reason} = erl_tar:table(Tar2, []), - ?line {ok, Names} = erl_tar:table(Tar2, [compressed,cooked]), - ?line {error, Reason} = erl_tar:table(Tar2, [cooked]), - ?line ok = io:format("No compressed option: ~p, ~s", - [Reason, erl_tar:format_error(Reason)]), + Tar2 = "compressed.tar", + erl_tar:create(Tar2, Names, [compressed]), + {ok, Names} = erl_tar:table(Tar2, [compressed]), + {error, Reason} = erl_tar:table(Tar2, []), + {ok, Names} = erl_tar:table(Tar2, [compressed,cooked]), + {error, Reason} = erl_tar:table(Tar2, [cooked]), + ok = io:format("No compressed option: ~p, ~s", + [Reason, erl_tar:format_error(Reason)]), %% Same test again, but this time created with 'cooked' - ?line Tar3 = "uncompressed_cooked.tar", - ?line erl_tar:create(Tar3, Names, [cooked]), - ?line {ok, Names} = erl_tar:table(Tar3, []), - ?line {ok, Names} = erl_tar:table(Tar3, [compressed]), - ?line {ok, Names} = erl_tar:table(Tar3, [cooked]), - ?line {ok, Names} = erl_tar:table(Tar3, [compressed,cooked]), - - ?line Tar4 = "compressed_cooked.tar", - ?line erl_tar:create(Tar4, Names, [compressed,cooked]), - ?line {ok, Names} = erl_tar:table(Tar4, [compressed]), - ?line {error, Reason} = erl_tar:table(Tar4, []), - ?line {ok, Names} = erl_tar:table(Tar4, [compressed,cooked]), - ?line {error, Reason} = erl_tar:table(Tar4, [cooked]), - ?line ok = io:format("No compressed option: ~p, ~s", - [Reason, erl_tar:format_error(Reason)]), + Tar3 = "uncompressed_cooked.tar", + erl_tar:create(Tar3, Names, [cooked]), + {ok, Names} = erl_tar:table(Tar3, []), + {ok, Names} = erl_tar:table(Tar3, [compressed]), + {ok, Names} = erl_tar:table(Tar3, [cooked]), + {ok, Names} = erl_tar:table(Tar3, [compressed,cooked]), + + Tar4 = "compressed_cooked.tar", + erl_tar:create(Tar4, Names, [compressed,cooked]), + {ok, Names} = erl_tar:table(Tar4, [compressed]), + {error, Reason} = erl_tar:table(Tar4, []), + {ok, Names} = erl_tar:table(Tar4, [compressed,cooked]), + {error, Reason} = erl_tar:table(Tar4, [cooked]), + ok = io:format("No compressed option: ~p, ~s", + [Reason, erl_tar:format_error(Reason)]), %% Clean up. - ?line delete_files([Tar1,Tar2,Tar3,Tar4|Names]), + delete_files([Tar1,Tar2,Tar3,Tar4|Names]), - ok. + verify_ports(Config). %% Returns a sequence of characters. @@ -279,50 +305,51 @@ create_files([{Name, Size, First}|Rest]) -> create_files([]) -> ok. -long_names(doc) -> - ["Test to extract an Unix tar file containing filenames longer than 100 ", - "characters and empty directories."]; +%% Test to extract an Unix tar file containing filenames longer than +%% 100 characters and empty directories. long_names(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line Long = filename:join(DataDir, "long_names.tar"), + DataDir = proplists:get_value(data_dir, Config), + Long = filename:join(DataDir, "long_names.tar"), run_in_short_tempdir(Config, - fun() -> do_long_names(Long) end). + fun() -> do_long_names(Long) end), + verify_ports(Config). + do_long_names(Long) -> %% Try table/2 and extract/2. - ?line case erl_tar:table(Long, [verbose]) of - {ok,List} when is_list(List) -> - ?line io:format("~p\n", [List]) - end, + case erl_tar:table(Long, [verbose]) of + {ok,List} when is_list(List) -> + io:format("~p\n", [List]) + end, - ?line {ok,Cwd} = file:get_cwd(), - ?line ok = erl_tar:extract(Long), - ?line Base = filename:join([Cwd, "original_software", "written_by", - "a_bunch_of_hackers", - "spending_all_their_nights", - "still", "not_long_enough", - "but_soon_it_will_be"]), + {ok,Cwd} = file:get_cwd(), + ok = erl_tar:extract(Long), + Base = filename:join([Cwd, "original_software", "written_by", + "a_bunch_of_hackers", + "spending_all_their_nights", + "still", "not_long_enough", + "but_soon_it_will_be"]), %% Verify that the empty directory was created. - ?line EmptyDir = filename:join(Base, "empty_directory"), - ?line {ok, #file_info{type=directory}} = file:read_file_info(EmptyDir), + EmptyDir = filename:join(Base, "empty_directory"), + {ok, #file_info{type=directory}} = file:read_file_info(EmptyDir), %% Verify that the files were created. - ?line {ok,First} = file:read_file(filename:join(Base, "first_file")), - ?line {ok,Second} = file:read_file(filename:join(Base, "second_file")), - ?line "Here"++_ = binary_to_list(First), - ?line "And"++_ = binary_to_list(Second), + {ok,First} = file:read_file(filename:join(Base, "first_file")), + {ok,Second} = file:read_file(filename:join(Base, "second_file")), + "Here"++_ = binary_to_list(First), + "And"++_ = binary_to_list(Second), ok. -create_long_names(doc) -> - ["Creates a tar file from a deep directory structure (filenames are ", - "longer than 100 characters)."]; +%% Creates a tar file from a deep directory structure (filenames are +%% longer than 100 characters). create_long_names(Config) when is_list(Config) -> - run_in_short_tempdir(Config, fun create_long_names/0). - + run_in_short_tempdir(Config, fun create_long_names/0), + verify_ports(Config). + create_long_names() -> - ?line {ok,Dir} = file:get_cwd(), + {ok,Dir} = file:get_cwd(), Dirs = ["aslfjkshjkhliuf", "asdhjfehnbfsky", "sahajfskdfhsz", @@ -330,92 +357,93 @@ create_long_names() -> "f7nafhjgffagkhsfkhsjk", "dfjasldkfjsdkfjashbv"], - ?line DeepDir = make_dirs(Dirs, []), - ?line AFile = filename:join(DeepDir, "a_file"), - ?line Hello = "hello, world\n", - ?line ok = file:write_file(AFile, Hello), - ?line TarName = filename:join(Dir, "my_tar_with_long_names.tar"), - ?line ok = erl_tar:create(TarName, [AFile]), + DeepDir = make_dirs(Dirs, []), + AFile = filename:join(DeepDir, "a_file"), + Hello = "hello, world\n", + ok = file:write_file(AFile, Hello), + TarName = filename:join(Dir, "my_tar_with_long_names.tar"), + ok = erl_tar:create(TarName, [AFile]), %% Print contents. - ?line ok = erl_tar:tt(TarName), + ok = erl_tar:tt(TarName), %% Extract and verify. - ?line ExtractDir = "extract_dir", - ?line ok = file:make_dir(ExtractDir), - ?line ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]), - ?line {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)), - ?line Hello = binary_to_list(Bin), + true = is_ustar(TarName), + ExtractDir = "extract_dir", + ok = file:make_dir(ExtractDir), + ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]), + {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)), + Hello = binary_to_list(Bin), ok. make_dirs([Dir|Rest], []) -> - ?line ok = file:make_dir(Dir), - ?line make_dirs(Rest, Dir); + ok = file:make_dir(Dir), + make_dirs(Rest, Dir); make_dirs([Dir|Rest], Parent) -> - ?line Name = filename:join(Parent, Dir), - ?line ok = file:make_dir(Name), - ?line make_dirs(Rest, Name); + Name = filename:join(Parent, Dir), + ok = file:make_dir(Name), + make_dirs(Rest, Name); make_dirs([], Dir) -> Dir. -bad_tar(doc) -> - ["Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files."]; +%% Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files. bad_tar(Config) when is_list(Config) -> - ?line try_bad("bad_checksum", bad_header, Config), - ?line try_bad("bad_octal", bad_header, Config), - ?line try_bad("bad_too_short", eof, Config), - ?line try_bad("bad_even_shorter", eof, Config), - ok. + try_bad("bad_checksum", bad_header, Config), + try_bad("bad_octal", invalid_tar_checksum, Config), + try_bad("bad_too_short", eof, Config), + try_bad("bad_even_shorter", eof, Config), + verify_ports(Config). try_bad(Name0, Reason, Config) -> - %% Intentionally no ?line macros here. + %% Intentionally no macros here. - DataDir = ?config(data_dir, Config), - PrivDir = ?config(priv_dir, Config), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Name = Name0 ++ ".tar", io:format("~nTrying ~s", [Name]), Full = filename:join(DataDir, Name), - Opts = [verbose, {cwd, PrivDir}], + Dest = filename:join(PrivDir, Name0), + Opts = [verbose, {cwd, Dest}], Expected = {error, Reason}, + io:fwrite("Expected: ~p\n", [Expected]), case {erl_tar:table(Full, Opts), erl_tar:extract(Full, Opts)} of {Expected, Expected} -> io:format("Result: ~p", [Expected]), case catch erl_tar:format_error(Reason) of {'EXIT', CrashReason} -> - test_server:fail({format_error, crashed, CrashReason}); + ct:fail({format_error, crashed, CrashReason}); String when is_list(String) -> io:format("format_error(~p) -> ~s", [Reason, String]); Other -> - test_server:fail({format_error, returned, Other}) + ct:fail({format_error, returned, Other}) end; {Other1, Other2} -> io:format("table/2 returned ~p", [Other1]), io:format("extract/2 returned ~p", [Other2]), - test_server:fail({bad_return_value, Other1, Other2}) + ct:fail({bad_return_value, Other1, Other2}) end. -errors(doc) -> - ["Tests that some common errors return correct error codes ", - "and that format_error/1 handles them correctly."]; +%% Tests that some common errors return correct error codes +%% and that format_error/1 handles them correctly. errors(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), %% Give the tar file the same name as a directory. - ?line BadTar = filename:join(PrivDir, "bad_tarfile.tar"), - ?line ok = file:make_dir(BadTar), - ?line try_error(erl_tar, create, [BadTar, []], {BadTar, eisdir}), + BadTar = filename:join(PrivDir, "bad_tarfile.tar"), + ok = file:make_dir(BadTar), + try_error(erl_tar, create, [BadTar, []], {BadTar, eisdir}), %% Try including non-existent files in the tar file. - ?line NonExistent = "non_existent_file", - ?line GoodTar = filename:join(PrivDir, "a_good_tarfile.tar"), - ?line try_error(erl_tar, create, [GoodTar, [NonExistent]], - {NonExistent, enoent}), + NonExistent = "non_existent_file", + GoodTar = filename:join(PrivDir, "a_good_tarfile.tar"), + try_error(erl_tar, create, [GoodTar, [NonExistent]], + {NonExistent, enoent}), %% Clean up. - ?line delete_files([GoodTar,BadTar]), - - ok. + delete_files([GoodTar,BadTar]), + + verify_ports(Config). try_error(M, F, A, Error) -> io:format("Trying ~p:~p(~p)", [M, F, A]), @@ -423,18 +451,18 @@ try_error(M, F, A, Error) -> {'EXIT', Reason} -> exit(Reason); ok -> - test_server:fail(unexpected_success); + ct:fail(unexpected_success); {error, Error} -> case catch erl_tar:format_error(Error) of {'EXIT', FReason} -> - test_server:fail({format_error, crashed, FReason}); + ct:fail({format_error, crashed, FReason}); String when is_list(String) -> io:format("format_error(~p) -> ~s", [Error, String]); Other -> - test_server:fail({format_error, returned, Other}) + ct:fail({format_error, returned, Other}) end; Other -> - test_server:fail({expected, {error, Error}, actual, Other}) + ct:fail({expected, {error, Error}, actual, Other}) end. %% remove_prefix(Prefix, List) -> ListWithoutPrefix. @@ -444,107 +472,126 @@ remove_prefix([C|Rest1], [C|Rest2]) -> remove_prefix(_, Result) -> Result. -extract_from_binary(doc) -> - "Test extracting a tar archive from a binary."; +%% Test extracting a tar archive from a binary. extract_from_binary(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Long = filename:join(DataDir, "no_fancy_stuff.tar"), - ?line ExtractDir = filename:join(PrivDir, "extract_from_binary"), - ?line ok = file:make_dir(ExtractDir), - + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Long = filename:join(DataDir, "no_fancy_stuff.tar"), + ExtractDir = filename:join(PrivDir, "extract_from_binary"), + ok = file:make_dir(ExtractDir), + %% Read a tar file into a binary and extract from the binary. - ?line {ok, Bin} = file:read_file(Long), - ?line ok = erl_tar:extract({binary, Bin}, [{cwd,ExtractDir}]), + {ok, Bin} = file:read_file(Long), + ok = erl_tar:extract({binary, Bin}, [{cwd,ExtractDir}]), %% Verify. Dir = filename:join(ExtractDir, "no_fancy_stuff"), - ?line true = filelib:is_dir(Dir), - ?line true = filelib:is_file(filename:join(Dir, "a_dir_list")), - ?line true = filelib:is_file(filename:join(Dir, "EPLICENCE")), + true = filelib:is_dir(Dir), + true = filelib:is_file(filename:join(Dir, "a_dir_list")), + true = filelib:is_file(filename:join(Dir, "EPLICENCE")), %% Clean up. - ?line delete_files([ExtractDir]), + delete_files([ExtractDir]), - ok. + verify_ports(Config). extract_from_binary_compressed(Config) when is_list(Config) -> %% Test extracting a compressed tar archive from a binary. - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"), - ?line ExtractDir = filename:join(PrivDir, "extract_from_binary_compressed"), - ?line ok = file:make_dir(ExtractDir), - ?line {ok,Bin} = file:read_file(Name), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"), + ExtractDir = filename:join(PrivDir, "extract_from_binary_compressed"), + ok = file:make_dir(ExtractDir), + {ok,Bin} = file:read_file(Name), %% Try taking contents. - ?line {ok,Files} = erl_tar:table({binary,Bin}, [compressed]), - ?line io:format("~p\n", [Files]), - ?line 19 = length(Files), - + {ok,Files} = erl_tar:table({binary,Bin}, [compressed]), + io:format("~p\n", [Files]), + 19 = length(Files), + %% Trying extracting from a binary. - ?line ok = erl_tar:extract({binary,Bin}, [compressed,{cwd,ExtractDir}]), - ?line {ok,List} = file:list_dir(filename:join(ExtractDir, "ddll_SUITE_data")), - ?line io:format("~p\n", [List]), - ?line 19 = length(List), + ok = erl_tar:extract({binary,Bin}, [compressed,{cwd,ExtractDir}]), + {ok,List} = file:list_dir(filename:join(ExtractDir, "ddll_SUITE_data")), + io:format("~p\n", [List]), + 19 = length(List), %% Clean up while at the same time testing that all file %% were extracted as expected. lists:foreach(fun(N) -> File = filename:join(ExtractDir, N), io:format("Deleting: ~p\n", [File]), - ?line ok = file:delete(File) + ok = file:delete(File) end, Files), %% Clean up the rest. - ?line delete_files([ExtractDir]), + delete_files([ExtractDir]), - ok. + verify_ports(Config). + +%% Test extracting a tar archive from a binary. +extract_filtered(Config) when is_list(Config) -> + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Long = filename:join(DataDir, "no_fancy_stuff.tar"), + ExtractDir = filename:join(PrivDir, "extract_from_binary"), + ok = file:make_dir(ExtractDir), + + ok = erl_tar:extract(Long, [{cwd,ExtractDir},{files,["no_fancy_stuff/EPLICENCE"]}]), -extract_from_open_file(doc) -> - "Test extracting a tar archive from an open file."; + %% Verify. + Dir = filename:join(ExtractDir, "no_fancy_stuff"), + true = filelib:is_dir(Dir), + false = filelib:is_file(filename:join(Dir, "a_dir_list")), + true = filelib:is_file(filename:join(Dir, "EPLICENCE")), + + %% Clean up. + delete_files([ExtractDir]), + + verify_ports(Config). + +%% Test extracting a tar archive from an open file. extract_from_open_file(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Long = filename:join(DataDir, "no_fancy_stuff.tar"), - ?line ExtractDir = filename:join(PrivDir, "extract_from_open_file"), - ?line ok = file:make_dir(ExtractDir), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Long = filename:join(DataDir, "no_fancy_stuff.tar"), + ExtractDir = filename:join(PrivDir, "extract_from_open_file"), + ok = file:make_dir(ExtractDir), - ?line {ok, File} = file:open(Long, [read]), - ?line ok = erl_tar:extract({file, File}, [{cwd,ExtractDir}]), + {ok, File} = file:open(Long, [read]), + ok = erl_tar:extract({file, File}, [{cwd,ExtractDir}]), %% Verify. Dir = filename:join(ExtractDir, "no_fancy_stuff"), - ?line true = filelib:is_dir(Dir), - ?line true = filelib:is_file(filename:join(Dir, "a_dir_list")), - ?line true = filelib:is_file(filename:join(Dir, "EPLICENCE")), + true = filelib:is_dir(Dir), + true = filelib:is_file(filename:join(Dir, "a_dir_list")), + true = filelib:is_file(filename:join(Dir, "EPLICENCE")), %% Close open file. - ?line ok = file:close(File), + ok = file:close(File), %% Clean up. - ?line delete_files([ExtractDir]), + delete_files([ExtractDir]), - ok. + verify_ports(Config). -symlinks(doc) -> - "Test that archives containing symlinks can be created and extracted."; +%% Test that archives containing symlinks can be created and extracted. symlinks(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), - ?line Dir = filename:join(PrivDir, "symlinks"), - ?line ok = file:make_dir(Dir), - ?line ABadSymlink = filename:join(Dir, "bad_symlink"), - ?line PointsTo = "/a/definitely/non_existing/path", - ?line Res = case make_symlink("/a/definitely/non_existing/path", ABadSymlink) of - {error, enotsup} -> - {skip, "Symbolic links not supported on this platform"}; - ok -> - symlinks(Dir, "bad_symlink", PointsTo), - long_symlink(Dir) - end, + PrivDir = proplists:get_value(priv_dir, Config), + Dir = filename:join(PrivDir, "symlinks"), + ok = file:make_dir(Dir), + ABadSymlink = filename:join(Dir, "bad_symlink"), + PointsTo = "/a/definitely/non_existing/path", + Res = case make_symlink("/a/definitely/non_existing/path", ABadSymlink) of + {error, enotsup} -> + {skip, "Symbolic links not supported on this platform"}; + ok -> + symlinks(Dir, "bad_symlink", PointsTo), + long_symlink(Dir) + end, %% Clean up. - ?line delete_files([Dir]), + delete_files([Dir]), + verify_ports(Config), Res. make_symlink(Path, Link) -> @@ -569,105 +616,154 @@ make_symlink(Path, Link) -> _ -> file:make_symlink(Path, Link) end. - + symlinks(Dir, BadSymlink, PointsTo) -> - ?line Tar = filename:join(Dir, "symlink.tar"), - ?line DerefTar = filename:join(Dir, "dereference.tar"), + Tar = filename:join(Dir, "symlink.tar"), + DerefTar = filename:join(Dir, "dereference.tar"), %% Create the archive. - ?line ok = file:set_cwd(Dir), - ?line GoodSymlink = "good_symlink", - ?line AFile = "a_good_file", - ?line ALine = "A line of text for a file.", - ?line ok = file:write_file(AFile, ALine), - ?line ok = file:make_symlink(AFile, GoodSymlink), - ?line ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]), + ok = file:set_cwd(Dir), + GoodSymlink = "good_symlink", + AFile = "a_good_file", + ALine = "A line of text for a file.", + ok = file:write_file(AFile, ALine), + ok = file:make_symlink(AFile, GoodSymlink), + ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]), + true = is_ustar(Tar), %% List contents of tar file. - ?line ok = erl_tar:tt(Tar), + ok = erl_tar:tt(Tar), %% Also create another archive with the dereference flag. - ?line ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]), + ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]), + true = is_ustar(DerefTar), %% Extract files to a new directory. - ?line NewDir = filename:join(Dir, "extracted"), - ?line ok = file:make_dir(NewDir), - ?line ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]), + NewDir = filename:join(Dir, "extracted"), + ok = file:make_dir(NewDir), + ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]), %% Verify that the files are there. - ?line ok = file:set_cwd(NewDir), - ?line {ok, #file_info{type=symlink}} = file:read_link_info(BadSymlink), - ?line {ok, PointsTo} = file:read_link(BadSymlink), - ?line {ok, #file_info{type=symlink}} = file:read_link_info(GoodSymlink), - ?line {ok, AFile} = file:read_link(GoodSymlink), - ?line Expected = list_to_binary(ALine), - ?line {ok, Expected} = file:read_file(GoodSymlink), + ok = file:set_cwd(NewDir), + {ok, #file_info{type=symlink}} = file:read_link_info(BadSymlink), + {ok, PointsTo} = file:read_link(BadSymlink), + {ok, #file_info{type=symlink}} = file:read_link_info(GoodSymlink), + {ok, AFile} = file:read_link(GoodSymlink), + Expected = list_to_binary(ALine), + {ok, Expected} = file:read_file(GoodSymlink), %% Extract the "dereferenced archive" to a new directory. - ?line NewDirDeref = filename:join(Dir, "extracted_deref"), - ?line ok = file:make_dir(NewDirDeref), - ?line ok = erl_tar:extract(DerefTar, [{cwd, NewDirDeref}, verbose]), + NewDirDeref = filename:join(Dir, "extracted_deref"), + ok = file:make_dir(NewDirDeref), + ok = erl_tar:extract(DerefTar, [{cwd, NewDirDeref}, verbose]), %% Verify that the files are there. - ?line ok = file:set_cwd(NewDirDeref), - ?line {ok, #file_info{type=regular}} = file:read_link_info(GoodSymlink), - ?line {ok, #file_info{type=regular}} = file:read_link_info(AFile), - ?line {ok, Expected} = file:read_file(GoodSymlink), - ?line {ok, Expected} = file:read_file(AFile), + ok = file:set_cwd(NewDirDeref), + {ok, #file_info{type=regular}} = file:read_link_info(GoodSymlink), + {ok, #file_info{type=regular}} = file:read_link_info(AFile), + {ok, Expected} = file:read_file(GoodSymlink), + {ok, Expected} = file:read_file(AFile), ok. long_symlink(Dir) -> - ?line Tar = filename:join(Dir, "long_symlink.tar"), - ?line ok = file:set_cwd(Dir), - - ?line AFile = "long_symlink", - ?line FarTooLong = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed", - ?line ok = file:make_symlink(FarTooLong, AFile), - ?line {error,Error} = erl_tar:create(Tar, [AFile], [verbose]), - ?line io:format("Error: ~s\n", [erl_tar:format_error(Error)]), - ?line {FarTooLong,symbolic_link_too_long} = Error, + Tar = filename:join(Dir, "long_symlink.tar"), + ok = file:set_cwd(Dir), + + AFile = "long_symlink", + RequiresPAX = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed", + ok = file:make_symlink(RequiresPAX, AFile), + ok = erl_tar:create(Tar, [AFile], [verbose]), + false = is_ustar(Tar), + NewDir = filename:join(Dir, "extracted"), + _ = file:make_dir(NewDir), + ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]), + ok = file:set_cwd(NewDir), + {ok, #file_info{type=symlink}} = file:read_link_info(AFile), + {ok, RequiresPAX} = file:read_link(AFile), ok. +init(Config) when is_list(Config) -> + PrivDir = proplists:get_value(priv_dir, Config), + ok = file:set_cwd(PrivDir), + Dir = filename:join(PrivDir, "init"), + ok = file:make_dir(Dir), + + [{FileOne,_,_}|_] = oac_files(), + TarOne = filename:join(Dir, "archive1.tar"), + {ok,Fd} = file:open(TarOne, [write]), + + %% If the arity of the fun is wrong, badarg should be returned + {error, badarg} = erl_tar:init(Fd, write, fun file_op_bad/1), + + %% Otherwise we should be good to go + {ok, Tar} = erl_tar:init(Fd, write, fun file_op/2), + ok = erl_tar:add(Tar, FileOne, []), + ok = erl_tar:close(Tar), + {ok, [FileOne]} = erl_tar:table(TarOne), + + verify_ports(Config). + +file_op_bad(_) -> + throw({error, should_never_be_called}). + +file_op(write, {Fd, Data}) -> + file:write(Fd, Data); +file_op(position, {Fd, Pos}) -> + file:position(Fd, Pos); +file_op(read2, {Fd, Size}) -> + file:read(Fd, Size); +file_op(close, Fd) -> + file:close(Fd). + open_add_close(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), - ?line ok = file:set_cwd(PrivDir), - ?line Dir = filename:join(PrivDir, "open_add_close"), - ?line ok = file:make_dir(Dir), - - ?line [{FileOne,_,_},{FileTwo,_,_},{FileThree,_,_}] = oac_files(), - ?line ADir = "empty_dir", - ?line AnotherDir = "another_dir", - ?line SomeContent = filename:join(AnotherDir, "some_content"), - ?line ok = file:make_dir(ADir), - ?line ok = file:make_dir(AnotherDir), - ?line ok = file:make_dir(SomeContent), - - ?line TarOne = filename:join(Dir, "archive1.tar"), - ?line {ok,AD} = erl_tar:open(TarOne, [write]), - ?line ok = erl_tar:add(AD, FileOne, []), - ?line ok = erl_tar:add(AD, FileTwo, "second file", []), - ?line ok = erl_tar:add(AD, FileThree, [verbose]), - ?line ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]), - ?line ok = erl_tar:add(AD, ADir, [verbose]), - ?line ok = erl_tar:add(AD, AnotherDir, [verbose]), - ?line ok = erl_tar:close(AD), - - ?line ok = erl_tar:t(TarOne), - ?line ok = erl_tar:tt(TarOne), - - ?line {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]} = erl_tar:table(TarOne), - - ?line delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]), + PrivDir = proplists:get_value(priv_dir, Config), + ok = file:set_cwd(PrivDir), + Dir = filename:join(PrivDir, "open_add_close"), + ok = file:make_dir(Dir), - ok. + [{FileOne,_,_},{FileTwo,_,_},{FileThree,_,_}] = oac_files(), + ADir = "empty_dir", + AnotherDir = "another_dir", + SomeContent = filename:join(AnotherDir, "some_content"), + ok = file:make_dir(ADir), + ok = file:make_dir(AnotherDir), + ok = file:make_dir(SomeContent), + + TarOne = filename:join(Dir, "archive1.tar"), + {ok,AD} = erl_tar:open(TarOne, [write]), + ok = erl_tar:add(AD, FileOne, []), + + %% Add with {NameInArchive,Name} + ok = erl_tar:add(AD, {"second file", FileTwo}, []), + + %% Add with {binary, Bin} + {ok,FileThreeBin} = file:read_file(FileThree), + ok = erl_tar:add(AD, {FileThree, FileThreeBin}, [verbose]), + + %% Add with Name + ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]), + ok = erl_tar:add(AD, ADir, [verbose]), + ok = erl_tar:add(AD, AnotherDir, [verbose]), + ok = erl_tar:close(AD), + true = is_ustar(TarOne), + + ok = erl_tar:t(TarOne), + ok = erl_tar:tt(TarOne), + + Expected = {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]}, + Expected = erl_tar:table(TarOne), + + delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]), + + verify_ports(Config). oac_files() -> Files = [{"oac_file", 1459, $x}, @@ -678,73 +774,116 @@ oac_files() -> cooked_compressed(Config) when is_list(Config) -> %% Test that a compressed archive can be read in cooked mode. - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"), %% Try table/2 and extract/2. - ?line {ok,List} = erl_tar:table(Name, [cooked,compressed]), - ?line io:format("~p\n", [List]), - ?line 19 = length(List), - ?line ok = erl_tar:extract(Name, [cooked,compressed,{cwd,PrivDir}]), + {ok,List} = erl_tar:table(Name, [cooked,compressed]), + io:format("~p\n", [List]), + 19 = length(List), + ok = erl_tar:extract(Name, [cooked,compressed,{cwd,PrivDir}]), %% Clean up while at the same time testing that all file %% were extracted as expected. lists:foreach(fun(N) -> File = filename:join(PrivDir, N), io:format("Deleting: ~p\n", [File]), - ?line ok = file:delete(File) + ok = file:delete(File) end, List), %% Clean up. - ?line delete_files([filename:join(PrivDir, "ddll_SUITE_data")]), - ok. + delete_files([filename:join(PrivDir, "ddll_SUITE_data")]), + + verify_ports(Config). -memory(doc) -> - ["Test that an archive can be created directly from binaries and " - "that an archive can be extracted into binaries."]; +%% Test that an archive can be created directly from binaries and +%% that an archive can be extracted into binaries. memory(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - - ?line FileBins = [{"bar/fum", <<"BARFUM">>},{"foo", <<"FOO">>}], - ?line Name1 = filename:join(DataDir, "memory.tar"), - ?line ok = erl_tar:create(Name1, FileBins, [write,verbose]), - ?line {ok,Extracted1} = erl_tar:extract(Name1, [memory,verbose]), - ?line FileBins1 = lists:sort(Extracted1), - - ?line io:format("FileBins: ~p\n", [FileBins]), - ?line io:format("FileBins1: ~p\n", [FileBins1]), - ?line FileBins = FileBins1, - - ?line Name2 = filename:join(DataDir, "memory2.tar"), - ?line {ok,Fd} = erl_tar:open(Name2, [write]), - ?line [ok,ok] = [erl_tar:add(Fd, B, N, [write,verbose]) || {N,B} <- FileBins], - ?line ok = erl_tar:close(Fd), - ?line {ok,Extracted2} = erl_tar:extract(Name2, [memory,verbose]), - ?line FileBins2 = lists:sort(Extracted2), - ?line io:format("FileBins2: ~p\n", [FileBins2]), - ?line FileBins = FileBins2, + DataDir = proplists:get_value(data_dir, Config), + + FileBins = [{"bar/fum", <<"BARFUM">>},{"foo", <<"FOO">>}], + Name1 = filename:join(DataDir, "memory.tar"), + ok = erl_tar:create(Name1, FileBins, [write,verbose]), + {ok,Extracted1} = erl_tar:extract(Name1, [memory,verbose]), + FileBins1 = lists:sort(Extracted1), + + io:format("FileBins: ~p\n", [FileBins]), + io:format("FileBins1: ~p\n", [FileBins1]), + FileBins = FileBins1, + + Name2 = filename:join(DataDir, "memory2.tar"), + {ok,Fd} = erl_tar:open(Name2, [write]), + [ok,ok] = [erl_tar:add(Fd, B, N, [write,verbose]) || {N,B} <- FileBins], + ok = erl_tar:close(Fd), + {ok,Extracted2} = erl_tar:extract(Name2, [memory,verbose]), + FileBins2 = lists:sort(Extracted2), + io:format("FileBins2: ~p\n", [FileBins2]), + FileBins = FileBins2, %% Clean up. - ?line ok = delete_files([Name1,Name2]), - ok. + ok = delete_files([Name1,Name2]), + + verify_ports(Config). + +read_other_implementations(Config) when is_list(Config) -> + DataDir = proplists:get_value(data_dir, Config), + Files = ["v7.tar", "gnu.tar", "bsd.tar", + "star.tar", "pax_mtime.tar"], + do_read_other_implementations(Files, DataDir), + verify_ports(Config). + +do_read_other_implementations([], _DataDir) -> + ok; +do_read_other_implementations([File|Rest], DataDir) -> + io:format("~nTrying ~s", [File]), + Full = filename:join(DataDir, File), + {ok, _} = erl_tar:table(Full), + {ok, _} = erl_tar:extract(Full, [memory]), + do_read_other_implementations(Rest, DataDir). + + +%% Test handling of sparse files +sparse(Config) when is_list(Config) -> + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Sparse01Empty = "sparse01_empty.tar", + Sparse01 = "sparse01.tar", + Sparse10Empty = "sparse10_empty.tar", + Sparse10 = "sparse10.tar", + do_sparse([Sparse01Empty, Sparse01, Sparse10Empty, Sparse10], DataDir, PrivDir), + verify_ports(Config). + +do_sparse([], _DataDir, _PrivDir) -> + ok; +do_sparse([Name|Rest], DataDir, PrivDir) -> + io:format("~nTrying sparse file ~s", [Name]), + Full = filename:join(DataDir, Name), + {ok, [_]} = erl_tar:table(Full), + {ok, _} = erl_tar:extract(Full, [memory]), + do_sparse(Rest, DataDir, PrivDir). %% Test filenames with characters outside the US ASCII range. unicode(Config) when is_list(Config) -> - PrivDir = ?config(priv_dir, Config), - do_unicode(PrivDir), + run_unicode_node(Config, "+fnu"), 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; + run_unicode_node(Config, "+fnl"); false -> ok end. +run_unicode_node(Config, Option) -> + PrivDir = proplists:get_value(priv_dir, Config), + Pa = filename:dirname(code:which(?MODULE)), + Args = Option ++ " -pa "++Pa, + io:format("~s\n", [Args]), + Node = start_node(unicode, Args), + ok = rpc:call(Node, erlang, apply, + [fun() -> do_unicode(PrivDir) end,[]]), + true = test_server:stop_node(Node), + ok. + has_transparent_naming() -> case os:type() of {unix,darwin} -> false; @@ -756,10 +895,14 @@ do_unicode(PrivDir) -> ok = file:set_cwd(PrivDir), ok = file:make_dir("unicöde"), - Names = unicode_create_files(), + Names = lists:sort(unicode_create_files()), Tar = "unicöde.tar", ok = erl_tar:create(Tar, ["unicöde"], []), - {ok,Names} = erl_tar:table(Tar, []), + + %% Unicode filenames require PAX format. + false = is_ustar(Tar), + {ok,Names0} = erl_tar:table(Tar, []), + Names = lists:sort(Names0), _ = [ok = file:delete(Name) || Name <- Names], ok = erl_tar:extract(Tar), _ = [{ok,_} = file:read_file(Name) || Name <- Names], @@ -779,6 +922,100 @@ unicode_create_files() -> [] end]. +leading_slash(Config) -> + PrivDir = proplists:get_value(priv_dir, Config), + Dir = filename:join(PrivDir, ?FUNCTION_NAME), + TarFile = filename:join(Dir, "leading_slash.tar"), + ok = filelib:ensure_dir(TarFile), + {ok,Fd} = erl_tar:open(TarFile, [write]), + TarMemberName = "e/d/c/b/a_member", + TarMemberNameAbs = "/" ++ TarMemberName, + Contents = <<"contents\n">>, + ok = erl_tar:add(Fd, Contents, TarMemberNameAbs, [verbose]), + ok = erl_tar:close(Fd), + + ok = erl_tar:extract(TarFile, [{cwd,Dir}]), + + {ok,Contents} = file:read_file(filename:join(Dir, TarMemberName)), + ok. + +dotdot(Config) -> + PrivDir = proplists:get_value(priv_dir, Config), + Dir = filename:join(PrivDir, ?FUNCTION_NAME), + ok = file:make_dir(Dir), + Tar = filename:join(Dir, "dotdot.tar"), + {ok,Fd} = erl_tar:open(Tar, [write]), + BeamFile = code:which(?MODULE), + ok = erl_tar:add(Fd, BeamFile, "a/./../../some_file", []), + ok = erl_tar:close(Fd), + + {error,{_,unsafe_path=Error}} = erl_tar:extract(Tar, [{cwd,Dir}]), + false = filelib:is_regular(filename:join(PrivDir, "some_file")), + io:format("~s\n", [erl_tar:format_error(Error)]), + + ok. + +roundtrip_metadata(Config) -> + PrivDir = proplists:get_value(priv_dir, Config), + Dir = filename:join(PrivDir, ?FUNCTION_NAME), + ok = file:make_dir(Dir), + + do_roundtrip_metadata(Dir, "name-does-not-matter"), + ok. + +do_roundtrip_metadata(Dir, File) -> + Tar = filename:join(Dir, atom_to_list(?FUNCTION_NAME)++".tar"), + BeamFile = code:which(compile), + {ok,Fd} = erl_tar:open(Tar, [write]), + ok = erl_tar:add(Fd, BeamFile, File, []), + ok = erl_tar:close(Fd), + + ok = erl_tar:extract(Tar, [{cwd,Dir}]), + + %% Make sure that size and modification times are the same + %% on all platforms. + {ok,OrigInfo} = file:read_file_info(BeamFile), + ExtractedFile = filename:join(Dir, File), + {ok,ExtractedInfo} = file:read_file_info(ExtractedFile), + #file_info{size=Size,mtime=Mtime,type=regular} = OrigInfo, + #file_info{size=Size,mtime=Mtime,type=regular} = ExtractedInfo, + + %% On Unix platforms more fields are expected to be the same. + case os:type() of + {unix,_} -> + #file_info{access=Access,mode=Mode} = OrigInfo, + #file_info{access=Access,mode=Mode} = ExtractedInfo, + ok; + _ -> + ok + end. + +apply_file_info_opts(Config) when is_list(Config) -> + ok = file:set_cwd(proplists:get_value(priv_dir, Config)), + + ok = file:make_dir("empty_directory"), + ok = file:write_file("file", "contents"), + + Opts = [{atime, 0}, {mtime, 0}, {ctime, 0}, {uid, 0}, {gid, 0}], + TarFile = "reproducible.tar", + {ok, Tar} = erl_tar:open(TarFile, [write]), + ok = erl_tar:add(Tar, "file", Opts), + ok = erl_tar:add(Tar, "empty_directory", Opts), + ok = erl_tar:add(Tar, <<"contents">>, "memory_file", Opts), + erl_tar:close(Tar), + + ok = file:make_dir("extracted"), + erl_tar:extract(TarFile, [{cwd, "extracted"}]), + + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/empty_directory", [{time, posix}]), + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/file", [{time, posix}]), + {ok, #file_info{mtime=0}} = + file:read_file_info("extracted/memory_file", [{time, posix}]), + + ok. + %% Delete the given list of files. delete_files([]) -> ok; delete_files([Item|Rest]) -> @@ -811,7 +1048,7 @@ delete_files([Item|Rest]) -> %% 260 characters. run_in_short_tempdir(Config, Fun) -> {ok,Cwd} = file:get_cwd(), - PrivDir0 = ?config(priv_dir, Config), + PrivDir0 = proplists:get_value(priv_dir, Config), %% Normalize name to make sure that there is no slash at the end. PrivDir = filename:absname(PrivDir0), @@ -850,8 +1087,31 @@ start_node(Name, Args) -> 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); + ct:fail(Reason); {ok,Node} -> ct:log("Node ~p started~n", [Node]), Node end. + +%% Test that the given tar file is a plain USTAR archive, +%% without any PAX extensions. +is_ustar(File) -> + {ok,Bin} = file:read_file(File), + <<_:257/binary,"ustar",0,_/binary>> = Bin, + <<_:156/binary,Type:8,_/binary>> = Bin, + case Type of + $x -> false; + $g -> false; + _ -> true + end. + + +verify_ports(Config) -> + PortsBefore = proplists:get_value(ports, Config), + PortsAfter = ordsets:from_list(erlang:ports()), + case ordsets:subtract(PortsAfter, PortsBefore) of + [] -> + ok; + [_|_]=Rem -> + error({leaked_ports,Rem}) + end. |