File 2624-tty-Fix-column-calculation-when-we-start-with-a-high.patch of Package erlang

From 27f76c000dc58fba17e9ca182789adba450a9be5 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Tue, 19 Dec 2023 21:56:05 +0100
Subject: [PATCH 04/11] tty: Fix column calculation when we start with a high
 col

When cols starts with a currcol > colsperline we first
calculate remove those extra rows from CurrCols so that
we don't mess things up when we encounter \r\n characters
later on.
---
 lib/kernel/src/prim_tty.erl                 | 22 +++++++----
 lib/kernel/test/interactive_shell_SUITE.erl | 41 ++++++++++++++++++---
 2 files changed, 51 insertions(+), 12 deletions(-)

diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index 755673a8cd..b8413cb090 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -1068,14 +1068,22 @@ cols([SkipSeq | T], Unicode) when is_binary(SkipSeq) ->
     %% so we skip that
     cols(T, Unicode).
 
-cols(ColsPerLine, CurrCols, Chars, Unicode) when CurrCols > ColsPerLine ->
-    ColsPerLine + cols(ColsPerLine, CurrCols - ColsPerLine, Chars, Unicode);
-cols(_ColsPerLine, CurrCols, [], _Unicode) ->
+%% If we call cols with a CurrCols that is higher than ColsPerLine,
+%% we add that many cols to the total before calculating more cols.
+cols(ColsPerLine, CurrCols, Chars, Unicode) when CurrCols >= ColsPerLine ->
+    ColsPerLine * ((CurrCols + 1) div ColsPerLine) +
+        cols(ColsPerLine, CurrCols rem ColsPerLine, Chars, Unicode);
+cols(ColsPerLine, CurrCols, Chars, Unicode) ->
+    cols_int(ColsPerLine, CurrCols, Chars, Unicode).
+
+cols_int(ColsPerLine, CurrCols, Chars, Unicode) when CurrCols > ColsPerLine ->
+    ColsPerLine + cols_int(ColsPerLine, CurrCols - ColsPerLine, Chars, Unicode);
+cols_int(_ColsPerLine, CurrCols, [], _Unicode) ->
     CurrCols;
-cols(ColsPerLine, CurrCols, ["\r\n" | T], Unicode) ->
-    CurrCols + (ColsPerLine - CurrCols) + cols(ColsPerLine, 0, T, Unicode);
-cols(ColsPerLine, CurrCols, [H | T], Unicode) ->
-    cols(ColsPerLine, CurrCols + cols([H], Unicode), T, Unicode).
+cols_int(ColsPerLine, CurrCols, ["\r\n" | T], Unicode) ->
+    CurrCols + (ColsPerLine - CurrCols) + cols_int(ColsPerLine, 0, T, Unicode);
+cols_int(ColsPerLine, CurrCols, [H | T], Unicode) ->
+    cols_int(ColsPerLine, CurrCols + cols([H], Unicode), T, Unicode).
 
 update_geometry(State) ->
     case tty_window_size(State#state.tty) of
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 4720917a15..6cbe545307 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -1121,9 +1121,10 @@ shell_expand_location_below(Config) ->
 
     Term = start_tty(Config),
 
-    {Rows, _} = get_location(Term),
+    {Rows, _} = get_window_size(Term),
+    {Row, Col} = get_location(Term),
 
-    NumFunctions = lists:seq(0, Rows*2),
+    NumFunctions = lists:seq(0, Row*2),
     FunctionName = "a_long_function_name",
 
     Module = lists:flatten(
@@ -1142,6 +1143,7 @@ shell_expand_location_below(Config) ->
 
     try
         tmux(["resize-window -t ",tty_name(Term)," -x 80"]),
+        Cols = 80,
 
         %% First check that basic completion works
         send_stdin(Term, "escript:"),
@@ -1219,14 +1221,43 @@ shell_expand_location_below(Config) ->
         check_content(Term, io_lib:format("rows ~w to ~w of ~w",
                                           [13, Rows1+12, Result])),
 
-        send_stdin(Term, "\t"),
+        send_tty(Term, "\t"),
 
         %% We resize the terminal to make everything fit and test that
         %% expand below displays everything
-        tmux(["resize-window -t ", tty_name(Term), " -y ", integer_to_list(Rows+10)]),
+        tmux(["resize-window -t ", tty_name(Term), " -y ", integer_to_list(Row+10)]),
         timer:sleep(1000), %% Sleep to make sure window has resized
-        send_stdin(Term, "\t\t"),
+        send_tty(Term, "\t\t"),
         check_content(Term, "3> long_module:" ++ FunctionName ++ "\nfunctions(\n|.)*a_long_function_name99\\($"),
+
+        %% Check that doing an expansion when cursor is in xnfix position works
+        send_tty(Term, "BSpace"),
+        check_content(Term, "3> long_module:a_long_function_nam$"),
+        send_tty(Term, "Home"),
+        send_tty(Term, lists:duplicate(Cols - Col - width(", long_module:a_long_function_name"), "a")),
+        send_tty(Term, ", "),
+        send_tty(Term, "End"),
+        send_tty(Term, "\t"),
+        check_location(Term, {-Rows + 2, -Col}),
+        send_tty(Term, "\t"),
+        check_content(Term, "3> a+, long_module:" ++ FunctionName ++ "\n\nfunctions(\n|.)*a_long_function_name0\\("),
+        check_location(Term, {-Rows + 2, -Col}),
+        send_tty(Term, "Down"),
+        check_location(Term, {-Rows + 2, -Col}),
+        send_tty(Term, "Down"),
+        check_location(Term, {-Rows + 2, -Col}),
+
+        send_tty(Term, "Home"),
+        send_tty(Term, lists:duplicate(Cols, "b")),
+        send_tty(Term, "End"),
+        send_tty(Term, "\t"),
+        check_content(Term, "3> b+\nb+a+, long_module:" ++ FunctionName ++ "\n\nfunctions(\n|.)*a_long_function_name0\\("),
+        check_location(Term, {-Rows + 3, -Col}),
+        send_tty(Term, "Down"),
+        check_location(Term, {-Rows + 3, -Col}),
+        send_tty(Term, "Down"),
+        check_location(Term, {-Rows + 3, -Col}),
+
         ok
     after
         stop_tty(Term),
-- 
2.35.3

openSUSE Build Service is sponsored by