File 4191-Document-epp-scan_erl_form-1-and-add-epp-scan_file-2.patch of Package erlang

From 81bce85477dea8ab3eb219130370458c9cae6a1d Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Fri, 12 Jun 2020 12:47:42 +0200
Subject: [PATCH] Document epp:scan_erl_form/1 and add epp:scan_file/2

---
 lib/stdlib/doc/src/epp.xml    | 30 ++++++++++++++++++++++-
 lib/stdlib/src/epp.erl        | 46 ++++++++++++++++++++++++++++++++++-
 lib/stdlib/src/erl_scan.erl   |  2 +-
 lib/stdlib/test/epp_SUITE.erl | 19 +++++++++++++--
 4 files changed, 92 insertions(+), 5 deletions(-)

diff --git a/lib/stdlib/doc/src/epp.xml b/lib/stdlib/doc/src/epp.xml
index 1c5fefe559..6cd715c55c 100644
--- a/lib/stdlib/doc/src/epp.xml
+++ b/lib/stdlib/doc/src/epp.xml
@@ -72,6 +72,9 @@
     <datatype>
       <name name="source_encoding"></name>
     </datatype>
+    <datatype>
+      <name name="warning_info"></name>
+    </datatype>
   </datatypes>
 
   <funcs>
@@ -160,7 +163,6 @@
       <name name="parse_erl_form" arity="1" since=""/>
       <fsummary>Return the next Erlang form from the opened Erlang source file.
       </fsummary>
-      <type name="warning_info"/>
       <desc>
         <p>Returns the next Erlang form from the opened Erlang source file.
           Tuple <c>{eof, <anno>Line</anno>}</c> is returned at the end of the
@@ -229,6 +231,32 @@
       </desc>
     </func>
 
+    <func>
+      <name name="scan_erl_form" arity="1" since="OTP R13B03"/>
+      <fsummary>Return the raw tokens of the next Erlang form from the opened
+      Erlang source file.</fsummary>
+      <desc>
+        <p>Returns the raw tokens of the next Erlang form from the opened
+        Erlang source file. A tuple <c>{eof, Line}</c> is
+        returned at the end of the file. The first form corresponds to an
+        implicit attribute <c>-file(File,1).</c>, where <c>File</c> is the
+        file name.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="scan_file" arity="2" since="OTP 24.0"/>
+      <fsummary>Preprocess an Erlang source file, returning raw tokens.</fsummary>
+      <desc>
+        <p>Preprocesses an Erlang source file returning a list of the lists
+        of raw tokens of each form.
+        Notice that the tuple <c>{eof, Line}</c> returned at the
+        end of the file is included as a "form", and any failures to scan a
+        form are included in the list as tuples <c>{error,
+        <anno>ErrorInfo</anno>}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="set_encoding" arity="1" since="OTP R16B"/>
       <fsummary>Read and set the encoding of an I/O device.</fsummary>
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index b390697a56..1ec3307dbd 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -23,7 +23,7 @@
 
 -export([open/1, open/2,open/3,open/5,close/1,format_error/1]).
 -export([scan_erl_form/1,parse_erl_form/1,macro_defs/1]).
--export([parse_file/1, parse_file/2, parse_file/3]).
+-export([scan_file/1, scan_file/2, parse_file/1, parse_file/2, parse_file/3]).
 -export([default_encoding/0, encoding_to_string/1,
          read_encoding_from_binary/1, read_encoding_from_binary/2,
          set_encoding/1, set_encoding/2, read_encoding/1, read_encoding/2]).
@@ -82,6 +82,8 @@
 %% close(Epp)
 %% scan_erl_form(Epp)
 %% parse_erl_form(Epp)
+%% scan_file(Epp)
+%% scan_file(FileName, Options)
 %% parse_file(Epp)
 %% parse_file(FileName, Options)
 %% parse_file(FileName, IncludePath, PreDefMacros)
@@ -151,6 +153,15 @@ close(Epp) ->
     receive {'DOWN',Ref,_,_,_} -> ok end,
     R.
 
