Skip to content

Commit 3ac2463

Browse files
committed
fixup! stdlib: shell pager
1 parent 1e648ef commit 3ac2463

File tree

2 files changed

+20
-15
lines changed

2 files changed

+20
-15
lines changed

lib/kernel/src/prim_tty.erl

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -652,7 +652,7 @@ handle_request(State = #state{unicode = U, cols = W, rows = R}, redraw_prompt_pr
652652
min(Limit, ExpandRows)
653653
end,
654654
ExpandRowsLimit1 = min(ExpandRowsLimit, R-1-InputRows),
655-
BufferExpand1 = case ExpandRows > (R-InputRows) of
655+
BufferExpand1 = case ExpandRows > ExpandRowsLimit1 of
656656
true ->
657657
Color = ansi_color(cyan, bright_white),
658658
StatusLine = io_lib:format(Color ++"\e[1m" ++ "rows ~w to ~w of ~w" ++ "\e[0m",
@@ -669,31 +669,32 @@ handle_request(State = #state{unicode = U, cols = W, rows = R}, redraw_prompt_pr
669669
false ->
670670
["\r\n",BufferExpand]
671671
end,
672-
{ExpandBuffer, NewState} = insert_buf(RedrawState#state{ buffer_expand = [] }, iolist_to_binary(BufferExpand1)),
672+
{ExpandBuffer, NewState} = insert_buf(RedrawState#state{ buffer_expand = [] }, unicode:characters_to_binary(BufferExpand1)),
673673
BECols = cols(W, End, NewState#state.buffer_expand, U),
674674
MoveToEnd = move_cursor(RedrawState, BECols, End),
675675
{[encode(Redraw,U),encode(ExpandBuffer, U), MoveToEnd, Movement], RedrawState}
676676
end,
677677
{Output, State};
678-
handle_request(State = #state{ buffer_expand = Expand, buffer_expand_row = ERow, cols = W, rows = WindowRows, unicode = U}, {move_expand, N}) ->
678+
handle_request(State = #state{ buffer_expand = Expand, buffer_expand_row = ERow, cols = W, rows = R, unicode = U}, {move_expand, N}) ->
679679
%% Get number of Lines in terminal window
680680
BufferExpandLines = case Expand of
681681
undefined -> [];
682682
_ -> string:split(erlang:binary_to_list(Expand), "\n", all)
683683
end,
684684
ExpandRows = (cols_multiline(BufferExpandLines, W, U) div W),
685685
InputRows = (cols_multiline([State#state.buffer_before ++ State#state.buffer_after], W, U) div W),
686-
ERow1 = if ExpandRows > WindowRows-InputRows -> %% We need to page expand rows
687-
StatusLine = lists:flatten(io_lib:format("rows ~w to ~w of ~w", [ERow, (ERow-1) + WindowRows-1-InputRows, ExpandRows])),
688-
StatusRows = (cols_multiline([StatusLine], W, U) div W),
689-
min(ExpandRows-(WindowRows-InputRows-StatusRows-1),max(1,ERow + N));
686+
ExpandRowsLimit = case State#state.buffer_expand_limit of
687+
0 ->
688+
ExpandRows;
689+
Limit ->
690+
min(Limit, ExpandRows)
691+
end,
692+
ExpandRowsLimit1 = min(ExpandRowsLimit, R-1-InputRows),
693+
ERow1 = if ExpandRows > ExpandRowsLimit1 -> %% We need to page expand rows
694+
min(ExpandRows-ExpandRowsLimit1+1,max(1,ERow + N));
690695
true -> 1 %% No need to page expand rows
691696
end,
692-
if ERow =:= ERow1 -> %% We don't need to do anything
693-
{[], State};
694-
true ->
695-
handle_request(State#state{buffer_expand_row = ERow1}, redraw_prompt)
696-
end;
697+
handle_request(State#state{buffer_expand_row = ERow1}, redraw_prompt);
697698
%% Clear the expand buffer after the cursor when we handle any request.
698699
handle_request(State = #state{ buffer_expand = Expand, unicode = U}, Request)
699700
when Expand =/= undefined ->
@@ -991,7 +992,7 @@ in_view(#state{lines_after = LinesAfter, buffer_before = Bef, buffer_after = Aft
991992
rows=R, cols=W, unicode=U, buffer_expand = BufferExpand, buffer_expand_limit = BufferExpandLimit} = State) ->
992993
BufferExpandLines = case BufferExpand of
993994
undefined -> [];
994-
_ -> string:split(erlang:binary_to_list(BufferExpand), "\r\n", all)
995+
_ -> string:split(unicode:characters_to_list(BufferExpand), "\r\n", all)
995996
end,
996997
ExpandLimit = case BufferExpandLimit of
997998
0 -> cols_multiline(BufferExpandLines, W, U) div W;
@@ -1087,7 +1088,10 @@ update_geometry(State) ->
10871088
case tty_window_size(State#state.tty) of
10881089
{ok, {Cols, Rows}} when Cols > 0 ->
10891090
?dbg({?FUNCTION_NAME, Cols}),
1090-
State#state{ cols = Cols, rows = Rows };
1091+
%% We also set buffer_expand_row to 0, in case we are in paging mode
1092+
%% this ensures that the expand area gets redrawn when we handle move_expand
1093+
%% event.
1094+
State#state{ cols = Cols, rows = Rows};
10911095
_Error ->
10921096
?dbg({?FUNCTION_NAME, _Error}),
10931097
State

lib/stdlib/src/edlin.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -206,7 +206,8 @@ edit(Buf, P, {LB, {Bef,Aft}, LA}=MultiLine, {ShellMode1, EscapePrefix}, Rs0) ->
206206
reverse(Rs0)};
207207
tab_expand_quit ->
208208
%% When exiting tab expand mode, we want to evaluate the key in normal mode
209-
edit(Buf, P, MultiLine, {normal,none}, Rs0);
209+
%% we send a {move_rel, 0} event to make sure the paging area is cleared
210+
edit(Buf, P, MultiLine, {normal,none}, [{move_rel, 0}|Rs0]);
210211
Op ->
211212
Op1 = case ShellMode of
212213
search ->

0 commit comments

Comments
 (0)