File 2369-Add-options-for-creating-reproducible-tars.patch of Package erlang

From bd3dc9ac24d76bbdc8ce973a739fd52b5caa63ff Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Eric=20Meadows-J=C3=B6nsson?=
 <eric.meadows.jonsson@gmail.com>
Date: Wed, 25 Oct 2017 21:12:21 +0200
Subject: [PATCH 2/2] Add options for creating reproducible tars

---
 lib/stdlib/doc/src/erl_tar.xml | 41 +++++++++++++++++++++++-
 lib/stdlib/src/erl_tar.erl     | 72 ++++++++++++++++++++++++++++++++----------
 lib/stdlib/src/erl_tar.hrl     | 16 ++++++++--
 lib/stdlib/test/tar_SUITE.erl  | 30 ++++++++++++++++--
 4 files changed, 137 insertions(+), 22 deletions(-)

diff --git a/lib/stdlib/doc/src/erl_tar.xml b/lib/stdlib/doc/src/erl_tar.xml
index 337028568a..caf8f4a96d 100644
--- a/lib/stdlib/doc/src/erl_tar.xml
+++ b/lib/stdlib/doc/src/erl_tar.xml
@@ -4,7 +4,7 @@
 <erlref>
   <header>
     <copyright>
-      <year>2003</year><year>2016</year>
+      <year>2003</year><year>2018</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -136,6 +136,9 @@
         <v>Filename = filename()|{NameInArchive,FilenameOrBin}</v>
         <v>Options = [Option]</v>
         <v>Option = dereference|verbose|{chunks,ChunkSize}</v>
+           <v>|{atime,non_neg_integer()}|{mtime,non_neg_integer()}</v>
+           <v>|{ctime,non_neg_integer()}|{uid,non_neg_integer()}</v>
+           <v>|{gid,non_neg_integer()}</v>
         <v>ChunkSize = positive_integer()</v>
         <v>RetValue = ok|{error,{Filename,Reason}}</v>
         <v>Reason = term()</v>
@@ -167,6 +170,42 @@
               <seealso marker="ssh:ssh_sftp#open_tar/3">
               <c>ssh_sftp:open_tar/3</c></seealso>.</p>
           </item>
