aboutsummaryrefslogtreecommitdiffstats
path: root/community/erlang/0015-otp-update-version-19.0.1.patch
diff options
context:
space:
mode:
authorMarlus Saraiva <marlus.saraiva@gmail.com>2016-07-11 23:33:13 +0000
committerBartłomiej Piotrowski <b@bpiotrowski.pl>2016-07-12 08:16:38 +0200
commitbad74ac0e89c284997e600f1769d43a36b1f8e84 (patch)
tree8c96b93aa2e883b0e26ad727c8ac50abd13a56dc /community/erlang/0015-otp-update-version-19.0.1.patch
parentab340c8532d061e965c5e60a3105d017d0041e9e (diff)
downloadaports-bad74ac0e89c284997e600f1769d43a36b1f8e84.tar.bz2
aports-bad74ac0e89c284997e600f1769d43a36b1f8e84.tar.xz
community/erlang: upgrade to 19.0.1
Diffstat (limited to 'community/erlang/0015-otp-update-version-19.0.1.patch')
-rw-r--r--community/erlang/0015-otp-update-version-19.0.1.patch1233
1 files changed, 1233 insertions, 0 deletions
diff --git a/community/erlang/0015-otp-update-version-19.0.1.patch b/community/erlang/0015-otp-update-version-19.0.1.patch
new file mode 100644
index 0000000000..31dcb29151
--- /dev/null
+++ b/community/erlang/0015-otp-update-version-19.0.1.patch
@@ -0,0 +1,1233 @@
+--- a/OTP_VERSION
++++ b/OTP_VERSION
+@@ -1 +1 @@
+-19.0
++19.0.1
+--- a/erts/doc/src/notes.xml
++++ b/erts/doc/src/notes.xml
+@@ -32,6 +32,24 @@
+ <p>This document describes the changes made to the ERTS application.</p>
+
+
++<section><title>Erts 8.0.1</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>
++ A memory allocation bug in <c>group_leader/2</c> could
++ cause an emulator crash when garbage collecting a process
++ that had been assigned a remote group leader. This bug
++ was introduced in ERTS version 8.0.</p>
++ <p>
++ Own Id: OTP-13716</p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
+ <section><title>Erts 8.0</title>
+
+ <section><title>Fixed Bugs and Malfunctions</title>
+--- a/erts/emulator/beam/bif.c
++++ b/erts/emulator/beam/bif.c
+@@ -4305,8 +4305,9 @@ BIF_RETTYPE group_leader_2(BIF_ALIST_2)
+ else {
+ locks &= ~ERTS_PROC_LOCK_STATUS;
+ erts_smp_proc_unlock(new_member, ERTS_PROC_LOCK_STATUS);
+- if (erts_smp_atomic32_read_nob(&new_member->state)
+- & !(ERTS_PSFLG_DIRTY_RUNNING|ERTS_PSFLG_DIRTY_RUNNING_SYS)) {
++ if (new_member == BIF_P
++ || !(erts_smp_atomic32_read_nob(&new_member->state)
++ & (ERTS_PSFLG_DIRTY_RUNNING|ERTS_PSFLG_DIRTY_RUNNING_SYS))) {
+ new_member->group_leader = STORE_NC_IN_PROC(new_member,
+ BIF_ARG_1);
+ }
+@@ -4326,6 +4327,7 @@ BIF_RETTYPE group_leader_2(BIF_ALIST_2)
+ BIF_ARG_1);
+ bp->next = new_member->mbuf;
+ new_member->mbuf = bp;
++ new_member->mbuf_sz += bp->used_size;
+ }
+ }
+ }
+--- a/erts/vsn.mk
++++ b/erts/vsn.mk
+@@ -18,7 +18,7 @@
+ # %CopyrightEnd%
+ #
+
+-VSN = 8.0
++VSN = 8.0.1
+
+ # Port number 4365 in 4.2
+ # Port number 4366 in 4.3
+--- a/lib/dialyzer/doc/src/notes.xml
++++ b/lib/dialyzer/doc/src/notes.xml
+@@ -32,6 +32,20 @@
+ <p>This document describes the changes made to the Dialyzer
+ application.</p>
+
++<section><title>Dialyzer 3.0.1</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>Fix a map related bug.</p>
++ <p>
++ Own Id: OTP-13709 Aux Id: ERL-177, PR-1115 </p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
+ <section><title>Dialyzer 3.0</title>
+
+ <section><title>Fixed Bugs and Malfunctions</title>
+--- /dev/null
++++ b/lib/dialyzer/test/map_SUITE_data/src/mand_remote_val/a.erl
+@@ -0,0 +1,9 @@
++-module(a).
++-export([to_map/1, to_map/2]).
++-type t() :: #{type := b:t()}.
++
++-spec to_map(t()) -> map().
++to_map(Resource) -> to_map(Resource, #{}).
++
++-spec to_map(t(), map()) -> map().
++to_map(_, Map) when is_map(Map) -> #{}.
+--- /dev/null
++++ b/lib/dialyzer/test/map_SUITE_data/src/mand_remote_val/b.erl
+@@ -0,0 +1,3 @@
++-module(b).
++-export_type([t/0]).
++-type t() :: binary().
+--- a/lib/dialyzer/vsn.mk
++++ b/lib/dialyzer/vsn.mk
+@@ -1 +1 @@
+-DIALYZER_VSN = 3.0
++DIALYZER_VSN = 3.0.1
+--- a/lib/hipe/cerl/erl_types.erl
++++ b/lib/hipe/cerl/erl_types.erl
+@@ -1664,10 +1664,12 @@ t_map(Pairs0, DefK0, DefV0) ->
+ %% define(DEBUG, true).
+ try
+ validate_map_elements(Pairs)
+- catch error:badarg -> error(badarg, [Pairs0,DefK0,DefV0]);
+- error:{badarg, E} -> error({badarg, E}, [Pairs0,DefK0,DefV0])
++ catch error:badarg -> error(badarg, [Pairs0,DefK0,DefV0])
+ end,
+- ?map(Pairs, DefK, DefV).
++ case map_pairs_are_none(Pairs) of
++ true -> ?none;
++ false -> ?map(Pairs, DefK, DefV)
++ end.
+
+ normalise_map_optionals([], _, _) -> [];
+ normalise_map_optionals([E={K,?opt,?none}|T], DefK, DefV) ->
+@@ -1684,7 +1686,6 @@ normalise_map_optionals([E={K,?opt,V}|T], DefK, DefV) ->
+ normalise_map_optionals([E|T], DefK, DefV) ->
+ [E|normalise_map_optionals(T, DefK, DefV)].
+
+-validate_map_elements([{_,?mand,?none}|_]) -> error({badarg, none_in_mand});
+ validate_map_elements([{K1,_,_}|Rest=[{K2,_,_}|_]]) ->
+ case is_singleton_type(K1) andalso K1 < K2 of
+ false -> error(badarg);
+@@ -1697,6 +1698,10 @@ validate_map_elements([{K,_,_}]) ->
+ end;
+ validate_map_elements([]) -> true.
+
++map_pairs_are_none([]) -> false;
++map_pairs_are_none([{_,?mand,?none}|_]) -> true;
++map_pairs_are_none([_|Ps]) -> map_pairs_are_none(Ps).
++
+ -spec t_is_map(erl_type()) -> boolean().
+
+ t_is_map(Type) ->
+@@ -2833,12 +2838,7 @@ t_inf(?map(_, ADefK, ADefV) = A, ?map(_, BDefK, BDefV) = B, _Opaques) ->
+ %% becomes mandatory in the infinumum
+ (K, _, V1, _, V2) -> {K, ?mand, t_inf(V1, V2)}
+ end, A, B),
+- %% If the infinimum of any mandatory values is ?none, the entire map infinimum
+- %% is ?none.
+- case lists:any(fun({_,?mand,?none})->true; ({_,_,_}) -> false end, Pairs) of
+- true -> t_none();
+- false -> t_map(Pairs, t_inf(ADefK, BDefK), t_inf(ADefV, BDefV))
+- end;
++ t_map(Pairs, t_inf(ADefK, BDefK), t_inf(ADefV, BDefV));
+ t_inf(?matchstate(Pres1, Slots1), ?matchstate(Pres2, Slots2), _Opaques) ->
+ ?matchstate(t_inf(Pres1, Pres2), t_inf(Slots1, Slots2));
+ t_inf(?nil, ?nil, _Opaques) -> ?nil;
+--- a/lib/inets/doc/src/notes.xml
++++ b/lib/inets/doc/src/notes.xml
+@@ -33,7 +33,23 @@
+ <file>notes.xml</file>
+ </header>
+
+- <section><title>Inets 6.3</title>
++ <section><title>Inets 6.3.1</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>
++ A debug message was accidently left enabled in the ftp
++ client.</p>
++ <p>
++ Own Id: OTP-13712 Aux Id: seq13143 </p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
++<section><title>Inets 6.3</title>
+
+ <section><title>Fixed Bugs and Malfunctions</title>
+ <list>
+--- a/lib/inets/src/ftp/ftp.erl
++++ b/lib/inets/src/ftp/ftp.erl
+@@ -106,8 +106,8 @@
+ -type common_reason() :: 'econn' | 'eclosed' | term().
+ -type file_write_error_reason() :: term(). % See file:write for more info
+
+-%%-define(DBG(F,A), 'n/a').
+--define(DBG(F,A), io:format(F,A)).
++-define(DBG(F,A), 'n/a').
++%%-define(DBG(F,A), io:format(F,A)).
+
+ %%%=========================================================================
+ %%% API - CLIENT FUNCTIONS
+@@ -2099,7 +2099,7 @@ handle_ctrl_result({pos_prel, _}, #state{caller = {transfer_data, Bin}}
+
+ %%--------------------------------------------------------------------------
+ %% Default
+-handle_ctrl_result({Status, Lines}, #state{client = From} = State)
++handle_ctrl_result({Status, _Lines}, #state{client = From} = State)
+ when From =/= undefined ->
+ ctrl_result_response(Status, State, {error, Status}).
+
+--- a/lib/inets/vsn.mk
++++ b/lib/inets/vsn.mk
+@@ -19,6 +19,6 @@
+ # %CopyrightEnd%
+
+ APPLICATION = inets
+-INETS_VSN = 6.3
++INETS_VSN = 6.3.1
+ PRE_VSN =
+ APP_VSN = "$(APPLICATION)-$(INETS_VSN)$(PRE_VSN)"
+--- a/lib/observer/doc/src/notes.xml
++++ b/lib/observer/doc/src/notes.xml
+@@ -32,6 +32,23 @@
+ <p>This document describes the changes made to the Observer
+ application.</p>
+
++<section><title>Observer 2.2.1</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>
++ Fixed a crash happening when observing another node, who
++ have a different number of schedulers than the current
++ one.</p>
++ <p>
++ Own Id: OTP-13702 Aux Id: ERL-171 </p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
+ <section><title>Observer 2.2</title>
+
+ <section><title>Improvements and New Features</title>
+--- a/lib/observer/src/observer_perf_wx.erl
++++ b/lib/observer/src/observer_perf_wx.erl
+@@ -235,12 +235,14 @@ terminate(_Event, #state{appmon=Pid}) ->
+ code_change(_, _, State) ->
+ State.
+
+-restart_fetcher(Node, #state{appmon=Old, panel=Panel, time=#ti{fetch=Freq}=Ti}=State) ->
++restart_fetcher(Node, #state{appmon=Old, panel=Panel, time=#ti{fetch=Freq}=Ti, wins=Wins0}=State) ->
+ catch Old ! exit,
+ Me = self(),
+ Pid = spawn_link(Node, observer_backend, fetch_stats, [Me, round(1000/Freq)]),
+ wxWindow:refresh(Panel),
+- precalc(State#state{active=true, appmon=Pid, samples=reset_data(), time=Ti#ti{tick=0}}).
++ Wins = [W#win{state=undefined} || W <- Wins0],
++ precalc(State#state{active=true, appmon=Pid, samples=reset_data(),
++ wins=Wins, time=Ti#ti{tick=0}}).
+
+ reset_data() ->
+ {0, queue:new()}.
+@@ -253,18 +255,25 @@ add_data(Stats, {N, Q}, Wins, _, Active) ->
+
+ add_data_1([#win{state={_,St}}|_]=Wins0, Last, N, {Drop, Q}, Active)
+ when St /= undefined ->
+- {Wins, Stat} =
+- lists:mapfoldl(fun(Win0, Entry) ->
+- {Win1,Stat} = add_data_2(Win0, Last, Entry),
+- case Active of
+- true ->
+- Win = add_data_3(Win1, N, Drop, Stat, Q),
+- {Win, Stat};
+- false ->
+- {Win1, Stat}
+- end
+- end, #{}, Wins0),
+- {Wins, {N,queue:in(Stat#{}, Q)}};
++ try
++ {Wins, Stat} =
++ lists:mapfoldl(fun(Win0, Entry) ->
++ {Win1,Stat} = add_data_2(Win0, Last, Entry),
++ case Active of
++ true ->
++ Win = add_data_3(Win1, N, Drop, Stat, Q),
++ {Win, Stat};
++ false ->
++ {Win1, Stat}
++ end
++ end, #{}, Wins0),
++ {Wins, {N,queue:in(Stat#{}, Q)}}
++ catch no_scheduler_change ->
++ {[Win#win{state=init_data(Id, Last),
++ info = info(Id, Last)}
++ || #win{name=Id}=Win <- Wins0], {0,queue:new()}}
++ end;
++
+ add_data_1(Wins, Stats, 1, {_, Q}, _) ->
+ {[Win#win{state=init_data(Id, Stats),
+ info = info(Id, Stats)}
+@@ -409,7 +418,8 @@ collect_data(utilz, MemInfo, Max) ->
+
+ calc_delta([{Id, WN, TN}|Ss], [{Id, WP, TP}|Ps]) ->
+ [100*(WN-WP) div (TN-TP)|calc_delta(Ss, Ps)];
+-calc_delta([], []) -> [].
++calc_delta([], []) -> [];
++calc_delta(_, _) -> throw(no_scheduler_change).
+
+ precalc(#state{samples=Data0, paint=Paint, time=Ti, wins=Wins0}=State) ->
+ Wins = [precalc(Ti, Data0, Paint, Win) || Win <- Wins0],
+--- a/lib/observer/vsn.mk
++++ b/lib/observer/vsn.mk
+@@ -1 +1 @@
+-OBSERVER_VSN = 2.2
++OBSERVER_VSN = 2.2.1
+--- a/lib/ssh/doc/src/notes.xml
++++ b/lib/ssh/doc/src/notes.xml
+@@ -30,6 +30,30 @@
+ <file>notes.xml</file>
+ </header>
+
++<section><title>Ssh 4.3.1</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>
++ SSH client does not any longer retry a bad password given
++ as option to ssh:connect et al.</p>
++ <p>
++ Own Id: OTP-13674 Aux Id: TR-HU92273 </p>
++ </item>
++ <item>
++ <p>
++ Removed possible hanging risk for a certain timing
++ sequence when communicating client and server executes on
++ the same node.</p>
++ <p>
++ Own Id: OTP-13715</p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
+ <section><title>Ssh 4.3</title>
+
+ <section><title>Improvements and New Features</title>
+--- a/lib/ssh/src/ssh_auth.erl
++++ b/lib/ssh/src/ssh_auth.erl
+@@ -31,12 +31,111 @@
+ -export([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,
+- handle_userauth_info_request/3, handle_userauth_info_response/2
++ handle_userauth_info_request/2, handle_userauth_info_response/2
+ ]).
+
+ %%--------------------------------------------------------------------
+ %%% Internal application API
+ %%--------------------------------------------------------------------
++%%%----------------------------------------------------------------
++userauth_request_msg(#ssh{userauth_methods = ServerMethods,
++ userauth_supported_methods = UserPrefMethods, % Note: this is not documented as supported for clients
++ userauth_preference = ClientMethods0
++ } = Ssh0) ->
++ case sort_select_mthds(ClientMethods0, UserPrefMethods, ServerMethods) of
++ [] ->
++ Msg = #ssh_msg_disconnect{code = ?SSH_DISCONNECT_NO_MORE_AUTH_METHODS_AVAILABLE,
++ description = "Unable to connect using the available authentication methods",
++ language = "en"},
++ {disconnect, Msg, ssh_transport:ssh_packet(Msg, Ssh0)};
++
++ [{Pref,Module,Function,Args} | Prefs] ->
++ Ssh = case Pref of
++ "keyboard-interactive" -> Ssh0;
++ _ -> Ssh0#ssh{userauth_preference = Prefs}
++ end,
++ case Module:Function(Args ++ [Ssh]) of
++ {not_ok, Ssh1} ->
++ userauth_request_msg(Ssh1#ssh{userauth_preference = Prefs});
++ Result ->
++ {Pref,Result}
++ end
++ end.
++
++
++
++sort_select_mthds(Clients, undefined, Servers) ->
++ %% User has not expressed an opinion via option "auth_methods", use the server's prefs
++ sort_select_mthds1(Clients, Servers, string:tokens(?SUPPORTED_AUTH_METHODS,","));
++
++sort_select_mthds(Clients, Users0, Servers0) ->
++ %% The User has an opinion, use the intersection of that and the Servers whishes but
++ %% in the Users order
++ sort_select_mthds1(Clients, string:tokens(Users0,","), Servers0).
++
++
++sort_select_mthds1(Clients, Users0, Servers0) ->
++ Servers = unique(Servers0),
++ Users = unique(Users0),
++ [C || Key <- Users,
++ lists:member(Key, Servers),
++ C <- Clients,
++ element(1,C) == Key].
++
++unique(L) ->
++ lists:reverse(
++ lists:foldl(fun(E,Acc) ->
++ case lists:member(E,Acc) of
++ true -> Acc;
++ false -> [E|Acc]
++ end
++ end, [], L)).
++
++
++%%%---- userauth_request_msg "callbacks"
++password_msg([#ssh{opts = Opts, io_cb = IoCb,
++ user = User, service = Service} = Ssh0]) ->
++ {Password,Ssh} =
++ case proplists:get_value(password, Opts) of
++ undefined when IoCb == ssh_no_io ->
++ {not_ok, Ssh0};
++ undefined ->
++ {IoCb:read_password("ssh password: ",Ssh0), Ssh0};
++ PW ->
++ %% If "password" option is given it should not be tried again
++ {PW, Ssh0#ssh{opts = lists:keyreplace(password,1,Opts,{password,not_ok})}}
++ end,
++ case Password of
++ 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)
++ end.
++
++%% See RFC 4256 for info on keyboard-interactive
++keyboard_interactive_msg([#ssh{user = User,
++ opts = Opts,
++ service = Service} = Ssh]) ->
++ case proplists:get_value(password, Opts) of
++ 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)
++ end.
++
+ publickey_msg([Alg, #ssh{user = User,
+ session_id = SessionId,
+ service = Service,
+@@ -48,7 +147,7 @@ publickey_msg([Alg, #ssh{user = User,
+ StrAlgo = atom_to_list(Alg),
+ case encode_public_key(StrAlgo, ssh_transport:extract_public_key(PrivKey)) of
+ not_ok ->
+- not_ok;
++ {not_ok, Ssh};
+ PubKeyBlob ->
+ SigData = build_sig_data(SessionId,
+ User, Service, PubKeyBlob, StrAlgo),
+@@ -65,52 +164,15 @@ publickey_msg([Alg, #ssh{user = User,
+ Ssh)
+ end;
+ _Error ->
+- not_ok
+- end.
+-
+-password_msg([#ssh{opts = Opts, io_cb = IoCb,
+- user = User, service = Service} = Ssh]) ->
+- Password = case proplists:get_value(password, Opts) of
+- undefined ->
+- user_interaction(IoCb, Ssh);
+- PW ->
+- PW
+- end,
+- case Password of
+- not_ok ->
+- not_ok;
+- _ ->
+- ssh_transport:ssh_packet(
+- #ssh_msg_userauth_request{user = User,
+- service = Service,
+- method = "password",
+- data =
+- <<?BOOLEAN(?FALSE),
+- ?STRING(unicode:characters_to_binary(Password))>>},
+- Ssh)
++ {not_ok, Ssh}
+ end.
+
+-user_interaction(ssh_no_io, _) ->
+- not_ok;
+-user_interaction(IoCb, Ssh) ->
+- IoCb:read_password("ssh password: ", Ssh).
+-
+-
+-%% See RFC 4256 for info on keyboard-interactive
+-keyboard_interactive_msg([#ssh{user = User,
+- service = Service} = Ssh]) ->
+- ssh_transport:ssh_packet(
+- #ssh_msg_userauth_request{user = User,
+- service = Service,
+- method = "keyboard-interactive",
+- data = << ?STRING(<<"">>),
+- ?STRING(<<>>) >> },
+- Ssh).
+-
++%%%----------------------------------------------------------------
+ service_request_msg(Ssh) ->
+ ssh_transport:ssh_packet(#ssh_msg_service_request{name = "ssh-userauth"},
+ Ssh#ssh{service = "ssh-userauth"}).
+
++%%%----------------------------------------------------------------
+ init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
+ case user_name(Opts) of
+ {ok, User} ->
+@@ -140,34 +202,9 @@ init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
+ description = ErrStr})
+ end.
+
+-userauth_request_msg(#ssh{userauth_preference = []} = Ssh) ->
+- Msg = #ssh_msg_disconnect{code =
+- ?SSH_DISCONNECT_NO_MORE_AUTH_METHODS_AVAILABLE,
+- description = "Unable to connect using the available"
+- " authentication methods",
+- language = "en"},
+- {disconnect, Msg, ssh_transport:ssh_packet(Msg, Ssh)};
+-
+-userauth_request_msg(#ssh{userauth_methods = Methods,
+- userauth_preference = [{Pref, Module,
+- Function, Args} | Prefs]}
+- = Ssh0) ->
+- Ssh = Ssh0#ssh{userauth_preference = Prefs},
+- case lists:member(Pref, Methods) of
+- true ->
+- case Module:Function(Args ++ [Ssh]) of
+- not_ok ->
+- userauth_request_msg(Ssh);
+- Result ->
+- {Pref,Result}
+- end;
+- false ->
+- userauth_request_msg(Ssh)
+- end.
+-
+-
+-handle_userauth_request(#ssh_msg_service_request{name =
+- Name = "ssh-userauth"},
++%%%----------------------------------------------------------------
++%%% 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"})};
+@@ -319,21 +356,28 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
+ partial_success = false}, Ssh)}.
+
+
+-
+-handle_userauth_info_request(
+- #ssh_msg_userauth_info_request{name = Name,
+- instruction = Instr,
+- num_prompts = NumPrompts,
+- data = Data}, IoCb,
+- #ssh{opts = Opts} = Ssh) ->
++%%%----------------------------------------------------------------
++%%% keyboard-interactive client
++handle_userauth_info_request(#ssh_msg_userauth_info_request{name = Name,
++ instruction = Instr,
++ num_prompts = NumPrompts,
++ data = Data},
++ #ssh{opts = Opts,
++ io_cb = IoCb
++ } = Ssh) ->
+ PromptInfos = decode_keyboard_interactive_prompts(NumPrompts,Data),
+- Responses = keyboard_interact_get_responses(IoCb, Opts,
+- Name, Instr, PromptInfos),
+- {ok,
+- ssh_transport:ssh_packet(
+- #ssh_msg_userauth_info_response{num_responses = NumPrompts,
+- data = Responses}, Ssh)}.
++ case keyboard_interact_get_responses(IoCb, Opts, Name, Instr, PromptInfos) of
++ not_ok ->
++ not_ok;
++ Responses ->
++ {ok,
++ ssh_transport:ssh_packet(
++ #ssh_msg_userauth_info_response{num_responses = NumPrompts,
++ data = Responses}, Ssh)}
++ end.
+
++%%%----------------------------------------------------------------
++%%% keyboard-interactive server
+ handle_userauth_info_response(#ssh_msg_userauth_info_response{num_responses = 1,
+ data = <<?UINT32(Sz), Password:Sz/binary>>},
+ #ssh{opts = Opts,
+@@ -369,11 +413,6 @@ method_preference(Algs) ->
+ [{"publickey", ?MODULE, publickey_msg, [A]} | Acc]
+ end,
+ [{"password", ?MODULE, password_msg, []},
+- {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []},
+- {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []},
+- {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []},
+- {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []},
+- {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []},
+ {"keyboard-interactive", ?MODULE, keyboard_interactive_msg, []}
+ ],
+ Algs).
+@@ -473,6 +512,9 @@ keyboard_interact_get_responses(IoCb, Opts, Name, Instr, PromptInfos) ->
+ proplists:get_value(password, Opts, undefined), IoCb, Name,
+ Instr, PromptInfos, Opts, NumPrompts).
+
++
++keyboard_interact_get_responses(_, _, not_ok, _, _, _, _, _, _) ->
++ not_ok;
+ keyboard_interact_get_responses(_, undefined, Password, _, _, _, _, _,
+ 1) when Password =/= undefined ->
+ [Password]; %% Password auth implemented with keyboard-interaction and passwd is known
+@@ -486,17 +528,18 @@ keyboard_interact_get_responses(true, Fun, _Pwd, _IoCb, Name, Instr, PromptInfos
+ keyboard_interact_fun(Fun, Name, Instr, PromptInfos, NumPrompts).
+
+ keyboard_interact(IoCb, Name, Instr, Prompts, Opts) ->
+- if Name /= "" -> IoCb:format("~s~n", [Name]);
+- true -> ok
+- end,
+- if Instr /= "" -> IoCb:format("~s~n", [Instr]);
+- true -> ok
+- end,
++ write_if_nonempty(IoCb, Name),
++ write_if_nonempty(IoCb, Instr),
+ lists:map(fun({Prompt, true}) -> IoCb:read_line(Prompt, Opts);
+ ({Prompt, false}) -> IoCb:read_password(Prompt, Opts)
+ end,
+ Prompts).
+
++write_if_nonempty(_, "") -> ok;
++write_if_nonempty(_, <<>>) -> ok;
++write_if_nonempty(IoCb, Text) -> IoCb:format("~s~n",[Text]).
++
++
+ keyboard_interact_fun(KbdInteractFun, Name, Instr, PromptInfos, NumPrompts) ->
+ Prompts = lists:map(fun({Prompt, _Echo}) -> Prompt end,
+ PromptInfos),
+--- a/lib/ssh/src/ssh_connection_handler.erl
++++ b/lib/ssh/src/ssh_connection_handler.erl
+@@ -428,7 +428,12 @@ init_connection(server, C = #connection{}, Opts) ->
+ init_ssh_record(Role, Socket, Opts) ->
+ {ok, PeerAddr} = inet:peername(Socket),
+ KeyCb = proplists:get_value(key_cb, Opts, ssh_file),
+- AuthMethods = proplists:get_value(auth_methods, Opts, ?SUPPORTED_AUTH_METHODS),
++ AuthMethods = proplists:get_value(auth_methods,
++ Opts,
++ case Role of
++ server -> ?SUPPORTED_AUTH_METHODS;
++ client -> undefined
++ end),
+ S0 = #ssh{role = Role,
+ key_cb = KeyCb,
+ opts = Opts,
+@@ -794,9 +799,13 @@ handle_event(_, #ssh_msg_userauth_banner{message = Msg}, {userauth,client}, D) -
+
+ handle_event(_, #ssh_msg_userauth_info_request{} = Msg, {userauth_keyboard_interactive, client},
+ #data{ssh_params = Ssh0} = D) ->
+- {ok, {Reply, Ssh}} = ssh_auth:handle_userauth_info_request(Msg, Ssh0#ssh.io_cb, Ssh0),
+- send_bytes(Reply, D),
+- {next_state, {userauth_keyboard_interactive_info_response,client}, D#data{ssh_params = Ssh}};
++ 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}};
++ not_ok ->
++ {next_state, {userauth,client}, D, [{next_event, internal, Msg}]}
++ 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
+@@ -819,7 +828,18 @@ handle_event(_, Msg = #ssh_msg_userauth_failure{}, {userauth_keyboard_interactiv
+ D = D0#data{ssh_params = Ssh0#ssh{userauth_preference=Prefs}},
+ {next_state, {userauth,client}, D, [{next_event, internal, Msg}]};
+
+-handle_event(_, Msg=#ssh_msg_userauth_failure{}, {userauth_keyboard_interactive_info_response, client}, D) ->
++handle_event(_, Msg=#ssh_msg_userauth_failure{}, {userauth_keyboard_interactive_info_response, client},
++ #data{ssh_params = Ssh0} = D0) ->
++ Opts = Ssh0#ssh.opts,
++ D = case proplists:get_value(password, Opts) of
++ undefined ->
++ D0;
++ _ ->
++ D0#data{ssh_params =
++ Ssh0#ssh{opts =
++ lists:keyreplace(password,1,Opts,
++ {password,not_ok})}} % FIXME:intermodule dependency
++ end,
+ {next_state, {userauth,client}, D, [{next_event, internal, Msg}]};
+
+ handle_event(_, Msg=#ssh_msg_userauth_success{}, {userauth_keyboard_interactive_info_response, client}, D) ->
+@@ -1006,13 +1026,13 @@ handle_event({call,From}, get_print_info, StateName, D) ->
+ {keep_state_and_data, [{reply,From,Reply}]};
+
+ handle_event({call,From}, {connection_info, Options}, _, D) ->
+- Info = ssh_info(Options, D, []),
++ Info = fold_keys(Options, fun conn_info/2, D),
+ {keep_state_and_data, [{reply,From,Info}]};
+
+ handle_event({call,From}, {channel_info,ChannelId,Options}, _, D) ->
+ case ssh_channel:cache_lookup(cache(D), ChannelId) of
+ #channel{} = Channel ->
+- Info = ssh_channel_info(Options, Channel, []),
++ Info = fold_keys(Options, fun chann_info/2, Channel),
+ {keep_state_and_data, [{reply,From,Info}]};
+ undefined ->
+ {keep_state_and_data, [{reply,From,[]}]}
+@@ -1206,8 +1226,9 @@ handle_event(internal, prepare_next_packet, _, D) ->
+ Sz when Sz >= Enough ->
+ self() ! {D#data.transport_protocol, D#data.socket, <<>>};
+ _ ->
+- inet:setopts(D#data.socket, [{active, once}])
++ ok
+ end,
++ inet:setopts(D#data.socket, [{active, once}]),
+ keep_state_and_data;
+
+ handle_event(info, {CloseTag,Socket}, StateName,
+@@ -1315,12 +1336,10 @@ terminate(shutdown, StateName, State0) ->
+ State = send_msg(#ssh_msg_disconnect{code = ?SSH_DISCONNECT_BY_APPLICATION,
+ description = "Application shutdown"},
+ State0),
+-timer:sleep(400), %% FIXME!!! gen_tcp:shutdown instead
+ finalize_termination(StateName, State);
+
+ %% terminate({shutdown,Msg}, StateName, State0) when is_record(Msg,ssh_msg_disconnect)->
+ %% State = send_msg(Msg, State0),
+-%% timer:sleep(400), %% FIXME!!! gen_tcp:shutdown instead
+ %% finalize_termination(StateName, Msg, State);
+
+ terminate({shutdown,_R}, StateName, State) ->
+@@ -1635,7 +1654,6 @@ new_channel_id(#data{connection_state = #connection{channel_id_seed = Id} =
+ disconnect(Msg=#ssh_msg_disconnect{description=Description}, _StateName, State0) ->
+ State = send_msg(Msg, State0),
+ disconnect_fun(Description, State),
+-timer:sleep(400),
+ {stop, {shutdown,Description}, State}.
+
+ %%%----------------------------------------------------------------
+@@ -1644,43 +1662,43 @@ counterpart_versions(NumVsn, StrVsn, #ssh{role = server} = Ssh) ->
+ counterpart_versions(NumVsn, StrVsn, #ssh{role = client} = Ssh) ->
+ Ssh#ssh{s_vsn = NumVsn , s_version = StrVsn}.
+
+-ssh_info([], _State, Acc) ->
+- Acc;
+-ssh_info([client_version | Rest], #data{ssh_params = #ssh{c_vsn = IntVsn,
+- c_version = StringVsn}} = State, Acc) ->
+- ssh_info(Rest, State, [{client_version, {IntVsn, StringVsn}} | Acc]);
+-
+-ssh_info([server_version | Rest], #data{ssh_params =#ssh{s_vsn = IntVsn,
+- s_version = StringVsn}} = State, Acc) ->
+- ssh_info(Rest, State, [{server_version, {IntVsn, StringVsn}} | Acc]);
+-ssh_info([peer | Rest], #data{ssh_params = #ssh{peer = Peer}} = State, Acc) ->
+- ssh_info(Rest, State, [{peer, Peer} | Acc]);
+-ssh_info([sockname | Rest], #data{socket = Socket} = State, Acc) ->
+- {ok, SockName} = inet:sockname(Socket),
+- ssh_info(Rest, State, [{sockname, SockName}|Acc]);
+-ssh_info([user | Rest], #data{auth_user = User} = State, Acc) ->
+- ssh_info(Rest, State, [{user, User}|Acc]);
+-ssh_info([ _ | Rest], State, Acc) ->
+- ssh_info(Rest, State, Acc).
+-
+-
+-ssh_channel_info([], _, Acc) ->
+- Acc;
++%%%----------------------------------------------------------------
++conn_info(client_version, #data{ssh_params=S}) -> {S#ssh.c_vsn, S#ssh.c_version};
++conn_info(server_version, #data{ssh_params=S}) -> {S#ssh.s_vsn, S#ssh.s_version};
++conn_info(peer, #data{ssh_params=S}) -> S#ssh.peer;
++conn_info(user, D) -> D#data.auth_user;
++conn_info(sockname, D) -> {ok, SockName} = inet:sockname(D#data.socket),
++ SockName;
++%% dbg options ( = not documented):
++conn_info(socket, D) -> D#data.socket;
++conn_info(chan_ids, D) ->
++ ssh_channel:cache_foldl(fun(#channel{local_id=Id}, Acc) ->
++ [Id | Acc]
++ end, [], cache(D)).
+
+-ssh_channel_info([recv_window | Rest], #channel{recv_window_size = WinSize,
+- recv_packet_size = Packsize
+- } = Channel, Acc) ->
+- ssh_channel_info(Rest, Channel, [{recv_window, {{win_size, WinSize},
+- {packet_size, Packsize}}} | Acc]);
+-ssh_channel_info([send_window | Rest], #channel{send_window_size = WinSize,
+- send_packet_size = Packsize
+- } = Channel, Acc) ->
+- ssh_channel_info(Rest, Channel, [{send_window, {{win_size, WinSize},
+- {packet_size, Packsize}}} | Acc]);
+-ssh_channel_info([ _ | Rest], Channel, Acc) ->
+- ssh_channel_info(Rest, Channel, Acc).
++%%%----------------------------------------------------------------
++chann_info(recv_window, C) ->
++ {{win_size, C#channel.recv_window_size},
++ {packet_size, C#channel.recv_packet_size}};
++chann_info(send_window, C) ->
++ {{win_size, C#channel.send_window_size},
++ {packet_size, C#channel.send_packet_size}};
++%% dbg options ( = not documented):
++chann_info(pid, C) ->
++ C#channel.user.
+
++%%%----------------------------------------------------------------
++%% Assisting meta function for the *_info functions
++fold_keys(Keys, Fun, Extra) ->
++ lists:foldr(fun(Key, Acc) ->
++ try Fun(Key, Extra) of
++ Value -> [{Key,Value}|Acc]
++ catch
++ _:_ -> Acc
++ end
++ end, [], Keys).
+
++%%%----------------------------------------------------------------
+ log_error(Reason) ->
+ Report = io_lib:format("Erlang ssh connection handler failed with reason:~n"
+ " ~p~n"
+@@ -1689,7 +1707,6 @@ log_error(Reason) ->
+ [Reason, erlang:get_stacktrace()]),
+ error_logger:error_report(Report).
+
+-
+ %%%----------------------------------------------------------------
+ not_connected_filter({connection_reply, _Data}) -> true;
+ not_connected_filter(_) -> false.
+--- a/lib/ssh/src/ssh_dbg.erl
++++ b/lib/ssh/src/ssh_dbg.erl
+@@ -24,6 +24,7 @@
+
+ -export([messages/0,
+ messages/1,
++ messages/2,
+ stop/0
+ ]).
+
+@@ -36,12 +37,16 @@
+ writer,
+ acc = []}).
+ %%%================================================================
+-messages() -> messages(fun(String,_D) -> io:format(String) end).
+-%% messages() -> messages(fun(String,Acc) -> [String|Acc] end)
++messages() ->
++ messages(fun(String,_D) -> io:format(String) end).
+
+ messages(Write) when is_function(Write,2) ->
++ messages(Write, fun(X) -> X end).
++
++messages(Write, MangleArg) when is_function(Write,2),
++ is_function(MangleArg,1) ->
+ catch dbg:start(),
+- setup_tracer(Write),
++ setup_tracer(Write, MangleArg),
+ dbg:p(new,c),
+ dbg_ssh_messages().
+
+@@ -63,18 +68,30 @@ msg_formater({trace,_Pid,return_from,{ssh_message,encode,1},_Res}, D) ->
+ msg_formater({trace,_Pid,call,{ssh_message,decode,_}}, D) ->
+ D;
+ msg_formater({trace,Pid,return_from,{ssh_message,decode,1},Msg}, D) ->
+- fmt("~nRECV ~p ~s~n", [Pid,wr_record(shrink_bin(Msg))], D);
++ fmt("~n~p RECV ~s~n", [Pid,wr_record(shrink_bin(Msg))], D);
+
+ msg_formater({trace,_Pid,call,{ssh_transport,select_algorithm,_}}, D) ->
+ D;
+ msg_formater({trace,Pid,return_from,{ssh_transport,select_algorithm,3},{ok,Alg}}, D) ->
+- fmt("~nALGORITHMS ~p~n~s~n", [Pid, wr_record(Alg)], D);
++ fmt("~n~p ALGORITHMS~n~s~n", [Pid, wr_record(Alg)], D);
++
++
++msg_formater({trace,Pid,send,{tcp,Sock,Bytes},Pid}, D) ->
++ fmt("~n~p TCP SEND on ~p~n ~p~n", [Pid,Sock, shrink_bin(Bytes)], D);
++
++msg_formater({trace,Pid,send,{tcp,Sock,Bytes},Dest}, D) ->
++ fmt("~n~p TCP SEND from ~p TO ~p~n ~p~n", [Pid,Sock,Dest, shrink_bin(Bytes)], D);
+
+ msg_formater({trace,Pid,send,ErlangMsg,Dest}, D) ->
+- fmt("~nERL MSG ~p SEND TO ~p~n ~p~n", [Pid,Dest, shrink_bin(ErlangMsg)], D);
++ fmt("~n~p ERL MSG SEND TO ~p~n ~p~n", [Pid,Dest, shrink_bin(ErlangMsg)], D);
++
++
++msg_formater({trace,Pid,'receive',{tcp,Sock,Bytes}}, D) ->
++ fmt("~n~p TCP RECEIVE on ~p~n ~p~n", [Pid,Sock,shrink_bin(Bytes)], D);
+
+ msg_formater({trace,Pid,'receive',ErlangMsg}, D) ->
+- fmt("~nERL MSG ~p RECIEVE~n ~p~n", [Pid,shrink_bin(ErlangMsg)], D);
++ fmt("~n~p ERL MSG RECEIVE~n ~p~n", [Pid,shrink_bin(ErlangMsg)], D);
++
+
+ msg_formater(M, D) ->
+ fmt("~nDBG ~n~p~n", [shrink_bin(M)], D).
+@@ -87,8 +104,10 @@ fmt(Fmt, Args, D=#data{writer=Write,acc=Acc}) ->
+ D#data{acc = Write(io_lib:format(Fmt, Args), Acc)}.
+
+ %%%----------------------------------------------------------------
+-setup_tracer(Write) ->
+- Handler = fun msg_formater/2,
++setup_tracer(Write, MangleArg) ->
++ Handler = fun(Arg, D) ->
++ msg_formater(MangleArg(Arg), D)
++ end,
+ InitialData = #data{writer = Write},
+ {ok,_} = dbg:tracer(process, {Handler, InitialData}),
+ ok.
+--- a/lib/ssh/src/ssh_io.erl
++++ b/lib/ssh/src/ssh_io.erl
+@@ -31,56 +31,55 @@ read_line(Prompt, Ssh) ->
+ format("~s", [listify(Prompt)]),
+ proplists:get_value(user_pid, Ssh) ! {self(), question},
+ receive
+- Answer ->
++ Answer when is_list(Answer) ->
+ Answer
+ end.
+
+ yes_no(Prompt, Ssh) ->
+- io:format("~s [y/n]?", [Prompt]),
++ format("~s [y/n]?", [Prompt]),
+ proplists:get_value(user_pid, Ssh#ssh.opts) ! {self(), question},
+ receive
+- Answer ->
++ %% I can't see that the atoms y and n are ever received, but it must
++ %% be investigated before removing
++ y -> yes;
++ n -> no;
++
++ Answer when is_list(Answer) ->
+ case trim(Answer) of
+ "y" -> yes;
+ "n" -> no;
+ "Y" -> yes;
+ "N" -> no;
+- y -> yes;
+- n -> no;
+ _ ->
+- io:format("please answer y or n\n"),
++ format("please answer y or n\n",[]),
+ yes_no(Prompt, Ssh)
+ end
+ end.
+
+
+-read_password(Prompt, Ssh) ->
++read_password(Prompt, #ssh{opts=Opts}) -> read_password(Prompt, Opts);
++read_password(Prompt, Opts) when is_list(Opts) ->
+ format("~s", [listify(Prompt)]),
+- case is_list(Ssh) of
+- false ->
+- proplists:get_value(user_pid, Ssh#ssh.opts) ! {self(), user_password};
+- _ ->
+- proplists:get_value(user_pid, Ssh) ! {self(), user_password}
+- end,
++ proplists:get_value(user_pid, Opts) ! {self(), user_password},
+ receive
+- Answer ->
+- case Answer of
+- "" ->
+- read_password(Prompt, Ssh);
+- Pass -> Pass
+- end
++ Answer when is_list(Answer) ->
++ case trim(Answer) of
++ "" ->
++ read_password(Prompt, Opts);
++ Pwd ->
++ Pwd
++ end
+ end.
+
+-listify(A) when is_atom(A) ->
+- atom_to_list(A);
+-listify(L) when is_list(L) ->
+- L;
+-listify(B) when is_binary(B) ->
+- binary_to_list(B).
+
+ format(Fmt, Args) ->
+ io:format(Fmt, Args).
+
++%%%================================================================
++listify(A) when is_atom(A) -> atom_to_list(A);
++listify(L) when is_list(L) -> L;
++listify(B) when is_binary(B) -> binary_to_list(B).
++
+
+ trim(Line) when is_list(Line) ->
+ lists:reverse(trim1(lists:reverse(trim1(Line))));
+@@ -93,6 +92,3 @@ trim1([$\r|Cs]) -> trim(Cs);
+ trim1([$\n|Cs]) -> trim(Cs);
+ trim1([$\t|Cs]) -> trim(Cs);
+ trim1(Cs) -> Cs.
+-
+-
+-
+--- a/lib/ssh/test/ssh_basic_SUITE.erl
++++ b/lib/ssh/test/ssh_basic_SUITE.erl
+@@ -50,7 +50,12 @@
+ inet6_option/1,
+ inet_option/1,
+ internal_error/1,
+- known_hosts/1,
++ known_hosts/1,
++ login_bad_pwd_no_retry1/1,
++ login_bad_pwd_no_retry2/1,
++ login_bad_pwd_no_retry3/1,
++ login_bad_pwd_no_retry4/1,
++ login_bad_pwd_no_retry5/1,
+ misc_ssh_options/1,
+ openssh_zlib_basic_test/1,
+ packet_size_zero/1,
+@@ -100,7 +105,8 @@ all() ->
+ daemon_opt_fd,
+ multi_daemon_opt_fd,
+ packet_size_zero,
+- ssh_info_print
++ ssh_info_print,
++ {group, login_bad_pwd_no_retry}
+ ].
+
+ groups() ->
+@@ -116,7 +122,13 @@ groups() ->
+ {dsa_pass_key, [], [pass_phrase]},
+ {rsa_pass_key, [], [pass_phrase]},
+ {key_cb, [], [key_callback, key_callback_options]},
+- {internal_error, [], [internal_error]}
++ {internal_error, [], [internal_error]},
++ {login_bad_pwd_no_retry, [], [login_bad_pwd_no_retry1,
++ login_bad_pwd_no_retry2,
++ login_bad_pwd_no_retry3,
++ login_bad_pwd_no_retry4,
++ login_bad_pwd_no_retry5
++ ]}
+ ].
+
+
+@@ -1090,6 +1102,72 @@ ssh_info_print(Config) ->
+
+
+ %%--------------------------------------------------------------------
++%% Check that a basd pwd is not tried more times. Could cause lock-out
++%% on server
++
++login_bad_pwd_no_retry1(Config) ->
++ login_bad_pwd_no_retry(Config, "keyboard-interactive,password").
++
++login_bad_pwd_no_retry2(Config) ->
++ login_bad_pwd_no_retry(Config, "password,keyboard-interactive").
++
++login_bad_pwd_no_retry3(Config) ->
++ login_bad_pwd_no_retry(Config, "password,publickey,keyboard-interactive").
++
++login_bad_pwd_no_retry4(Config) ->
++ login_bad_pwd_no_retry(Config, "password,other,keyboard-interactive").
++
++login_bad_pwd_no_retry5(Config) ->
++ login_bad_pwd_no_retry(Config, "password,other,keyboard-interactive,password,password").
++
++
++
++
++
++login_bad_pwd_no_retry(Config, AuthMethods) ->
++ PrivDir = proplists:get_value(priv_dir, Config),
++ UserDir = filename:join(PrivDir, nopubkey), % to make sure we don't use public-key-auth
++ file:make_dir(UserDir),
++ SysDir = proplists:get_value(data_dir, Config),
++
++ Parent = self(),
++ PwdFun = fun(_, _, _, undefined) -> {false, 1};
++ (_, _, _, _) -> Parent ! retry_bad_pwd,
++ false
++ end,
++
++ {DaemonRef, _Host, Port} =
++ ssh_test_lib:daemon([{system_dir, SysDir},
++ {user_dir, UserDir},
++ {auth_methods, AuthMethods},
++ {user_passwords, [{"foo","somepwd"}]},
++ {pwdfun, PwdFun}
++ ]),
++
++ ConnRes = ssh:connect("localhost", Port,
++ [{silently_accept_hosts, true},
++ {user, "foo"},
++ {password, "badpwd"},
++ {user_dir, UserDir},
++ {user_interaction, false}]),
++
++ receive
++ retry_bad_pwd ->
++ ssh:stop_daemon(DaemonRef),
++ {fail, "Retry bad password"}
++ after 0 ->
++ case ConnRes of
++ {error,"Unable to connect using the available authentication methods"} ->
++ ssh:stop_daemon(DaemonRef),
++ ok;
++ {ok,Conn} ->
++ ssh:close(Conn),
++ ssh:stop_daemon(DaemonRef),
++ {fail, "Connect erroneosly succeded"}
++ end
++ end.
++
++%%--------------------------------------------------------------------
+ %% Internal functions ------------------------------------------------
+ %%--------------------------------------------------------------------
+ %% Due to timing the error message may or may not be delivered to
+--- a/lib/ssh/vsn.mk
++++ b/lib/ssh/vsn.mk
+@@ -1,5 +1,5 @@
+ #-*-makefile-*- ; force emacs to enter makefile-mode
+
+-SSH_VSN = 4.3
++SSH_VSN = 4.3.1
+
+ APP_VSN = "ssh-$(SSH_VSN)"
+--- a/lib/tools/doc/src/notes.xml
++++ b/lib/tools/doc/src/notes.xml
+@@ -31,6 +31,21 @@
+ </header>
+ <p>This document describes the changes made to the Tools application.</p>
+
++<section><title>Tools 2.8.5</title>
++
++ <section><title>Fixed Bugs and Malfunctions</title>
++ <list>
++ <item>
++ <p>Correct a bug when adding multiple modules to an Xref
++ server. The bug was introduced in OTP-19.0. </p>
++ <p>
++ Own Id: OTP-13708 Aux Id: ERL-173 </p>
++ </item>
++ </list>
++ </section>
++
++</section>
++
+ <section><title>Tools 2.8.4</title>
+
+ <section><title>Fixed Bugs and Malfunctions</title>
+--- a/lib/tools/src/xref_base.erl
++++ b/lib/tools/src/xref_base.erl
+@@ -746,7 +746,7 @@ read_a_module({Dir, BaseName}, AppName, Builtins, Verbose, Warnings, Mode) ->
+ message(Warnings, no_debug_info, [File]),
+ no;
+ {ok, M, Data, UnresCalls0} ->
+- message(Verbose, done, [File]),
++ message(Verbose, done_file, [File]),
+ %% Remove duplicates. Identical unresolved calls on the
+ %% same line are counted as _one_ unresolved call.
+ UnresCalls = usort(UnresCalls0),
+@@ -1842,6 +1842,8 @@ message(true, What, Arg) ->
+ set_up ->
+ io:format("Setting up...", Arg);
+ done ->
++ io:format("done~n", Arg);
++ done_file ->
+ io:format("done reading ~ts~n", Arg);
+ error ->
+ io:format("error~n", Arg);
+--- a/lib/tools/test/xref_SUITE.erl
++++ b/lib/tools/test/xref_SUITE.erl
+@@ -50,7 +50,7 @@
+
+ -export([analyze/1, basic/1, md/1, q/1, variables/1, unused_locals/1]).
+
+--export([format_error/1, otp_7423/1, otp_7831/1, otp_10192/1]).
++-export([format_error/1, otp_7423/1, otp_7831/1, otp_10192/1, otp_13708/1]).
+
+ -import(lists, [append/2, flatten/1, keysearch/3, member/2, sort/1, usort/1]).
+
+@@ -82,7 +82,7 @@ groups() ->
+ fun_mfa_r14, fun_mfa_vars, qlc]},
+ {analyses, [],
+ [analyze, basic, md, q, variables, unused_locals]},
+- {misc, [], [format_error, otp_7423, otp_7831, otp_10192]}].
++ {misc, [], [format_error, otp_7423, otp_7831, otp_10192, otp_13708]}].
+
+
+ init_per_suite(Conf) when is_list(Conf) ->
+@@ -2393,6 +2393,19 @@ otp_10192(Conf) when is_list(Conf) ->
+ xref:stop(s),
+ ok.
+
++%% OTP-10192. Allow filenames with character codes greater than 126.
++otp_13708(Conf) when is_list(Conf) ->
++ {ok, _} = start(s),
++ ok = xref:set_default(s, [{verbose, true}]),
++ {ok, []} = xref:q(s,"E"),
++ xref:stop(s),
++
++ CopyDir = ?copydir,
++ Dir = fname(CopyDir,"lib_test"),
++ {ok, _} = start(s),
++ ok = xref:set_library_path(s, [Dir], [{verbose, true}]),
++ xref:stop(s).
++
+ %%%
+ %%% Utilities
+ %%%
+--- a/lib/tools/vsn.mk
++++ b/lib/tools/vsn.mk
+@@ -1 +1 @@
+-TOOLS_VSN = 2.8.4
++TOOLS_VSN = 2.8.5
+--- a/otp_versions.table
++++ b/otp_versions.table
+@@ -1,3 +1,4 @@
++OTP-19.0.1 : dialyzer-3.0.1 erts-8.0.1 inets-6.3.1 observer-2.2.1 ssh-4.3.1 tools-2.8.5 # asn1-4.0.3 common_test-1.12.2 compiler-7.0 cosEvent-2.2.1 cosEventDomain-1.2.1 cosFileTransfer-1.2.1 cosNotification-1.2.2 cosProperty-1.2.1 cosTime-1.2.2 cosTransactions-1.3.2 crypto-3.7 debugger-4.2 diameter-1.12 edoc-0.7.19 eldap-1.2.2 erl_docgen-0.5 erl_interface-3.9 et-1.6 eunit-2.3 gs-1.6.1 hipe-3.15.1 ic-4.4.1 jinterface-1.7 kernel-5.0 megaco-3.18.1 mnesia-4.14 odbc-2.11.2 orber-3.8.2 os_mon-2.4.1 otp_mibs-1.1.1 parsetools-2.1.2 percept-0.9 public_key-1.2 reltool-0.7.1 runtime_tools-1.10 sasl-3.0 snmp-5.2.3 ssl-8.0 stdlib-3.0 syntax_tools-2.0 typer-0.9.11 wx-1.7 xmerl-1.3.11 :
+ OTP-19.0 : asn1-4.0.3 common_test-1.12.2 compiler-7.0 cosEvent-2.2.1 cosEventDomain-1.2.1 cosFileTransfer-1.2.1 cosNotification-1.2.2 cosProperty-1.2.1 cosTime-1.2.2 cosTransactions-1.3.2 crypto-3.7 debugger-4.2 dialyzer-3.0 diameter-1.12 edoc-0.7.19 eldap-1.2.2 erl_docgen-0.5 erl_interface-3.9 erts-8.0 et-1.6 eunit-2.3 gs-1.6.1 hipe-3.15.1 ic-4.4.1 inets-6.3 jinterface-1.7 kernel-5.0 megaco-3.18.1 mnesia-4.14 observer-2.2 odbc-2.11.2 orber-3.8.2 os_mon-2.4.1 otp_mibs-1.1.1 parsetools-2.1.2 percept-0.9 public_key-1.2 reltool-0.7.1 runtime_tools-1.10 sasl-3.0 snmp-5.2.3 ssh-4.3 ssl-8.0 stdlib-3.0 syntax_tools-2.0 tools-2.8.4 typer-0.9.11 wx-1.7 xmerl-1.3.11 # :
+ OTP-18.3.4 : inets-6.2.4 ssl-7.3.3 # asn1-4.0.2 common_test-1.12.1 compiler-6.0.3 cosEvent-2.2 cosEventDomain-1.2 cosFileTransfer-1.2 cosNotification-1.2.1 cosProperty-1.2 cosTime-1.2.1 cosTransactions-1.3.1 crypto-3.6.3 debugger-4.1.2 dialyzer-2.9 diameter-1.11.2 edoc-0.7.18 eldap-1.2.1 erl_docgen-0.4.2 erl_interface-3.8.2 erts-7.3.1 et-1.5.1 eunit-2.2.13 gs-1.6 hipe-3.15 ic-4.4 jinterface-1.6.1 kernel-4.2 megaco-3.18 mnesia-4.13.4 observer-2.1.2 odbc-2.11.1 orber-3.8.1 os_mon-2.4 ose-1.1 otp_mibs-1.1 parsetools-2.1.1 percept-0.8.11 public_key-1.1.1 reltool-0.7 runtime_tools-1.9.3 sasl-2.7 snmp-5.2.2 ssh-4.2.2 stdlib-2.8 syntax_tools-1.7 test_server-3.10 tools-2.8.3 typer-0.9.10 webtool-0.9.1 wx-1.6.1 xmerl-1.3.10 :
+ OTP-18.3.3 : common_test-1.12.1 inets-6.2.3 ssl-7.3.2 # asn1-4.0.2 compiler-6.0.3 cosEvent-2.2 cosEventDomain-1.2 cosFileTransfer-1.2 cosNotification-1.2.1 cosProperty-1.2 cosTime-1.2.1 cosTransactions-1.3.1 crypto-3.6.3 debugger-4.1.2 dialyzer-2.9 diameter-1.11.2 edoc-0.7.18 eldap-1.2.1 erl_docgen-0.4.2 erl_interface-3.8.2 erts-7.3.1 et-1.5.1 eunit-2.2.13 gs-1.6 hipe-3.15 ic-4.4 jinterface-1.6.1 kernel-4.2 megaco-3.18 mnesia-4.13.4 observer-2.1.2 odbc-2.11.1 orber-3.8.1 os_mon-2.4 ose-1.1 otp_mibs-1.1 parsetools-2.1.1 percept-0.8.11 public_key-1.1.1 reltool-0.7 runtime_tools-1.9.3 sasl-2.7 snmp-5.2.2 ssh-4.2.2 stdlib-2.8 syntax_tools-1.7 test_server-3.10 tools-2.8.3 typer-0.9.10 webtool-0.9.1 wx-1.6.1 xmerl-1.3.10 :