File 0507-erl_tar-Improve-documentation.patch of Package erlang

From b99cd6ec1d4915ced16edae0cffed51187a6c822 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Mon, 23 Sep 2019 13:28:20 +0200
Subject: [PATCH] erl_tar: Improve documentation

Variable names weren't always in sync with the type names, making
the docs for functions like add/3 unnecessarily difficult to read.

This also fixes a few badly-chosen types. For example, string() was
used when the equivalent but more descriptive name_in_archive()
would be better suited.
---
 lib/stdlib/doc/src/erl_tar.xml | 29 +++++++++--------
 lib/stdlib/src/erl_tar.erl     | 74 +++++++++++++++++++++++-------------------
 lib/stdlib/src/erl_tar.hrl     | 29 +++++++++--------
 3 files changed, 71 insertions(+), 61 deletions(-)

diff --git a/lib/stdlib/doc/src/erl_tar.xml b/lib/stdlib/doc/src/erl_tar.xml
index 9be3594724..b062c5cef3 100644
--- a/lib/stdlib/doc/src/erl_tar.xml
+++ b/lib/stdlib/doc/src/erl_tar.xml
@@ -130,10 +130,10 @@
       <name name="name_in_archive"/>
     </datatype>
     <datatype>
-      <name name="open_handle"/>
+      <name name="open_type"/>
     </datatype>
     <datatype>
-      <name name="reader"/>
+      <name name="tar_descriptor"/>
     </datatype>
   </datatypes>
 
@@ -365,7 +365,7 @@
       <name name="init" arity="3" since="OTP 17.4"/>
       <fsummary>Create a <c>TarDescriptor</c> used in subsequent tar operations
         when defining own low-level storage access functions.</fsummary>
-      <type name="handle"/>
+      <type name="user_data"/>
       <type name="file_op"/>
       <desc>
         <p>The <c>Fun</c> is the definition of what to do when the different
@@ -374,33 +374,33 @@
           <c>close/1</c>).</p>
         <p>The <c>Fun</c> is called when the tar function wants to do a
           low-level operation, like writing a block to a file. The <c>Fun</c>
-          is called as <c>Fun(Op, {UserPrivate,Parameters...})</c>, where
-          <c>Op</c> is the operation name, <c>UserPrivate</c> is the term
+          is called as <c>Fun(Op, {UserData,Parameters...})</c>, where
+          <c>Op</c> is the operation name, <c>UserData</c> is the term
           passed as the first argument to <c>init/1</c> and
           <c>Parameters...</c> are the data added by the tar function to be
           passed down to the storage handling function.</p>
-        <p>Parameter <c>UserPrivate</c> is typically the result of opening a
+        <p>Parameter <c>UserData</c> is typically the result of opening a
           low-level structure like a file descriptor or an SFTP channel id.
           The different <c>Fun</c> clauses operate on that very term.</p>
         <p>The following are the fun clauses parameter lists:</p>
         <taglist>
-          <tag><c>(write, {UserPrivate,DataToWrite})</c></tag>
+          <tag><c>(write, {UserData,DataToWrite})</c></tag>
           <item>
-            <p>Writes term <c>DataToWrite</c> using <c>UserPrivate</c>.</p>
+            <p>Writes term <c>DataToWrite</c> using <c>UserData</c>.</p>
           </item>
-          <tag><c>(close, UserPrivate)</c></tag>
+          <tag><c>(close, UserData)</c></tag>
           <item>
             <p>Closes the access.</p>
           </item>
-          <tag><c>(read2, {UserPrivate,Size})</c></tag>
+          <tag><c>(read2, {UserData,Size})</c></tag>
           <item>
-            <p>Reads using <c>UserPrivate</c> but only <c>Size</c> bytes.
+            <p>Reads using <c>UserData</c> but only <c>Size</c> bytes.
             Notice that there is only an arity-2 read function, not an arity-1
             function.</p>
           </item>
-          <tag><c>(position,{UserPrivate,Position})</c></tag>
+          <tag><c>(position,{UserData,Position})</c></tag>
           <item>
-            <p>Sets the position of <c>UserPrivate</c> as defined for files in
+            <p>Sets the position of <c>UserData</c> as defined for files in
               <seealso marker="kernel:file#position-2">
               <c>file:position/2</c></seealso></p>
           </item>
