File 2613-fixup-stdlib-add-auto-formatting-to-the-shell.patch of Package erlang

From d1dc73a2b70b11bbfe7dae668802dff35e53aa1d Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Mon, 11 Dec 2023 14:28:37 +0100
Subject: [PATCH 3/3] fixup! stdlib: add auto formatting to the shell

Adding erl_pp format function in shell.erl
---
 lib/kernel/src/group.erl                    |  9 ++++---
 lib/kernel/test/interactive_shell_SUITE.erl | 13 +++++-----
 lib/stdlib/doc/src/shell.xml                | 12 +++++++++
 lib/stdlib/doc/src/stdlib_app.xml           |  1 +
 lib/stdlib/src/shell.erl                    | 28 ++++++++++++++++++++-
 5 files changed, 51 insertions(+), 12 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index bd9dfaf491..b8375a480d 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -527,9 +527,10 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
             %% Prompt was valid expression, clear the prompt in user_drv
             %% First redraw without the multi line prompt
             FormattedLine = format_expression(LineCont, Drv),
-            case lists:reverse(string:split(FormattedLine, "\n", all)) of
-                [CL|LB] when is_list(CL) ->
-                    LineCont1 = {LB,{lists:reverse(CL++"\n"), []},[]},
+            case LineCont of
+                {[_|_], _, _} ->
+                    [CL1|LB1] = lists:reverse(string:split(FormattedLine, "\n", all)),
+                    LineCont1 = {LB1,{lists:reverse(CL1++"\n"), []},[]},
                     MultiLinePrompt = lists:duplicate(shell:prompt_width(Pbs), $\s),
                     send_drv_reqs(Drv, [{redraw_prompt, Pbs, MultiLinePrompt, LineCont1},new_prompt]);
                 _ -> skip %% oldshell mode
@@ -944,7 +945,7 @@ format_expression(Cont, Drv) ->
         end
     catch _:_ ->
             send_drv_reqs(Drv, [{put_chars, unicode, io_lib:format("* Bad format function: ~tp~n", [FormatingCommand])}]),
-            shell:format_shell_func(default),
+            _ = shell:format_shell_func(default),
             Buffer
     end.
 format_expression1(Buffer, FormatingCommand) ->
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index e3473307d0..4a7a303656 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -59,7 +59,7 @@
          shell_receive_standard_out/1,
          shell_receive_user_output/1,
          shell_standard_error_nlcr/1, shell_clear/1,
-         shell_format/1, format_func/1,
+         shell_format/1,
          remsh_basic/1, remsh_error/1, remsh_longnames/1, remsh_no_epmd/1,
          remsh_dont_terminate_remote/1,
          remsh_expand_compatibility_25/1, remsh_expand_compatibility_later_version/1,
@@ -478,29 +478,28 @@ shell_multiline_navigation(Config) ->
         stop_tty(Term)
     end.
 
-format_func(String) ->
-    lists:flatten(string:replace(String, "  ", " ", all)).
-
 shell_format(Config) ->
-    Term1 = start_tty([{args,["-stdlib","format_shell_func","{interactive_shell_SUITE,format_func}"]}|Config]),
+    Term1 = start_tty([{args,["-stdlib","format_shell_func","{shell,erl_pp_format_func}"]}|Config]),
     DataDir = proplists:get_value(data_dir, Config),
     EmacsFormat = "\""++DataDir ++ "emacs-format-file\"\n",
     try
         send_tty(Term1,"fun(X) ->\n  X\nend.\n"),
         send_tty(Term1,"Up"),
-        check_content(Term1, "fun\\(X\\) ->\\s*..  X\\s*.. end."),
+        %% Note, erl_pp puts 7 spaces before X
+        check_content(Term1, "fun\\(X\\) ->\\s*..        X\\s*.. end."),
         send_tty(Term1, "Down"),
         tmux(["resize-window -t ",tty_name(Term1)," -x ",200]),
         timer:sleep(1000),
         send_stdin(Term1, "shell:format_shell_func(\"emacs -batch \${file} -l \"\n"),
         send_stdin(Term1, EmacsFormat),
         send_stdin(Term1, "\" -f emacs-format-function\").\n"),
-        check_content(Term1, "{interactive_shell_SUITE,format_func}"),
+        check_content(Term1, "{shell,erl_pp_format_func}"),
         send_tty(Term1, "Up"),
         send_tty(Term1, "Up"),
         send_tty(Term1, "\n"),
         timer:sleep(1000),
         send_tty(Term1, "Up"),
