Skip to content

Commit

Permalink
Merge branch 'hans/ssh/maint-r16/patch_1261' into maint-r16
Browse files Browse the repository at this point in the history
  • Loading branch information
HansN committed Feb 24, 2014
2 parents ce3d6e8 + 8071fde commit 450f0f8
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 30 deletions.
17 changes: 13 additions & 4 deletions lib/ssh/src/ssh_cli.erl
Expand Up @@ -170,10 +170,19 @@ handle_msg({Group, get_unicode_state}, State) ->
{ok, State};

handle_msg({Group, tty_geometry}, #state{group = Group,
pty = #ssh_pty{width=Width,
height=Height}
pty = Pty
} = State) ->
Group ! {self(),tty_geometry,{Width,Height}},
case Pty of
#ssh_pty{width=Width,height=Height} ->
Group ! {self(),tty_geometry,{Width,Height}};
_ ->
%% This is a dirty fix of the problem with the otp ssh:shell
%% client. That client will not allocate a tty, but someone
%% asks for the tty_geometry just before every erlang prompt.
%% If that question is not answered, there is a 2 sec timeout
%% Until the prompt is seen by the user at the client side ...
Group ! {self(),tty_geometry,{0,0}}
end,
{ok,State};

handle_msg({Group, Req}, #state{group = Group, buf = Buf, pty = Pty,
Expand Down Expand Up @@ -349,7 +358,7 @@ delete_chars(N, {Buf, BufTail, Col}, Tty) when N > 0 ->
{Buf, NewBufTail, Col}};
delete_chars(N, {Buf, BufTail, Col}, Tty) -> % N < 0
NewBuf = nthtail(-N, Buf),
NewCol = Col + N,
NewCol = case Col + N of V when V >= 0 -> V; _ -> 0 end,
M1 = move_cursor(Col, NewCol, Tty),
M2 = move_cursor(NewCol + length(BufTail) - N, NewCol, Tty),
{[M1, BufTail, lists:duplicate(-N, $ ) | M2],
Expand Down
26 changes: 13 additions & 13 deletions lib/ssh/src/ssh_file.erl
Expand Up @@ -65,7 +65,7 @@ is_auth_key(Key, User,Opts) ->

%% Used by client
is_host_key(Key, PeerName, Algorithm, Opts) ->
case lookup_host_key(PeerName, Algorithm, Opts) of
case lookup_host_key(Key, PeerName, Algorithm, Opts) of
{ok, Key} ->
true;
_ ->
Expand Down Expand Up @@ -121,9 +121,9 @@ decode_ssh_file(Pem, Password) ->
%% return {ok, Key(s)} or {error, not_found}
%%

lookup_host_key(Host, Alg, Opts) ->
lookup_host_key(KeyToMatch, Host, Alg, Opts) ->
Host1 = replace_localhost(Host),
do_lookup_host_key(Host1, Alg, Opts).
do_lookup_host_key(KeyToMatch, Host1, Alg, Opts).


add_host_key(Host, Key, Opts) ->
Expand Down Expand Up @@ -204,10 +204,10 @@ replace_localhost("localhost") ->
replace_localhost(Host) ->
Host.

do_lookup_host_key(Host, Alg, Opts) ->
do_lookup_host_key(KeyToMatch, Host, Alg, Opts) ->
case file:open(file_name(user, "known_hosts", Opts), [read, binary]) of
{ok, Fd} ->
Res = lookup_host_key_fd(Fd, Host, Alg),
Res = lookup_host_key_fd(Fd, KeyToMatch, Host, Alg),
file:close(Fd),
{ok, Res};
{error, enoent} -> {error, not_found};
Expand All @@ -228,16 +228,16 @@ identity_pass_phrase('ssh-rsa') ->
identity_pass_phrase("ssh-rsa") ->
rsa_pass_phrase.

lookup_host_key_fd(Fd, Host, KeyType) ->
lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType) ->
case io:get_line(Fd, '') of
eof ->
{error, not_found};
Line ->
case ssh_decode_line(Line, known_hosts) of
[{Key, Attributes}] ->
handle_host(Fd, Host, proplists:get_value(hostnames, Attributes), Key, KeyType);
handle_host(Fd, KeyToMatch, Host, proplists:get_value(hostnames, Attributes), Key, KeyType);
[] ->
lookup_host_key_fd(Fd, Host, KeyType)
lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType)
end
end.

Expand All @@ -248,13 +248,13 @@ ssh_decode_line(Line, Type) ->
[]
end.

