Skip to content

Commit

Permalink
ssh: update ssh tests
Browse files Browse the repository at this point in the history
  • Loading branch information
frazze-jobb committed Oct 10, 2024
1 parent 147f0d6 commit 1efe40a
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 19 deletions.
10 changes: 6 additions & 4 deletions lib/ssh/src/ssh_cli.erl
Original file line number Diff line number Diff line change
Expand Up @@ -67,9 +67,11 @@
%% Description: Initiates the CLI
%%--------------------------------------------------------------------
init([Shell, Exec]) ->
{ok, #state{shell = Shell, exec = Exec}};
TTY = prim_tty:init_ssh(#{input => false}, {80, 24}, utf8),
{ok, #state{shell = Shell, exec = Exec, tty = TTY}};
init([Shell]) ->
{ok, #state{shell = Shell}}.
TTY = prim_tty:init_ssh(#{input => false}, {80, 24}, utf8),
{ok, #state{shell = Shell, tty = TTY}}.

%%--------------------------------------------------------------------
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
Expand All @@ -95,7 +97,7 @@ handle_ssh_msg({ssh_cm, ConnectionHandler,
pixel_width = PixWidth,
pixel_height = PixHeight,
modes = Modes}},
TTY = prim_tty:init_ssh(#{input => false, output => false}, {not_zero(Width, 80), not_zero(Height, 24)}, State#state.encoding),
TTY = prim_tty:init_ssh(#{input => false}, {not_zero(Width, 80), not_zero(Height, 24)}, State#state.encoding),
set_echo(State),
ssh_connection:reply_request(ConnectionHandler, WantReply,
success, ChannelId),
Expand Down Expand Up @@ -432,7 +434,7 @@ replace_escapes(Data) ->
%%% We are *not* really unicode aware yet, we just filter away characters
%%% beyond the latin1 range. We however handle the unicode binaries...
%%%
-spec io_request(term(), prim_tty:state(), term()) -> {list(), prim_tty:state()}.
%%-spec io_request(term(), prim_tty:state(), state()) -> {list(), prim_tty:state()}.
io_request({requests,Rs}, TTY, State) ->
io_requests(Rs, TTY, State, []);
io_request(redraw_prompt, TTY, _State) ->
Expand Down
29 changes: 14 additions & 15 deletions lib/ssh/test/ssh_connection_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -814,12 +814,11 @@ new_shell_xterm_term(Config) when is_list(Config) ->
exp_output =>
[<<"Enter command\r\n">>,
<<"1> ">>,
<<"one_atom_please.\r\n\e[1022D\e[1B">>,
<<"one_atom_please.\r\n">>,
<<"{simple_eval,one_atom_please}\r\n">>,
<<"2> ">>,
<<"\e[3D\e[J">>,
<<"\e[;1;4msearch:\e[0m ">>,
<<"\r\n one_atom_please.">>]},
<<"\b\b\b\b\b\b\b\b\e[J\e[;1;4msearch:\e[0m \r\n one_atom_please.\e[A\b\b\b\b\b\b\b\b\b\b">>]},
Config).

new_shell_helper(#{term := Term, cmds := Cmds,
Expand Down Expand Up @@ -994,7 +993,7 @@ start_shell_exec_fun(Config) ->
io:format("echo ~s\n", [Cmd])
end)
end,
"testing", <<"echo testing\n">>, 0,
"testing", <<"echo testing\r\n">>, 0,
Config).

start_shell_exec_fun2(Config) ->
Expand All @@ -1003,7 +1002,7 @@ start_shell_exec_fun2(Config) ->
io:format("echo ~s ~s\n",[User,Cmd])
end)
end,
"testing", <<"echo foo testing\n">>, 0,
"testing", <<"echo foo testing\r\n">>, 0,
Config).

start_shell_exec_fun3(Config) ->
Expand All @@ -1012,7 +1011,7 @@ start_shell_exec_fun3(Config) ->
io:format("echo ~s ~s\n",[User,Cmd])
end)
end,
"testing", <<"echo foo testing\n">>, 0,
"testing", <<"echo foo testing\r\n">>, 0,
Config).

start_shell_exec_direct_fun(Config) ->
Expand Down Expand Up @@ -1077,11 +1076,11 @@ start_exec_direct_fun1_read_write(Config) ->
{ok, Ch} = ssh_connection:session_channel(C, infinity),

success = ssh_connection:exec(C, Ch, "> ", infinity),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"Tiny read/write test\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"Tiny read/write test\r\n">>}}),

ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"1> ">>}}),
ok = ssh_connection:send(C, Ch, "hej.\n", 5000),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,hej}\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,hej}\r\n">>}}),

ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"2> ">>}}),
ok = ssh_connection:send(C, Ch, "quit.\n", 5000),
Expand Down Expand Up @@ -1125,18 +1124,18 @@ start_exec_direct_fun1_read_write_advanced(Config) ->
{ok, Ch} = ssh_connection:session_channel(C, infinity),

success = ssh_connection:exec(C, Ch, "> ", infinity),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"Tiny read/write test\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"Tiny read/write test\r\n">>}}),

ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"1> ">>}}),
ok = ssh_connection:send(C, Ch, "hej.\n", 5000),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,hej}\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,hej}\r\n">>}}),

ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"2> ">>}}),
ok = ssh_connection:send(C, Ch, "'Hi ", 5000),
ok = ssh_connection:send(C, Ch, "there", 5000),
ok = ssh_connection:send(C, Ch, "'", 5000),
ok = ssh_connection:send(C, Ch, ".\n", 5000),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,'Hi there'}\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"{simple_eval,'Hi there'}\r\n">>}}),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,0,<<"3> ">>}}),
ok = ssh_connection:send(C, Ch, "bad_input.\n", 5000),
ssh_test_lib:receive_exec_result_or_fail({ssh_cm,C,{data,Ch,1,<<"**Error** {bad_input,3}">>}}),
Expand Down Expand Up @@ -1251,7 +1250,7 @@ start_shell_sock_exec_fun(Config) when is_list(Config) ->
"testing", infinity),

receive
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\n">>}} ->
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\r\n">>}} ->
ok
after 5000 ->
ct:fail("Exec Timeout")
Expand Down Expand Up @@ -1296,7 +1295,7 @@ start_shell_sock_daemon_exec(Config) ->
"testing", infinity),

receive
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\n">>}} ->
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\r\n">>}} ->
ok
after 5000 ->
ct:fail("Exec Timeout")
Expand Down Expand Up @@ -1356,7 +1355,7 @@ start_shell_sock_daemon_exec_multi(Config) ->
success = ssh_connection:exec(ConnectionRef, ChannelId0, "testing", infinity),
ct:log("~p:~p: exec on connection ~p", [?MODULE,?LINE,ConnectionRef]),
receive
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\n">>}} ->
{ssh_cm, ConnectionRef, {data, _ChannelId, 0, <<"echo testing\r\n">>}} ->
Parent ! {answer_received,self()},
ct:log("~p:~p: received result on connection ~p", [?MODULE,?LINE,ConnectionRef])
after 5000 ->
Expand Down Expand Up @@ -1565,7 +1564,7 @@ stop_listener(Config) when is_list(Config) ->
"testing", infinity),
receive
{ssh_cm, ConnectionRef0,
{data, ChannelId0, 0, <<"echo testing\n">>}} ->
{data, ChannelId0, 0, <<"echo testing\r\n">>}} ->
ok
after 5000 ->
ct:fail("Exec Timeout")
Expand Down

0 comments on commit 1efe40a

Please sign in to comment.