File 2590-erl_tar-Document-and-improve-errors-for-a-file-Fd-re.patch of Package erlang

From 363e286e548a007dc954bdaa29ab78a96674d010 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 9 Oct 2019 12:48:25 +0200
Subject: [PATCH] erl_tar: Document and improve errors for a {file,Fd}-related
 quirk

---
 lib/stdlib/doc/src/erl_tar.xml | 17 ++++++++++++++++-
 lib/stdlib/src/erl_tar.erl     | 27 +++++++++++++++++----------
 lib/stdlib/test/tar_SUITE.erl  | 28 ++++++++++++++++++++++++++--
 3 files changed, 59 insertions(+), 13 deletions(-)

diff --git a/lib/stdlib/doc/src/erl_tar.xml b/lib/stdlib/doc/src/erl_tar.xml
index b062c5cef3..ee66b581f8 100644
--- a/lib/stdlib/doc/src/erl_tar.xml
+++ b/lib/stdlib/doc/src/erl_tar.xml
@@ -288,6 +288,11 @@
 	writing the file. That is, absolute paths will be turned into
 	relative paths. There will be an info message written to the error
 	logger when paths are changed in this way.</p></note>
+        <warning>
+          <p>The <c>compressed</c> and <c>cooked</c> flags are invalid when
+            passing a file descriptor with <c>{file,Fd}</c>. The file is
+            assumed to have been opened with the appropriate flags.</p>
+        </warning>
       </desc>
     </func>
 
@@ -349,6 +354,11 @@
             <p>Prints an informational message for each extracted file.</p>
           </item>
         </taglist>
+        <warning>
+          <p>The <c>compressed</c> and <c>cooked</c> flags are invalid when
+            passing a file descriptor with <c>{file,Fd}</c>. The file is
+            assumed to have been opened with the appropriate flags.</p>
+        </warning>
       </desc>
     </func>
 
@@ -473,11 +483,16 @@ erl_tar:close(TarDesc)</code>
           <seealso marker="#add/3"><c>add/3,4</c></seealso>. When you are
           finished adding files, use function <seealso marker="#close/1">
           <c>close/1</c></seealso> to close the tar file.</p>
+        <warning>
+          <p>The <c>compressed</c> and <c>cooked</c> flags are invalid when
+            passing a file descriptor with <c>{file,Fd}</c>. The file must
+            already be opened with the appropriate flags.</p>
+        </warning>
         <warning>
           <p>The <c>TarDescriptor</c> term is not a file descriptor. You are
             advised not to rely on the specific contents of this term, as it
             can change in future Erlang/OTP releases when more features are
-            added to this module..</p>
+            added to this module.</p>
         </warning>
       </desc>
     </func>
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 591aea2f83..db490e8ce9 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -321,22 +321,29 @@ do_open(Name, Mode) when is_list(Mode) ->
             {error, {Name, Reason}}
     end.
 
-open1({binary,Bin}, read, _Raw, Opts) when is_binary(Bin) ->
+open1({binary,Bin}=Handle, read, _Raw, Opts) when is_binary(Bin) ->
     case file:open(Bin, [ram,binary,read]) of
         {ok,File} ->
             _ = [ram_file:uncompress(File) || lists:member(compressed, Opts)],
             {ok, #reader{handle=File,access=read,func=fun file_op/2}};
-        Error ->
-            Error
+        {error, Reason} ->
+            {error, {Handle, Reason}}
     end;
-open1({file, Fd}, read, _Raw, _Opts) ->
-    Reader = #reader{handle=Fd,access=read,func=fun file_op/2},
-    case do_position(Reader, {cur, 0}) of
-        {ok, Pos, Reader2} ->
-            {ok, Reader2#reader{pos=Pos}};
-        {error, _} = Err ->
-            Err
+open1({file, Fd}=Handle, read, [raw], Opts) ->
+    case not lists:member(compressed, Opts) of
+        true ->
+            Reader = #reader{handle=Fd,access=read,func=fun file_op/2},
+            case do_position(Reader, {cur, 0}) of
+                {ok, Pos, Reader2} ->
+                    {ok, Reader2#reader{pos=Pos}};
+                {error, Reason} ->
+                    {error, {Handle, Reason}}
+            end;
+        false ->
+            {error, {Handle, {incompatible_option, compressed}}}
     end;
+open1({file, _Fd}=Handle, read, [], _Opts) ->
+    {error, {Handle, {incompatible_option, cooked}}};
 open1(Name, Access, Raw, Opts) when is_list(Name) or is_binary(Name) ->
     case file:open(Name, Raw ++ [binary, Access|Opts]) of
         {ok, File} ->
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 32a33283d1..645099e2b8 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -28,7 +28,8 @@
 	 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, apply_file_info_opts/1]).
+         roundtrip_metadata/1, apply_file_info_opts/1,
+         incompatible_options/1]).
 
 -include_lib("common_test/include/ct.hrl").
 -include_lib("kernel/include/file.hrl").
@@ -43,7 +44,7 @@ all() ->
      symlinks, open_add_close, cooked_compressed, memory, unicode,
      read_other_implementations,
      sparse,init,leading_slash,dotdot,roundtrip_metadata,
-     apply_file_info_opts].
+     apply_file_info_opts,incompatible_options].
 
 groups() -> 
     [].
@@ -574,6 +575,29 @@ extract_from_open_file(Config) when is_list(Config) ->
 
     verify_ports(Config).
 
+%% Make sure incompatible options are rejected when opening archives with file
+%% descriptors.
+incompatible_options(Config) when is_list(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    Long = filename:join(DataDir, "no_fancy_stuff.tar"),
+
+    {ok, File} = file:open(Long, [read]),
+    Handle = {file, File},
+
+    {error, {Handle, {incompatible_option, compressed}}}
+        = erl_tar:open(Handle, [read, compressed]),
+    {error, {Handle, {incompatible_option, cooked}}}
+        = erl_tar:open(Handle, [read, cooked]),
+
+    {error, {Handle, {incompatible_option, compressed}}}
+        = erl_tar:extract(Handle, [compressed]),
+    {error, {Handle, {incompatible_option, cooked}}}
+        = erl_tar:extract(Handle, [cooked]),
+
+    ok = file:close(File),
+
+    verify_ports(Config).
+
 %% Test that archives containing symlinks can be created and extracted.
 symlinks(Config) when is_list(Config) ->
     PrivDir = proplists:get_value(priv_dir, Config),
-- 
2.16.4

openSUSE Build Service is sponsored by