Skip to content

Commit

Permalink
ssh: support dumb terminals in ssh client
Browse files Browse the repository at this point in the history
  • Loading branch information
frazze-jobb committed Sep 8, 2023
1 parent 5ac156d commit dd137f3
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 5 deletions.
37 changes: 32 additions & 5 deletions lib/ssh/src/ssh_cli.erl
Original file line number Diff line number Diff line change
Expand Up @@ -418,6 +418,28 @@ to_group(Data, Group) ->
%%% displaying device...
%%% We are *not* really unicode aware yet, we just filter away characters
%%% beyond the latin1 range. We however handle the unicode binaries...
io_request(Request, Buf, Tty = #ssh_pty{term = "dumb"}, Group) ->
%% When we have a dumb terminal, we should only support outputing text, no navigation
%% or redraws necessary.
case Request of
{put_chars, Cs} ->
put_chars_dumb(bin_to_list(Cs), Buf, Tty);
{put_chars, unicode, Cs} ->
put_chars_dumb(unicode:characters_to_list(Cs,unicode), Buf, Tty);
{put_chars_sync, unicode, Cs, Reply} ->
Group ! {reply, Reply, ok},
put_chars_dumb(unicode:characters_to_list(Cs,unicode), Buf, Tty);
{insert_chars, Cs} ->
put_chars_dumb(bin_to_list(Cs), Buf, Tty);
{insert_chars, unicode, Cs} ->
put_chars_dumb(unicode:characters_to_list(Cs,unicode), Buf, Tty);
{requests,Rs} ->
io_requests(Rs, Buf, Tty, [], Group);
beep ->
{[7], Buf};
_Ignore ->
{[], Buf}
end;
io_request({window_change, OldTty}, Buf, Tty, _Group) ->
window_change(Tty, OldTty, Buf);
io_request({put_chars, Cs}, Buf, Tty, _Group) ->
Expand Down Expand Up @@ -509,10 +531,10 @@ get_tty_command(left, N, _TerminalType) ->
-define(TABWIDTH, 8).

%% convert input characters to buffer and to writeout
%% Note that the buf is reversed but the buftail is not
%% Note that Bef is reversed but Aft is not
%% (this is handy; the head is always next to the cursor)
conv_buf([], {LB, {Bef, Aft}, LA, Col}, AccWrite, _Tty) ->
{{LB, {Bef, Aft}, LA}, lists:reverse(AccWrite), Col};
{{LB, {Bef, Aft}, LA, Col}, lists:reverse(AccWrite)};
conv_buf([13, 10 | Rest], {LB, {Bef, Aft}, LA, Col}, AccWrite, Tty = #ssh_pty{width = W}) ->
conv_buf(Rest, {[lists:reverse(Bef)|LB], {[], tl2(Aft)}, LA, Col+(W-(Col rem W))}, [10, 13 | AccWrite], Tty);
conv_buf([13 | Rest], {LB, {Bef, Aft}, LA, Col}, AccWrite, Tty = #ssh_pty{width = W}) ->
Expand All @@ -531,20 +553,25 @@ conv_buf([C | Rest], {LB, {Bef, Aft}, LA, Col}, AccWrite, Tty) ->
%%% put characters before the prompt
put_chars(Chars, Buf, Tty) ->
case Buf of
{[],{[],[]},[],_} -> {_, WriteBuf, _} = conv_buf(Chars, Buf, [], Tty),
{[],{[],[]},[],_} -> {_, WriteBuf} = conv_buf(Chars, Buf, [], Tty),
{WriteBuf, Buf};
_ ->
{Delete, DeletedState} = io_request(delete_line, Buf, Tty, []),
{_, PutBuffer, _} = conv_buf(Chars, DeletedState, [], Tty),
{_, PutBuffer} = conv_buf(Chars, DeletedState, [], Tty),
{Redraw, _} = io_request(redraw_prompt_pre_deleted, Buf, Tty, []),
{[Delete, PutBuffer, Redraw], Buf}
end.
%%% put characters at current position (possibly overwriting
%%% characters after current position in buffer)
put_chars_dumb(Chars, Buf, Tty) ->
{NewBuf, WriteBuf} = conv_buf(Chars, Buf, [], Tty),
{WriteBuf, NewBuf}.

%%% insert character at current position
insert_chars([], Buf, _Tty) ->
{[], Buf};
insert_chars(Chars, {_LB,{_Bef, Aft},LA, _Col}=Buf, Tty) ->
{{NewLB, {NewBef, _NewAft}, _NewLA}, WriteBuf, NewCol} = conv_buf(Chars, Buf, [], Tty),
{{NewLB, {NewBef, _NewAft}, _NewLA, NewCol}, WriteBuf} = conv_buf(Chars, Buf, [], Tty),
M = move_cursor(special_at_width(NewCol+length(Aft), Tty), NewCol, Tty),
{[WriteBuf, Aft | M], {NewLB,{NewBef, Aft},LA, NewCol}}.

Expand Down
3 changes: 3 additions & 0 deletions lib/stdlib/src/edlin.erl
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,9 @@ start(Pbs) ->

%% Only two modes used: 'none' and 'search'. Other modes can be
%% handled inline through specific character handling.
start(Pbs, {_,{_,_},[]}=Cont) ->
%% Skip redraw if the cursor is at the end.
{more_chars,{line,Pbs,Cont,none},[{insert_chars,unicode,multi_line_prompt(Pbs)}]};
start(Pbs, {_,{_,_},_}=Cont) ->
{more_chars,{line,Pbs,Cont,none},redraw(Pbs, Cont, [])};

Expand Down

0 comments on commit dd137f3

Please sign in to comment.