File 2291-Export-multiline-prompt-functions.patch of Package erlang

From 8fc5c402476bad44fe4c3c178a9c579b2764f04e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Sat, 23 Sep 2023 12:30:55 +0200
Subject: [PATCH] Export multiline prompt functions

Both shell:default_multiline_prompt/1 and
shell:inverted_space_prompt/1 have been exported.

shell:prompt_width/1 is now also available as a
helper function for custom prompt implementations.
---
 lib/kernel/src/group.erl                    |  2 +-
 lib/kernel/src/prim_tty.erl                 | 23 ++++----------
 lib/kernel/test/interactive_shell_SUITE.erl |  2 +-
 lib/stdlib/doc/src/shell.xml                | 30 +++++++++++++++++++
 lib/stdlib/src/edlin.erl                    | 14 +++------
 lib/stdlib/src/shell.erl                    | 33 +++++++++++++++++++++
 lib/stdlib/test/shell_SUITE.erl             |  7 +++++
 7 files changed, 81 insertions(+), 30 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index bfb6e51e1c..f7f34659e6 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -525,7 +525,7 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->
             case LineCont of
                 {[CL|LB], _, _} ->
                     LineCont1 = {LB,{lists:reverse(CL++"\n"), []},[]},
-                    MultiLinePrompt = lists:duplicate(prim_tty:npwcwidthstring(Pbs), $\s),
+                    MultiLinePrompt = lists:duplicate(shell:prompt_width(Pbs), $\s),
                     send_drv_reqs(Drv, [{redraw_prompt, Pbs, MultiLinePrompt, LineCont1},new_prompt]);
                 _ -> skip %% oldshell mode
             end,
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index 5b402c0236..4197b00dff 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -106,7 +106,7 @@
 
 -export([init/1, reinit/2, isatty/1, handles/1, unicode/1, unicode/2,
          handle_signal/2, window_size/1, handle_request/2, write/2, write/3, npwcwidth/1,
-         npwcwidthstring/1]).
+         ansi_regexp/0]).
 -export([reader_stop/1, disable_reader/1, enable_reader/1]).
 
 -nifs([isatty/1, tty_create/0, tty_init/3, tty_set/1, setlocale/1,
@@ -190,6 +190,10 @@
 -opaque state() :: #state{}.
 -export_type([state/0]).
 
+-spec ansi_regexp() -> binary().
+ansi_regexp() ->
+    ?ANSI_REGEXP.
+
 -spec on_load() -> ok.
 on_load() ->
     on_load(#{}).
@@ -1007,23 +1011,6 @@ update_geometry(State) ->
             State
     end.
 
-npwcwidthstring(String) when is_list(String) ->
-    npwcwidthstring(unicode:characters_to_binary(String));
-npwcwidthstring(String) ->
-    case string:next_grapheme(String) of
-        [] -> 0;
-        [$\e | Rest] ->
-            case re:run(String, ?ANSI_REGEXP, [unicode]) of
-                {match, [{0, N}]} ->
-                    <<_Ansi:N/binary, AnsiRest/binary>> = String,
-                    npwcwidthstring(AnsiRest);
-                _ ->
-                    npwcwidth($\e) + npwcwidthstring(Rest)
-            end;
-        [H|Rest] when is_list(H)-> lists:sum([npwcwidth(A)||A<-H]) + npwcwidthstring(Rest);
-        [H|Rest] -> npwcwidth(H) + npwcwidthstring(Rest)
-    end.
-
 npwcwidth(Char) ->
     npwcwidth(Char, true).
 npwcwidth(Char, true) ->
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 558dac998c..7f3918aba2 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -476,7 +476,7 @@ shell_multiline_navigation(Config) ->
     end.
 
 shell_multiline_prompt(Config) ->
-    Term1 = start_tty([{args,["-stdlib","shell_multiline_prompt","{edlin,inverted_space_prompt}"]}|Config]),
+    Term1 = start_tty([{args,["-stdlib","shell_multiline_prompt","{shell,inverted_space_prompt}"]}|Config]),
     Term2 = start_tty([{args,["-stdlib","shell_multiline_prompt","\"...> \""]}|Config]),
     Term3 = start_tty([{args,["-stdlib","shell_multiline_prompt","edlin"]}|Config]),
 
diff --git a/lib/stdlib/doc/src/shell.xml b/lib/stdlib/doc/src/shell.xml
index 3ce6ef9298..151ca4d8a4 100644
--- a/lib/stdlib/doc/src/shell.xml
+++ b/lib/stdlib/doc/src/shell.xml
@@ -929,6 +929,16 @@ q                 - quit erlang
       </desc>
     </func>
 
+    <func>
+      <name name="default_multiline_prompt" arity="1" since="OTP 27.0"/>
+      <fsummary>The default multiline prompt implementation.</fsummary>
+      <desc>
+        <p>Configures the multiline prompt as two trailing dots.
+          This is the default function but it may also be set explicitly as
+          <c>-stdlib shell_multiline_prompt {shell, default_multiline_prompt}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="history" arity="1" since=""/>
       <fsummary>Set the number of previous commands to keep.</fsummary>
@@ -939,6 +949,16 @@ q                 - quit erlang
       </desc>
     </func>
 
+    <func>
+      <name name="inverted_space_prompt" arity="1" since="OTP 27.0"/>
+      <fsummary>An anternative multiline prompt implementation.</fsummary>
+      <desc>
+        <p>Configures the multiline prompt as inverted space.
+          It may be set explicitly as
+          <c>-stdlib shell_multiline_prompt {shell, inverted_space_prompt}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="prompt_func" arity="1" since="OTP R13B04"/>
       <fsummary>Set the shell prompt.</fsummary>
@@ -948,6 +968,16 @@ q                 - quit erlang
       </desc>
     </func>
 
+    <func>
+      <name name="prompt_width" arity="1" since="OTP 27.0"/>
+      <fsummary>Computes the width of a prompt.</fsummary>
+      <desc>
+        <p>It receives a prompt and computes its width,
+          considering its Unicode characters and ANSI escapes.</p>
+        <p>Useful for creating custom multiline prompts.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="results" arity="1" since=""/>
       <fsummary>Set the number of previous results to keep.</fsummary>
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 431a3dc0ba..f4565730e1 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -28,7 +28,6 @@
 -export([current_line/1, current_chars/1]).
 
 -export([edit_line1/2]).
--export([inverted_space_prompt/1]).
 -export([keymap/0]).
 -import(lists, [reverse/1, reverse/2]).
 
@@ -616,28 +615,23 @@ redraw_line({line, Pbs, L,_}) ->
 multi_line_prompt(Pbs) ->
     case application:get_env(stdlib, shell_multiline_prompt, default) of
         default -> %% Default multiline prompt
-            default_multiline_prompt(Pbs);
+            shell:default_multiline_prompt(Pbs);
         {M,F} when is_atom(M), is_atom(F) ->
             case catch apply(M,F,[Pbs]) of
                 Prompt when is_list(Prompt) -> Prompt;
                 _ ->
                     application:set_env(stdlib, shell_multiline_prompt, default),
                     io:format("Invalid call: ~p:~p/1~n", [M,F]),
-                    default_multiline_prompt(Pbs)
+                    shell:default_multiline_prompt(Pbs)
             end;
         Prompt when is_list(Prompt) ->
-            lists:duplicate(max(0,prim_tty:npwcwidthstring(Pbs) - prim_tty:npwcwidthstring(Prompt)), $\s) ++ Prompt;
+            lists:duplicate(max(0,shell:prompt_width(Pbs) - shell:prompt_width(Prompt)), $\s) ++ Prompt;
         Prompt ->
             application:set_env(stdlib, shell_multiline_prompt, default),
             io:format("Invalid multiline prompt: ~p~n", [Prompt]),
-            default_multiline_prompt(Pbs)
+            shell:default_multiline_prompt(Pbs)
     end.
 
-default_multiline_prompt(Pbs) ->
-    lists:duplicate(max(0,prim_tty:npwcwidthstring(Pbs) - 3), $\s) ++ ".. ".
-inverted_space_prompt(Pbs) ->
-    "\e[7m" ++ lists:duplicate(prim_tty:npwcwidthstring(Pbs) - 1, $\s) ++ "\e[27m ".
-
 redraw(Pbs, {_,{_,_},_}=L, Rs) ->
     [{redraw_prompt, Pbs, multi_line_prompt(Pbs), L} |Rs].
 
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 834a570c7f..f1b35039a1 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -26,6 +26,8 @@
 -export([catch_exception/1, prompt_func/1, strings/1]).
 -export([start_interactive/0, start_interactive/1]).
 -export([read_and_add_records/5]).
+-export([default_multiline_prompt/1, inverted_space_prompt/1]).
+-export([prompt_width/1]).
 -export([whereis/0]).
 
 -define(LINEMAX, 30).
@@ -1696,3 +1698,34 @@ prompt_func(PromptFunc) ->
 
 strings(Strings) ->
     set_env(stdlib, shell_strings, Strings, ?DEF_STRINGS).
+
+-spec prompt_width(unicode:chardata()) -> non_neg_integer().
+
+prompt_width(String) when is_list(String) ->
+    prompt_width(unicode:characters_to_binary(String));
+prompt_width(String) ->
+    case string:next_grapheme(String) of
+        [] -> 0;
+        [$\e | Rest] ->
+            case re:run(String, prim_tty:ansi_regexp(), [unicode]) of
+                {match, [{0, N}]} ->
+                    <<_Ansi:N/binary, AnsiRest/binary>> = String,
+                    prompt_width(AnsiRest);
+                _ ->
+                    prim_tty:npwcwidth($\e) + prompt_width(Rest)
+            end;
+        [H|Rest] when is_list(H)-> lists:sum([prim_tty:npwcwidth(A)||A<-H]) + prompt_width(Rest);
+        [H|Rest] -> prim_tty:npwcwidth(H) + prompt_width(Rest)
+    end.
+
+-spec default_multiline_prompt(unicode:chardata()) ->
+      unicode:chardata().
+
+default_multiline_prompt(Pbs) ->
+    lists:duplicate(max(0, prompt_width(Pbs) - 3), $\s) ++ ".. ".
+
+-spec inverted_space_prompt(unicode:chardata()) ->
+      unicode:chardata().
+
+inverted_space_prompt(Pbs) ->
+    "\e[7m" ++ lists:duplicate(prompt_width(Pbs) - 1, $\s) ++ "\e[27m ".
\ No newline at end of file
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 142f8ad445..2491b34020 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -25,6 +25,7 @@
 	 bs_match_misc_SUITE/1, bs_match_int_SUITE/1,
 	 bs_match_tail_SUITE/1, bs_match_bin_SUITE/1,
 	 bs_construct_SUITE/1,
+     prompt_width/1,
 	 refman_bit_syntax/1,
 	 progex_bit_syntax/1, progex_records/1,
 	 progex_lc/1, progex_funs/1,
@@ -77,6 +78,7 @@ suite() ->
 all() ->
     [forget, known_bugs, otp_5226, otp_5327,
      otp_5435, otp_5195, otp_5915, otp_5916,
+     prompt_width,
      start_interactive, whereis, {group, bits},
      {group, refman}, {group, progex}, {group, tickets},
      {group, restricted}, {group, records}, {group, definitions}].
@@ -380,6 +382,11 @@ shell_attribute_test(Config) ->
         "-kernel","shell_history_drop","[\"init:stop().\"]"]),
     ok.
 
+prompt_width(Config) when is_list(Config) ->
+    5 = shell:prompt_width("\e[31molá> "),
+    5 = shell:prompt_width(<<"\e[31molá> "/utf8>>),
+    ok.
+
 %% Test of the record support. OTP-5063.
 records(Config) when is_list(Config) ->
     %% rd/2
-- 
2.35.3

openSUSE Build Service is sponsored by