diff options
author | Björn Gustavsson <[email protected]> | 2016-03-02 06:50:54 +0100 |
---|---|---|
committer | Björn Gustavsson <[email protected]> | 2016-03-09 13:22:59 +0100 |
commit | 33b414783b37dc0c242c729fa3fa843cd648e3e0 (patch) | |
tree | 7d4f40be30fca15fa09efdc89334246f4a0c7da9 /lib/stdlib/test/tar_SUITE.erl | |
parent | 477f490820a28e479527e93d420f26ea23fdf3e3 (diff) | |
download | otp-33b414783b37dc0c242c729fa3fa843cd648e3e0.tar.gz otp-33b414783b37dc0c242c729fa3fa843cd648e3e0.tar.bz2 otp-33b414783b37dc0c242c729fa3fa843cd648e3e0.zip |
Remove ?line macros
While we are it, also re-ident the files.
Diffstat (limited to 'lib/stdlib/test/tar_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 544 |
1 files changed, 272 insertions, 272 deletions
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 2584f9c01f..28f42c6b37 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -63,47 +63,47 @@ 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 = ?config(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. 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]), + Archive = filename:join(TempDir, "ar_"++integer_to_list(Size)++".tar"), + Name = filename:join(TempDir, "file_"++integer_to_list(Size)), + io:format("Testing size ~p", [Size]), %% 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), + 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]), + {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), + tar_tf(Archive, Name), ok. @@ -116,20 +116,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 @@ -142,21 +142,21 @@ 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), @@ -201,52 +201,52 @@ next_random(X) -> %% 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(?config(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. @@ -279,35 +279,35 @@ create_files([]) -> %% 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 = ?config(data_dir, Config), + Long = filename:join(DataDir, "long_names.tar"), run_in_short_tempdir(Config, fun() -> do_long_names(Long) end). 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. @@ -315,9 +315,9 @@ do_long_names(Long) -> %% longer than 100 characters). create_long_names(Config) when is_list(Config) -> run_in_short_tempdir(Config, fun create_long_names/0). - + create_long_names() -> - ?line {ok,Dir} = file:get_cwd(), + {ok,Dir} = file:get_cwd(), Dirs = ["aslfjkshjkhliuf", "asdhjfehnbfsky", "sahajfskdfhsz", @@ -325,45 +325,45 @@ 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), + 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. %% 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), + try_bad("bad_checksum", bad_header, Config), + try_bad("bad_octal", bad_header, Config), + try_bad("bad_too_short", eof, Config), + try_bad("bad_even_shorter", eof, Config), ok. try_bad(Name0, Reason, Config) -> - %% Intentionally no ?line macros here. + %% Intentionally no macros here. DataDir = ?config(data_dir, Config), PrivDir = ?config(priv_dir, Config), @@ -392,22 +392,22 @@ try_bad(Name0, Reason, Config) -> %% 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 = ?config(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]), - + delete_files([GoodTar,BadTar]), + ok. try_error(M, F, A, Error) -> @@ -439,102 +439,102 @@ remove_prefix(_, Result) -> %% 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 = ?config(data_dir, Config), + PrivDir = ?config(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. 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 = ?config(data_dir, Config), + PrivDir = ?config(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. %% 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 = ?config(data_dir, Config), + PrivDir = ?config(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. %% 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 = ?config(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]), Res. make_symlink(Path, Link) -> @@ -559,103 +559,103 @@ 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]), %% 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]), %% 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", + FarTooLong = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed", + ok = file:make_symlink(FarTooLong, AFile), + {error,Error} = erl_tar:create(Tar, [AFile], [verbose]), + io:format("Error: ~s\n", [erl_tar:format_error(Error)]), + {FarTooLong,symbolic_link_too_long} = Error, ok. 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 = ?config(priv_dir, Config), + ok = file:set_cwd(PrivDir), + Dir = filename:join(PrivDir, "open_add_close"), + ok = file:make_dir(Dir), + + [{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, []), + ok = erl_tar:add(AD, FileTwo, "second file", []), + ok = erl_tar:add(AD, FileThree, [verbose]), + 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), + + ok = erl_tar:t(TarOne), + ok = erl_tar:tt(TarOne), + + {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]} = erl_tar:table(TarOne), + + delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]), ok. @@ -668,54 +668,54 @@ 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 = ?config(data_dir, Config), + PrivDir = ?config(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")]), + delete_files([filename:join(PrivDir, "ddll_SUITE_data")]), ok. %% 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 = ?config(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 = delete_files([Name1,Name2]), ok. %% Test filenames with characters outside the US ASCII range. |