handle_host(Fd, Host, HostList, Key, KeyType) ->
handle_host(Fd, KeyToMatch, Host, HostList, Key, KeyType) ->
Host1 = host_name(Host),
case lists:member(Host1, HostList) and key_match(Key, KeyType) of
true ->
case lists:member(Host1, HostList) andalso key_match(Key, KeyType) of
true when KeyToMatch == Key ->
Key;
false ->
lookup_host_key_fd(Fd, Host, KeyType)
_ ->
lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType)
end.

host_name(Atom) when is_atom(Atom) ->
Expand Down
30 changes: 17 additions & 13 deletions lib/ssh/src/ssh_message.erl
Expand Up @@ -315,8 +315,8 @@ decode(<<?BYTE(?SSH_MSG_CHANNEL_DATA), ?UINT32(Recipient), ?UINT32(Len), Data:Le
recipient_channel = Recipient,
data = Data
};
decode(<<?BYTE(?SSH_MSG_CHANNEL_EXTENDED_DATA), ?UINT32(Recipient),
?UINT32(DataType), Data/binary>>) ->
decode(<<?BYTE(?SSH_MSG_CHANNEL_EXTENDED_DATA), ?UINT32(Recipient),
?UINT32(DataType), ?UINT32(Len), Data:Len/binary>>) ->
#ssh_msg_channel_extended_data{
recipient_channel = Recipient,
data_type_code = DataType,
Expand Down Expand Up @@ -380,27 +380,30 @@ decode(<<?BYTE(?SSH_MSG_USERAUTH_BANNER),
language = Lang
};

decode(<<?BYTE(?SSH_MSG_USERAUTH_INFO_REQUEST), ?UINT32(Len0), Name:Len0/binary,
?UINT32(Len1), Inst:Len1/binary, ?UINT32(Len2), Lang:Len2/binary,
?UINT32(NumPromtps), Data/binary>>) ->
#ssh_msg_userauth_info_request{
name = Name,
instruction = Inst,
language_tag = Lang,
num_prompts = NumPromtps,
data = Data};

%%% Unhandled message, also masked by same 1:st byte value as ?SSH_MSG_USERAUTH_INFO_REQUEST:
decode(<<?BYTE(?SSH_MSG_USERAUTH_PK_OK), ?UINT32(Len), Alg:Len/binary, KeyBlob/binary>>) ->
#ssh_msg_userauth_pk_ok{
algorithm_name = Alg,
key_blob = KeyBlob
};

%%% Unhandled message, also masked by same 1:st byte value as ?SSH_MSG_USERAUTH_INFO_REQUEST:
decode(<<?BYTE(?SSH_MSG_USERAUTH_PASSWD_CHANGEREQ), ?UINT32(Len0), Prompt:Len0/binary,
?UINT32(Len1), Lang:Len1/binary>>) ->
#ssh_msg_userauth_passwd_changereq{
prompt = Prompt,
languge = Lang
};
decode(<<?BYTE(?SSH_MSG_USERAUTH_INFO_REQUEST), ?UINT32(Len0), Name:Len0/binary,
?UINT32(Len1), Inst:Len1/binary, ?UINT32(Len2), Lang:Len2/binary,
?UINT32(NumPromtps), Data/binary>>) ->
#ssh_msg_userauth_info_request{
name = Name,
instruction = Inst,
language_tag = Lang,
num_prompts = NumPromtps,
data = Data};

decode(<<?BYTE(?SSH_MSG_USERAUTH_INFO_RESPONSE), ?UINT32(Num), Data/binary>>) ->
#ssh_msg_userauth_info_response{
Expand All @@ -424,8 +427,9 @@ decode(<<?BYTE(?SSH_MSG_KEX_DH_GEX_REQUEST_OLD), ?UINT32(N)>>) ->
#ssh_msg_kex_dh_gex_request_old{
n = N
};
decode(<<?BYTE(?SSH_MSG_KEX_DH_GEX_GROUP), ?UINT32(Len0), Prime:Len0/big-signed-integer,
?UINT32(Len1), Generator:Len1/big-signed-integer>>) ->
decode(<<?BYTE(?SSH_MSG_KEX_DH_GEX_GROUP),
?UINT32(Len0), Prime:Len0/big-signed-integer-unit:8,
?UINT32(Len1), Generator:Len1/big-signed-integer-unit:8>>) ->
#ssh_msg_kex_dh_gex_group{
p = Prime,
g = Generator
Expand Down

0 comments on commit 450f0f8

Please sign in to comment.