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

From 66bf5da17a4001df11910fc07e6d7683a23f93a9 Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Thu, 30 Nov 2023 00:47:33 +0100
Subject: [PATCH 2/3] fixup! stdlib: add auto formatting to the shell

---
 lib/kernel/src/group.erl                    | 22 ++++++++++++---------
 lib/kernel/test/interactive_shell_SUITE.erl | 10 ++++++++++
 lib/stdlib/doc/src/stdlib_app.xml           |  4 ++--
 3 files changed, 25 insertions(+), 11 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 447a88a20f..bd9dfaf491 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -526,7 +526,7 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
         {stop,Result,Rest} ->
             %% Prompt was valid expression, clear the prompt in user_drv
             %% First redraw without the multi line prompt
-            FormattedLine = format_expression(LineCont),
+            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"), []},[]},
@@ -606,7 +606,7 @@ get_line1({open_editor, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
     end;
 get_line1({format_expression, _Cs, {line, _, _, _} = Cont, Rs}, Drv, Shell, Ls, Encoding) ->
     send_drv_reqs(Drv, Rs),
-    Cs1 = format_expression(Cont),
+    Cs1 = format_expression(Cont, Drv),
     send_drv_reqs(Drv, edlin:erase_line()),
     {more_chars,NewCont,NewRs} = edlin:start(edlin:prompt(Cont)),
     send_drv_reqs(Drv, NewRs),
@@ -930,18 +930,22 @@ get_chars_echo_off1(Drv, Shell) ->
             exit(R)
     end.
 
-format_expression(Cont) ->
-    FormatingCommand = application:get_env(stdlib, format_shell_func),
+format_expression(Cont, Drv) ->
+    FormatingCommand = application:get_env(stdlib, format_shell_func, default),
     Buffer = edlin:current_line(Cont),
     try
         case FormatingCommand of
-            {ok, {M,F}} when is_atom(M), is_atom(F) ->
-                    M:F(Buffer);
-            {ok, FormatingCommand1} when is_list(FormatingCommand1) ->
+            default ->
+                Buffer;
+            {M,F} when is_atom(M), is_atom(F) ->
+                M:F(Buffer);
+            FormatingCommand1 when is_list(FormatingCommand1) ->
                 format_expression1(Buffer, FormatingCommand1)
         end
-    catch
-        _:_ -> Buffer
+    catch _:_ ->
+            send_drv_reqs(Drv, [{put_chars, unicode, io_lib:format("* Bad format function: ~tp~n", [FormatingCommand])}]),
+            shell:format_shell_func(default),
+            Buffer
     end.
 format_expression1(Buffer, FormatingCommand) ->
     %% Write the current expression to a file, format it with a formatting tool
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 34e6a73f01..e3473307d0 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -502,6 +502,16 @@ shell_format(Config) ->
         timer:sleep(1000),
         send_tty(Term1, "Up"),
         check_content(Term1, "fun\\(X\\) ->\\s*..         X\\s*.. end."),
+        send_tty(Term1, "Down"),
+        send_stdin(Term1, "shell:format_shell_func({bad,format}).\n"),
+        send_tty(Term1, "Up"),
+        send_tty(Term1, "Up"),
+        send_tty(Term1, "\n"),
+        timer:sleep(1000),
+        check_content(Term1, "\\Q* Bad format function: {bad,format}\\E"),
+        send_tty(Term1, "Up"),
+        %% No modifications should be made, when default format function is used
+        check_content(Term1, "fun\\(X\\) ->\\s*..         X\\s*.. end."),
         ok
     after
         stop_tty(Term1)
diff --git a/lib/stdlib/doc/src/stdlib_app.xml b/lib/stdlib/doc/src/stdlib_app.xml
index f6ade68d02..10a10458c8 100644
--- a/lib/stdlib/doc/src/stdlib_app.xml
+++ b/lib/stdlib/doc/src/stdlib_app.xml
@@ -74,8 +74,8 @@
       </item>
       <tag><marker id="format_shell_func"/><c>format_shell_func = {Mod, Func} | string() | default</c></tag>
       <item>
-        <p>Can be used to set the formatting of the Erlang shell output. This have an effect
-        on commands that have been submitted, and how it is saved in history. Or if the
+        <p>Can be used to set the formatting of the Erlang shell output. This has an effect
+        on commands that have been submitted and how it is saved in history or if the
         formatting hotkey is pressed while editing an expression (Alt-f by default). You can specify a Mod:Func/1 that
         expects the whole expression as a string and returns a formatted expressions as a string.
         See <seemfa marker="shell#format_shell_func/1"><c>shell:format_shell_func/1</c></seemfa>
-- 
2.35.3

openSUSE Build Service is sponsored by