1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(tar_SUITE).
21
22-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
23	 init_per_group/2, end_per_group/2,
24         init_per_testcase/2,
25         borderline/1, atomic/1, long_names/1,
26	 create_long_names/1, bad_tar/1, errors/1, extract_from_binary/1,
27	 extract_from_binary_compressed/1, extract_filtered/1,
28	 extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1,
29	 memory/1,unicode/1,read_other_implementations/1,
30         sparse/1, init/1, leading_slash/1, dotdot/1,
31         roundtrip_metadata/1, apply_file_info_opts/1,
32         incompatible_options/1]).
33
34-include_lib("common_test/include/ct.hrl").
35-include_lib("kernel/include/file.hrl").
36
37suite() -> [{ct_hooks,[ts_install_cth]}].
38
39all() ->
40    [borderline, atomic, long_names, create_long_names,
41     bad_tar, errors, extract_from_binary,
42     extract_from_binary_compressed, extract_from_open_file,
43     extract_filtered,
44     symlinks, open_add_close, cooked_compressed, memory, unicode,
45     read_other_implementations,
46     sparse,init,leading_slash,dotdot,roundtrip_metadata,
47     apply_file_info_opts,incompatible_options].
48
49groups() ->
50    [].
51
52init_per_suite(Config) ->
53    Config.
54
55end_per_suite(_Config) ->
56    ok.
57
58init_per_group(_GroupName, Config) ->
59    Config.
60
61end_per_group(_GroupName, Config) ->
62    Config.
63
64init_per_testcase(_Case, Config) ->
65    Ports = ordsets:from_list(erlang:ports()),
66    [{ports,Ports}|Config].
67
68%% Test creating, listing and extracting one file from an archive,
69%% multiple times with different file sizes.  Also check that the file
70%% attributes of the extracted file has survived.
71borderline(Config) when is_list(Config) ->
72
73    %% Note: We cannot use absolute paths, because the pathnames will be
74    %% too long for the limit allowed in tar files (100 characters).
75    %% Therefore, strip off the current working directory from the front
76    %% of the private directory path.
77
78    {ok, Cwd} = file:get_cwd(),
79    RootDir = proplists:get_value(priv_dir, Config),
80    TempDir = remove_prefix(Cwd++"/", filename:join(RootDir, "borderline")),
81    ok = file:make_dir(TempDir),
82
83    Record = 512,
84    Block = 20 * Record,
85
86    lists:foreach(fun(Size) -> borderline_test(Size, TempDir) end,
87		  [0, 1, 10, 13, 127, 333, Record-1, Record, Record+1,
88		   Block-2*Record-1, Block-2*Record, Block-2*Record+1,
89		   Block-Record-1, Block-Record, Block-Record+1,
90		   Block-1, Block, Block+1,
91		   Block+Record-1, Block+Record, Block+Record+1]),
92
93    %% Clean up.
94    delete_files([TempDir]),
95
96    verify_ports(Config).
97
98borderline_test(Size, TempDir) ->
99    io:format("Testing size ~p", [Size]),
100    borderline_test(Size, TempDir, true),
101    borderline_test(Size, TempDir, false),
102    ok.
103
104borderline_test(Size, TempDir, IsUstar) ->
105    Prefix = case IsUstar of
106                 true ->
107                     "file_";
108                 false ->
109                     lists:duplicate(100, $f) ++ "ile_"
110             end,
111    SizeList = integer_to_list(Size),
112    Archive = filename:join(TempDir, "ar_"++ SizeList ++".tar"),
113    Name = filename:join(TempDir, Prefix++SizeList),
114
115    %% Create a file and archive it.
116    X0 = erlang:monotonic_time(),
117    ok = file:write_file(Name, random_byte_list(X0, Size)),
118    ok = erl_tar:create(Archive, [Name]),
119    ok = file:delete(Name),
120
121    %% Verify listing and extracting.
122    IsUstar = is_ustar(Archive),
123    {ok, [Name]} = erl_tar:table(Archive),
124    ok = erl_tar:extract(Archive, [verbose]),
125
126    %% Verify contents of extracted file.
127    {ok, Bin} = file:read_file(Name),
128    true = match_byte_list(X0, binary_to_list(Bin)),
129
130    %% Verify that Unix tar can read it.
131    case IsUstar of
132        true ->
133            tar_tf(Archive, Name);
134        false ->
135            ok
136    end,
137
138    ok.
139
140tar_tf(Archive, Name) ->
141    case os:type() of
142	{unix, _} ->
143	    tar_tf1(Archive, Name);
144	_ ->
145	    ok
146    end.
147
148tar_tf1(Archive, Name) ->
149    Expect = Name ++ "\n",
150    cmd_expect("tar tf " ++ Archive, Expect).
151
152%% We can't use os:cmd/1, because Unix 'tar tf Name' on Solaris never
153%% terminates when given an archive of a size it doesn't like.
154
155cmd_expect(Cmd, Expect) ->
156    Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]),
157    get_data(Port, Expect).
158
159get_data(Port, Expect) ->
160    receive
161	{Port, {data, Bytes}} ->
162	    get_data(Port, match_output(Bytes, Expect, Port));
163	{Port, eof} ->
164	    Port ! {self(), close},
165	    receive
166		{Port, closed} ->
167		    true
168	    end,
169	    receive
170		{'EXIT',  Port,  _} ->
171		    ok
172	    after 1 ->				% force context switch
173		    ok
174	    end,
175	    match_output(eof, Expect, Port)
176    end.
177
178match_output([C|Output], [C|Expect], Port) ->
179    match_output(Output, Expect, Port);
180match_output([_|_], [_|_], Port) ->
181    kill_port_and_fail(Port, badmatch);
182match_output([X|Output], [], Port) ->
183    kill_port_and_fail(Port, {too_much_data, [X|Output]});
184match_output([], Expect, _Port) ->
185    Expect;
186match_output(eof, [], _Port) ->
187    [];
188match_output(eof, _Expect, Port) ->
189    kill_port_and_fail(Port, unexpected_end_of_input).
190
191kill_port_and_fail(Port, Reason) ->
192    unlink(Port),
193    exit(Port, die),
194    ct:fail(Reason).
195
196make_cmd(Cmd) ->
197    case os:type() of
198	{win32, _} -> lists:concat(["cmd /c",  Cmd]);
199	{unix, _}  -> lists:concat(["sh -c '",  Cmd,  "'"])
200    end.
201
202%% Verifies a random byte list.
203
204match_byte_list(X0, [Byte|Rest]) ->
205    X = next_random(X0),
206    case (X bsr 26) band 16#ff of
207	Byte -> match_byte_list(X, Rest);
208	_ -> false
209    end;
210match_byte_list(_, []) ->
211    true.
212
213%% Generates a random byte list.
214
215random_byte_list(X0, Count) ->
216    random_byte_list(X0, Count, []).
217
218random_byte_list(X0, Count, Result) when Count > 0->
219    X = next_random(X0),
220    random_byte_list(X, Count-1, [(X bsr 26) band 16#ff|Result]);
221random_byte_list(_X, 0, Result) ->
222    lists:reverse(Result).
223
224%% This RNG is from line 21 on page 102 in Knuth: The Art of Computer Programming,
225%% Volume II, Seminumerical Algorithms.
226
227next_random(X) ->
228    (X*17059465+1) band 16#fffffffff.
229
230%% Test the 'atomic' operations: create/extract/table, on compressed
231%% and uncompressed archives.
232%% Also test the 'cooked' option.
233atomic(Config) when is_list(Config) ->
234    ok = file:set_cwd(proplists:get_value(priv_dir, Config)),
235    DataFiles = data_files(),
236    Names = [Name || {Name,_,_} <- DataFiles],
237    io:format("Names: ~p", [Names]),
238
239    %% Create an uncompressed archive.  The compressed flag should still be
240    %% allowed when listing contents or extracting.
241
242    Tar1 = "uncompressed.tar",
243    erl_tar:create(Tar1, Names, []),
244    {ok, Names} = erl_tar:table(Tar1, []),
245    {ok, Names} = erl_tar:table(Tar1, [compressed]),
246    {ok, Names} = erl_tar:table(Tar1, [cooked]),
247    {ok, Names} = erl_tar:table(Tar1, [compressed,cooked]),
248
249    %% Create a compressed archive.
250
251    Tar2 = "compressed.tar",
252    erl_tar:create(Tar2, Names, [compressed]),
253    {ok, Names} = erl_tar:table(Tar2, [compressed]),
254    {error, Reason} = erl_tar:table(Tar2, []),
255    {ok, Names} = erl_tar:table(Tar2, [compressed,cooked]),
256    {error, Reason} = erl_tar:table(Tar2, [cooked]),
257    ok = io:format("No compressed option: ~p, ~s",
258		   [Reason, erl_tar:format_error(Reason)]),
259
260    %% Same test again, but this time created with 'cooked'
261
262    Tar3 = "uncompressed_cooked.tar",
263    erl_tar:create(Tar3, Names, [cooked]),
264    {ok, Names} = erl_tar:table(Tar3, []),
265    {ok, Names} = erl_tar:table(Tar3, [compressed]),
266    {ok, Names} = erl_tar:table(Tar3, [cooked]),
267    {ok, Names} = erl_tar:table(Tar3, [compressed,cooked]),
268
269    Tar4 = "compressed_cooked.tar",
270    erl_tar:create(Tar4, Names, [compressed,cooked]),
271    {ok, Names} = erl_tar:table(Tar4, [compressed]),
272    {error, Reason} = erl_tar:table(Tar4, []),
273    {ok, Names} = erl_tar:table(Tar4, [compressed,cooked]),
274    {error, Reason} = erl_tar:table(Tar4, [cooked]),
275    ok = io:format("No compressed option: ~p, ~s",
276		   [Reason, erl_tar:format_error(Reason)]),
277
278    %% Clean up.
279    delete_files([Tar1,Tar2,Tar3,Tar4|Names]),
280
281    verify_ports(Config).
282
283%% Returns a sequence of characters.
284
285char_seq(N, First) ->
286    char_seq(N, First, []).
287
288char_seq(0, _, Result) ->
289    Result;
290char_seq(N, C, Result) when C < 127 ->
291    char_seq(N-1, C+1, [C|Result]);
292char_seq(N, _, Result) ->
293    char_seq(N, $!, Result).
294
295data_files() ->
296    Files = [{"first_file", 1555, $a},
297	     {"small_file", 7, $d},
298	     {"big_file", 23875, $e},
299	     {"last_file", 7500, $g}],
300    create_files(Files),
301    Files.
302
303create_files([{Name, Size, First}|Rest]) ->
304    ok = file:write_file(Name, char_seq(Size, First)),
305    create_files(Rest);
306create_files([]) ->
307    ok.
308
309%% Test to extract an Unix tar file containing filenames longer than
310%% 100 characters and empty directories.
311long_names(Config) when is_list(Config) ->
312    DataDir = proplists:get_value(data_dir, Config),
313    Long = filename:join(DataDir, "long_names.tar"),
314    run_in_short_tempdir(Config,
315			 fun() -> do_long_names(Long) end),
316    verify_ports(Config).
317
318
319do_long_names(Long) ->
320    %% Try table/2 and extract/2.
321    case erl_tar:table(Long, [verbose]) of
322	{ok,List} when is_list(List) ->
323	    io:format("~p\n", [List])
324    end,
325
326    {ok,Cwd} = file:get_cwd(),
327    ok = erl_tar:extract(Long),
328    Base = filename:join([Cwd, "original_software", "written_by",
329			  "a_bunch_of_hackers",
330			  "spending_all_their_nights",
331			  "still", "not_long_enough",
332			  "but_soon_it_will_be"]),
333
334    %% Verify that the empty directory was created.
335    EmptyDir = filename:join(Base, "empty_directory"),
336    {ok, #file_info{type=directory}} = file:read_file_info(EmptyDir),
337
338    %% Verify that the files were created.
339    {ok,First} = file:read_file(filename:join(Base, "first_file")),
340    {ok,Second} = file:read_file(filename:join(Base, "second_file")),
341    "Here"++_ = binary_to_list(First),
342    "And"++_ = binary_to_list(Second),
343
344    ok.
345
346%% Creates a tar file from a deep directory structure (filenames are
347%% longer than 100 characters).
348create_long_names(Config) when is_list(Config) ->
349    run_in_short_tempdir(Config, fun create_long_names/0),
350    verify_ports(Config).
351
352create_long_names() ->
353    {ok,Dir} = file:get_cwd(),
354    Dirs = ["aslfjkshjkhliuf",
355	    "asdhjfehnbfsky",
356	    "sahajfskdfhsz",
357	    "asldfkdlfy4y8rchg",
358	    "f7nafhjgffagkhsfkhsjk",
359	    "dfjasldkfjsdkfjashbv"],
360
361    DeepDir = make_dirs(Dirs, []),
362    AFile = filename:join(DeepDir, "a_file"),
363    Hello = "hello, world\n",
364    ok = file:write_file(AFile, Hello),
365    TarName = filename:join(Dir,  "my_tar_with_long_names.tar"),
366    ok = erl_tar:create(TarName, [AFile]),
367
368    %% Print contents.
369    ok = erl_tar:tt(TarName),
370
371    %% Extract and verify.
372    true = is_ustar(TarName),
373    ExtractDir = "extract_dir",
374    ok = file:make_dir(ExtractDir),
375    ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]),
376    {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)),
377    Hello = binary_to_list(Bin),
378
379    ok.
380
381make_dirs([Dir|Rest], []) ->
382    ok = file:make_dir(Dir),
383    make_dirs(Rest, Dir);
384make_dirs([Dir|Rest], Parent) ->
385    Name = filename:join(Parent, Dir),
386    ok = file:make_dir(Name),
387    make_dirs(Rest, Name);
388make_dirs([], Dir) ->
389    Dir.
390
391%% Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files.
392bad_tar(Config) when is_list(Config) ->
393    try_bad("bad_checksum", bad_header, Config),
394    try_bad("bad_octal",    invalid_tar_checksum, Config),
395    try_bad("bad_too_short",    eof, Config),
396    try_bad("bad_even_shorter", eof, Config),
397    verify_ports(Config).
398
399try_bad(Name0, Reason, Config) ->
400    %% Intentionally no macros here.
401
402    DataDir = proplists:get_value(data_dir, Config),
403    PrivDir = proplists:get_value(priv_dir, Config),
404    Name = Name0 ++ ".tar",
405    io:format("~nTrying ~s", [Name]),
406    Full = filename:join(DataDir, Name),
407    Dest = filename:join(PrivDir, Name0),
408    Opts = [verbose, {cwd, Dest}],
409    Expected = {error, Reason},
410    io:fwrite("Expected: ~p\n", [Expected]),
411    case {erl_tar:table(Full, Opts), erl_tar:extract(Full, Opts)} of
412	{Expected, Expected} ->
413	    io:format("Result: ~p", [Expected]),
414	    case catch erl_tar:format_error(Reason) of
415		{'EXIT', CrashReason} ->
416		    ct:fail({format_error, crashed, CrashReason});
417		String when is_list(String) ->
418		    io:format("format_error(~p) -> ~s", [Reason, String]);
419		Other ->
420		    ct:fail({format_error, returned, Other})
421	    end;
422	{Other1, Other2} ->
423	    io:format("table/2 returned ~p", [Other1]),
424	    io:format("extract/2 returned ~p", [Other2]),
425	    ct:fail({bad_return_value, Other1, Other2})
426    end.
427
428%% Tests that some common errors return correct error codes
429%% and that format_error/1 handles them correctly.
430errors(Config) when is_list(Config) ->
431    PrivDir = proplists:get_value(priv_dir, Config),
432
433    %% Give the tar file the same name as a directory.
434    BadTar = filename:join(PrivDir, "bad_tarfile.tar"),
435    ok = file:make_dir(BadTar),
436    try_error(erl_tar, create, [BadTar, []], {BadTar, eisdir}),
437
438    %% Try including non-existent files in the tar file.
439    NonExistent = "non_existent_file",
440    GoodTar = filename:join(PrivDir, "a_good_tarfile.tar"),
441    try_error(erl_tar, create, [GoodTar, [NonExistent]],
442	      {NonExistent, enoent}),
443
444    %% Clean up.
445    delete_files([GoodTar,BadTar]),
446
447    verify_ports(Config).
448
449try_error(M, F, A, Error) ->
450    io:format("Trying ~p:~p(~p)", [M, F, A]),
451    case catch apply(M, F, A) of
452	{'EXIT', Reason} ->
453	    exit(Reason);
454	ok ->
455	    ct:fail(unexpected_success);
456	{error, Error} ->
457	    case catch erl_tar:format_error(Error) of
458		{'EXIT', FReason} ->
459		    ct:fail({format_error, crashed, FReason});
460		String when is_list(String) ->
461		    io:format("format_error(~p) -> ~s", [Error, String]);
462		Other ->
463		    ct:fail({format_error, returned, Other})
464	    end;
465	Other ->
466	    ct:fail({expected, {error, Error}, actual, Other})
467    end.
468
469%% remove_prefix(Prefix, List) -> ListWithoutPrefix.
470
471remove_prefix([C|Rest1], [C|Rest2]) ->
472    remove_prefix(Rest1, Rest2);
473remove_prefix(_, Result) ->
474    Result.
475
476%% Test extracting a tar archive from a binary.
477extract_from_binary(Config) when is_list(Config) ->
478    DataDir = proplists:get_value(data_dir, Config),
479    PrivDir = proplists:get_value(priv_dir, Config),
480    Long = filename:join(DataDir, "no_fancy_stuff.tar"),
481    ExtractDir = filename:join(PrivDir, "extract_from_binary"),
482    ok = file:make_dir(ExtractDir),
483
484    %% Read a tar file into a binary and extract from the binary.
485    {ok, Bin} = file:read_file(Long),
486    ok = erl_tar:extract({binary, Bin}, [{cwd,ExtractDir}]),
487
488    %% Verify.
489    Dir = filename:join(ExtractDir, "no_fancy_stuff"),
490    true = filelib:is_dir(Dir),
491    true = filelib:is_file(filename:join(Dir, "a_dir_list")),
492    true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
493
494    %% Clean up.
495    delete_files([ExtractDir]),
496
497    verify_ports(Config).
498
499extract_from_binary_compressed(Config) when is_list(Config) ->
500    %% Test extracting a compressed tar archive from a binary.
501    DataDir = proplists:get_value(data_dir, Config),
502    PrivDir = proplists:get_value(priv_dir, Config),
503    Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
504    ExtractDir = filename:join(PrivDir, "extract_from_binary_compressed"),
505    ok = file:make_dir(ExtractDir),
506    {ok,Bin} = file:read_file(Name),
507
508    %% Try taking contents.
509    {ok,Files} = erl_tar:table({binary,Bin}, [compressed]),
510    io:format("~p\n", [Files]),
511    19 = length(Files),
512
513    %% Trying extracting from a binary.
514    ok = erl_tar:extract({binary,Bin}, [compressed,{cwd,ExtractDir}]),
515    {ok,List} = file:list_dir(filename:join(ExtractDir, "ddll_SUITE_data")),
516    io:format("~p\n", [List]),
517    19 = length(List),
518
519    %% Clean up while at the same time testing that all file
520    %% were extracted as expected.
521    lists:foreach(fun(N) ->
522			  File = filename:join(ExtractDir, N),
523			  io:format("Deleting: ~p\n", [File]),
524			  ok = file:delete(File)
525		  end, Files),
526
527    %% Clean up the rest.
528    delete_files([ExtractDir]),
529
530    verify_ports(Config).
531
532%% Test extracting a tar archive from a binary.
533extract_filtered(Config) when is_list(Config) ->
534    DataDir = proplists:get_value(data_dir, Config),
535    PrivDir = proplists:get_value(priv_dir, Config),
536    Long = filename:join(DataDir, "no_fancy_stuff.tar"),
537    ExtractDir = filename:join(PrivDir, "extract_from_binary"),
538    ok = file:make_dir(ExtractDir),
539
540    ok = erl_tar:extract(Long, [{cwd,ExtractDir},{files,["no_fancy_stuff/EPLICENCE"]}]),
541
542    %% Verify.
543    Dir = filename:join(ExtractDir, "no_fancy_stuff"),
544    true = filelib:is_dir(Dir),
545    false = filelib:is_file(filename:join(Dir, "a_dir_list")),
546    true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
547
548    %% Clean up.
549    delete_files([ExtractDir]),
550
551    verify_ports(Config).
552
553%% Test extracting a tar archive from an open file.
554extract_from_open_file(Config) when is_list(Config) ->
555    DataDir = proplists:get_value(data_dir, Config),
556    PrivDir = proplists:get_value(priv_dir, Config),
557    Long = filename:join(DataDir, "no_fancy_stuff.tar"),
558    ExtractDir = filename:join(PrivDir, "extract_from_open_file"),
559    ok = file:make_dir(ExtractDir),
560
561    {ok, File} = file:open(Long, [read]),
562    ok = erl_tar:extract({file, File}, [{cwd,ExtractDir}]),
563
564    %% Verify.
565    Dir = filename:join(ExtractDir, "no_fancy_stuff"),
566    true = filelib:is_dir(Dir),
567    true = filelib:is_file(filename:join(Dir, "a_dir_list")),
568    true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
569
570    %% Close open file.
571    ok = file:close(File),
572
573    %% Clean up.
574    delete_files([ExtractDir]),
575
576    verify_ports(Config).
577
578%% Make sure incompatible options are rejected when opening archives with file
579%% descriptors.
580incompatible_options(Config) when is_list(Config) ->
581    DataDir = proplists:get_value(data_dir, Config),
582    Long = filename:join(DataDir, "no_fancy_stuff.tar"),
583
584    {ok, File} = file:open(Long, [read]),
585    Handle = {file, File},
586
587    {error, {Handle, {incompatible_option, compressed}}}
588        = erl_tar:open(Handle, [read, compressed]),
589    {error, {Handle, {incompatible_option, cooked}}}
590        = erl_tar:open(Handle, [read, cooked]),
591
592    {error, {Handle, {incompatible_option, compressed}}}
593        = erl_tar:extract(Handle, [compressed]),
594    {error, {Handle, {incompatible_option, cooked}}}
595        = erl_tar:extract(Handle, [cooked]),
596
597    ok = file:close(File),
598
599    verify_ports(Config).
600
601%% Test that archives containing symlinks can be created and extracted.
602symlinks(Config) when is_list(Config) ->
603    PrivDir = proplists:get_value(priv_dir, Config),
604    Dir = filename:join(PrivDir, "symlinks"),
605    VulnerableDir = filename:join(PrivDir, "vulnerable_symlinks"),
606    ok = file:make_dir(Dir),
607    ok = file:make_dir(VulnerableDir),
608    ABadSymlink = filename:join(Dir, "bad_symlink"),
609    PointsTo = "a/definitely/non_existing/path",
610    Res = case make_symlink("a/definitely/non_existing/path", ABadSymlink) of
611	      {error, enotsup} ->
612		  {skip, "Symbolic links not supported on this platform"};
613	      ok ->
614		  symlinks(Dir, "bad_symlink", PointsTo),
615		  long_symlink(Dir),
616                  symlink_vulnerability(VulnerableDir)
617	  end,
618
619    %% Clean up.
620    delete_files([Dir,VulnerableDir]),
621    verify_ports(Config),
622    Res.
623
624make_symlink(Path, Link) ->
625    case os:type() of
626	{win32,_} ->
627	    %% Symlinks on Windows have two problems:
628	    %%   1) file:read_link_info/1 cannot read out the target
629	    %%      of the symlink if the target does not exist.
630	    %%      That is possible (but not easy) to fix in the
631	    %%      efile driver.
632	    %%
633	    %%   2) Symlinks to files and directories are different
634	    %%      creatures. If the target is not existing, the
635	    %%      symlink will be created to be of the file-pointing
636	    %%      type. That can be partially worked around in erl_tar
637	    %%      by creating all symlinks when the end of the tar
638	    %%      file has been reached.
639	    %%
640	    %% But for now, pretend that there are no symlinks on
641	    %% Windows.
642	    {error, enotsup};
643	_ ->
644	    file:make_symlink(Path, Link)
645    end.
646
647symlinks(Dir, BadSymlink, PointsTo) ->
648    Tar = filename:join(Dir, "symlink.tar"),
649    DerefTar = filename:join(Dir, "dereference.tar"),
650
651    %% Create the archive.
652
653    ok = file:set_cwd(Dir),
654    GoodSymlink = "good_symlink",
655    AFile = "a_good_file",
656    ALine = "A line of text for a file.",
657    ok = file:write_file(AFile, ALine),
658    ok = file:make_symlink(AFile, GoodSymlink),
659    ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]),
660    true = is_ustar(Tar),
661
662    %% List contents of tar file.
663
664    ok = erl_tar:tt(Tar),
665
666    %% Also create another archive with the dereference flag.
667
668    ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]),
669    true = is_ustar(DerefTar),
670
671    %% Extract files to a new directory.
672
673    NewDir = filename:join(Dir, "extracted"),
674    ok = file:make_dir(NewDir),
675    ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]),
676
677    %% Verify that the files are there.
678
679    ok = file:set_cwd(NewDir),
680    {ok, #file_info{type=symlink}} = file:read_link_info(BadSymlink),
681    {ok, PointsTo} = file:read_link(BadSymlink),
682    {ok, #file_info{type=symlink}} = file:read_link_info(GoodSymlink),
683    {ok, AFile} = file:read_link(GoodSymlink),
684    Expected = list_to_binary(ALine),
685    {ok, Expected} = file:read_file(GoodSymlink),
686
687    %% Extract the "dereferenced archive"  to a new directory.
688
689    NewDirDeref = filename:join(Dir, "extracted_deref"),
690    ok = file:make_dir(NewDirDeref),
691    ok = erl_tar:extract(DerefTar, [{cwd, NewDirDeref}, verbose]),
692
693    %% Verify that the files are there.
694
695    ok = file:set_cwd(NewDirDeref),
696    {ok, #file_info{type=regular}} = file:read_link_info(GoodSymlink),
697    {ok, #file_info{type=regular}} = file:read_link_info(AFile),
698    {ok, Expected} = file:read_file(GoodSymlink),
699    {ok, Expected} = file:read_file(AFile),
700
701    ok.
702
703long_symlink(Dir) ->
704    Tar = filename:join(Dir, "long_symlink.tar"),
705    ok = file:set_cwd(Dir),
706
707    AFile = "long_symlink",
708    RequiresPAX = "tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed",
709    ok = file:make_symlink(RequiresPAX, AFile),
710    ok = erl_tar:create(Tar, [AFile], [verbose]),
711    false = is_ustar(Tar),
712    NewDir = filename:join(Dir, "extracted"),
713    _ = file:make_dir(NewDir),
714    ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]),
715    ok = file:set_cwd(NewDir),
716    {ok, #file_info{type=symlink}} = file:read_link_info(AFile),
717    {ok, RequiresPAX} = file:read_link(AFile),
718    ok.
719
720symlink_vulnerability(Dir) ->
721    ok = file:set_cwd(Dir),
722    ok = file:make_dir("tar"),
723    ok = file:set_cwd("tar"),
724    ok = file:make_symlink("..", "link"),
725    ok = file:write_file("../file", <<>>),
726    ok = erl_tar:create("../my.tar", ["link","link/file"]),
727    ok = erl_tar:tt("../my.tar"),
728
729    ok = file:set_cwd(Dir),
730    delete_files(["file","tar"]),
731    ok = file:make_dir("tar"),
732    ok = file:set_cwd("tar"),
733    {error,{"..",unsafe_symlink}} = erl_tar:extract("../my.tar"),
734
735    ok.
736
737init(Config) when is_list(Config) ->
738    PrivDir = proplists:get_value(priv_dir, Config),
739    ok = file:set_cwd(PrivDir),
740    Dir = filename:join(PrivDir, "init"),
741    ok = file:make_dir(Dir),
742
743    [{FileOne,_,_}|_] = oac_files(),
744    TarOne = filename:join(Dir, "archive1.tar"),
745    {ok,Fd} = file:open(TarOne, [write]),
746
747    %% If the arity of the fun is wrong, badarg should be returned
748    {error, badarg} = erl_tar:init(Fd, write, fun file_op_bad/1),
749
750    %% Otherwise we should be good to go
751    {ok, Tar} = erl_tar:init(Fd, write, fun file_op/2),
752    ok = erl_tar:add(Tar, FileOne, []),
753    ok = erl_tar:close(Tar),
754    {ok, [FileOne]} = erl_tar:table(TarOne),
755
756    verify_ports(Config).
757
758file_op_bad(_) ->
759    throw({error, should_never_be_called}).
760
761file_op(write, {Fd, Data}) ->
762    file:write(Fd, Data);
763file_op(position, {Fd, Pos}) ->
764    file:position(Fd, Pos);
765file_op(read2, {Fd, Size}) ->
766    file:read(Fd, Size);
767file_op(close, Fd) ->
768    file:close(Fd).
769
770open_add_close(Config) when is_list(Config) ->
771    PrivDir = proplists:get_value(priv_dir, Config),
772    ok = file:set_cwd(PrivDir),
773    Dir = filename:join(PrivDir, "open_add_close"),
774    ok = file:make_dir(Dir),
775
776    [{FileOne,_,_},{FileTwo,_,_},{FileThree,_,_}] = oac_files(),
777    ADir = "empty_dir",
778    AnotherDir = "another_dir",
779    SomeContent = filename:join(AnotherDir, "some_content"),
780    ok = file:make_dir(ADir),
781    ok = file:make_dir(AnotherDir),
782    ok = file:make_dir(SomeContent),
783
784    TarOne = filename:join(Dir, "archive1.tar"),
785    {ok,AD} = erl_tar:open(TarOne, [write]),
786    ok = erl_tar:add(AD, FileOne, []),
787
788    %% Add with {NameInArchive,Name}
789    ok = erl_tar:add(AD, {"second file", FileTwo}, []),
790
791    %% Add with {binary, Bin}
792    {ok,FileThreeBin} = file:read_file(FileThree),
793    ok = erl_tar:add(AD, {FileThree, FileThreeBin}, [verbose]),
794
795    %% Add with Name
796    ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]),
797    ok = erl_tar:add(AD, ADir, [verbose]),
798    ok = erl_tar:add(AD, AnotherDir, [verbose]),
799    ok = erl_tar:close(AD),
800    true = is_ustar(TarOne),
801
802    ok = erl_tar:t(TarOne),
803    ok = erl_tar:tt(TarOne),
804
805    Expected = {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]},
806    Expected = erl_tar:table(TarOne),
807
808    delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]),
809
810    verify_ports(Config).
811
812oac_files() ->
813    Files = [{"oac_file", 1459, $x},
814	     {"oac_small", 99, $w},
815	     {"oac_big", 33896, $A}],
816    create_files(Files),
817    Files.
818
819cooked_compressed(Config) when is_list(Config) ->
820    %% Test that a compressed archive can be read in cooked mode.
821    DataDir = proplists:get_value(data_dir, Config),
822    PrivDir = proplists:get_value(priv_dir, Config),
823    Name = filename:join(DataDir, "cooked_tar_problem.tar.gz"),
824
825    %% Try table/2 and extract/2.
826    {ok,List} = erl_tar:table(Name, [cooked,compressed]),
827    io:format("~p\n", [List]),
828    19 = length(List),
829    ok = erl_tar:extract(Name, [cooked,compressed,{cwd,PrivDir}]),
830
831    %% Clean up while at the same time testing that all file
832    %% were extracted as expected.
833    lists:foreach(fun(N) ->
834			  File = filename:join(PrivDir, N),
835			  io:format("Deleting: ~p\n", [File]),
836			  ok = file:delete(File)
837		  end, List),
838
839    %% Clean up.
840    delete_files([filename:join(PrivDir, "ddll_SUITE_data")]),
841
842    verify_ports(Config).
843
844%% Test that an archive can be created directly from binaries and
845%% that an archive can be extracted into binaries.
846memory(Config) when is_list(Config) ->
847    DataDir = proplists:get_value(data_dir, Config),
848
849    FileBins = [{"bar/fum", <<"BARFUM">>},{"foo", <<"FOO">>}],
850    Name1 = filename:join(DataDir, "memory.tar"),
851    ok = erl_tar:create(Name1, FileBins, [write,verbose]),
852    {ok,Extracted1} = erl_tar:extract(Name1, [memory,verbose]),
853    FileBins1 = lists:sort(Extracted1),
854
855    io:format("FileBins: ~p\n", [FileBins]),
856    io:format("FileBins1: ~p\n", [FileBins1]),
857    FileBins = FileBins1,
858
859    Name2 = filename:join(DataDir, "memory2.tar"),
860    {ok,Fd} = erl_tar:open(Name2, [write]),
861    [ok,ok] = [erl_tar:add(Fd, B, N, [write,verbose]) || {N,B} <- FileBins],
862    ok = erl_tar:close(Fd),
863    {ok,Extracted2} = erl_tar:extract(Name2, [memory,verbose]),
864    FileBins2 = lists:sort(Extracted2),
865    io:format("FileBins2: ~p\n", [FileBins2]),
866    FileBins = FileBins2,
867
868    %% Clean up.
869    ok = delete_files([Name1,Name2]),
870
871    verify_ports(Config).
872
873read_other_implementations(Config) when is_list(Config) ->
874    DataDir = proplists:get_value(data_dir, Config),
875    Files = ["v7.tar", "gnu.tar", "bsd.tar",
876             "star.tar", "pax_mtime.tar"],
877    do_read_other_implementations(Files, DataDir),
878    verify_ports(Config).
879
880do_read_other_implementations([], _DataDir) ->
881    ok;
882do_read_other_implementations([File|Rest], DataDir) ->
883    io:format("~nTrying ~s", [File]),
884    Full = filename:join(DataDir, File),
885    {ok, _} = erl_tar:table(Full),
886    {ok, _} = erl_tar:extract(Full, [memory]),
887    do_read_other_implementations(Rest, DataDir).
888
889
890%% Test handling of sparse files
891sparse(Config) when is_list(Config) ->
892    DataDir = proplists:get_value(data_dir, Config),
893    PrivDir = proplists:get_value(priv_dir, Config),
894    Sparse01Empty = "sparse01_empty.tar",
895    Sparse01 = "sparse01.tar",
896    Sparse10Empty = "sparse10_empty.tar",
897    Sparse10 = "sparse10.tar",
898    do_sparse([Sparse01Empty, Sparse01, Sparse10Empty, Sparse10], DataDir, PrivDir),
899    verify_ports(Config).
900
901do_sparse([], _DataDir, _PrivDir) ->
902    ok;
903do_sparse([Name|Rest], DataDir, PrivDir) ->
904    io:format("~nTrying sparse file ~s", [Name]),
905    Full = filename:join(DataDir, Name),
906    {ok, [_]} = erl_tar:table(Full),
907    {ok, _} = erl_tar:extract(Full, [memory]),
908    do_sparse(Rest, DataDir, PrivDir).
909
910%% Test filenames with characters outside the US ASCII range.
911unicode(Config) when is_list(Config) ->
912    run_unicode_node(Config, "+fnu"),
913    case has_transparent_naming() of
914	true ->
915	    run_unicode_node(Config, "+fnl");
916	false ->
917	    ok
918    end.
919
920run_unicode_node(Config, Option) ->
921    PrivDir = proplists:get_value(priv_dir, Config),
922    Pa = filename:dirname(code:which(?MODULE)),
923    Args = Option ++ " -pa "++Pa,
924    io:format("~s\n", [Args]),
925    Node = start_node(unicode, Args),
926    ok = rpc:call(Node, erlang, apply,
927		  [fun() -> do_unicode(PrivDir) end,[]]),
928    true = test_server:stop_node(Node),
929    ok.
930
931has_transparent_naming() ->
932    case os:type() of
933	{unix,darwin} -> false;
934	{unix,_} -> true;
935	_ -> false
936    end.
937
938do_unicode(PrivDir) ->
939    ok = file:set_cwd(PrivDir),
940    ok = file:make_dir("unicöde"),
941
942    Names = lists:sort(unicode_create_files()),
943    Tar = "unicöde.tar",
944    ok = erl_tar:create(Tar, ["unicöde"], []),
945
946    %% Unicode filenames require PAX format.
947    false = is_ustar(Tar),
948    {ok,Names0} = erl_tar:table(Tar, []),
949    Names = lists:sort(Names0),
950    _ = [ok = file:delete(Name) || Name <- Names],
951    ok = erl_tar:extract(Tar),
952    _ = [{ok,_} = file:read_file(Name) || Name <- Names],
953    _ = [ok = file:delete(Name) || Name <- Names],
954    ok = file:del_dir("unicöde"),
955    ok.
956
957unicode_create_files() ->
958    FileA = "unicöde/smörgåsbord",
959    ok = file:write_file(FileA, "yum!\n"),
960    [FileA|case file:native_name_encoding() of
961	       utf8 ->
962		   FileB = "unicöde/Хороший файл!",
963		   ok = file:write_file(FileB, "But almost empty.\n"),
964		   [FileB];
965	       latin1 ->
966		   []
967	   end].
968
969leading_slash(Config) ->
970    PrivDir = proplists:get_value(priv_dir, Config),
971    Dir = filename:join(PrivDir, ?FUNCTION_NAME),
972    TarFile = filename:join(Dir, "leading_slash.tar"),
973    ok = filelib:ensure_dir(TarFile),
974    {ok,Fd} = erl_tar:open(TarFile, [write]),
975    TarMemberName = "e/d/c/b/a_member",
976    TarMemberNameAbs = "/" ++ TarMemberName,
977    Contents = <<"contents\n">>,
978    ok = erl_tar:add(Fd, Contents, TarMemberNameAbs, [verbose]),
979    ok = erl_tar:close(Fd),
980
981    ok = erl_tar:extract(TarFile, [{cwd,Dir}]),
982
983    {ok,Contents} = file:read_file(filename:join(Dir, TarMemberName)),
984    ok.
985
986dotdot(Config) ->
987    PrivDir = proplists:get_value(priv_dir, Config),
988    Dir = filename:join(PrivDir, ?FUNCTION_NAME),
989    ok = file:make_dir(Dir),
990    Tar = filename:join(Dir, "dotdot.tar"),
991    {ok,Fd} = erl_tar:open(Tar, [write]),
992    BeamFile = code:which(?MODULE),
993    ok = erl_tar:add(Fd, BeamFile, "a/./../../some_file", []),
994    ok = erl_tar:close(Fd),
995
996    {error,{_,unsafe_path=Error}} = erl_tar:extract(Tar, [{cwd,Dir}]),
997    false = filelib:is_regular(filename:join(PrivDir, "some_file")),
998    io:format("~s\n", [erl_tar:format_error(Error)]),
999
1000    ok.
1001
1002roundtrip_metadata(Config) ->
1003    PrivDir = proplists:get_value(priv_dir, Config),
1004    Dir = filename:join(PrivDir, ?FUNCTION_NAME),
1005    ok = file:make_dir(Dir),
1006
1007    do_roundtrip_metadata(Dir, "name-does-not-matter"),
1008    ok.
1009
1010do_roundtrip_metadata(Dir, File) ->
1011    Tar = filename:join(Dir, atom_to_list(?FUNCTION_NAME)++".tar"),
1012    BeamFile = code:which(compile),
1013    {ok,Fd} = erl_tar:open(Tar, [write]),
1014    ok = erl_tar:add(Fd, BeamFile, File, []),
1015    ok = erl_tar:close(Fd),
1016
1017    ok = erl_tar:extract(Tar, [{cwd,Dir}]),
1018
1019    %% Make sure that size and modification times are the same
1020    %% on all platforms.
1021    {ok,OrigInfo} = file:read_file_info(BeamFile),
1022    ExtractedFile = filename:join(Dir, File),
1023    {ok,ExtractedInfo} = file:read_file_info(ExtractedFile),
1024    #file_info{size=Size,mtime=Mtime,type=regular} = OrigInfo,
1025    #file_info{size=Size,mtime=Mtime,type=regular} = ExtractedInfo,
1026
1027    %% On Unix platforms more fields are expected to be the same.
1028    case os:type() of
1029        {unix,_} ->
1030            #file_info{access=Access,mode=Mode} = OrigInfo,
1031            #file_info{access=Access,mode=Mode} = ExtractedInfo,
1032            ok;
1033        _ ->
1034            ok
1035    end.
1036
1037apply_file_info_opts(Config) when is_list(Config) ->
1038    ok = file:set_cwd(proplists:get_value(priv_dir, Config)),
1039
1040    ok = file:make_dir("empty_directory"),
1041    ok = file:write_file("file", "contents"),
1042
1043    Opts = [{atime, 0}, {mtime, 0}, {ctime, 0}, {uid, 0}, {gid, 0}],
1044    TarFile = "reproducible.tar",
1045    {ok, Tar} = erl_tar:open(TarFile, [write]),
1046    ok = erl_tar:add(Tar, "file", Opts),
1047    ok = erl_tar:add(Tar, "empty_directory", Opts),
1048    ok = erl_tar:add(Tar, <<"contents">>, "memory_file", Opts),
1049    erl_tar:close(Tar),
1050
1051    ok = file:make_dir("extracted"),
1052    erl_tar:extract(TarFile, [{cwd, "extracted"}]),
1053
1054    {ok, #file_info{mtime=0}} =
1055        file:read_file_info("extracted/empty_directory", [{time, posix}]),
1056    {ok, #file_info{mtime=0}} =
1057        file:read_file_info("extracted/file", [{time, posix}]),
1058    {ok, #file_info{mtime=0}} =
1059        file:read_file_info("extracted/memory_file", [{time, posix}]),
1060
1061    ok.
1062
1063%% Delete the given list of files.
1064delete_files([]) -> ok;
1065delete_files([Item|Rest]) ->
1066    case file:delete(Item) of
1067	ok ->
1068	    delete_files(Rest);
1069	{error,eperm} ->
1070	    file:change_mode(Item, 8#777),
1071	    delete_files(filelib:wildcard(filename:join(Item, "*"))),
1072	    file:del_dir(Item),
1073	    ok;
1074	{error,eacces} ->
1075	    %% We'll see about that!
1076	    file:change_mode(Item, 8#777),
1077	    case file:delete(Item) of
1078		ok -> ok;
1079		{error,_} ->
1080		    erlang:yield(),
1081		    file:change_mode(Item, 8#777),
1082		    file:delete(Item),
1083		    ok
1084	    end;
1085	{error,_} -> ok
1086    end,
1087    delete_files(Rest).
1088
1089%% Move to a temporary directory with as short name as possible and
1090%% execute Fun. Remove the directory and any files in it afterwards.
1091%% This is necessary because pathnames on Windows may be limited to
1092%% 260 characters.
1093run_in_short_tempdir(Config, Fun) ->
1094    {ok,Cwd} = file:get_cwd(),
1095    PrivDir0 = proplists:get_value(priv_dir, Config),
1096
1097    %% Normalize name to make sure that there is no slash at the end.
1098    PrivDir = filename:absname(PrivDir0),
1099
1100    %% We need a base directory with a much shorter pathname than
1101    %% priv_dir. We KNOW that priv_dir is located four levels below
1102    %% the directory that common_test puts the ct_run.* directories
1103    %% in. That fact is not documented, but a usually reliable source
1104    %% assured me that the directory structure is unlikely to change
1105    %% in future versions of common_test because of backwards
1106    %% compatibility (tools developed by users of common_test depend
1107    %% on the current directory layout).
1108    Base = lists:foldl(fun(_, D) ->
1109			       filename:dirname(D)
1110		       end, PrivDir, [1,2,3,4]),
1111
1112    Dir = make_temp_dir(Base, 0),
1113    ok = file:set_cwd(Dir),
1114    io:format("Running test in ~s\n", [Dir]),
1115    try
1116	Fun()
1117    after
1118	file:set_cwd(Cwd),
1119	delete_files([Dir])
1120    end.
1121
1122make_temp_dir(Base, I) ->
1123    Name = filename:join(Base, integer_to_list(I, 36)),
1124    case file:make_dir(Name) of
1125	ok -> Name;
1126	{error,eexist} -> make_temp_dir(Base, I+1)
1127    end.
1128
1129start_node(Name, Args) ->
1130    [_,Host] = string:tokens(atom_to_list(node()), "@"),
1131    ct:log("Trying to start ~w@~s~n", [Name,Host]),
1132    case test_server:start_node(Name, peer, [{args,Args}]) of
1133	{error,Reason} ->
1134	    ct:fail(Reason);
1135	{ok,Node} ->
1136	    ct:log("Node ~p started~n", [Node]),
1137	    Node
1138    end.
1139
1140%% Test that the given tar file is a plain USTAR archive,
1141%% without any PAX extensions.
1142is_ustar(File) ->
1143    {ok,Bin} = file:read_file(File),
1144    <<_:257/binary,"ustar",0,_/binary>> = Bin,
1145    <<_:156/binary,Type:8,_/binary>> = Bin,
1146    case Type of
1147        $x -> false;
1148        $g -> false;
1149        _ -> true
1150    end.
1151
1152
1153verify_ports(Config) ->
1154    PortsBefore = proplists:get_value(ports, Config),
1155    PortsAfter = ordsets:from_list(erlang:ports()),
1156    case ordsets:subtract(PortsAfter, PortsBefore) of
1157        [] ->
1158            ok;
1159        [_|_]=Rem ->
1160            error({leaked_ports,Rem})
1161    end.
1162