File 2591-stdlib-shell-pager.patch of Package erlang

From 48baaf814547fcc915e63eff4c59f74719004c68 Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Mon, 6 Nov 2023 17:46:30 +0100
Subject: [PATCH 1/4] stdlib: shell pager

Add a pager for large outputs
---
 lib/kernel/src/group.erl                    | 102 ++++++++----------
 lib/kernel/src/prim_tty.erl                 | 110 +++++++++++++++++---
 lib/kernel/src/user_drv.erl                 |  15 +--
 lib/kernel/test/interactive_shell_SUITE.erl |  44 ++++++--
 lib/stdlib/doc/src/stdlib_app.xml           |   3 +-
 lib/stdlib/src/edlin.erl                    |  84 +++++++++------
 lib/stdlib/src/edlin_key.erl                |  16 +++
 7 files changed, 259 insertions(+), 115 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 376480ad04..9d7c263bb6 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -604,7 +604,7 @@ get_line1({open_editor, _Cs, Cont, Rs}, Drv, Shell, Ls0, Encoding) ->
             get_line1(edlin:edit_line(Cs1, NewCont), Drv, Shell, Ls0, Encoding)
     end;
 %% Move Up, Down in History: Ctrl+P, Ctrl+N
-get_line1({history_up,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
+get_line1({history_up,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
     send_drv_reqs(Drv, Rs),
     case up_stack(save_line(Ls0, edlin:current_line(Cont))) of
         {none,_Ls} ->
@@ -612,7 +612,8 @@ get_line1({history_up,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
             get_line1(edlin:edit_line(Cs, Cont), Drv, Shell, Ls0, Encoding);
         {Lcs,Ls} ->
             send_drv_reqs(Drv, edlin:erase_line()),
-            {more_chars,Ncont,Nrs} = edlin:start(edlin:prompt(Cont)),
+            {more_chars,{A,B,C,_},Nrs} = edlin:start(edlin:prompt(Cont)),
+            Ncont = {A,B,C,Mode0},
             send_drv_reqs(Drv, Nrs),
             get_line1(
               edlin:edit_line1(
@@ -621,7 +622,7 @@ get_line1({history_up,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
                 Ncont),
               Drv, Shell, Ls, Encoding)
     end;
-get_line1({history_down,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
+get_line1({history_down,Cs,{_,_,_,Mode0}=Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
     send_drv_reqs(Drv, Rs),
     case down_stack(save_line(Ls0, edlin:current_line(Cont))) of
         {none,_Ls} ->
@@ -629,7 +630,8 @@ get_line1({history_down,Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding) ->
             get_line1(edlin:edit_line(Cs, Cont), Drv, Shell, Ls0, Encoding);
         {Lcs,Ls} ->
             send_drv_reqs(Drv, edlin:erase_line()),
-            {more_chars,Ncont,Nrs} = edlin:start(edlin:prompt(Cont)),
+            {more_chars,{A,B,C,_},Nrs} = edlin:start(edlin:prompt(Cont)),
+            Ncont = {A,B,C,Mode0},
             send_drv_reqs(Drv, Nrs),
             get_line1(edlin:edit_line1(string:to_graphemes(lists:sublist(Lcs,
                                                                          1,
@@ -656,6 +658,7 @@ get_line1({search,Cs,Cont,Rs}, Drv, Shell, Ls, Encoding) ->
     put(search_quit_prompt, Cont),
     Pbs = prompt_bytes("\033[;1;4msearch:\033[0m ", Encoding),
     {more_chars,Ncont,_Nrs} = edlin:start(Pbs, {search,none}),
+    put(search, new_search),
     get_line1(edlin:edit_line1(Cs, Ncont), Drv, Shell, Ls, Encoding);
 get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
   when Expand =:= expand; Expand =:= expand_full ->
@@ -678,34 +681,14 @@ get_line1({Expand, Before, Cs0, Cont,Rs}, Drv, Shell, Ls0, Encoding)
              {Cs1, _} when Cs1 =/= [] -> Cs1;
              _ ->
                  NlMatchStr = unicode:characters_to_binary("\n"++MatchStr),
+                 NLines = case Expand of
+                                expand -> 7;
+                                expand_full -> 0
+                            end,
                  case get(expand_below) of
                      true ->
-                         Lines = string:split(string:trim(MatchStr), "\n", all),
-                         NoLines = length(Lines),
-                         if NoLines > 5, Expand =:= expand ->
-                                 %% Only show 5 lines to start with
-                                 [L1,L2,L3,L4,L5|_] = Lines,
-                                 String = lists:join(
-                                            $\n,
-                                            [L1,L2,L3,L4,L5,
-                                             io_lib:format("Press tab to see all ~p expansions",
-                                                           [edlin_expand:number_matches(Matches)])]),
-                                 send_drv(Drv, {put_expand, unicode,
-                                                unicode:characters_to_binary(String)}),
-                                 Cs1;
-                            true ->
-                                 case get_tty_geometry(Drv) of
-                                     {_, Rows} when Rows > NoLines ->
-                                         %% If all lines fit on screen, we expand below
-                                         send_drv(Drv, {put_expand, unicode, NlMatchStr}),
-                                         Cs1;
-                                     _ ->
-                                         %% If there are more results than fit on
-                                         %% screen we expand above
-                                         send_drv_reqs(Drv, [{put_chars, unicode, NlMatchStr}]),
-                                         [$\e, $l | Cs1]
-                                 end
-                         end;
+                        send_drv(Drv, {put_expand, unicode, NlMatchStr, NLines}),
+                        Cs1;
                      false ->
                          send_drv(Drv, {put_chars, unicode, NlMatchStr}),
                          [$\e, $l | Cs1]
@@ -753,42 +736,49 @@ get_line1({search_cancel,_Cs,_,Rs}, Drv, Shell, Ls, Encoding) ->
     send_drv_reqs(Drv, edlin:redraw_line(NCont)),
     get_line1({more_chars, NCont, []}, Drv, Shell, Ls, Encoding);
 %% Search mode is entered.
-get_line1({What,{line,Prompt,{_,{RevCmd0,_},_},{search, none}},_Rs},
+get_line1({What,{line,Prompt,{_,{RevCmd0,_},_},{search, none}}=Cont0,Rs},
           Drv, Shell, Ls0, Encoding) ->
     %% Figure out search direction. ^S and ^R are returned through edlin
     %% whenever we received a search while being already in search mode.
+    OldSearch = get(search),
     {Search, Ls1, RevCmd} = case RevCmd0 of
                                 [$\^S|RevCmd1] ->
                                     {fun search_down_stack/2, Ls0, RevCmd1};
                                 [$\^R|RevCmd1] ->
                                     {fun search_up_stack/2, Ls0, RevCmd1};
-                                _ -> % new search, rewind stack for a proper search.
-                                    {fun search_up_stack/2, new_stack(get_lines(Ls0)), RevCmd0}
+                                _ when RevCmd0 =/= OldSearch -> % new search, rewind stack for a proper search.
+                                    {fun search_up_stack/2, new_stack(get_lines(Ls0)), RevCmd0};
+                                _ ->
+                                    {skip, Ls0, RevCmd0}
                             end,
+    put(search, RevCmd),
     Cmd = lists:reverse(RevCmd),
-    {Ls, NewStack} = case Search(Ls1, Cmd) of
-                         {none, Ls2} ->
-                             send_drv(Drv, beep),
-                             put(search_result, []),
-                             send_drv(Drv, delete_line),
-                             send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
-                             {Ls2, {[],{RevCmd, []},[]}};
-                         {Line, Ls2} -> % found. Complete the output edlin couldn't have done.
-                             Lines = string:split(string:to_graphemes(Line), "\n", all),
-                             Output = if length(Lines) > 5 ->
-                                            [A,B,C,D,E|_]=Lines,
-                                            (["\n  " ++ Line1 || Line1 <- [A,B,C,D,E]] ++
-                                                [io_lib:format("~n  ... (~w lines omitted)",[length(Lines)-5])]);
-                                         true -> ["\n  " ++ Line1 || Line1 <- Lines]
-                                      end,
-                             put(search_result, Lines),
-                             send_drv(Drv, delete_line),
-                             send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
-                             send_drv(Drv, {put_expand_no_trim, unicode, unicode:characters_to_binary(Output)}),
-                             {Ls2, {[],{RevCmd, []},[]}}
-                     end,
-    Cont = {line,Prompt,NewStack,{search, none}},
-    more_data(What, Cont, Drv, Shell, Ls, Encoding);
+    if Search =:= skip ->
+        %% Move expand are the only valid requests to bypass search mode
+        %% Sending delete_chars, insert_chars, etc. will result in
+        %% expand area being cleared.
+        Rs1 = [R||{move_expand,_}=R<-Rs],
+        send_drv_reqs(Drv, Rs1),
+        more_data(What, Cont0, Drv, Shell, Ls0, Encoding);
+       true ->
+        {Ls, NewStack} = case Search(Ls1, Cmd) of
+            {none, Ls2} ->
+                send_drv(Drv, beep),
+                put(search_result, []),
+                send_drv(Drv, delete_line),
+                send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
+                {Ls2, {[],{RevCmd, []},[]}};
+            {Line, Ls2} -> % found. Complete the output edlin couldn't have done.
+                Lines = string:split(string:to_graphemes(Line), "\n", all),
+                put(search_result, Lines),
+                send_drv(Drv, delete_line),
+                send_drv(Drv, {insert_chars, unicode, unicode:characters_to_binary(Prompt++Cmd)}),
+                send_drv(Drv, {put_expand_no_trim, unicode, unicode:characters_to_binary(Line), 7}),
+                {Ls2, {[],{RevCmd, []},[]}}
+        end,
+        Cont = {line,Prompt,NewStack,{search, none}},
+        more_data(What, Cont, Drv, Shell, Ls, Encoding)
+    end;
 get_line1({What,Cont0,Rs}, Drv, Shell, Ls, Encoding) ->
     send_drv_reqs(Drv, Rs),
     more_data(What, Cont0, Drv, Shell, Ls, Encoding).
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index 4197b00dff..c6ff0601cd 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,
-         ansi_regexp/0]).
+         ansi_regexp/0, ansi_color/2]).
 -export([reader_stop/1, disable_reader/1, enable_reader/1]).
 
 -nifs([isatty/1, tty_create/0, tty_init/3, tty_set/1, setlocale/1,
@@ -143,6 +143,8 @@
                 buffer_before = [],  %% Current line before cursor in reverse
                 buffer_after = [],   %% Current line after  cursor not in reverse
                 buffer_expand,       %% Characters in expand buffer
+                buffer_expand_row = 1,
+                buffer_expand_limit = 0 :: non_neg_integer(),
                 cols = 80,
                 rows = 24,
                 xn = false,
@@ -170,8 +172,8 @@
 -type request() ::
         {putc_raw, binary()} |
         {putc, unicode:unicode_binary()} |
-        {expand, unicode:unicode_binary()} |
-        {expand_with_trim, unicode:unicode_binary()} |
+        {expand, unicode:unicode_binary(), integer()} |
+        {expand_with_trim, unicode:unicode_binary(), integer()} |
         {insert, unicode:unicode_binary()} |
         {insert_over, unicode:unicode_binary()} |
         {delete, integer()} |
@@ -184,6 +186,7 @@
         {move, integer()} |
         {move_line, integer()} |
         {move_combo, integer(), integer(), integer()} |
+        {move_expand, -32768..32767} |
         clear |
         beep.
 -type tty() :: reference().
@@ -194,6 +197,32 @@
 ansi_regexp() ->
     ?ANSI_REGEXP.
 
+ansi_fg_color(Color) ->
+    case Color of
+        black -> 30;
+        red -> 31;
+        green -> 32;
+        yellow -> 33;
+        blue -> 34;
+        magenta -> 35;
+        cyan -> 36;
+        white -> 37;
+        bright_black -> 90;
+        bright_red -> 91;
+        bright_green -> 92;
+        bright_yellow -> 93;
+        bright_blue -> 94;
+        bright_magenta -> 95;
+        bright_cyan -> 96;
+        bright_white -> 97
+    end.
+ansi_bg_color(Color) ->
+    ansi_fg_color(Color) + 10.
+
+-spec ansi_color(BgColor :: atom(), FgColor :: atom()) -> iolist().
+ansi_color(BgColor, FgColor) ->
+    io_lib:format("\e[~w;~wm", [ansi_bg_color(BgColor), ansi_fg_color(FgColor)]).
+
 -spec on_load() -> ok.
 on_load() ->
     on_load(#{}).
@@ -597,7 +626,7 @@ handle_request(State, redraw_prompt) ->
     {ClearLine, _} = handle_request(State, delete_line),
     {Redraw, NewState} = handle_request(State, redraw_prompt_pre_deleted),
     {[ClearLine, Redraw], NewState};
-handle_request(State = #state{unicode = U, cols = W}, redraw_prompt_pre_deleted) ->
+handle_request(State = #state{unicode = U, cols = W, rows = R}, redraw_prompt_pre_deleted) ->
     {Movement, TextInView, EverythingFitsInView} = in_view(State),
     {_, NewPrompt} = handle_request(State, new_prompt),
     {Redraw, RedrawState} = insert_buf(NewPrompt, unicode:characters_to_binary(TextInView)),
@@ -611,17 +640,65 @@ handle_request(State = #state{unicode = U, cols = W}, redraw_prompt_pre_deleted)
                             true when Last =/= [] -> cols(Last, U);
                             _ -> cols(State#state.buffer_before, U) + cols(State#state.buffer_after,U)
                           end,
-                          {ExpandBuffer, NewState} = insert_buf(RedrawState#state{ buffer_expand = [] }, iolist_to_binary(BufferExpand)),
+                          ERow = State#state.buffer_expand_row,
+
+                            BufferExpandLines = string:split(erlang:binary_to_list(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
+                                0 ->
+                                     ExpandRows;
+                                Limit ->
+                                    min(Limit, ExpandRows)
+                            end,
+                            ExpandRowsLimit1 = min(ExpandRowsLimit, R-1-InputRows),
+                            BufferExpand1 = case ExpandRows > (R-InputRows) of
+                                true ->
+                                        Color = ansi_color(cyan, bright_white),
+                                        StatusLine = io_lib:format(Color ++"\e[1m" ++ "rows ~w to ~w of ~w" ++ "\e[0m",
+                                                                   [ERow, (ERow-1) + ExpandRowsLimit1, ExpandRows]),
+                                        Cols1 = max(0,W*ExpandRowsLimit1),
+                                        Cols0 = max(0,W*(ERow-1)),
+                                        {_, _, BufferExpandLinesInViewStart, {_, BEStartIVHalf}} = split_cols_multiline(Cols0, BufferExpandLines, U, W),
+                                        {_, BufferExpandLinesInViewRev, _, {BEIVHalf, _}} = split_cols_multiline(Cols1, BufferExpandLinesInViewStart++[BEStartIVHalf], U, W),
+                                        BEIVHalf1 = case BEIVHalf of [] -> [];
+                                            _ -> [BEIVHalf]
+                                        end,
+                                        ExpandInView = lists:reverse(BEIVHalf1++BufferExpandLinesInViewRev),
+                                        ["\r\n",lists:join("\n", ExpandInView ++ [StatusLine])];
+                                false ->
+                                    ["\r\n",BufferExpand]
+                                end,
+                          {ExpandBuffer, NewState} = insert_buf(RedrawState#state{ buffer_expand = [] }, iolist_to_binary(BufferExpand1)),
                           BECols = cols(W, End, NewState#state.buffer_expand, U),
                           MoveToEnd = move_cursor(RedrawState, BECols, End),
                           {[encode(Redraw,U),encode(ExpandBuffer, U), MoveToEnd, Movement], RedrawState}
                   end,
     {Output, State};
+handle_request(State = #state{ buffer_expand = Expand, buffer_expand_row = ERow, cols = W, rows = WindowRows, unicode = U}, {move_expand, N}) ->
+    %% Get number of Lines in terminal window
+    BufferExpandLines = case Expand of
+        undefined -> [];
+        _ -> string:split(erlang:binary_to_list(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),
+    ERow1 = if ExpandRows > WindowRows-InputRows -> %% We need to page expand rows
+        StatusLine = lists:flatten(io_lib:format("rows ~w to ~w of ~w", [ERow, (ERow-1) + WindowRows-1-InputRows, ExpandRows])),
+        StatusRows = (cols_multiline([StatusLine], W, U) div W),
+        min(ExpandRows-(WindowRows-InputRows-StatusRows-1),max(1,ERow + N));
+        true -> 1 %% No need to page expand rows
+    end,
+    if ERow =:= ERow1 -> %% We don't need to do anything
+        {[], State};
+        true ->
+            handle_request(State#state{buffer_expand_row = ERow1}, redraw_prompt)
+    end;
 %% Clear the expand buffer after the cursor when we handle any request.
 handle_request(State = #state{ buffer_expand = Expand, unicode = U}, Request)
   when Expand =/= undefined ->
-    {Redraw, NoExpandState} = handle_request(State#state{ buffer_expand = undefined }, redraw_prompt),
-    {Output, NewState} = handle_request(NoExpandState#state{ buffer_expand = undefined }, Request),
+    {Redraw, NoExpandState} = handle_request(State#state{ buffer_expand = undefined, buffer_expand_row = 1 }, redraw_prompt),
+    {Output, NewState} = handle_request(NoExpandState#state{ buffer_expand = undefined, buffer_expand_row = 1 }, Request),
     {[encode(Redraw, U), encode(Output, U)], NewState};
 handle_request(State, new_prompt) ->
     {"", State#state{buffer_before = [],
@@ -629,11 +706,11 @@ handle_request(State, new_prompt) ->
                      lines_before = [],
                      lines_after = []}};
 %% Print characters in the expandbuffer after the cursor
-handle_request(State, {expand, Expand}) ->
-    handle_request(State#state{buffer_expand = Expand}, redraw_prompt);
-handle_request(State, {expand_with_trim, Binary}) ->
+handle_request(State, {expand, Expand, N}) ->
+    handle_request(State#state{buffer_expand = Expand, buffer_expand_limit = N}, redraw_prompt);
+handle_request(State, {expand_with_trim, Binary, N}) ->
     handle_request(State, 
-                   {expand, iolist_to_binary(["\r\n",string:trim(Binary, both)])});
+                   {expand, iolist_to_binary([string:trim(Binary, both)]), N});
 %% putc prints Binary and overwrites any existing characters
 handle_request(State = #state{ redraw_prompt_on_output = RedrawOnOutput,
                                unicode = U }, {putc, Binary}) ->
@@ -910,18 +987,23 @@ move(left, #state{ left = Left }, N) ->
 move(right, #state{ right = Right }, N) ->
     lists:duplicate(N, Right).
 
-in_view(#state{lines_after = LinesAfter, buffer_before = Bef, buffer_after = Aft, lines_before = LinesBefore, rows=R, cols=W, unicode=U, buffer_expand = BufferExpand} = State) ->
+in_view(#state{lines_after = LinesAfter, buffer_before = Bef, buffer_after = Aft, lines_before = LinesBefore,
+               rows=R, cols=W, unicode=U, buffer_expand = BufferExpand, buffer_expand_limit = BufferExpandLimit} = State) ->
     BufferExpandLines = case BufferExpand of
                             undefined -> [];
                             _ -> string:split(erlang:binary_to_list(BufferExpand), "\r\n", all)
                         end,
-    ExpandRows = (cols_multiline(BufferExpandLines, W, U) div W),
+    ExpandLimit = case BufferExpandLimit of
+                        0 -> cols_multiline(BufferExpandLines, W, U) div W;
+                        _ -> min(cols_multiline(BufferExpandLines, W, U) div W, BufferExpandLimit)
+                    end,
+    ExpandRows = ExpandLimit,
     InputBeforeRows = (cols_multiline(LinesBefore, W, U) div W),
     InputRows = (cols_multiline([Bef ++ Aft], W, U) div W),
     InputAfterRows = (cols_multiline(LinesAfter, W, U) div W),
     %% Dont print lines after if we have expansion rows
     SumRows = InputBeforeRows+ InputRows + ExpandRows + InputAfterRows,
-    if SumRows > R -> 
+    if SumRows > R ->
             RowsLeftAfterInputRows = R - InputRows,
             RowsLeftAfterExpandRows = RowsLeftAfterInputRows - ExpandRows,
             RowsLeftAfterInputBeforeRows = RowsLeftAfterExpandRows - InputBeforeRows,
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index 5017235d3f..777e0be2f8 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -52,8 +52,9 @@
         %% guaranteed to have been written to the terminal
         {put_chars_sync, unicode, binary(), {From :: pid(), Reply :: term()}} |
         %% Put text in expansion area
-        {put_expand, unicode, binary()} |
-        {put_expand_no_trim,  unicode, binary()} |
+        {put_expand, unicode, binary(), integer()} |
+        {put_expand_no_trim,  unicode, binary(), integer()} |
+        {move_expand, -32768..32767} |
         %% Move the cursor X characters left or right (negative is left)
         {move_rel, -32768..32767} |
         %% Move the cursor Y rows up or down (negative is up)
@@ -789,10 +790,12 @@ io_request({put_chars_sync, unicode, Chars, Reply}, TTY) ->
     {Output, NewTTY} = prim_tty:handle_request(TTY, {putc, unicode:characters_to_binary(Chars)}),
     {ok, MonitorRef} = prim_tty:write(NewTTY, Output, self()),
     {Reply, MonitorRef, NewTTY};
-io_request({put_expand, unicode, Chars}, TTY) ->
-    write(prim_tty:handle_request(TTY, {expand_with_trim, unicode:characters_to_binary(Chars)}));
-io_request({put_expand_no_trim, unicode, Chars}, TTY) ->
-    write(prim_tty:handle_request(TTY, {expand, unicode:characters_to_binary(Chars)}));
+io_request({put_expand, unicode, Chars, N}, TTY) ->
+    write(prim_tty:handle_request(TTY, {expand_with_trim, unicode:characters_to_binary(Chars), N}));
+io_request({put_expand_no_trim, unicode, Chars, N}, TTY) ->
+    write(prim_tty:handle_request(TTY, {expand, unicode:characters_to_binary(Chars), N}));
+io_request({move_expand, N}, TTY) ->
+    write(prim_tty:handle_request(TTY, {move_expand, N}));
 io_request({move_rel, N}, TTY) ->
     write(prim_tty:handle_request(TTY, {move, N}));
 io_request({move_line, R}, TTY) ->
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index b15216317e..e18cf1345b 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -1128,20 +1128,48 @@ shell_expand_location_below(Config) ->
                           {module, long_module} = code:load_binary(long_module, "long_module.beam", Bin)
                   end),
         check_content(Term, "3>"),
+        tmux(["resize-window -t ",tty_name(Term)," -y 50"]),
+        timer:sleep(1000), %% Sleep to make sure window has resized
+        Result = 61,
+        Rows1 = 48,
         send_stdin(Term, "long_module:" ++ FunctionName),
         send_stdin(Term, "\t"),
+        check_content(Term, "3> long_module:" ++ FunctionName ++ "\nfunctions(\n|.)*a_long_function_name0\\("),
+
         %% Check that correct text is printed below expansion
-        check_content(Term, io_lib:format("Press tab to see all ~p expansions",
-                                          [length(NumFunctions)])),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [1, 7, Result])),
+        send_stdin(Term, "\t"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+            [1, Rows1, Result])),
+        send_tty(Term, "Down"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [2, Rows1+1, Result])),
+        send_tty(Term, "PgDn"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [7, Rows1+6, Result])),
+        send_tty(Term, "PgUp"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [2, Rows1+1, Result])),
+        send_tty(Term, "PgUp"),
+        %% Overshoot up
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [1, Rows1, Result])),
+        %% Overshoot down
+        send_tty(Term, "PgDn"),
+        send_tty(Term, "PgDn"),
+        send_tty(Term, "PgDn"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [14, Rows1+13, Result])),
+        check_content(Term, "\n.*a_long_function_name99\\("),
+        send_tty(Term, "Up"),
+        check_content(Term, io_lib:format("rows ~w to ~w of ~w",
+                                          [13, Rows1+12, Result])),
+
         send_stdin(Term, "\t"),
-        %% The expansion does not fit on screen, verify that
-        %% expand above mode is used
-        check_content(fun() -> get_content(Term, "-S -5") end,
-                      "\nfunctions\n"),
-        check_content(Term, "3> long_module:" ++ FunctionName ++ "$"),
 
         %% We resize the terminal to make everything fit and test that
-        %% expand below mode is used
+        %% expand below displays everything
         tmux(["resize-window -t ", tty_name(Term), " -y ", integer_to_list(Rows+10)]),
         timer:sleep(1000), %% Sleep to make sure window has resized
         send_stdin(Term, "\t\t"),
diff --git a/lib/stdlib/doc/src/stdlib_app.xml b/lib/stdlib/doc/src/stdlib_app.xml
index 6d455d0949..35283c4029 100644
--- a/lib/stdlib/doc/src/stdlib_app.xml
+++ b/lib/stdlib/doc/src/stdlib_app.xml
@@ -60,7 +60,8 @@
       <tag><marker id="shell_expand_location"/><c>shell_expand_location = above | below</c></tag>
       <item>
           <p>Sets where the tab expansion text should appear in the shell.
-            The default is <c>below</c>.</p>
+            The default is <c>below</c>. This will open a pager below the cursor that is scrollable
+            one line at a time with <c>Up/Down</c> arrow keys or 5 lines at a time with <c>PgUp/PgDn</c>.</p>
       </item>
       <tag><marker id="shell_redraw_prompt_on_output"/><c>shell_redraw_prompt_on_output = boolean()</c></tag>
       <item>
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 3aae25e7af..4ad4343851 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -114,15 +114,19 @@ edit(eof, _, {_,{Bef,Aft0},LA} = L, _, Rs) ->
         _ -> Aft0
     end,
     {done,L,[],reverse(Rs, [{move_combo,-cp_len(Bef), length(LA), cp_len(Aft1)}])};
-edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
+edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode1, EscapePrefix}, Rs0) ->
+    {ShellMode, NextMode} = case ShellMode1 of
+        {_, _}=M -> M;
+        Mode -> {Mode, Mode}
+    end,
     case edlin_key:get_valid_escape_key(Buf, EscapePrefix) of
         {escape_prefix, EscapePrefix1} ->
             case ShellMode of
                 tab_expand -> edit(Buf, P, MultiLine, {normal, none}, Rs0);
-                _ -> edit([], P, MultiLine, {ShellMode, EscapePrefix1}, Rs0)
+                _ -> edit([], P, MultiLine, {NextMode, EscapePrefix1}, Rs0)
             end;
         {invalid, _I, Rest} ->
-            edit(Rest, P, MultiLine, {ShellMode, none}, Rs0);
+            edit(Rest, P, MultiLine, {NextMode, none}, Rs0);
         {insert, C1, Cs2} ->
             %% If its a printable character
             %% we could in theory override it in the keymap,
@@ -148,10 +152,10 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
                     case do_op(Op, MultiLine, Rs0) of
                         {blink,N,MultiLine1,Rs} ->
                             edit(Cs2, P, MultiLine1, {blink,N}, Rs);
-                        {redraw, MultiLine1, Rs} ->
-                            edit(Cs2, P, MultiLine1, {ShellMode, none}, redraw(P, MultiLine1, Rs));
-                        {MultiLine1,Rs} ->
-                            edit(Cs2, P, MultiLine1, {ShellMode, none}, Rs)
+                        {redraw, {_LB1, {_Bef1, _Aft1}, _LA1}=MultiLine1, Rs} ->
+                            edit(Cs2, P, MultiLine1, {NextMode, none}, redraw(P, MultiLine1, Rs));
+                        {{_LB1, {_Bef1, _Aft1}, _LA1}=MultiLine1,Rs} ->
+                            edit(Cs2, P, MultiLine1, {NextMode, none}, Rs)
                     end
             end;
         {key, Key, Cs} ->
@@ -165,18 +169,22 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
                     end;
                 {ok, Value0} -> Value0
             end,
+            Cont = {line,P,MultiLine,{NextMode, none}},
             case Value of
-                none -> edit(Cs, P, MultiLine, {normal,none}, Rs0);
-                search -> {search,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                search_found -> {search_found,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                search_cancel -> {search_cancel,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                search_quit -> {search_quit,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                open_editor -> {open_editor,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                history_up -> {history_up,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
-                history_down -> {history_down,Cs,{line,P,MultiLine,{normal, none}},reverse(Rs0)};
+                {mode, Mode1} ->
+                    edit(Buf, P, MultiLine, {{Mode1, ShellMode}, none}, Rs0);
+                none -> edit(Cs, P, MultiLine, {NextMode,none}, Rs0);
+                search -> {search,Cs,Cont,reverse(Rs0)};
+                search_found -> {search_found,Cs,Cont,reverse(Rs0)};
+                search_cancel -> {search_cancel,Cs,Cont,reverse(Rs0)};
+                search_quit -> {search_quit,Cs,Cont,reverse(Rs0)};
+                format_expression -> {format_expression,Cs,Cont,reverse(Rs0)};
+                open_editor -> {open_editor,Cs,Cont,reverse(Rs0)};
+                history_up -> {history_up,Cs,Cont,reverse(Rs0)};
+                history_down -> {history_down,Cs,Cont,reverse(Rs0)};
                 new_line ->
                     MultiLine1 = {[lists:reverse(Bef)|LB],{[],Aft},LA},
-                    edit(Cs, P, MultiLine1, {normal, none}, reverse(redraw(P, MultiLine1, Rs0)));
+                    edit(Cs, P, MultiLine1, {NextMode, none}, reverse(redraw(P, MultiLine1, Rs0)));
                 new_line_finish ->
                     % Move to end
                     {{LB1,{Bef1,[]},[]}, Rs1} = do_op(end_of_expression, MultiLine, Rs0),
@@ -184,10 +192,10 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
                 redraw_line ->
                     Rs1 = erase_line(Rs0),
                     Rs = redraw(P, MultiLine, Rs1),
-                    edit(Cs, P, MultiLine, {normal, none}, Rs);
+                    edit(Cs, P, MultiLine, {NextMode, none}, Rs);
                 clear ->
                     Rs = redraw(P, MultiLine, [clear|Rs0]),
-                    edit(Cs, P, MultiLine, {normal, none}, Rs);
+                    edit(Cs, P, MultiLine, {NextMode, none}, Rs);
                 tab_expand ->
                     {expand, chars_before(MultiLine), Cs,
                      {line, P, MultiLine, {tab_expand, none}},
@@ -209,14 +217,14 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode, EscapePrefix}, Rs0) ->
                         {blink,N,MultiLine1,Rs} ->
                             edit(Cs, P, MultiLine1, {blink,N}, Rs);
                         {redraw, MultiLine1, Rs} ->
-                            edit(Cs, P, MultiLine1, {normal, none}, redraw(P, MultiLine1, Rs));
+                            edit(Cs, P, MultiLine1, {NextMode, none}, redraw(P, MultiLine1, Rs));
                         {MultiLine1,Rs} ->
-                            edit(Cs, P, MultiLine1, {ShellMode, none}, Rs)
+                            edit(Cs, P, MultiLine1, {NextMode, none}, Rs)
                     end
             end
     end.
 
-%% do_op(Action, Before, After, Requests)
+%% do_op(Action, {LinesBefore, {Before, After}, LinesAfter}, Requests)
 %% Before and After are of lists of type string:grapheme_cluster()
 do_op({insert,C}, {LB,{[],[]},LA}, Rs) ->
     {{LB,{[C],[]},LA},[{insert_chars, unicode,[C]}|Rs]};
@@ -246,6 +254,22 @@ do_op({insert,C}, {LB,{[Bef|Bef0], Aft},LA}, Rs) ->
 %% search: $TERMS
 %%   $ResultLine1
 %%   $ResultLine2
+do_op(move_expand_up, Cont, Rs) ->
+    {Cont, [{move_expand, -1}|Rs]};
+do_op(move_expand_down, Cont, Rs) ->
+    {Cont, [{move_expand, 1}|Rs]};
+do_op({search,move_expand_up}, Cont, Rs) ->
+    {Cont, [{move_expand, -1}|Rs]};
+do_op({search,move_expand_down}, Cont, Rs) ->
+    {Cont, [{move_expand, 1}|Rs]};
+do_op(scroll_expand_up, Cont, Rs) ->
+    {Cont, [{move_expand, -5}|Rs]};
+do_op(scroll_expand_down, Cont, Rs) ->
+    {Cont, [{move_expand, 5}|Rs]};
+do_op({search,scroll_expand_up}, Cont, Rs) ->
+    {Cont, [{move_expand, -5}|Rs]};
+do_op({search,scroll_expand_down}, Cont, Rs) ->
+    {Cont, [{move_expand, 5}|Rs]};
 do_op({insert_search, C}, {LB,{Bef, []},LA}, Rs) ->
     {{LB, {[C|Bef],[]}, LA},
      [{insert_chars, unicode, [C]}, delete_after_cursor | Rs]};
@@ -256,9 +280,9 @@ do_op({insert_search, C}, {LB,{Bef, _Aft},LA}, Rs) ->
 do_op({search, backward_delete_char}, {LB,{[_|Bef], Aft},LA}, Rs) ->
     Offset= cp_len(Aft)+1,
     {{LB, {Bef,Aft}, LA},
-     [{insert_chars, unicode, Aft}, {delete_chars,-Offset}|Rs]};
+     [redraw, {insert_chars, unicode, Aft}, {delete_chars,-Offset}|Rs]};
 do_op({search, backward_delete_char}, {LB,{[], Aft},LA}, Rs) ->
-    {{LB, {[],Aft}, LA}, [{insert_chars, unicode, Aft}, {delete_chars,-cp_len(Aft)}|Rs]};
+    {redraw, {LB, {[],Aft}, LA}, [{insert_chars, unicode, Aft}, {delete_chars,-cp_len(Aft)}|Rs]};
 do_op({search, skip_up}, {_,{Bef, Aft},_}, Rs) ->
     Offset= cp_len(Aft),
     {{[],{[$\^R|Bef],Aft},[]}, % we insert ^R as a flag to whoever called us
@@ -286,7 +310,7 @@ do_op(backward_delete_char, {[PrevLine|LB],{[], Aft},LA}, Rs) ->
     NewLine = {LB, {lists:reverse(PrevLine), Aft}, LA},
     {redraw, NewLine,Rs};
 do_op(backward_delete_char, {LB,{[GC|Bef], Aft},LA}, Rs) ->
-    {{LB, {Bef,Aft}, LA},[{delete_chars,-gc_len(GC)}|Rs]};
+    {redraw, {LB, {Bef,Aft}, LA},[{delete_chars,-gc_len(GC)}|Rs]};
 do_op(forward_delete_word, {LB,{Bef, []},[NextLine|LA]}, Rs) ->
     NewLine = {LB, {Bef, NextLine}, LA},
     {redraw, NewLine, Rs};
@@ -294,7 +318,7 @@ do_op(forward_delete_word, {LB,{Bef, Aft0},LA}, Rs) ->
     {Aft1,Kill0,N0} = over_non_word(Aft0, [], 0),
     {Aft,Kill,N} = over_word(Aft1, Kill0, N0),
     put(kill_buffer, reverse(Kill)),
-    {{LB, {Bef,Aft}, LA},[{delete_chars,N}|Rs]};
+    {redraw, {LB, {Bef,Aft}, LA},[{delete_chars,N}|Rs]};
 do_op(backward_delete_word, {[PrevLine|LB],{[], Aft},LA}, Rs) ->
     NewLine = {LB, {lists:reverse(PrevLine), Aft}, LA},
     {redraw, NewLine,Rs};
@@ -339,20 +363,20 @@ do_op(transpose_word, {LB,{Bef0, Aft0},LA}, Rs) ->
             {Bef3,Word1,B2} = over_word(Bef2, [], B1),
             {Bef3, Word2B++reverse(Word2A)++NonWord++Word1, Aft1, B2}
     end,
-    {{LB, {reverse(TransposedWords)++Bef, Aft}, LA},[{insert_chars_over, unicode, TransposedWords}, {move_rel, -N}|Rs]};
+    {redraw,{LB, {reverse(TransposedWords)++Bef, Aft}, LA},[{insert_chars_over, unicode, TransposedWords}, {move_rel, -N}|Rs]};
 do_op(kill_word, {LB,{Bef, Aft0},LA}, Rs) ->
     {Aft1,Kill0,N0} = over_non_word(Aft0, [], 0),
     {Aft,Kill,N} = over_word(Aft1, Kill0, N0),
     put(kill_buffer, reverse(Kill)),
-    {{LB, {Bef,Aft}, LA},[{delete_chars,N}|Rs]};
+    {redraw,{LB, {Bef,Aft}, LA},[{delete_chars,N}|Rs]};
 do_op(backward_kill_word, {LB,{Bef0, Aft},LA}, Rs) ->
     {Bef1,Kill0,N0} = over_non_word(Bef0, [], 0),
     {Bef,Kill,N} = over_word(Bef1, Kill0, N0),
     put(kill_buffer, Kill),
-    {{LB,{Bef,Aft},LA},[{delete_chars,-N}|Rs]};
+    {redraw,{LB,{Bef,Aft},LA},[{delete_chars,-N}|Rs]};
 do_op(kill_line, {LB, {Bef, Aft}, LA}, Rs) ->
     put(kill_buffer, Aft),
-    {{LB, {Bef,[]}, LA},[{delete_chars,cp_len(Aft)}|Rs]};
+    {redraw,{LB, {Bef,[]}, LA},[{delete_chars,cp_len(Aft)}|Rs]};
 do_op(clear_line, _, Rs) ->
     {redraw, {[], {[],[]},[]}, Rs};
 do_op(yank, {LB,{Bef, []},LA}, Rs) ->
@@ -360,7 +384,7 @@ do_op(yank, {LB,{Bef, []},LA}, Rs) ->
     {{LB, {reverse(Kill, Bef),[]}, LA},[{insert_chars, unicode,Kill}|Rs]};
 do_op(yank, {LB,{Bef, Aft},LA}, Rs) ->
     Kill = get(kill_buffer),
-    {{LB, {reverse(Kill, Bef),Aft}, LA},[{insert_chars, unicode,Kill}|Rs]};
+    {redraw,{LB, {reverse(Kill, Bef),Aft}, LA},[{insert_chars, unicode,Kill}|Rs]};
 do_op(forward_line, {_,_,[]} = MultiLine, Rs) ->
     {MultiLine, Rs};
 do_op(forward_line, {LB,{Bef, Aft},[AL|LA]}, Rs) ->
diff --git a/lib/stdlib/src/edlin_key.erl b/lib/stdlib/src/edlin_key.erl
index 90b3d3e207..8d16f1237b 100644
--- a/lib/stdlib/src/edlin_key.erl
+++ b/lib/stdlib/src/edlin_key.erl
@@ -153,6 +153,12 @@ merge(InputKeyMap, [Mode|ShellModes], KeyMap) ->
 key_map() -> #{
         normal => normal_map(),
         search => #{
+            "\^[OA" => move_expand_up,
+            "\^[[A" => move_expand_up,
+            "\^[OB" => move_expand_down,
+            "\^[[B" => move_expand_down,
+            "\^[[6~" => scroll_expand_down,
+            "\^[[5~" => scroll_expand_up,
             "\^R" => skip_up,
             "\^S" => skip_down,
             "\^[C" => search_cancel,
@@ -165,6 +171,12 @@ key_map() -> #{
             %% # everything else should exit search mode and edit the search result (search_quit),
         },
         tab_expand => #{
+            "\^[OA" => move_expand_up,
+            "\^[[A" => move_expand_up,
+            "\^[OB" => move_expand_down,
+            "\^[[B" => move_expand_down,
+            "\^[[6~" => scroll_expand_down,
+            "\^[[5~" => scroll_expand_up,
             "\t" => tab_expand_full,
             default => tab_expand_quit %% go to normal mode and evaluate key input again
         }
@@ -298,11 +310,15 @@ valid_functions() ->
      %%jcl_menu,
      kill_line,            %% Delete all characters from the cursor to the end of the line and save them in the kill buffer
      kill_word,            %% Delete the word behind the cursor and save it in the kill buffer
+     move_expand_up,       %% Move up one line in the expand area e.g. help or tab completion pager
+     move_expand_down,     %% Move down one line in the expand area e.g. help or tab completion pager
      new_line_finish,      %% Add a newline at the end of the line and try to evaluate the current expression
      new_line,             %% Add a newline at the cursor position
      none,                 %% Do nothing
      open_editor,          %% Open the current line in an editor i.e. EDITOR=code -w
      redraw_line,          %% Redraw the current line
+     scroll_expand_up,     %% Scroll up five lines in the expand area e.g. help or tab completion pager
+     scroll_expand_down,   %% Scroll down five lines in the expand area e.g. help or tab completion pager
      search_cancel,        %% Cancel the current search
      search_found,         %% Accept the current search result and submit it
      search_quit,          %% Accept the current search result, but edit it before submitting
-- 
2.35.3

openSUSE Build Service is sponsored by