@@ -427,7 +427,7 @@ erl_tar:add(TarDesc, SomeValueIwantToAdd, FileNameInTarFile),
 erl_tar:close(TarDesc)</code>
         <p>When the <c>erl_tar</c> core wants to, for example, write a piece
           of <c>Data</c>, it would call
-          <c>ExampleFun(write, {UserPrivate,Data})</c>.</p>
+          <c>ExampleFun(write, {UserData,Data})</c>.</p>
         <note>
           <p>This example with the <c>file</c> module operations is
             not necessary to use directly, as that is what function
@@ -488,6 +488,7 @@ erl_tar:close(TarDesc)</code>
       <fsummary>Retrieve name and information of all files in a tar file.
       </fsummary>
       <type name="tar_entry"/>
+      <type name="tar_time"/>
       <type name="typeflag"/>
       <type name="mode"/>
       <type name="uid"/>
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 2dddee632a..591aea2f83 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -79,17 +79,18 @@ format_error(Term) ->
     lists:flatten(io_lib:format("~tp", [Term])).
 
 %% Initializes a new reader given a custom file handle and I/O wrappers
--spec init(handle(), write | read, file_op()) -> {ok, reader()} | {error, badarg}.
-init(Handle, AccessMode, Fun) when is_function(Fun, 2) ->
-    Reader = #reader{handle=Handle,access=AccessMode,func=Fun},
+-spec init(UserData :: user_data(), write | read, file_op()) ->
+                  {ok, tar_descriptor()} | {error, badarg}.
+init(UserData, AccessMode, Fun) when is_function(Fun, 2) ->
+    Reader = #reader{handle=UserData,access=AccessMode,func=Fun},
     {ok, Pos, Reader2} = do_position(Reader, {cur, 0}),
     {ok, Reader2#reader{pos=Pos}};
-init(_Handle, _AccessMode, _Fun) ->
+init(_UserData, _AccessMode, _Fun) ->
     {error, badarg}.
 
 %%%================================================================
 %% Extracts all files from the tar file Name.
--spec extract(open_handle()) -> ok | {error, term()}.
+-spec extract(Open :: open_type()) -> ok | {error, term()}.
 extract(Name) ->
     extract(Name, []).
 
@@ -102,10 +103,10 @@ extract(Name) ->
 %%  - {files, ListOfFilesToExtract}: Only extract ListOfFilesToExtract
 %%  - verbose: Prints verbose information about the extraction,
 %%  - {cwd, AbsoluteDir}: Sets the current working directory for the extraction
--spec extract(open_handle(), [extract_opt()]) ->
-                     ok
-                         | {ok, [{string(), binary()}]}
-                         | {error, term()}.
+-spec extract(Open :: open_type(), [extract_opt()]) ->
+                     {ok, [{string(), binary()}]} |
+                     {error, term()} |
+                     ok.
 extract({binary, Bin}, Opts) when is_list(Opts) ->
     do_extract({binary, Bin}, Opts);
 extract({file, Fd}, Opts) when is_list(Opts) ->
@@ -165,7 +166,6 @@ check_extract(Name, #read_opts{files=Files}) ->
 %%%================================================================
 %% The following table functions produce a list of information about
 %% the files contained in the archive.
--type name_in_archive() :: string().
 -type typeflag() :: regular | link | symlink |
                     char | block | directory |
                     fifo | reserved | unknown.
@@ -173,23 +173,23 @@ check_extract(Name, #read_opts{files=Files}) ->
 -type uid() :: non_neg_integer().
 -type gid() :: non_neg_integer().
 
--type tar_entry() :: {name_in_archive(),
-                      typeflag(),
-                      non_neg_integer(),
-                      tar_time(),
-                      mode(),
-                      uid(),
-                      gid()}.
+-type tar_entry() :: {Name :: name_in_archive(),
+                      Type :: typeflag(),
+                      Size :: non_neg_integer(),
+                      MTime :: tar_time(),
+                      Mode :: mode(),
+                      Uid :: uid(),
+                      Gid :: gid()}.
 
 %% Returns a list of names of the files in the tar file Name.
--spec table(open_handle()) -> {ok, [string()]} | {error, term()}.
+-spec table(Open :: open_type()) -> {ok, [name_in_archive()]} | {error, term()}.
 table(Name) ->
     table(Name, []).
 
 %% Returns a list of names of the files in the tar file Name.
 %% Options accepted: compressed, verbose, cooked.
--spec table(open_handle(), [compressed | verbose | cooked]) ->
-                   {ok, [string() | tar_entry()]} | {error, term()}.
+-spec table(Open :: open_type(), [compressed | verbose | cooked]) ->
+                   {ok, [name_in_archive() | tar_entry()]} | {error, term()}.
 table(Name, Opts) when is_list(Opts) ->
     foldl_read(Name, fun table1/4, [], table_opts(Opts)).
 
@@ -239,7 +239,7 @@ t(Name) when is_list(Name); is_binary(Name) ->
     end.
 
 %% Prints verbose information about each file in the archive
--spec tt(open_handle()) -> ok | {error, term()}.
+-spec tt(open_type()) -> ok | {error, term()}.
 tt(Name) ->
     case table(Name, [verbose]) of
         {ok, List} ->
@@ -301,11 +301,11 @@ month(12) -> "Dec".
 
 %%%================================================================
 %% The open function with friends is to keep the file and binary api of this module
--type open_handle() :: file:filename_all()
+-type open_type() :: file:filename_all()
                      | {binary, binary()}
-                     | {file, term()}.
--spec open(open_handle(), [write | compressed | cooked]) ->
-                  {ok, reader()} | {error, term()}.
+                     | {file, file:io_device()}.
+-spec open(Open :: open_type(), [write | compressed | cooked]) ->
+                  {ok, tar_descriptor()} | {error, term()}.
 open({binary, Bin}, Mode) when is_binary(Bin) ->
     do_open({binary, Bin}, Mode);
 open({file, Fd}, Mode) ->
@@ -375,7 +375,7 @@ file_op(close, Fd) ->
     file:close(Fd).
 
 %% Closes a tar archive.
--spec close(reader()) -> ok | {error, term()}.
+-spec close(TarDescriptor :: tar_descriptor()) -> ok | {error, term()}.
 close(#reader{access=read}=Reader) ->
     ok = do_close(Reader);
 close(#reader{access=write}=Reader) ->
@@ -435,8 +435,11 @@ do_create(TarFile, [Name|Rest], Opts) ->
 
 %% Adds a file to a tape archive.
 -type add_type() :: name_in_archive()
-                  | {name_in_archive(), string()|binary()}.
--spec add(reader(), add_type(), [add_opt()]) -> ok | {error, term()}.
+                  | {name_in_archive(), file:filename_all()}.
+-spec add(TarDescriptor, AddType, Options) -> ok | {error, term()} when
+    TarDescriptor :: tar_descriptor(),
+    AddType :: add_type(),
+    Options :: [add_opt()].
 add(Reader, {NameInArchive, Name}, Opts)
   when is_list(NameInArchive), is_list(Name) ->
     do_add(Reader, Name, NameInArchive, Opts);
@@ -446,9 +449,12 @@ add(Reader, {NameInArchive, Bin}, Opts)
 add(Reader, Name, Opts) when is_list(Name) ->
     do_add(Reader, Name, Name, Opts).
 
-
--spec add(reader(), file:filename_all(), name_in_archive(), [add_opt()]) ->
-                 ok | {error, term()}.
+-spec add(TarDescriptor, Filename, NameInArchive, Options) ->
+        ok | {error, term()} when
+    TarDescriptor :: tar_descriptor(),
+    Filename :: file:filename_all(),
+    NameInArchive :: name_in_archive(),
+    Options :: [add_opt()].
 add(Reader, NameOrBin, NameInArchive, Options)
   when is_list(NameOrBin); is_binary(NameOrBin),
        is_list(NameInArchive), is_list(Options) ->
@@ -1139,8 +1145,8 @@ validate_sparse_entries([#sparse_entry{}=Entry|Rest], RealSize, I, LastOffset) -
     validate_sparse_entries(Rest, RealSize, I+1, Offset+NumBytes).
 
 
--spec parse_sparse_map(header_gnu(), reader_type()) ->
-                              {[sparse_entry()], reader_type()}.
+-spec parse_sparse_map(header_gnu(), descriptor_type()) ->
+                              {[sparse_entry()], descriptor_type()}.
 parse_sparse_map(#header_gnu{sparse=Sparse}, Reader)
   when Sparse#sparse_array.is_extended ->
     parse_sparse_map(Sparse, Reader, []);
@@ -1898,7 +1904,7 @@ read_sparse_hole(#sparse_file_reader{pos=Pos}=Reader, Offset, Len) ->
                 num_bytes=NumBytes,
                 pos=Pos+N2}}.
 
--spec do_close(reader()) -> ok | {error, term()}.
+-spec do_close(tar_descriptor()) -> ok | {error, term()}.
 do_close(#reader{handle=Handle,func=Fun}) when is_function(Fun,2) ->
     Fun(close,Handle).
 
diff --git a/lib/stdlib/src/erl_tar.hrl b/lib/stdlib/src/erl_tar.hrl
index 5d6cecbb66..44f9adb8f6 100644
--- a/lib/stdlib/src/erl_tar.hrl
+++ b/lib/stdlib/src/erl_tar.hrl
@@ -48,8 +48,10 @@
                    {uid, non_neg_integer()} |
                    {gid, non_neg_integer()}.
 
+-type name_in_archive() :: string().
+
 -type extract_opt() :: {cwd, string()} |
-                       {files, [string()]} |
+                       {files, [name_in_archive()]} |
                        compressed |
                        cooked |
                        memory |
@@ -62,21 +64,20 @@
                       verbose.
 
 -type filelist() :: [file:filename() |
-                     {string(), binary()} |
-                     {string(), file:filename()}].
+                     {name_in_archive(), file:filename_all()}].
 
 -type tar_time() :: non_neg_integer().
 
 %% The tar header, once fully parsed.
 -record(tar_header, {
-          name = "" :: string(),                %% name of header file entry
+          name = "" :: name_in_archive(),       %% name of header file entry
           mode = 8#100644 :: non_neg_integer(), %% permission and mode bits
           uid = 0 :: non_neg_integer(),         %% user id of owner
           gid = 0 :: non_neg_integer(),         %% group id of owner
           size = 0 :: non_neg_integer(),        %% length in bytes
           mtime :: tar_time(),                  %% modified time
           typeflag :: char(),                   %% type of header entry
-          linkname = "" :: string(),            %% target name of link
+          linkname = "" :: name_in_archive(),   %% target name of link
           uname = "" :: string(),               %% user name of owner
           gname = "" :: string(),               %% group name of owner
           devmajor = 0 :: non_neg_integer(),    %% major number of character or block device
@@ -157,16 +158,18 @@
 %% The overall tar reader, it holds the low-level file handle,
 %% its access, position, and the I/O primitives wrapper.
 -record(reader, {
-          handle :: file:io_device() | term(),
+          handle :: user_data(),
           access :: read | write | ram,
           pos = 0 :: non_neg_integer(),
           func :: file_op()
          }).
--type reader() :: #reader{}.
+-opaque tar_descriptor() :: #reader{}.
+-export_type([tar_descriptor/0]).
+
 %% A reader for a regular file within the tar archive,
 %% It tracks its current state relative to that file.
 -record(reg_file_reader, {
-          handle :: reader(),
+          handle :: tar_descriptor(),
           num_bytes = 0,
           pos = 0,
           size = 0
@@ -175,7 +178,7 @@
 %% A reader for a sparse file within the tar archive,
 %% It tracks its current state relative to that file.
 -record(sparse_file_reader, {
-          handle :: reader(),
+          handle :: tar_descriptor(),
           num_bytes = 0, %% bytes remaining
           pos = 0, %% pos
           size = 0, %% total size of file
@@ -184,13 +187,13 @@
 -type sparse_file_reader() :: #sparse_file_reader{}.
 
 %% Types for the readers
--type reader_type() :: reader() | reg_file_reader() | sparse_file_reader().
--type handle() :: file:io_device() | term().
+-type descriptor_type() :: tar_descriptor() | reg_file_reader() | sparse_file_reader().
+-type user_data() :: term().
 
 %% Type for the I/O primitive wrapper function
 -type file_op() :: fun((write | close | read2 | position,
-                       {handle(), iodata()} | handle() | {handle(), non_neg_integer()}
-                        | {handle(), non_neg_integer()}) ->
+                       {user_data(), iodata()} | user_data() | {user_data(), non_neg_integer()}
+                        | {user_data(), non_neg_integer()}) ->
                               ok | eof | {ok, string() | binary()} | {ok, non_neg_integer()}
                                  | {error, term()}).
 
-- 
2.16.4

openSUSE Build Service is sponsored by