File 2602-add-test-case.patch of Package erlang

From f075334363a13e74c1629d42720a1b9e0ad30a22 Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Thu, 9 Nov 2023 12:57:12 +0100
Subject: [PATCH 2/2] add test case

changed formatting of doc text
---
 erts/doc/src/tty.xml                        | 12 +++++++
 lib/kernel/src/group.erl                    | 36 +++++++++++++++------
 lib/kernel/src/prim_tty.erl                 | 11 +++----
 lib/kernel/test/interactive_shell_SUITE.erl | 14 ++++++++
 lib/stdlib/doc/src/edlin.xml                | 24 ++++++++++++--
 lib/stdlib/src/edlin_expand.erl             |  1 +
 lib/stdlib/test/edlin_context_SUITE.erl     |  4 +--
 7 files changed, 82 insertions(+), 20 deletions(-)

diff --git a/erts/doc/src/tty.xml b/erts/doc/src/tty.xml
index a14e3a2b1d..054e9ab219 100644
--- a/erts/doc/src/tty.xml
+++ b/erts/doc/src/tty.xml
@@ -229,6 +229,18 @@ erl</pre>
         <cell align="left" valign="middle">M-c</cell>
         <cell align="left" valign="middle">Clear current expression</cell>
       </row>
+      <row>
+        <cell align="left" valign="middle">M-h</cell>
+        <cell align="left" valign="middle">Display help for the module or function closest on the left of the cursor.</cell>
+      </row>
+      <row>
+        <cell align="left" valign="middle">PageUp</cell>
+        <cell align="left" valign="middle">Scroll the expand, search or help buffer 5 lines upwards.</cell>
+      </row>
+      <row>
+        <cell align="left" valign="middle">PageDown</cell>
+        <cell align="left" valign="middle">Scroll the expand, search or help buffer 5 lines downwards.</cell>
+      </row>
       <tcaption>tty Text Editing</tcaption>
     </table>
   </section>
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 743bc6fd81..f37fc211e9 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -663,19 +663,37 @@ get_line1({search,Cs,Cont,Rs}, Drv, Shell, Ls, Encoding) ->
 get_line1({help, Before, Cs0, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
     send_drv_reqs(Drv, Rs),
     {_,Word,_} = edlin:over_word(Before, [], 0),
-    Docs = case edlin_context:get_context(Before) of
+    {R,Docs} = case edlin_context:get_context(Before) of
         {function, Mod} when Word =/= [] -> try
-                    c:h1(list_to_atom(Mod), list_to_atom(Word))
+                    {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+                    {ok, [{atom,_,Word1}], _} = erl_scan:string(Word),
+                    {function, c:h1(Module, Word1)}
                 catch _:_ ->
-                    c:h1(list_to_atom(Mod))
+                    {ok, [{atom,_,Module1}], _} = erl_scan:string(Mod),
+                    {module, c:h1(Module1)}
                 end;
-        {function, Mod} -> c:h1(list_to_atom(Mod));
-        {function, Mod, Fun, _Args, _Unfinished, _Nesting} -> c:h1(list_to_atom(Mod), list_to_atom(Fun));
-        _ -> ""
+        {function, Mod} ->
+            {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+            {module, c:h1(Module)};
+        {function, Mod, Fun, _Args, _Unfinished, _Nesting} ->
+            {ok, [{atom,_,Module}], _} = erl_scan:string(Mod),
+            {ok, [{atom,_,Function}], _} = erl_scan:string(Fun),
+            {function, c:h1(Module, Function)};
+        {term, _, {atom, Word1}}->
+            {ok, [{atom,_,Module}], _} = erl_scan:string(Word1),
+            {module, c:h1(Module)};
+        _ -> {error, {error, no_help}}
     end,
-    case Docs of
-        {error, _} -> send_drv(Drv, beep);
-            _ -> send_drv(Drv, {put_expand, unicode, ["\n",unicode:characters_to_binary(string:trim(Docs, both))]})
+    case {R, Docs} of
+        {_, {error, _}} -> send_drv(Drv, beep);
+        {module, _} ->
+                Docs1 = "  "++string:trim(lists:nthtail(3, Docs),both),
+                send_drv(Drv, {put_expand, unicode,
+                    [unicode:characters_to_binary(Docs1)], 7});
+        {function, _} ->
+                Docs1 = "  "++string:trim(Docs,both),
+                send_drv(Drv, {put_expand, unicode,
+                    [unicode:characters_to_binary(Docs1)], 7})
     end,
     get_line1(edlin:edit_line(Cs0, Cont), Drv, Shell, Ls0, Encoding);
 get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index 183b8ac219..480b399d4b 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -640,8 +640,7 @@ handle_request(State = #state{unicode = U, cols = W, rows = R}, redraw_prompt_pr
                             _ -> cols(State#state.buffer_before, U) + cols(State#state.buffer_after,U)
                           end,
                           ERow = State#state.buffer_expand_row,
-
-                            BufferExpandLines = string:split(unicode:characters_to_list(BufferExpand), "\n", all),
+                            BufferExpandLines = string:split(BufferExpand, "\n", all),
                             InputRows = (cols_multiline([State#state.buffer_before ++ State#state.buffer_after], W, U) div W),
                             ExpandRows = (cols_multiline(BufferExpandLines, W, U) div W),
                             ExpandRowsLimit = case State#state.buffer_expand_limit of
@@ -678,7 +677,7 @@ handle_request(State = #state{ buffer_expand = Expand, buffer_expand_row = ERow,
     %% Get number of Lines in terminal window
     BufferExpandLines = case Expand of
         undefined -> [];
-        _ -> string:split(unicode:characters_to_list(Expand), "\n", all)
+        _ -> string:split(Expand, "\n", all)
     end,
     ExpandRows = (cols_multiline(BufferExpandLines, W, U) div W),
     InputRows = (cols_multiline([State#state.buffer_before ++ State#state.buffer_after], W, U) div W),
@@ -707,7 +706,8 @@ handle_request(State, new_prompt) ->
                      lines_after = []}};
 %% Print characters in the expandbuffer after the cursor
 handle_request(State, {expand, Expand, N}) ->
-    handle_request(State#state{buffer_expand = Expand, buffer_expand_limit = N}, redraw_prompt);
+    {_, NewState} = insert_buf(State#state{buffer_expand = []}, Expand),
+    handle_request(NewState#state{buffer_expand_limit = N}, redraw_prompt);
 %% putc prints Binary and overwrites any existing characters
 handle_request(State = #state{ redraw_prompt_on_output = RedrawOnOutput,
                                unicode = U }, {putc, Binary}) ->
@@ -1084,9 +1084,6 @@ update_geometry(State) ->
     case tty_window_size(State#state.tty) of
         {ok, {Cols, Rows}} when Cols > 0 ->
             ?dbg({?FUNCTION_NAME, Cols}),
-            %% We also set buffer_expand_row to 0, in case we are in paging mode
-            %% this ensures that the expand area gets redrawn when we handle move_expand
-            %% event.
             State#state{ cols = Cols, rows = Rows};
         _Error ->
             ?dbg({?FUNCTION_NAME, _Error}),
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index e18cf1345b..d6c688f1df 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -1202,6 +1202,20 @@ shell_expand_location_above(Config) ->
         ok
     end.
 
+shell_help(Config) ->
+    Term = start_tty(Config),
+    try
+        send_stdin(Term, "lists"),
+        send_stdin(Term, "\^[h"),
+        check_content(Term, "List processing functions."),
+        send_stdin(Term, ":all"),
+        send_stdin(Term, "\^[h"),
+        check_content(Term, "-spec all(Pred, List) -> boolean()"),
+        ok
+    after
+        stop_tty(Term),
+        ok
+    end.
 %% Test the we can handle invalid ansi escape chars.
 %%   tmux cannot handle this... so we test this using to_erl
 shell_invalid_ansi(_Config) ->
diff --git a/lib/stdlib/doc/src/edlin.xml b/lib/stdlib/doc/src/edlin.xml
index 56af730ef0..1c95113853 100644
--- a/lib/stdlib/doc/src/edlin.xml
+++ b/lib/stdlib/doc/src/edlin.xml
@@ -142,6 +142,10 @@ $ ERL_FLAGS="-config $HOME/.erlang_keymap" erl
       <item>
         <p>Move forward one word.</p>
       </item>
+      <tag><c>help</c></tag>
+      <item>
+        <p>Display help for the module or function closest on the left of the cursor.</p>
+      </item>
       <tag><c>history_down</c></tag>
       <item>
         <p>Move to the next item in the history.</p>
@@ -158,6 +162,14 @@ $ ERL_FLAGS="-config $HOME/.erlang_keymap" erl
       <item>
         <p>Delete the word under the cursor and save it in the kill buffer.</p>
       </item>
+      <tag><c>move_expand_down</c></tag>
+      <item>
+        <p>Move down one line in the expand area e.g. help or tab completion pager.</p>
+      </item>
+      <tag><c>move_expand_up</c></tag>
+      <item>
+        <p>Move up one line in the expand area e.g. help or tab completion pager.</p>
+      </item>
       <tag><c>new_line_finish</c></tag>
       <item>
         <p>Add a newline at the end of the line and try to evaluate the current expression.</p>
@@ -176,6 +188,14 @@ $ ERL_FLAGS="-config $HOME/.erlang_keymap" erl
       <item>
         <p>Redraw the current line.</p>
       </item>
+      <tag><c>scroll_expand_down</c></tag>
+      <item>
+        <p>Scroll down five lines in the expand area e.g. help or tab completion pager.</p>
+      </item>
+      <tag><c>scroll_expand_up</c></tag>
+      <item>
+        <p>Scroll up five lines in the expand area e.g. help or tab completion pager.</p>
+      </item>
       <tag><c>search_cancel</c></tag>
       <item>
         <p>Cancel the current search.</p>
@@ -192,11 +212,11 @@ $ ERL_FLAGS="-config $HOME/.erlang_keymap" erl
       <item>
         <p>Enter search mode, search the history.</p>
       </item>
-      <tag><c>search_down</c></tag>
+      <tag><c>skip_down</c></tag>
       <item>
         <p>Skip to the next line in the history that matches the current search expression.</p>
       </item>
-      <tag><c>search_up</c></tag>
+      <tag><c>skip_up</c></tag>
       <item>
         <p>Skip to the previous line in the history that matches the current search expression.</p>
       </item>
diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index 7841e3df74..37707348f2 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -89,6 +89,7 @@ expand(Bef0, Opts, #shell_state{bindings = Bs, records = RT, functions = FT}) ->
                  {error, _Column} ->
                     {no, [], []};
                  {function} -> expand_module_function(Bef0, FT);
+                 {function, _Mod} -> expand_module_function(Bef0, FT);
                  {fun_} -> expand_module_function(Bef0, FT);
 
                  {fun_, Mod} -> expand_function_name(Mod, Word, "/", FT);
diff --git a/lib/stdlib/test/edlin_context_SUITE.erl b/lib/stdlib/test/edlin_context_SUITE.erl
index 5e84a90199..fe25293fbb 100644
--- a/lib/stdlib/test/edlin_context_SUITE.erl
+++ b/lib/stdlib/test/edlin_context_SUITE.erl
@@ -42,8 +42,8 @@ get_context(_Config) ->
     {term} = edlin_context:get_context(lists:reverse("h(file,open), h(file")),
     {term} = edlin_context:get_context(lists:reverse("h(file,open), h(file,open")),
     {term, [{call, "h(file,open)"}], {call, "h(file,open)"}} = edlin_context:get_context(lists:reverse("h(file,open), h(file,open)")),
-    {function} = edlin_context:get_context(lists:reverse("file:")),
-    {function} = edlin_context:get_context(lists:reverse("file:open")),
+    {function, "file"} = edlin_context:get_context(lists:reverse("file:")),
+    {function, "file"} = edlin_context:get_context(lists:reverse("file:open")),
     {function, "file", "open", [], [], []} = edlin_context:get_context(lists:reverse("file:open(")),
     {string} = edlin_context:get_context(lists:reverse("file:open(\"")),
     {string} = edlin_context:get_context(lists:reverse("file:open(\"/")),
-- 
2.35.3

openSUSE Build Service is sponsored by