+          <tag><c>{atime,non_neg_integer()}</c></tag>
+          <item>
+            <p>Sets the last time, as
+	            <seealso marker="erts:time_correction#POSIX_Time">
+              POSIX time</seealso>, when the file was read. See also
+              <seealso marker="kernel:file#read_file_info/1">
+              <c>file:read_file_info/1</c></seealso>.</p>
+          </item>
+          <tag><c>{mtime,non_neg_integer()}</c></tag>
+          <item>
+            <p>Sets the last time, as
+	            <seealso marker="erts:time_correction#POSIX_Time">
+              POSIX time</seealso>, when the file was written. See also
+              <seealso marker="kernel:file#read_file_info/1">
+              <c>file:read_file_info/1</c></seealso>.</p>
+          </item>
+          <tag><c>{ctime,non_neg_integer()}</c></tag>
+          <item>
+            <p>Sets the time, as
+	            <seealso marker="erts:time_correction#POSIX_Time">
+              POSIX time</seealso>, when the file was created. See also
+              <seealso marker="kernel:file#read_file_info/1">
+              <c>file:read_file_info/1</c></seealso>.</p>
+          </item>
+          <tag><c>{uid,non_neg_integer()}</c></tag>
+          <item>
+            <p>Sets the file owner.
+              <seealso marker="kernel:file#read_file_info/1">
+              <c>file:read_file_info/1</c></seealso>.</p>
+          </item>
+          <tag><c>{gid,non_neg_integer()}</c></tag>
+          <item>
+            <p>Sets the group that the file owner belongs to.
+              <seealso marker="kernel:file#read_file_info/1">
+              <c>file:read_file_info/1</c></seealso>.</p>
+          </item>
         </taglist>
       </desc>
     </func>
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 48bbd38f9b..b04cdb3609 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2017. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2018. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -457,26 +457,61 @@ add(Reader, NameOrBin, NameInArchive, Options)
 
 do_add(#reader{access=write}=Reader, Name, NameInArchive, Options)
   when is_list(NameInArchive), is_list(Options) ->
-    RF = fun(F) -> file:read_link_info(F, [{time, posix}]) end,
+    RF = apply_file_info_opts_fun(Options, read_link_info),
     Opts = #add_opts{read_info=RF},
-    add1(Reader, Name, NameInArchive, add_opts(Options, Opts));
+    add1(Reader, Name, NameInArchive, add_opts(Options, Options, Opts));
 do_add(#reader{access=read},_,_,_) ->
     {error, eacces};
 do_add(Reader,_,_,_) ->
     {error, {badarg, Reader}}.
 
-add_opts([dereference|T], Opts) ->
-    RF = fun(F) -> file:read_file_info(F, [{time, posix}]) end,
-    add_opts(T, Opts#add_opts{read_info=RF});
-add_opts([verbose|T], Opts) ->
-    add_opts(T, Opts#add_opts{verbose=true});
-add_opts([{chunks,N}|T], Opts) ->
-    add_opts(T, Opts#add_opts{chunk_size=N});
-add_opts([_|T], Opts) ->
-    add_opts(T, Opts);
-add_opts([], Opts) ->
+add_opts([dereference|T], AllOptions, Opts) ->
+    RF = apply_file_info_opts_fun(AllOptions, read_file_info),
+    add_opts(T, AllOptions, Opts#add_opts{read_info=RF});
+add_opts([verbose|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{verbose=true});
+add_opts([{chunks,N}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{chunk_size=N});
+add_opts([{atime,Value}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{atime=Value});
+add_opts([{mtime,Value}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{mtime=Value});
+add_opts([{ctime,Value}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{ctime=Value});
+add_opts([{uid,Value}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{uid=Value});
+add_opts([{gid,Value}|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts#add_opts{gid=Value});
+add_opts([_|T], AllOptions, Opts) ->
+    add_opts(T, AllOptions, Opts);
+add_opts([], _AllOptions, Opts) ->
     Opts.
 
+apply_file_info_opts(Opts, {ok, FileInfo}) ->
+    {ok, do_apply_file_info_opts(Opts, FileInfo)};
+apply_file_info_opts(_Opts, Other) ->
+    Other.
+
+do_apply_file_info_opts([{atime,Value}|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo#file_info{atime=Value});
+do_apply_file_info_opts([{mtime,Value}|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo#file_info{mtime=Value});
+do_apply_file_info_opts([{ctime,Value}|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo#file_info{ctime=Value});
+do_apply_file_info_opts([{uid,Value}|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo#file_info{uid=Value});
+do_apply_file_info_opts([{gid,Value}|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo#file_info{gid=Value});
+do_apply_file_info_opts([_|T], FileInfo) ->
+    do_apply_file_info_opts(T, FileInfo);
+do_apply_file_info_opts([], FileInfo) ->
+    FileInfo.
+
+apply_file_info_opts_fun(Options, InfoFunction) ->
+   fun(F) ->
+       apply_file_info_opts(Options, file:InfoFunction(F, [{time, posix}]))
+   end.
+
 add1(#reader{}=Reader, Name, NameInArchive, #add_opts{read_info=ReadInfo}=Opts)
   when is_list(Name) ->
     Res = case ReadInfo(Name) of
@@ -515,9 +550,11 @@ add1(Reader, Bin, NameInArchive, Opts) when is_binary(Bin) ->
                 name = NameInArchive,
                 size = byte_size(Bin),
                 typeflag = ?TYPE_REGULAR,
-                atime = Now,
-                mtime = Now,
-                ctime = Now,
+                atime = add_opts_time(Opts#add_opts.atime, Now),
+                mtime = add_opts_time(Opts#add_opts.mtime, Now),
+                ctime = add_opts_time(Opts#add_opts.ctime, Now),
+                uid = Opts#add_opts.uid,
+                gid = Opts#add_opts.gid,
                 mode = 8#100644},
     {ok, Reader2} = add_header(Reader, Header, Opts),
     Padding = skip_padding(byte_size(Bin)),
@@ -527,6 +564,9 @@ add1(Reader, Bin, NameInArchive, Opts) when is_binary(Bin) ->
         {error, Reason} -> {error, {NameInArchive, Reason}}
     end.
 
+add_opts_time(undefined, Now) -> Now;
+add_opts_time(Time, _Now) -> Time.
+
 add_directory(Reader, DirName, NameInArchive, Info, Opts) ->
     case file:list_dir(DirName) of
         {ok, []} ->
diff --git a/lib/stdlib/src/erl_tar.hrl b/lib/stdlib/src/erl_tar.hrl
index cff0c2f500..5d6cecbb66 100644
--- a/lib/stdlib/src/erl_tar.hrl
+++ b/lib/stdlib/src/erl_tar.hrl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2017. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2018. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -21,7 +21,12 @@
 -record(add_opts, {
 	 read_info,          %% Fun to use for read file/link info.
 	 chunk_size = 0,     %% For file reading when sending to sftp. 0=do not chunk
-         verbose = false}).  %% Verbose on/off.
+         verbose = false,    %% Verbose on/off.
+         atime = undefined,
+         mtime = undefined,
+         ctime = undefined,
+         uid = 0,
+         gid = 0}).
 -type add_opts() :: #add_opts{}.
 
 %% Options used when reading a tar archive.
@@ -36,7 +41,12 @@
 
 -type add_opt() :: dereference |
                    verbose |
-                   {chunks, pos_integer()}.
+                   {chunks, pos_integer()} |
+                   {atime, non_neg_integer()} |
+                   {mtime, non_neg_integer()} |
+                   {ctime, non_neg_integer()} |
+                   {uid, non_neg_integer()} |
+                   {gid, non_neg_integer()}.
 
 -type extract_opt() :: {cwd, string()} |
                        {files, [string()]} |
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 4061008812..32a33283d1 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -28,7 +28,7 @@
 	 extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1,
 	 memory/1,unicode/1,read_other_implementations/1,
          sparse/1, init/1, leading_slash/1, dotdot/1,
-         roundtrip_metadata/1]).
+         roundtrip_metadata/1, apply_file_info_opts/1]).
 
 -include_lib("common_test/include/ct.hrl").
 -include_lib("kernel/include/file.hrl").
@@ -42,7 +42,8 @@ all() ->
      extract_filtered,
      symlinks, open_add_close, cooked_compressed, memory, unicode,
      read_other_implementations,
-     sparse,init,leading_slash,dotdot,roundtrip_metadata].
+     sparse,init,leading_slash,dotdot,roundtrip_metadata,
+     apply_file_info_opts].
 
 groups() -> 
     [].
@@ -989,6 +990,31 @@ do_roundtrip_metadata(Dir, File) ->
             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;
-- 
2.16.1

openSUSE Build Service is sponsored by