+        %% Note, emacs-format puts 8 spaces before X
         check_content(Term1, "fun\\(X\\) ->\\s*..         X\\s*.. end."),
         send_tty(Term1, "Down"),
         send_stdin(Term1, "shell:format_shell_func({bad,format}).\n"),
diff --git a/lib/stdlib/doc/src/shell.xml b/lib/stdlib/doc/src/shell.xml
index 82fdcfdb57..59beb02485 100644
--- a/lib/stdlib/doc/src/shell.xml
+++ b/lib/stdlib/doc/src/shell.xml
@@ -1057,6 +1057,18 @@ q                 - quit erlang
         somewhere in the string, for the shell to know where the file goes in the command.
         </p>
         <code>shell:format_shell_func("\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\"").</code>
+        <code>shell:format_shell_func({shell, erl_pp_format_func}).</code>
+      </desc>
+    </func>
+
+    <func>
+      <name name="erl_pp_format_func" arity="1" since="OTP 27.0"/>
+      <fsummary>A formatting function that makes use of erl_pp.</fsummary>
+      <desc>
+        <p>A formatting function that can be set with <seemfa marker="#format_shell_func/1"><c>format_shell_func/1</c></seemfa>
+        that will make expressions submitted to the shell prettier.
+        </p>
+        <note><p>This formatting function filter comments away from the expressions.</p></note>
       </desc>
     </func>
 
diff --git a/lib/stdlib/doc/src/stdlib_app.xml b/lib/stdlib/doc/src/stdlib_app.xml
index 10a10458c8..b99bebe695 100644
--- a/lib/stdlib/doc/src/stdlib_app.xml
+++ b/lib/stdlib/doc/src/stdlib_app.xml
@@ -85,6 +85,7 @@
         somewhere in the string, for the shell to know where the file goes in the command.
         </p>
         <code>-stdlib format_shell_func "\"emacs -batch \${file} -l ~/erlang-format/emacs-format-file -f emacs-format-function\""</code>
+        <code>-stdlib format_shell_func "{shell, erl_pp_format_func}"</code>
       </item>
       <tag><marker id="shell_prompt_func"/><c>shell_prompt_func = {Mod, Func} | default</c></tag>
       <item>
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index f33dd0c944..1e2f8d0d31 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -23,7 +23,8 @@
 -export([get_state/0, get_function/2]).
 -export([start_restricted/1, stop_restricted/0]).
 -export([local_func/0, local_func/1, local_allowed/3, non_local_allowed/3]).
--export([catch_exception/1, prompt_func/1, multiline_prompt_func/1, format_shell_func/1, strings/1]).
+-export([catch_exception/1, prompt_func/1, multiline_prompt_func/1, strings/1]).
+-export([format_shell_func/1, erl_pp_format_func/1]).
 -export([start_interactive/0, start_interactive/1]).
 -export([read_and_add_records/5]).
 -export([default_multiline_prompt/1, inverted_space_prompt/1]).
@@ -1873,6 +1874,31 @@ multiline_prompt_func(PromptFunc) ->
 format_shell_func(ShellFormatFunc) ->
     set_env(stdlib, format_shell_func, ShellFormatFunc, default).
 
+-spec erl_pp_format_func(String) -> String2 when
+      String :: string(),
+      String2 :: string().
+erl_pp_format_func(String) ->
+    %% A simple pretty printer function of shell expressions.
+    %% 
+    %% Comments will be filtered.
+    %% If you add return_comments to the option list,
+    %% parsing will fail, and we will end up with the original string.
+    Options = [text,{reserved_word_fun,fun erl_scan:reserved_word/1}],
+    case erl_scan:tokens([], String, {1,1}, Options) of
+        {done, {ok, Toks, _}, _} ->
+            try
+                case erl_parse:parse_form(Toks) of
+                    {ok, Def} -> lists:flatten(erl_pp:form(Def))
+                end
+            catch
+                _:_ -> case erl_parse:parse_exprs(Toks) of
+                          {ok, Def1} -> lists:flatten(erl_pp:exprs(Def1))++".";
+                          _ -> String
+                      end
+            end;
+        _ -> String
+    end.
+
 -spec strings(Strings) -> Strings2 when
       Strings :: boolean(),
       Strings2 :: boolean().
-- 
2.35.3

openSUSE Build Service is sponsored by