File 3135-ssh-Add-dbg-of-authentication.patch of Package erlang
From 8ee597c0cfc01bfe3cda04a9ae3be12bfd560157 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Wed, 29 Apr 2020 11:17:03 +0200
Subject: [PATCH 5/5] ssh: Add dbg of authentication
Change return from misc functions in ssh_auth to message record from bin blob
---
lib/ssh/src/ssh_auth.erl | 358 +++++++++++++++++++------
lib/ssh/src/ssh_connection_handler.erl | 99 ++++---
2 files changed, 329 insertions(+), 128 deletions(-)
diff --git a/lib/ssh/src/ssh_auth.erl b/lib/ssh/src/ssh_auth.erl
index aeb8e4d5fb..19df20c9f1 100644
--- a/lib/ssh/src/ssh_auth.erl
+++ b/lib/ssh/src/ssh_auth.erl
@@ -32,10 +32,13 @@
-export([get_public_key/2,
publickey_msg/1, password_msg/1, keyboard_interactive_msg/1,
service_request_msg/1, init_userauth_request_msg/1,
- userauth_request_msg/1, handle_userauth_request/3,
+ userauth_request_msg/1, handle_userauth_request/3, ssh_msg_userauth_result/1,
handle_userauth_info_request/2, handle_userauth_info_response/2
]).
+-behaviour(ssh_dbg).
+-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1, ssh_dbg_format/3]).
+
%%--------------------------------------------------------------------
%%% Internal application API
%%--------------------------------------------------------------------
@@ -110,14 +113,13 @@ password_msg([#ssh{opts = Opts,
not_ok ->
{not_ok, Ssh};
_ ->
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_request{user = User,
- service = Service,
- method = "password",
- data =
- <<?BOOLEAN(?FALSE),
- ?STRING(unicode:characters_to_binary(Password))>>},
- Ssh)
+ {#ssh_msg_userauth_request{user = User,
+ service = Service,
+ method = "password",
+ data =
+ <<?BOOLEAN(?FALSE),
+ ?STRING(unicode:characters_to_binary(Password))>>},
+ Ssh}
end.
%% See RFC 4256 for info on keyboard-interactive
@@ -128,13 +130,12 @@ keyboard_interactive_msg([#ssh{user = User,
not_ok ->
{not_ok,Ssh}; % No need to use a failed pwd once more
_ ->
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_request{user = User,
- service = Service,
- method = "keyboard-interactive",
- data = << ?STRING(<<"">>),
- ?STRING(<<>>) >> },
- Ssh)
+ {#ssh_msg_userauth_request{user = User,
+ service = Service,
+ method = "keyboard-interactive",
+ data = << ?STRING(<<"">>),
+ ?STRING(<<>>) >> },
+ Ssh}
end.
@@ -183,15 +184,14 @@ publickey_msg([SigAlg, #ssh{user = User,
SigBlob = list_to_binary([?string(SigAlgStr),
?binary(Sig)]),
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_request{user = User,
- service = Service,
- method = "publickey",
- data = [?TRUE,
- ?string(SigAlgStr),
- ?binary(PubKeyBlob),
- ?binary(SigBlob)]},
- Ssh);
+ {#ssh_msg_userauth_request{user = User,
+ service = Service,
+ method = "publickey",
+ data = [?TRUE,
+ ?string(SigAlgStr),
+ ?binary(PubKeyBlob),
+ ?binary(SigBlob)]},
+ Ssh};
_ ->
{not_ok, Ssh}
@@ -199,8 +199,8 @@ publickey_msg([SigAlg, #ssh{user = User,
%%%----------------------------------------------------------------
service_request_msg(Ssh) ->
- ssh_transport:ssh_packet(#ssh_msg_service_request{name = "ssh-userauth"},
- Ssh#ssh{service = "ssh-userauth"}).
+ {#ssh_msg_service_request{name = "ssh-userauth"},
+ Ssh#ssh{service = "ssh-userauth"}}.
%%%----------------------------------------------------------------
init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
@@ -210,24 +210,23 @@ init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
?DISCONNECT(?SSH_DISCONNECT_ILLEGAL_USER_NAME,
"Could not determine the users name");
User ->
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_request{user = User,
- service = "ssh-connection",
- method = "none",
- data = <<>>},
- Ssh#ssh{user = User,
- userauth_preference = method_preference(Ssh#ssh.userauth_pubkeys),
- userauth_methods = none,
- service = "ssh-connection"}
- )
+ {#ssh_msg_userauth_request{user = User,
+ service = "ssh-connection",
+ method = "none",
+ data = <<>>},
+ Ssh#ssh{user = User,
+ userauth_preference = method_preference(Ssh#ssh.userauth_pubkeys),
+ userauth_methods = none,
+ service = "ssh-connection"}
+ }
end.
%%%----------------------------------------------------------------
%%% called by server
handle_userauth_request(#ssh_msg_service_request{name = Name = "ssh-userauth"},
_, Ssh) ->
- {ok, ssh_transport:ssh_packet(#ssh_msg_service_accept{name = Name},
- Ssh#ssh{service = "ssh-connection"})};
+ {ok, {#ssh_msg_service_accept{name = Name},
+ Ssh#ssh{service = "ssh-connection"}}};
handle_userauth_request(#ssh_msg_userauth_request{user = User,
service = "ssh-connection",
@@ -239,12 +238,13 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
case check_password(User, Password, Opts, Ssh) of
{true,Ssh1} ->
{authorized, User,
- ssh_transport:ssh_packet(#ssh_msg_userauth_success{}, Ssh1)};
+ {#ssh_msg_userauth_success{}, Ssh1}
+ };
{false,Ssh1} ->
{not_authorized, {User, {error,"Bad user or password"}},
- ssh_transport:ssh_packet(#ssh_msg_userauth_failure{
- authentications = Methods,
- partial_success = false}, Ssh1)}
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh1}
+ }
end;
handle_userauth_request(#ssh_msg_userauth_request{user = User,
@@ -264,18 +264,18 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
%% or the old password was bad.
{not_authorized, {User, {error,"Password change not supported"}},
- ssh_transport:ssh_packet(#ssh_msg_userauth_failure{
- authentications = Methods,
- partial_success = false}, Ssh)};
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ };
handle_userauth_request(#ssh_msg_userauth_request{user = User,
service = "ssh-connection",
method = "none"}, _,
#ssh{userauth_supported_methods = Methods} = Ssh) ->
{not_authorized, {User, undefined},
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_failure{authentications = Methods,
- partial_success = false}, Ssh)};
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ };
handle_userauth_request(#ssh_msg_userauth_request{user = User,
service = "ssh-connection",
@@ -293,14 +293,14 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
case pre_verify_sig(User, KeyBlob, Opts) of
true ->
{not_authorized, {User, undefined},
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_pk_ok{algorithm_name = binary_to_list(BAlg),
- key_blob = KeyBlob}, Ssh)};
+ {#ssh_msg_userauth_pk_ok{algorithm_name = binary_to_list(BAlg),
+ key_blob = KeyBlob}, Ssh}
+ };
false ->
{not_authorized, {User, undefined},
- ssh_transport:ssh_packet(#ssh_msg_userauth_failure{
- authentications = Methods,
- partial_success = false}, Ssh)}
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ }
end;
handle_userauth_request(#ssh_msg_userauth_request{user = User,
@@ -318,13 +318,13 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
BAlg, KeyBlob, SigWLen, Ssh) of
true ->
{authorized, User,
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_success{}, Ssh)};
+ {#ssh_msg_userauth_success{}, Ssh}
+ };
false ->
{not_authorized, {User, undefined},
- ssh_transport:ssh_packet(#ssh_msg_userauth_failure{
- authentications = Methods,
- partial_success = false}, Ssh)}
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ }
end;
handle_userauth_request(#ssh_msg_userauth_request{user = User,
@@ -337,9 +337,9 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
case KbTriesLeft of
N when N<1 ->
{not_authorized, {User, {authmethod, "keyboard-interactive"}},
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_failure{authentications = Methods,
- partial_success = false}, Ssh)};
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ };
_ ->
%% RFC4256
@@ -384,8 +384,8 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
>>
},
{not_authorized, {User, undefined},
- ssh_transport:ssh_packet(Msg, Ssh#ssh{user = User
- })}
+ {Msg, Ssh#ssh{user = User}}
+ }
end;
handle_userauth_request(#ssh_msg_userauth_request{user = User,
@@ -393,9 +393,9 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
method = Other}, _,
#ssh{userauth_supported_methods = Methods} = Ssh) ->
{not_authorized, {User, {authmethod, Other}},
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_failure{authentications = Methods,
- partial_success = false}, Ssh)}.
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false}, Ssh}
+ }.
%%%----------------------------------------------------------------
@@ -411,9 +411,9 @@ handle_userauth_info_request(#ssh_msg_userauth_info_request{name = Name,
not_ok;
Responses ->
{ok,
- ssh_transport:ssh_packet(
- #ssh_msg_userauth_info_response{num_responses = NumPrompts,
- data = Responses}, Ssh)}
+ {#ssh_msg_userauth_info_response{num_responses = NumPrompts,
+ data = Responses},
+ Ssh}}
end.
%%%----------------------------------------------------------------
@@ -431,32 +431,30 @@ handle_userauth_info_response(#ssh_msg_userauth_info_response{num_responses = 1,
case check_password(User, unicode:characters_to_list(Password), Opts, Ssh) of
{true,Ssh1} when SendOneEmpty==true ->
- Msg = #ssh_msg_userauth_info_request{name = "",
- instruction = "",
- language_tag = "",
- num_prompts = 0,
- data = <<?BOOLEAN(?FALSE)>>
- },
{authorized_but_one_more, User,
- ssh_transport:ssh_packet(Msg, Ssh1)};
+ {#ssh_msg_userauth_info_request{name = "",
+ instruction = "",
+ language_tag = "",
+ num_prompts = 0,
+ data = <<?BOOLEAN(?FALSE)>>
+ },
+ Ssh1}};
{true,Ssh1} ->
{authorized, User,
- ssh_transport:ssh_packet(#ssh_msg_userauth_success{}, Ssh1)};
+ {#ssh_msg_userauth_success{}, Ssh1}};
{false,Ssh1} ->
{not_authorized, {User, {error,"Bad user or password"}},
- ssh_transport:ssh_packet(#ssh_msg_userauth_failure{
- authentications = Methods,
- partial_success = false},
- Ssh1#ssh{kb_tries_left = max(KbTriesLeft-1, 0)}
- )}
+ {#ssh_msg_userauth_failure{authentications = Methods,
+ partial_success = false},
+ Ssh1#ssh{kb_tries_left = max(KbTriesLeft-1, 0)}}}
end;
handle_userauth_info_response({extra,#ssh_msg_userauth_info_response{}},
#ssh{user = User} = Ssh) ->
{authorized, User,
- ssh_transport:ssh_packet(#ssh_msg_userauth_success{}, Ssh)};
+ {#ssh_msg_userauth_success{}, Ssh}};
handle_userauth_info_response(#ssh_msg_userauth_info_response{},
_Auth) ->
@@ -622,3 +620,193 @@ write_if_nonempty(_, "") -> ok;
write_if_nonempty(_, <<>>) -> ok;
write_if_nonempty(IoCb, Text) -> IoCb:format("~s~n",[Text]).
+%%%----------------------------------------------------------------
+%%% Called just for the tracer ssh_dbg
+ssh_msg_userauth_result(_R) -> ok.
+
+%%%################################################################
+%%%#
+%%%# Tracing
+%%%#
+
+ssh_dbg_trace_points() -> [authentication].
+
+ssh_dbg_flags(authentication) -> [c].
+
+ssh_dbg_on(authentication) -> dbg:tp(?MODULE, handle_userauth_request, 3, x),
+ dbg:tp(?MODULE, init_userauth_request_msg, 1, x),
+ dbg:tp(?MODULE, ssh_msg_userauth_result, 1, x),
+ dbg:tp(?MODULE, userauth_request_msg, 1, x).
+
+ssh_dbg_off(authentication) -> dbg:ctpg(?MODULE, handle_userauth_request, 3),
+ dbg:ctpg(?MODULE, init_userauth_request_msg, 1),
+ dbg:ctpg(?MODULE, ssh_msg_userauth_result, 1),
+ dbg:ctpg(?MODULE, userauth_request_msg, 1).
+
+
+
+%%% Server ----------------
+ssh_dbg_format(authentication, {call, {?MODULE,handle_userauth_request, [Req,_SessionID,Ssh]}},
+ Stack) ->
+ {skip, [{Req,Ssh}|Stack]};
+
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,handle_userauth_request,3},
+ {ok,{#ssh_msg_service_accept{name=Name},_Ssh}}},
+ [{#ssh_msg_service_request{name=Name},_} | Stack]) ->
+ {skip, Stack};
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,handle_userauth_request,3},
+ {authorized,User,_Repl}},
+ [{#ssh_msg_userauth_request{}=Req,Ssh}|Stack]) ->
+ {["AUTH srvr: Peer client authorized\n",
+ io_lib:format("user = ~p~n", [User]),
+ fmt_req(Req, Ssh)],
+ Stack};
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,handle_userauth_request,3},
+ {not_authorized,{User,_X},_Repl}},
+ [{#ssh_msg_userauth_request{method="none"},Ssh}|Stack]) ->
+ Methods = Ssh#ssh.userauth_supported_methods,
+ {["AUTH srvr: Peer queries auth methods\n",
+ io_lib:format("user = ~p~nsupported methods = ~p ?", [User,Methods])
+ ],
+ Stack};
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,handle_userauth_request,3},
+ {not_authorized,{User,_X}, Repl}
+ },
+ [{#ssh_msg_userauth_request{method = "publickey",
+ data = <<?BYTE(?FALSE), _/binary>>
+ }=Req,Ssh}|Stack]) ->
+ {case Repl of
+ {#ssh_msg_userauth_pk_ok{}, _} ->
+ ["AUTH srvr: Answer - pub key supported\n"];
+ {#ssh_msg_userauth_failure{}, _} ->
+ ["AUTH srvr: Answer - pub key not supported\n"];
+ {Other, _} ->
+ ["AUTH srvr: Answer - strange answer\n",
+ io_lib:format("strange answer = ~p~n",[Other])
+ ]
+ end
+ ++ [io_lib:format("user = ~p~n", [User]),
+ fmt_req(Req, Ssh)],
+ Stack};
+
+
+ssh_dbg_format(authentication, {call, {?MODULE,ssh_msg_userauth_result,[success]}},
+ Stack) ->
+ {["AUTH client: Success"],Stack};
+ssh_dbg_format(authentication, {return_from, {?MODULE,ssh_msg_userauth_result,1}, _Result},
+ Stack) ->
+ {skip, Stack};
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,handle_userauth_request,3},
+ {not_authorized,{User,_X},_Repl}},
+ [{#ssh_msg_userauth_request{}=Req,Ssh}|Stack]) ->
+ {["AUTH srvr: Peer client authorization failed\n",
+ io_lib:format("user = ~p~n", [User]),
+ fmt_req(Req, Ssh)],
+ Stack};
+
+%%% Client ----------------
+ssh_dbg_format(authentication, {call, {?MODULE,init_userauth_request_msg, [#ssh{opts = Opts}]}},
+ Stack) ->
+ {["AUTH client: Service ssh-userauth accepted\n",
+ case ?GET_OPT(user, Opts) of
+ undefined ->
+ io_lib:format("user = undefined *** ERROR ***", []);
+ User ->
+ io_lib:format("user = ~p", [User])
+ end
+ ],
+ Stack};
+ssh_dbg_format(authentication, {return_from, {?MODULE,init_userauth_request_msg,1},
+ {Repl = #ssh_msg_userauth_request{user = User,
+ service = "ssh-connection",
+ method = "none"},
+ _Ssh}},
+ Stack) ->
+ {["AUTH client: Query for accepted methods\n",
+ io_lib:format("user = ~p", [User])],
+ [Repl|Stack]};
+
+ssh_dbg_format(authentication, {call, {?MODULE,userauth_request_msg,
+ [#ssh{userauth_methods = Methods}]}},
+ [ #ssh_msg_userauth_request{user = User,
+ service = "ssh-connection",
+ method = "none"} | Stack]) ->
+ {["AUTH client: Server supports\n",
+ io_lib:format("user = ~p~nmethods = ~p", [User,Methods])],
+ Stack};
+
+ssh_dbg_format(authentication, {call, {?MODULE,userauth_request_msg,[_Ssh]}},
+ Stack) ->
+ {skip,Stack};
+
+ssh_dbg_format(authentication, {return_from, {?MODULE,userauth_request_msg,1},
+ {send_disconnect, _Code, _Ssh}},
+ Stack) ->
+ {skip,Stack};
+ssh_dbg_format(authentication, {return_from, {?MODULE,userauth_request_msg,1},
+ {Method,{_Msg,_Ssh}}},
+ Stack) ->
+ {["AUTH client: Try auth with\n",
+ io_lib:format("method = ~p", [Method])],
+ Stack};
+
+
+
+ssh_dbg_format(authentication, Unhandled, Stack) ->
+ case Unhandled of
+ {call, {?MODULE,_F,_Args}} -> ok;
+ {return_from, {?MODULE,_F,_A}, _Resp} -> ok
+ end,
+ {["UNHANDLED AUTH FORMAT\n",
+ io_lib:format("Unhandled = ~p~nStack = ~p", [Unhandled,Stack])],
+ Stack}.
+
+
+%%% Dbg helpers ----------------
+
+
+fmt_req(#ssh_msg_userauth_request{user = User,
+ service = "ssh-connection",
+ method = Method,
+ data = Data},
+ #ssh{kb_tries_left = KbTriesLeft,
+ userauth_supported_methods = Methods}) ->
+ [io_lib:format("req user = ~p~n"
+ "req method = ~p~n"
+ "supported methods = ~p",
+ [User,Method,Methods]),
+ case Method of
+ "none" -> "";
+ "password" -> fmt_bool(Data);
+ "keyboard-interactive" -> fmt_kb_tries_left(KbTriesLeft);
+ "publickey" -> [case Data of
+ <<?BYTE(_), ?UINT32(ALen), Alg:ALen/binary, _/binary>> ->
+ io_lib:format("~nkey-type = ~p", [Alg]);
+ _ ->
+ ""
+ end];
+ _ -> ""
+ end].
+
+
+fmt_kb_tries_left(N) when is_integer(N)->
+ io_lib:format("~ntries left = ~p", [N-1]).
+
+
+fmt_bool(<<?BYTE(Bool),_/binary>>) ->
+ io_lib:format("~nBool = ~s",
+ [case Bool of
+ ?TRUE -> "true";
+ ?FALSE -> "false";
+ _ -> io_lib:format("? (~p)",[Bool])
+ end]);
+fmt_bool(<<>>) ->
+ "".
+
+
+
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index e21d809685..5e5ed9b79a 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -825,13 +825,13 @@ handle_event(_, #ssh_msg_kex_dh_gex_reply{} = Msg, {key_exchange_dh_gex_reply,cl
%%% ######## {new_keys, client|server} ####
%% First key exchange round:
-handle_event(_, #ssh_msg_newkeys{} = Msg, {new_keys,client,init}, D) ->
- {ok, Ssh1} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
+handle_event(_, #ssh_msg_newkeys{} = Msg, {new_keys,client,init}, D0) ->
+ {ok, Ssh1} = ssh_transport:handle_new_keys(Msg, D0#data.ssh_params),
%% {ok, ExtInfo, Ssh2} = ssh_transport:ext_info_message(Ssh1),
- %% send_bytes(ExtInfo, D),
+ %% send_bytes(ExtInfo, D0),
{MsgReq, Ssh} = ssh_auth:service_request_msg(Ssh1),
- send_bytes(MsgReq, D),
- {next_state, {ext_info,client,init}, D#data{ssh_params=Ssh}};
+ D = send_msg(MsgReq, D0#data{ssh_params = Ssh}),
+ {next_state, {ext_info,client,init}, D};
handle_event(_, #ssh_msg_newkeys{} = Msg, {new_keys,server,init}, D) ->
{ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
@@ -877,8 +877,8 @@ handle_event(_, Msg = #ssh_msg_service_request{name=ServiceName}, StateName = {s
"ssh-userauth" ->
Ssh0 = #ssh{session_id=SessionId} = D0#data.ssh_params,
{ok, {Reply, Ssh}} = ssh_auth:handle_userauth_request(Msg, SessionId, Ssh0),
- send_bytes(Reply, D0),
- {next_state, {userauth,server}, D0#data{ssh_params = Ssh}};
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth,server}, D};
_ ->
{Shutdown, D} =
@@ -889,10 +889,12 @@ handle_event(_, Msg = #ssh_msg_service_request{name=ServiceName}, StateName = {s
end;
handle_event(_, #ssh_msg_service_accept{name = "ssh-userauth"}, {service_request,client},
- #data{ssh_params = #ssh{service="ssh-userauth"} = Ssh0} = State) ->
+ #data{ssh_params = #ssh{service="ssh-userauth"} = Ssh0} = D0) ->
{Msg, Ssh} = ssh_auth:init_userauth_request_msg(Ssh0),
- send_bytes(Msg, State),
- {next_state, {userauth,client}, State#data{auth_user = Ssh#ssh.user, ssh_params = Ssh}};
+ D = send_msg(Msg, D0#data{ssh_params = Ssh,
+ auth_user = Ssh#ssh.user
+ }),
+ {next_state, {userauth,client}, D};
%%% ######## {userauth, client|server} ####
@@ -908,8 +910,8 @@ handle_event(_,
%% Probably the very first userauth_request but we deny unauthorized login
{not_authorized, _, {Reply,Ssh}} =
ssh_auth:handle_userauth_request(Msg, Ssh0#ssh.session_id, Ssh0),
- send_bytes(Reply, D0),
- {keep_state, D0#data{ssh_params = Ssh}};
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {keep_state, D};
{"ssh-connection", "ssh-connection", Method} ->
%% Userauth request with a method like "password" or so
@@ -917,21 +919,24 @@ handle_event(_,
true ->
%% Yepp! we support this method
case ssh_auth:handle_userauth_request(Msg, Ssh0#ssh.session_id, Ssh0) of
- {authorized, User, {Reply, Ssh}} ->
- send_bytes(Reply, D0),
- D0#data.starter ! ssh_connected,
- connected_fun(User, Method, D0),
+ {authorized, User, {Reply, Ssh1}} ->
+ D = #data{ssh_params=Ssh} =
+ send_msg(Reply, D0#data{ssh_params = Ssh1}),
+ D#data.starter ! ssh_connected,
+ connected_fun(User, Method, D),
{next_state, {connected,server},
- D0#data{auth_user = User,
- ssh_params = Ssh#ssh{authenticated = true}}};
+ D#data{auth_user=User,
+ %% Note: authenticated=true MUST NOT be sent
+ %% before send_msg!
+ ssh_params = Ssh#ssh{authenticated = true}}};
{not_authorized, {User, Reason}, {Reply, Ssh}} when Method == "keyboard-interactive" ->
retry_fun(User, Reason, D0),
- send_bytes(Reply, D0),
- {next_state, {userauth_keyboard_interactive,server}, D0#data{ssh_params = Ssh}};
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth_keyboard_interactive,server}, D};
{not_authorized, {User, Reason}, {Reply, Ssh}} ->
retry_fun(User, Reason, D0),
- send_bytes(Reply, D0),
- {keep_state, D0#data{ssh_params = Ssh}}
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {keep_state, D}
end;
false ->
%% No we do not support this method (=/= none)
@@ -959,6 +964,7 @@ handle_event(_, #ssh_msg_ext_info{}=Msg, {userauth,client}, D0) ->
{keep_state, D};
handle_event(_, #ssh_msg_userauth_success{}, {userauth,client}, D=#data{ssh_params = Ssh}) ->
+ ssh_auth:ssh_msg_userauth_result(success),
D#data.starter ! ssh_connected,
{next_state, {connected,client}, D#data{ssh_params=Ssh#ssh{authenticated = true}}};
@@ -990,11 +996,11 @@ handle_event(_, #ssh_msg_userauth_failure{authentications = Methods}, StateName=
StateName, D0#data{ssh_params = Ssh}),
{stop, Shutdown, D};
{"keyboard-interactive", {Msg, Ssh}} ->
- send_bytes(Msg, D0),
- {next_state, {userauth_keyboard_interactive,client}, D0#data{ssh_params = Ssh}};
+ D = send_msg(Msg, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth_keyboard_interactive,client}, D};
{_Method, {Msg, Ssh}} ->
- send_bytes(Msg, D0),
- {keep_state, D0#data{ssh_params = Ssh}}
+ D = send_msg(Msg, D0#data{ssh_params = Ssh}),
+ {keep_state, D}
end;
%%---- banner to client
@@ -1009,39 +1015,46 @@ handle_event(_, #ssh_msg_userauth_banner{message = Msg}, {userauth,client}, D) -
%%% ######## {userauth_keyboard_interactive, client|server}
handle_event(_, #ssh_msg_userauth_info_request{} = Msg, {userauth_keyboard_interactive, client},
- #data{ssh_params = Ssh0} = D) ->
+ #data{ssh_params = Ssh0} = D0) ->
case ssh_auth:handle_userauth_info_request(Msg, Ssh0) of
{ok, {Reply, Ssh}} ->
- send_bytes(Reply, D),
- {next_state, {userauth_keyboard_interactive_info_response,client}, D#data{ssh_params = Ssh}};
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth_keyboard_interactive_info_response,client}, D};
not_ok ->
- {next_state, {userauth,client}, D, [postpone]}
+ {next_state, {userauth,client}, D0, [postpone]}
end;
-handle_event(_, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboard_interactive, server}, D) ->
- case ssh_auth:handle_userauth_info_response(Msg, D#data.ssh_params) of
- {authorized, User, {Reply, Ssh}} ->
- send_bytes(Reply, D),
+handle_event(_, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboard_interactive, server}, D0) ->
+ case ssh_auth:handle_userauth_info_response(Msg, D0#data.ssh_params) of
+ {authorized, User, {Reply, Ssh1}} ->
+ D = #data{ssh_params=Ssh} =
+ send_msg(Reply, D0#data{ssh_params = Ssh1}),
D#data.starter ! ssh_connected,
connected_fun(User, "keyboard-interactive", D),
{next_state, {connected,server}, D#data{auth_user = User,
+ %% Note: authenticated=true MUST NOT be sent
+ %% before send_msg!
ssh_params = Ssh#ssh{authenticated = true}}};
{not_authorized, {User, Reason}, {Reply, Ssh}} ->
- retry_fun(User, Reason, D),
- send_bytes(Reply, D),
- {next_state, {userauth,server}, D#data{ssh_params = Ssh}};
+ retry_fun(User, Reason, D0),
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth,server}, D};
{authorized_but_one_more, _User, {Reply, Ssh}} ->
- send_bytes(Reply, D),
- {next_state, {userauth_keyboard_interactive_extra,server}, D#data{ssh_params = Ssh}}
+ D = send_msg(Reply, D0#data{ssh_params = Ssh}),
+ {next_state, {userauth_keyboard_interactive_extra,server}, D}
end;
-handle_event(_, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboard_interactive_extra, server}, D) ->
- {authorized, User, {Reply, Ssh}} = ssh_auth:handle_userauth_info_response({extra,Msg}, D#data.ssh_params),
- send_bytes(Reply, D),
+handle_event(_, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboard_interactive_extra, server}, D0) ->
+ {authorized, User, {Reply, Ssh1}} =
+ ssh_auth:handle_userauth_info_response({extra,Msg}, D0#data.ssh_params),
+ D = #data{ssh_params=Ssh} =
+ send_msg(Reply, D0#data{ssh_params = Ssh1}),
D#data.starter ! ssh_connected,
connected_fun(User, "keyboard-interactive", D),
{next_state, {connected,server}, D#data{auth_user = User,
+ %% Note: authenticated=true MUST NOT be sent
+ %% before send_msg!
ssh_params = Ssh#ssh{authenticated = true}}};
handle_event(_, #ssh_msg_userauth_failure{}, {userauth_keyboard_interactive, client},
@@ -2119,7 +2132,7 @@ start_rekeying(Role, D0) ->
{next_state, {kexinit,Role,renegotiate}, D}.
-init_renegotiate_timers(OldState, NewState, D) ->
+init_renegotiate_timers(_OldState, NewState, D) ->
{RekeyTimeout,_MaxSent} = ?GET_OPT(rekey_limit, (D#data.ssh_params)#ssh.opts),
{next_state, NewState, D, [{{timeout,renegotiate}, RekeyTimeout, none},
{{timeout,check_data_size}, ?REKEY_DATA_TIMOUT, none} ]}.
--
2.26.1