+-spec scan_erl_form(Epp) ->
+    {'ok', Tokens} | {error, ErrorInfo} |
+    {'warning',WarningInfo} | {'eof',Line} when
+      Epp :: epp_handle(),
+      Tokens :: erl_scan:tokens(),
+      Line :: erl_anno:line(),
+      ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),
+      WarningInfo :: warning_info().
+
 scan_erl_form(Epp) ->
     epp_request(Epp, scan_erl_form).
 
@@ -230,6 +241,39 @@ format_error({warning,Term}) ->
     io_lib:format("-warning(~tp).", [Term]);
 format_error(E) -> file:format_error(E).
 
+-spec scan_file(FileName, Options) ->
+        {'ok', [Form], Extra} | {error, OpenError} when
+      FileName :: file:name(),
+      Options :: [{'includes', IncludePath :: [DirectoryName :: file:name()]} |
+		  {'source_name', SourceName :: file:name()} |
+		  {'macros', PredefMacros :: macros()} |
+		  {'default_encoding', DefEncoding :: source_encoding()}],
+      Form :: erl_scan:tokens() | {'error', ErrorInfo} | {'eof', Loc},
+      Loc :: erl_anno:location(),
+      ErrorInfo :: erl_scan:error_info(),
+      Extra :: [{'encoding', source_encoding() | 'none'}],
+      OpenError :: file:posix() | badarg | system_limit.
+
+scan_file(Ifile, Options) ->
+    case open([{name, Ifile}, extra | Options]) of
+	{ok,Epp,Extra} ->
+	    Forms = scan_file(Epp),
+	    close(Epp),
+	    {ok,Forms,Extra};
+	{error,E} ->
+	    {error,E}
+    end.
+
+scan_file(Epp) ->
+    case scan_erl_form(Epp) of
+	{ok,Toks} ->
+            [Toks|scan_file(Epp)];
+	{error,E} ->
+	    [{error,E}|scan_file(Epp)];
+	{eof,Location} ->
+	    [{eof,Location}]
+    end.
+
 -spec parse_file(FileName, IncludePath, PredefMacros) ->
                 {'ok', [Form]} | {error, OpenError} when
       FileName :: file:name(),
diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index 312b040002..0fe242220f 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -63,7 +63,7 @@
 -export_type([error_info/0,
               options/0,
               return_cont/0,
-              token/0,
+              token/0, tokens/0,
               tokens_result/0]).
 
 %% Removed functions and types
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 81457863ab..572c719417 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -29,7 +29,7 @@
          otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
          otp_11728/1, encoding/1, extends/1,  function_macro/1,
 	 test_error/1, test_warning/1, otp_14285/1,
-	 test_if/1,source_name/1,otp_16978/1,file_macro/1]).
+	 test_if/1,source_name/1,otp_16978/1,scan_file/1,file_macro/1]).
 
 -export([epp_parse_erl_form/2]).
 
@@ -70,7 +70,7 @@ all() ->
      overload_mac, otp_8388, otp_8470, otp_8562,
      otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
      encoding, extends, function_macro, test_error, test_warning,
-     otp_14285, test_if, source_name, otp_16978, file_macro].
+     otp_14285, test_if, source_name, otp_16978, scan_file, file_macro].
 
 groups() ->
     [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -842,6 +842,21 @@ otp_8130(Config) when is_list(Config) ->
 
     ok.
 
+scan_file(Config) when is_list(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    File = filename:join(DataDir, "source_name.erl"),
+
+    {ok, Toks, [{encoding, _}]} = epp:scan_file(File, []),
+    [FileForm1, ModuleForm, ExportForm,
+     FileForm2, FileForm3, FunctionForm,
+     {eof,_}] = Toks,
+    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm1,
+    [{'-',_}, {atom,_,module}, {'(',_} | _ ] = ModuleForm,
+    [{'-',_}, {atom,_,export}, {'(',_} | _ ] = ExportForm,
+    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm2,
+    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm3,
+    ok.
+
 macs(Epp) ->
     Macros = epp:macro_defs(Epp), % not documented
     lists:sort([MName || {{atom,MName},_} <- Macros]).
-- 
2.26.2

openSUSE Build Service is sponsored by