File 2261-ssh-Initial-commit-of-option-handling-changes.patch of Package erlang

From 89a829f32d855610b0bc0c3ea53e7c05454b7a24 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Thu, 16 Feb 2017 14:48:04 +0100
Subject: [PATCH 1/4] ssh: Initial commit of option handling changes

---
 lib/ssh/src/Makefile                   |   1 +
 lib/ssh/src/ssh.app.src                |   1 +
 lib/ssh/src/ssh.erl                    | 817 ++++++------------------------
 lib/ssh/src/ssh.hrl                    |  27 +-
 lib/ssh/src/ssh_acceptor.erl           | 117 +++--
 lib/ssh/src/ssh_acceptor_sup.erl       |  28 +-
 lib/ssh/src/ssh_auth.erl               |  79 ++-
 lib/ssh/src/ssh_cli.erl                |  12 +-
 lib/ssh/src/ssh_connection.erl         |  38 +-
 lib/ssh/src/ssh_connection_handler.erl | 124 +++--
 lib/ssh/src/ssh_file.erl               |   4 +-
 lib/ssh/src/ssh_io.erl                 |  16 +-
 lib/ssh/src/ssh_options.erl            | 897 +++++++++++++++++++++++++++++++++
 lib/ssh/src/ssh_sftp.erl               |  43 +-
 lib/ssh/src/ssh_subsystem_sup.erl      |  36 +-
 lib/ssh/src/ssh_system_sup.erl         |  34 +-
 lib/ssh/src/ssh_transport.erl          |  72 +--
 lib/ssh/src/sshd_sup.erl               |  22 +-
 lib/ssh/test/ssh_trpt_test_lib.erl     |  30 +-
 19 files changed, 1385 insertions(+), 1013 deletions(-)
 create mode 100644 lib/ssh/src/ssh_options.erl

diff --git a/lib/ssh/src/Makefile b/lib/ssh/src/Makefile
index 7ab6f2242..f826fdfd9 100644
--- a/lib/ssh/src/Makefile
+++ b/lib/ssh/src/Makefile
@@ -51,6 +51,7 @@ MODULES= \
 	ssh_sup \
 	sshc_sup \
 	sshd_sup \
+	ssh_options \
 	ssh_connection_sup \
 	ssh_connection \
 	ssh_connection_handler \
diff --git a/lib/ssh/src/ssh.app.src b/lib/ssh/src/ssh.app.src
index 2bb7491b0..95d268609 100644
--- a/lib/ssh/src/ssh.app.src
+++ b/lib/ssh/src/ssh.app.src
@@ -7,6 +7,7 @@
 	     ssh_app,
 	     ssh_acceptor,
 	     ssh_acceptor_sup,
+             ssh_options,
 	     ssh_auth,
 	     ssh_message,
 	     ssh_bits,
diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl
index 68d98d387..0186ac792 100644
--- a/lib/ssh/src/ssh.erl
+++ b/lib/ssh/src/ssh.erl
@@ -41,7 +41,8 @@
 
 %%% Type exports
 -export_type([connection_ref/0,
-	      channel_id/0
+	      channel_id/0,
+              role/0
 	     ]).
 
 %%--------------------------------------------------------------------
@@ -71,55 +72,63 @@ stop() ->
     application:stop(ssh).
 
 %%--------------------------------------------------------------------
--spec connect(port(), proplists:proplist()) -> {ok, pid()} |  {error, term()}.
+-spec connect(inet:socket(), proplists:proplist()) -> ok_error(connection_ref()).
 
--spec connect(port(),   proplists:proplist(), timeout()) -> {ok, pid()} |  {error, term()}
-           ; (string(), integer(), proplists:proplist()) -> {ok, pid()} |  {error, term()}.
+-spec connect(inet:socket(), proplists:proplist(), timeout()) -> ok_error(connection_ref())
+           ; (string(), inet:port_number(), proplists:proplist()) -> ok_error(connection_ref()).
+
+-spec connect(string(), inet:port_number(), proplists:proplist(), timeout()) -> ok_error(connection_ref()).
 
--spec connect(string(), integer(), proplists:proplist(), timeout()) -> {ok, pid()} |  {error, term()}.
 %%
 %% Description: Starts an ssh connection.
 %%--------------------------------------------------------------------
-connect(Socket, Options) ->
-    connect(Socket, Options, infinity).
+connect(Socket, UserOptions) when is_port(Socket),
+                                  is_list(UserOptions) ->
+    connect(Socket, UserOptions, infinity).
 
-connect(Socket, Options, Timeout) when is_port(Socket) ->
-    case handle_options(Options) of
+connect(Socket, UserOptions, Timeout) when is_port(Socket),
+                                           is_list(UserOptions) ->
+    case ssh_options:handle_options(client, UserOptions) of
 	{error, Error} ->
 	    {error, Error};
-	{_SocketOptions, SshOptions} ->
-	    case valid_socket_to_use(Socket, Options) of
+	Options ->
+            case valid_socket_to_use(Socket, ?GET_OPT(transport,Options)) of
 		ok ->
 		    {ok, {Host,_Port}} = inet:sockname(Socket),
-		    Opts =  [{user_pid,self()}, {host,fmt_host(Host)} | SshOptions],
+		    Opts = ?PUT_INTERNAL_OPT([{user_pid,self()}, {host,fmt_host(Host)}], Options),
 		    ssh_connection_handler:start_connection(client, Socket, Opts, Timeout);
 		{error,SockError} ->
 		    {error,SockError}
 	    end
     end;
 
-connect(Host, Port, Options) when is_integer(Port), Port>0 ->
-    connect(Host, Port, Options, infinity).
+connect(Host, Port, UserOptions) when is_integer(Port),
+                                      Port>0,
+                                      is_list(UserOptions) ->
+    connect(Host, Port, UserOptions, infinity).
 
-connect(Host, Port, Options, Timeout) ->
-    case handle_options(Options) of
+connect(Host, Port, UserOptions, Timeout) when is_integer(Port),
+                                               Port>0,
+                                               is_list(UserOptions) ->
+    case ssh_options:handle_options(client, UserOptions) of
 	{error, _Reason} = Error ->
 	    Error;
-	{SocketOptions, SshOptions} ->
-	    {_, Transport, _} = TransportOpts =
-		proplists:get_value(transport, Options, {tcp, gen_tcp, tcp_closed}),
-	    ConnectionTimeout = proplists:get_value(connect_timeout, Options, infinity),
-	    try Transport:connect(Host, Port,  [ {active, false} | SocketOptions], ConnectionTimeout) of
+        Options ->
+	    {_, Transport, _} = TransportOpts = ?GET_OPT(transport, Options),
+	    ConnectionTimeout = ?GET_OPT(connect_timeout, Options),
+            SocketOpts = [{active,false} | ?GET_OPT(socket_options,Options)],
+	    try Transport:connect(Host, Port, SocketOpts, ConnectionTimeout) of
 		{ok, Socket} ->
-		    Opts =  [{user_pid,self()}, {host,Host} | SshOptions],
+		    Opts = ?PUT_INTERNAL_OPT([{user_pid,self()}, {host,Host}], Options),
 		    ssh_connection_handler:start_connection(client, Socket, Opts, Timeout);
 		{error, Reason} ->
 		    {error, Reason}
 	    catch
-		exit:{function_clause, _} ->
+		exit:{function_clause, _F} ->
+                    io:format('function_clause ~p~n',[_F]),
 		    {error, {options, {transport, TransportOpts}}};
 		exit:badarg ->
-		    {error, {options, {socket_options, SocketOptions}}}
+		    {error, {options, {socket_options, SocketOpts}}}
 	    end
     end.
 
@@ -148,9 +157,11 @@ channel_info(ConnectionRef, ChannelId, Options) ->
     ssh_connection_handler:channel_info(ConnectionRef, ChannelId, Options).
 
 %%--------------------------------------------------------------------
--spec daemon(integer()) -> {ok, pid()} | {error, term()}.
--spec daemon(integer()|port(), proplists:proplist()) -> {ok, pid()} | {error, term()}.
--spec daemon(any | inet:ip_address(), integer(), proplists:proplist()) -> {ok, pid()} | {error, term()}.
+-spec daemon(inet:port_number()) ->  ok_error(pid()).
+-spec daemon(inet:port_number()|inet:socket(), proplists:proplist()) -> ok_error(pid()).
+-spec daemon(any | inet:ip_address(), inet:port_number(), proplists:proplist()) -> ok_error(pid())
+           ;(socket, inet:socket(), proplists:proplist()) -> ok_error(pid())
+            .
 
 %% Description: Starts a server listening for SSH connections
 %% on the given port.
@@ -158,19 +169,21 @@ channel_info(ConnectionRef, ChannelId, Options) ->
 daemon(Port) ->
     daemon(Port, []).
 
-daemon(Port, Options) when is_integer(Port) ->
-    daemon(any, Port, Options);
 
-daemon(Socket, Options0) when is_port(Socket) ->
-    Options = daemon_shell_opt(Options0),
-    start_daemon(Socket, Options).
+daemon(Port, UserOptions) when is_integer(Port), Port >= 0 ->
+    daemon(any, Port, UserOptions);
+
+daemon(Socket, UserOptions) when is_port(Socket) ->
+    daemon(socket, Socket, UserOptions).
+
 
-daemon(HostAddr, Port, Options0) ->
-    Options1 = daemon_shell_opt(Options0),
-    {Host, Inet, Options} = daemon_host_inet_opt(HostAddr, Options1),
-    start_daemon(Host, Port, Options, Inet).
+daemon(Host0, Port, UserOptions0) ->
+    {Host, UserOptions} = handle_daemon_args(Host0, UserOptions0),
+    start_daemon(Host, Port, ssh_options:handle_options(server, UserOptions)).
 
 %%--------------------------------------------------------------------
+-spec daemon_info(pid()) -> ok_error( [{atom(), term()}] ).
+
 daemon_info(Pid) ->
     case catch ssh_system_sup:acceptor_supervisor(Pid) of
 	AsupPid when is_pid(AsupPid) ->
@@ -185,7 +198,7 @@ daemon_info(Pid) ->
 
 %%--------------------------------------------------------------------
 -spec stop_listener(pid()) -> ok.
--spec stop_listener(inet:ip_address(), integer()) -> ok.
+-spec stop_listener(inet:ip_address(), inet:port_number()) -> ok.
 %%
 %% Description: Stops the listener, but leaves
 %% existing connections started by the listener up and running.
@@ -199,7 +212,8 @@ stop_listener(Address, Port, Profile) ->
 
 %%--------------------------------------------------------------------
 -spec stop_daemon(pid()) -> ok.
--spec stop_daemon(inet:ip_address(), integer()) -> ok.
+-spec stop_daemon(inet:ip_address(), inet:port_number()) -> ok.
+-spec stop_daemon(inet:ip_address(), inet:port_number(), atom()) -> ok.
 %%
 %% Description: Stops the listener and all connections started by
 %% the listener.
@@ -210,10 +224,11 @@ stop_daemon(Address, Port) ->
     ssh_system_sup:stop_system(Address, Port, ?DEFAULT_PROFILE).
 stop_daemon(Address, Port, Profile) ->
     ssh_system_sup:stop_system(Address, Port, Profile).
+
 %%--------------------------------------------------------------------
--spec shell(port() | string()) ->  _.
--spec shell(port() | string(), proplists:proplist()) ->  _.
--spec shell(string(), integer(), proplists:proplist()) ->  _.
+-spec shell(inet:socket() | string()) ->  _.
+-spec shell(inet:socket() | string(), proplists:proplist()) ->  _.
+-spec shell(string(), inet:port_number(), proplists:proplist()) ->  _.
 
 %%   Host = string()
 %%   Port = integer()
@@ -261,112 +276,96 @@ default_algorithms() ->
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
-valid_socket_to_use(Socket, Options) ->
-    case proplists:get_value(transport, Options, {tcp, gen_tcp, tcp_closed}) of
-	{tcp,_,_} ->
-	    %% Is this tcp-socket a valid socket?
-	    case {is_tcp_socket(Socket),
-		  {ok,[{active,false}]} == inet:getopts(Socket, [active])
-		 }
-	    of
-		{true, true} ->
-		    ok;
-		{true, false} ->
-		    {error, not_passive_mode};
-		_ ->
-		    {error, not_tcp_socket}
-	    end;
-	{L4,_,_} ->
-	    {error, {unsupported,L4}}
+handle_daemon_args(Host, UserOptions0) ->
+    case Host of
+        socket ->
+            {Host, UserOptions0};
+        any ->
+            {ok, Host0} = inet:gethostname(),
+            Inet = proplists:get_value(inet, UserOptions0, inet),
+            {Host0, [Inet | UserOptions0]};
+        {_,_,_,_} ->
+            {Host, [inet, {ip,Host} | UserOptions0]};
+        {_,_,_,_,_,_,_,_} ->
+            {Host, [inet6, {ip,Host} | UserOptions0]};
+        _ ->
+            error(badarg)
     end.
 
+%%%----------------------------------------------------------------
+valid_socket_to_use(Socket, {tcp,_,_}) ->
+    %% Is this tcp-socket a valid socket?
+    case {is_tcp_socket(Socket),
+          {ok,[{active,false}]} == inet:getopts(Socket, [active])
+         }
+    of
+        {true, true} ->
+            ok;
+        {true, false} ->
+            {error, not_passive_mode};
+        _ ->
+            {error, not_tcp_socket}
+    end;
+
+valid_socket_to_use(_, {L4,_,_}) ->
+    {error, {unsupported,L4}}.
+
+
 is_tcp_socket(Socket) ->
     case inet:getopts(Socket, [delay_send]) of
         {ok,[_]} -> true;
         _ -> false
     end.
 
-daemon_shell_opt(Options) ->
-     case proplists:get_value(shell, Options) of
-	 undefined ->
-	     [{shell, ?DEFAULT_SHELL}  | Options];
-	 _ ->
-	     Options
-     end.
-
-daemon_host_inet_opt(HostAddr, Options1) ->
-    case HostAddr of
-	any ->
-	    {ok, Host0} = inet:gethostname(),
-	    {Host0,  proplists:get_value(inet, Options1, inet), Options1};
-	{_,_,_,_} ->
-	    {HostAddr, inet,
-	     [{ip, HostAddr} | Options1]};
-	{_,_,_,_,_,_,_,_} ->
-	    {HostAddr, inet6,
-	     [{ip, HostAddr} | Options1]}
-    end.
-
+%%%----------------------------------------------------------------
+start_daemon(_, _, {error,Error}) ->
+    {error,Error};
+
+start_daemon(socket, Socket, Options) ->
+    case valid_socket_to_use(Socket, ?GET_OPT(transport,Options)) of
+        ok ->
+            try
+                do_start_daemon(Socket, Options)
+            catch
+                throw:bad_fd -> {error,bad_fd};
+                throw:bad_socket -> {error,bad_socket};
+                _C:_E -> {error,{cannot_start_daemon,_C,_E}}
+            end;
+        {error,SockError} ->
+            {error,SockError}
+    end;
 
-start_daemon(Socket, Options) ->
-    case handle_options(Options) of
-	{error, Error} ->
-	    {error, Error};
-	{SocketOptions, SshOptions} ->
-	    case valid_socket_to_use(Socket, Options) of
-		ok ->
-		    try
-			do_start_daemon(Socket, [{role,server}|SshOptions], SocketOptions)
-		    catch
-			throw:bad_fd -> {error,bad_fd};
-			throw:bad_socket -> {error,bad_socket};
-			_C:_E -> {error,{cannot_start_daemon,_C,_E}}
-		    end;
-		{error,SockError} ->
-		    {error,SockError}
-	    end
+start_daemon(Host, Port, Options) ->
+    try
+        do_start_daemon(Host, Port, Options)
+    catch
+        throw:bad_fd -> {error,bad_fd};
+        throw:bad_socket -> {error,bad_socket};
+        _C:_E -> {error,{cannot_start_daemon,_C,_E}}
     end.
 
-start_daemon(Host, Port, Options, Inet) ->
-    case handle_options(Options) of
-	{error, _Reason} = Error ->
-	    Error;
-	{SocketOptions, SshOptions}->
-	    try
-		do_start_daemon(Host, Port, [{role,server}|SshOptions] , [Inet|SocketOptions])
-	    catch
-		throw:bad_fd -> {error,bad_fd};
-		throw:bad_socket -> {error,bad_socket};
-		_C:_E -> {error,{cannot_start_daemon,_C,_E}}
-	    end
-    end.
 
-do_start_daemon(Socket, SshOptions, SocketOptions) ->
+do_start_daemon(Socket, Options) ->
     {ok, {IP,Port}} =
 	try {ok,_} = inet:sockname(Socket)
 	catch
 	    _:_ -> throw(bad_socket)
 	end,
     Host = fmt_host(IP),
-    Profile = proplists:get_value(profile, SshOptions, ?DEFAULT_PROFILE),
-    Opts = [{asocket, Socket},
-	    {asock_owner,self()},
-	    {address, Host},
-	    {port, Port},
-	    {role, server},
-	    {socket_opts, SocketOptions},
-	    {ssh_opts, SshOptions}],
-    {_, Callback, _} = proplists:get_value(transport, SshOptions, {tcp, gen_tcp, tcp_closed}),
+    Opts = ?PUT_INTERNAL_OPT([{asocket, Socket},
+                              {asock_owner,self()},
+                              {address, Host},
+                              {port, Port},
+                              {role, server}], Options),
+    
+    Profile = ?GET_OPT(profile, Options),
     case ssh_system_sup:system_supervisor(Host, Port, Profile) of
 	undefined ->
-	    %% It would proably make more sense to call the
-	    %% address option host but that is a too big change at the
-	    %% monent. The name is a legacy name!
 	    try sshd_sup:start_child(Opts) of
 		{error, {already_started, _}} ->
 		    {error, eaddrinuse};
 		Result = {ok,_} ->
-		    call_ssh_acceptor_handle_connection(Callback, Host, Port, Opts, Socket, Result);
+		    call_ssh_acceptor_handle_connection(Host, Port, Opts, Socket, Result);
 		Result = {error, _} ->
 		    Result
 	    catch
@@ -379,56 +378,47 @@ do_start_daemon(Socket, SshOptions, SocketOptions) ->
 		{error, {already_started, _}} ->
 		    {error, eaddrinuse};
 		{ok, _} ->
-		    call_ssh_acceptor_handle_connection(Callback, Host, Port, Opts, Socket, {ok, Sup});
+		    call_ssh_acceptor_handle_connection(Host, Port, Opts, Socket, {ok,Sup});
 		Other ->
 		    Other
 	    end
     end.
 
-do_start_daemon(Host0, Port0, SshOptions, SocketOptions) ->
+do_start_daemon(Host0, Port0, Options0) ->
     {Host,Port1} =
 	try
-	    case proplists:get_value(fd, SocketOptions) of
+	    case ?GET_SOCKET_OPT(fd, Options0) of
 		undefined ->
 		    {Host0,Port0};
 		Fd when Port0==0 ->
-		    find_hostport(Fd);
-		_ ->
-		    {Host0,Port0}
+		    find_hostport(Fd)
 	    end
 	catch
 	    _:_ -> throw(bad_fd)
 	end,
-    Profile = proplists:get_value(profile, SshOptions, ?DEFAULT_PROFILE),
-    {Port, WaitRequestControl, Opts0} =
+    {Port, WaitRequestControl, Options1} =
 	case Port1 of
 	    0 -> %% Allocate the socket here to get the port number...
-		{_, Callback, _} =
-		    proplists:get_value(transport, SshOptions, {tcp, gen_tcp, tcp_closed}),
-		{ok,LSock} = ssh_acceptor:callback_listen(Callback, 0, SocketOptions),
+		{ok,LSock} = ssh_acceptor:callback_listen(0, Options0),
 		{ok,{_,LPort}} = inet:sockname(LSock),
 		{LPort,
-		 {LSock,Callback},
-		 [{lsocket,LSock},{lsock_owner,self()}]
+		 LSock,
+		 ?PUT_INTERNAL_OPT({lsocket,{LSock,self()}}, Options0)
 		};
 	    _ ->
-		{Port1, false, []}
+		{Port1, false, Options0}
 	end,
-    Opts = [{address, Host},
-	    {port, Port},
-	    {role, server},
-	    {socket_opts, SocketOptions},
-	    {ssh_opts, SshOptions} | Opts0],
+    Options = ?PUT_INTERNAL_OPT([{address, Host},
+                                 {port, Port},
+                                 {role, server}], Options1),
+    Profile = ?GET_OPT(profile, Options0),
     case ssh_system_sup:system_supervisor(Host, Port, Profile) of
 	undefined ->
-	    %% It would proably make more sense to call the
-	    %% address option host but that is a too big change at the
-	    %% monent. The name is a legacy name!
-	    try sshd_sup:start_child(Opts) of
+	    try sshd_sup:start_child(Options) of
 		{error, {already_started, _}} ->
 		    {error, eaddrinuse};
 		Result = {ok,_} ->
-		    sync_request_control(WaitRequestControl),
+		    sync_request_control(WaitRequestControl, Options),
 		    Result;
 		Result = {error, _} ->
 		    Result
@@ -436,21 +426,22 @@ do_start_daemon(Host0, Port0, SshOptions, SocketOptions) ->
 		exit:{noproc, _} ->
 		    {error, ssh_not_started}
 	    end;
-	Sup  ->
+	Sup ->
 	    AccPid = ssh_system_sup:acceptor_supervisor(Sup),
-	    case ssh_acceptor_sup:start_child(AccPid, Opts) of
+	    case ssh_acceptor_sup:start_child(AccPid, Options) of
 		{error, {already_started, _}} ->
 		    {error, eaddrinuse};
 		{ok, _} ->
-		    sync_request_control(WaitRequestControl),
+		    sync_request_control(WaitRequestControl, Options),
 		    {ok, Sup};
 		Other ->
 		    Other
 	    end
     end.
 
-call_ssh_acceptor_handle_connection(Callback, Host, Port, Opts, Socket, DefaultResult) ->
-    try ssh_acceptor:handle_connection(Callback, Host, Port, Opts, Socket)
+call_ssh_acceptor_handle_connection(Host, Port, Options, Socket, DefaultResult) ->
+    {_, Callback, _} = ?GET_OPT(transport, Options),
+    try ssh_acceptor:handle_connection(Callback, Host, Port, Options, Socket)
     of
         {error,Error} -> {error,Error};
         _ -> DefaultResult
@@ -459,9 +450,10 @@ call_ssh_acceptor_handle_connection(Callback, Host, Port, Opts, Socket, DefaultR
     end.
              
 
-sync_request_control(false) ->
+sync_request_control(false, _Options) ->
     ok;
-sync_request_control({LSock,Callback}) ->
+sync_request_control(LSock, Options) ->
+    {_, Callback, _} = ?GET_OPT(transport, Options),
     receive
 	{request_control,LSock,ReqPid} ->
 	    ok = Callback:controlling_process(LSock, ReqPid),
@@ -477,523 +469,6 @@ find_hostport(Fd) ->
     ok = inet:close(S),
     HostPort.
 
-
-handle_options(Opts) ->
-    try handle_option(algs_compatibility(proplists:unfold(Opts)), [], []) of
-	{Inet, Ssh} ->
-	    {handle_ip(Inet), Ssh}
-    catch
-	throw:Error ->
-	    Error
-    end.
-
-
-algs_compatibility(Os0) ->
-    %% Take care of old options 'public_key_alg' and 'pref_public_key_algs'
-    case proplists:get_value(public_key_alg, Os0) of
-	undefined ->
-	    Os0;
-	A when is_atom(A) ->
-	    %% Skip public_key_alg if pref_public_key_algs is defined:
-	    Os = lists:keydelete(public_key_alg, 1, Os0),
-	    case proplists:get_value(pref_public_key_algs,Os) of
-		undefined when A == 'ssh-rsa' ; A==ssh_rsa ->
-		    [{pref_public_key_algs,['ssh-rsa','ssh-dss']} | Os];
-		undefined when A == 'ssh-dss' ; A==ssh_dsa ->
-		    [{pref_public_key_algs,['ssh-dss','ssh-rsa']} | Os];
-		undefined ->
-		    throw({error, {eoptions, {public_key_alg,A} }});
-		_ ->
-		    Os
-	    end;
-	V ->
-	    throw({error, {eoptions, {public_key_alg,V} }})
-    end.
-
-
-handle_option([], SocketOptions, SshOptions) ->
-    {SocketOptions, SshOptions};
-handle_option([{system_dir, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{user_dir, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{user_dir_fun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{silently_accept_hosts, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{user_interaction, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{connect_timeout, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{user, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{dsa_pass_phrase, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{rsa_pass_phrase, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{password, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{user_passwords, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{pwdfun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{key_cb, {Module, Options}} | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option({key_cb, Module}),
-                                        handle_ssh_priv_option({key_cb_private, Options}) |
-                                        SshOptions]);
-handle_option([{key_cb, Module} | Rest], SocketOptions, SshOptions) ->
-    handle_option([{key_cb, {Module, []}} | Rest], SocketOptions, SshOptions);
-handle_option([{keyboard_interact_fun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-%%Backwards compatibility
-handle_option([{allow_user_interaction, Value}  | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option({user_interaction, Value}) | SshOptions]);
-handle_option([{infofun, _} = Opt | Rest],SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{connectfun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{disconnectfun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{unexpectedfun, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{failfun, _} = Opt | Rest],  SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{ssh_msg_debug_fun, _} = Opt | Rest],  SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-%%Backwards compatibility should not be underscore between ip and v6 in API
-handle_option([{ip_v6_disabled, Value} | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option({ipv6_disabled, Value}) | SshOptions]);
-handle_option([{ipv6_disabled, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{transport, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{subsystems, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{ssh_cli, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{shell, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{exec, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{auth_methods, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{auth_method_kb_interactive_data, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{pref_public_key_algs, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{preferred_algorithms,_} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{dh_gex_groups,_} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{dh_gex_limits,_} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{quiet_mode, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{idle_time, _} = Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{rekey_limit, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{max_sessions, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{max_channels, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{negotiation_timeout, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{parallel_login, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-%% (Is handled by proplists:unfold above:)
-%% handle_option([parallel_login|Rest], SocketOptions, SshOptions) ->
-%%     handle_option(Rest, SocketOptions, [handle_ssh_option({parallel_login,true}) | SshOptions]);
-handle_option([{minimal_remote_max_packet_size, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{id_string, _ID} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{profile, _ID} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{max_random_length_padding, _Bool} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([{tstflg, _} = Opt|Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
-handle_option([Opt | Rest], SocketOptions, SshOptions) ->
-    handle_option(Rest, [handle_inet_option(Opt) | SocketOptions], SshOptions).
-
-
-handle_ssh_option({tstflg,_F} = Opt) -> Opt;
-handle_ssh_option({minimal_remote_max_packet_size, Value} = Opt) when is_integer(Value), Value >=0 ->
-    Opt;
-handle_ssh_option({system_dir, Value} = Opt) when is_list(Value) ->
-    check_dir(Opt);
-handle_ssh_option({user_dir, Value} = Opt) when is_list(Value) ->
-    check_dir(Opt);
-handle_ssh_option({user_dir_fun, Value} = Opt) when is_function(Value) ->
-    Opt;
-handle_ssh_option({silently_accept_hosts, Value} = Opt) when is_boolean(Value) ->
-    Opt;
-handle_ssh_option({silently_accept_hosts, Value} = Opt) when is_function(Value,2) ->
-    Opt;
-handle_ssh_option({silently_accept_hosts, {DigestAlg,Value}} = Opt) when is_function(Value,2) ->
-    Algs = if is_atom(DigestAlg) -> [DigestAlg];
-              is_list(DigestAlg) -> DigestAlg;
-              true -> throw({error, {eoptions, Opt}})
-           end,
-    case [A || A <- Algs,
-               not lists:member(A, [md5, sha, sha224, sha256, sha384, sha512])] of
-        [_|_] = UnSup1 ->
-            throw({error, {{eoptions, Opt}, {not_fingerprint_algos,UnSup1}}});
-        [] ->
-            CryptoHashAlgs = proplists:get_value(hashs, crypto:supports(), []),
-            case [A || A <- Algs,
-                       not lists:member(A, CryptoHashAlgs)] of
-                [_|_] = UnSup2 ->
-                    throw({error, {{eoptions, Opt}, {unsupported_algo,UnSup2}}});
-                [] -> Opt
-            end
-    end;
-handle_ssh_option({user_interaction, Value} = Opt) when is_boolean(Value) ->
-    Opt;
-handle_ssh_option({preferred_algorithms,[_|_]} = Opt) ->
-    handle_pref_algs(Opt);
-
-handle_ssh_option({dh_gex_groups,L0}) when is_list(L0) ->
-    {dh_gex_groups,
-     collect_per_size(
-       lists:foldl(
-	 fun({N,G,P}, Acc) when is_integer(N),N>0,
-				is_integer(G),G>0,
-				is_integer(P),P>0 ->
-		 [{N,{G,P}} | Acc];
-	    ({N,{G,P}}, Acc) when is_integer(N),N>0,
-				  is_integer(G),G>0,
-				  is_integer(P),P>0 ->
-		 [{N,{G,P}} | Acc];
-	    ({N,GPs}, Acc) when is_list(GPs) ->
-		 lists:foldr(fun({Gi,Pi}, Acci) when is_integer(Gi),Gi>0,
-						     is_integer(Pi),Pi>0 ->
-				     [{N,{Gi,Pi}} | Acci]
-			     end, Acc, GPs)
-	 end, [], L0))};
-
-handle_ssh_option({dh_gex_groups,{Tag,File=[C|_]}}=Opt) when is_integer(C), C>0,
-							      Tag == file ;
-							      Tag == ssh_moduli_file ->
-    {ok,GroupDefs} =
-	case Tag of
-	    file ->
-		file:consult(File);
-	    ssh_moduli_file ->
-		case file:open(File,[read]) of
-		    {ok,D} ->
-			try
-			    {ok,Moduli} = read_moduli_file(D, 1, []),
-			    file:close(D),
-			    {ok, Moduli}
-			catch
-			    _:_ ->
-				throw({error, {{eoptions, Opt}, "Bad format in file "++File}})
-			end;
-		    {error,enoent} ->
-			throw({error, {{eoptions, Opt}, "File not found:"++File}});
-		    {error,Error} ->
-			throw({error, {{eoptions, Opt}, io_lib:format("Error reading file ~s: ~p",[File,Error])}})
-		end
-	end,
-
-    try
-	handle_ssh_option({dh_gex_groups,GroupDefs})
-    catch
-	_:_ ->
-	    throw({error, {{eoptions, Opt}, "Bad format in file: "++File}})
-    end;
-
-
-handle_ssh_option({dh_gex_limits,{Min,Max}} = Opt) when is_integer(Min), Min>0,
-							is_integer(Max), Max>=Min ->
-    %% Server
-    Opt;
-handle_ssh_option({dh_gex_limits,{Min,I,Max}} = Opt) when is_integer(Min), Min>0,
-							  is_integer(I),   I>=Min,
-							  is_integer(Max), Max>=I ->
-    %% Client
-    Opt;
-handle_ssh_option({pref_public_key_algs, Value} = Opt) when is_list(Value), length(Value) >= 1 ->
-    case handle_user_pref_pubkey_algs(Value, []) of
-	{true, NewOpts} ->
-	    {pref_public_key_algs, NewOpts};
-	_ ->
-	    throw({error, {eoptions, Opt}})
-    end;
-handle_ssh_option({connect_timeout, Value} = Opt) when is_integer(Value); Value == infinity ->
-    Opt;
-handle_ssh_option({max_sessions, Value} = Opt) when is_integer(Value), Value>0 ->
-    Opt;
-handle_ssh_option({max_channels, Value} = Opt) when is_integer(Value), Value>0 ->
-    Opt;
-handle_ssh_option({negotiation_timeout, Value} = Opt) when is_integer(Value); Value == infinity ->
-    Opt;
-handle_ssh_option({parallel_login, Value} = Opt) when Value==true ; Value==false ->
-    Opt;
-handle_ssh_option({user, Value} = Opt) when is_list(Value) ->
-    Opt;
-handle_ssh_option({dsa_pass_phrase, Value} = Opt) when is_list(Value) ->
-    Opt;
-handle_ssh_option({rsa_pass_phrase, Value} = Opt) when is_list(Value) ->
-    Opt;
-handle_ssh_option({password, Value} = Opt) when is_list(Value) ->
-    Opt;
-handle_ssh_option({user_passwords, Value} = Opt) when is_list(Value)->
-    Opt;
-handle_ssh_option({pwdfun, Value} = Opt) when is_function(Value,2) ->
-    Opt;
-handle_ssh_option({pwdfun, Value} = Opt) when is_function(Value,4) ->
-    Opt;
-handle_ssh_option({key_cb, Value} = Opt)  when is_atom(Value) ->
-    Opt;
-handle_ssh_option({key_cb, {CallbackMod, CallbackOptions}} = Opt) when is_atom(CallbackMod),
-                                                                      is_list(CallbackOptions) ->
-    Opt;
-handle_ssh_option({keyboard_interact_fun, Value} = Opt) when is_function(Value,3) ->
-    Opt;
-handle_ssh_option({compression, Value} = Opt) when is_atom(Value) ->
-    Opt;
-handle_ssh_option({exec, {Module, Function, _}} = Opt) when is_atom(Module),
-							    is_atom(Function) ->
-    Opt;
-handle_ssh_option({exec, Function} = Opt) when is_function(Function) ->
-    Opt;
-handle_ssh_option({auth_methods, Value} = Opt)  when is_list(Value) ->
-    Opt;
-handle_ssh_option({auth_method_kb_interactive_data, {Name,Instruction,Prompt,Echo}} = Opt) when is_list(Name),
-												is_list(Instruction),
-												is_list(Prompt),
-												is_boolean(Echo) ->
-    Opt;
-handle_ssh_option({auth_method_kb_interactive_data, F} = Opt) when is_function(F,3) ->
-    Opt;
-handle_ssh_option({infofun, Value} = Opt)  when is_function(Value) ->
-    Opt;
-handle_ssh_option({connectfun, Value} = Opt) when is_function(Value) ->
-    Opt;
-handle_ssh_option({disconnectfun, Value} = Opt) when is_function(Value) ->
-    Opt;
-handle_ssh_option({unexpectedfun, Value} = Opt) when is_function(Value,2) ->
-    Opt;
-handle_ssh_option({failfun, Value} = Opt) when is_function(Value) ->
-    Opt;
-handle_ssh_option({ssh_msg_debug_fun, Value} = Opt) when is_function(Value,4) ->
-    Opt;
-
-handle_ssh_option({ipv6_disabled, Value} = Opt) when is_boolean(Value) ->
-    throw({error, {{ipv6_disabled, Opt}, option_no_longer_valid_use_inet_option_instead}});
-handle_ssh_option({transport, {Protocol, Cb, ClosTag}} = Opt) when is_atom(Protocol),
-								   is_atom(Cb),
-								   is_atom(ClosTag) ->
-    Opt;
-handle_ssh_option({subsystems, Value} = Opt) when is_list(Value) ->
-    Opt;
-handle_ssh_option({ssh_cli, {Cb, _}}= Opt) when is_atom(Cb) ->
-    Opt;
-handle_ssh_option({ssh_cli, no_cli} = Opt) ->
-    Opt;
-handle_ssh_option({shell, {Module, Function, _}} = Opt)  when is_atom(Module),
-							      is_atom(Function) ->
-    Opt;
-handle_ssh_option({shell, Value} = Opt) when is_function(Value) ->
-    Opt;
-handle_ssh_option({quiet_mode, Value} = Opt) when is_boolean(Value) ->
-    Opt;
-handle_ssh_option({idle_time, Value} = Opt) when is_integer(Value), Value > 0 ->
-    Opt;
-handle_ssh_option({rekey_limit, Value} = Opt) when is_integer(Value) ->
-    Opt;
-handle_ssh_option({id_string, random}) ->
-    {id_string, {random,2,5}}; %% 2 - 5 random characters
-handle_ssh_option({id_string, ID} = Opt) when is_list(ID) ->
-    Opt;
-handle_ssh_option({max_random_length_padding, Value} = Opt) when is_integer(Value),
-								 Value =< 255 ->
-    Opt;
-handle_ssh_option({profile, Value} = Opt) when is_atom(Value) ->
-    Opt;
-handle_ssh_option(Opt) ->
-    throw({error, {eoptions, Opt}}).
-
-handle_ssh_priv_option({key_cb_private, Value} = Opt) when is_list(Value) ->
-    Opt.
-
-handle_inet_option({active, _} = Opt) ->
-    throw({error, {{eoptions, Opt}, "SSH has built in flow control, "
-		   "and active is handled internally, user is not allowed"
-		   "to specify this option"}});
-
-handle_inet_option({inet, Value}) when (Value == inet) or (Value == inet6) ->
-    Value;
-handle_inet_option({reuseaddr, _} = Opt) ->
-    throw({error, {{eoptions, Opt},"Is set internally, user is not allowed"
-		   "to specify this option"}});
-%% Option verified by inet
-handle_inet_option(Opt) ->
-    Opt.
-
-
-%% Check preferred algs
-
-handle_pref_algs({preferred_algorithms,Algs}) ->
-    try alg_duplicates(Algs, [], []) of
-	[] ->
-	    {preferred_algorithms,
-	     [try ssh_transport:supported_algorithms(Key)
-	      of
-		  DefAlgs -> handle_pref_alg(Key,Vals,DefAlgs)
-	      catch
-		  _:_ -> throw({error, {{eoptions, {preferred_algorithms,Key}},
-					"Bad preferred_algorithms key"}})
-	      end  || {Key,Vals} <- Algs]
-	    };
-
-	Dups ->
-	    throw({error, {{eoptions, {preferred_algorithms,Dups}}, "Duplicates found"}})
-    catch
-	_:_ ->
-	    throw({error, {{eoptions, preferred_algorithms}, "Malformed"}})
-    end.
-
-alg_duplicates([{K,V}|KVs], Ks, Dups0) ->
-    Dups =
-	case lists:member(K,Ks) of
-	    true ->
-		[K|Dups0];
-	    false ->
-		Dups0
-	end,
-    case V--lists:usort(V) of
-	[] ->
-	    alg_duplicates(KVs, [K|Ks], Dups);
-	Ds ->
-	    alg_duplicates(KVs, [K|Ks], Dups++Ds)
-    end;
-alg_duplicates([], _Ks, Dups) ->
-    Dups.
-
-handle_pref_alg(Key,
-		Vs=[{client2server,C2Ss=[_|_]},{server2client,S2Cs=[_|_]}],
-		[{client2server,Sup_C2Ss},{server2client,Sup_S2Cs}]
-	       ) ->
-    chk_alg_vs(Key, C2Ss, Sup_C2Ss),
-    chk_alg_vs(Key, S2Cs, Sup_S2Cs),
-    {Key, Vs};
-
-handle_pref_alg(Key,
-		Vs=[{server2client,[_|_]},{client2server,[_|_]}],
-		Sup=[{client2server,_},{server2client,_}]
-	       ) ->
-    handle_pref_alg(Key, lists:reverse(Vs), Sup);
-
-handle_pref_alg(Key,
-		Vs=[V|_],
-		Sup=[{client2server,_},{server2client,_}]
-	       ) when is_atom(V) ->
-    handle_pref_alg(Key, [{client2server,Vs},{server2client,Vs}], Sup);
-
-handle_pref_alg(Key,
-		Vs=[V|_],
-		Sup=[S|_]
-	       ) when is_atom(V), is_atom(S) ->
-    chk_alg_vs(Key, Vs, Sup),
-    {Key, Vs};
-
-handle_pref_alg(Key, Vs, _) ->
-    throw({error, {{eoptions, {preferred_algorithms,[{Key,Vs}]}}, "Badly formed list"}}).
-
-chk_alg_vs(OptKey, Values, SupportedValues) ->
-    case (Values -- SupportedValues) of
-	[] -> Values;
-	Bad -> throw({error, {{eoptions, {OptKey,Bad}}, "Unsupported value(s) found"}})
-    end.
-
-handle_ip(Inet) -> %% Default to ipv4
-    case lists:member(inet, Inet) of
-	true ->
-	    Inet;
-	false ->
-	    case lists:member(inet6, Inet) of
-		true ->
-		    Inet;
-		false ->
-		    [inet | Inet]
-	    end
-    end.
-
-check_dir({_,Dir} = Opt) ->
-    case directory_exist_readable(Dir) of
-	ok ->
-	    Opt;
-	{error,Error} ->
-	    throw({error, {eoptions,{Opt,Error}}})
-    end.
-
-directory_exist_readable(Dir) ->
-    case file:read_file_info(Dir) of
-	{ok, #file_info{type = directory,
-			access = Access}} ->
-	    case Access of
-		read -> ok;
-		read_write -> ok;
-		_ -> {error, eacces}
-	    end;
-
-	{ok, #file_info{}}->
-	    {error, enotdir};
-
-	{error, Error} ->
-	    {error, Error}
-    end.
-
-
-
-collect_per_size(L) ->
-    lists:foldr(
-      fun({Sz,GP}, [{Sz,GPs}|Acc]) -> [{Sz,[GP|GPs]}|Acc];
-	 ({Sz,GP}, Acc) -> [{Sz,[GP]}|Acc]
-      end, [], lists:sort(L)).
-
-read_moduli_file(D, I, Acc) ->
-    case io:get_line(D,"") of
-	{error,Error} ->
-	    {error,Error};
-	eof ->
-	    {ok, Acc};
-	"#" ++ _ -> read_moduli_file(D, I+1, Acc);
-	<<"#",_/binary>> ->  read_moduli_file(D, I+1, Acc);
-	Data ->
-	    Line = if is_binary(Data) -> binary_to_list(Data);
-		      is_list(Data) -> Data
-		   end,
-	    try
-		[_Time,_Type,_Tests,_Tries,Size,G,P] = string:tokens(Line," \r\n"),
-		M = {list_to_integer(Size),
-		     {list_to_integer(G), list_to_integer(P,16)}
-		    },
-		read_moduli_file(D, I+1, [M|Acc])
-	    catch
-		_:_ ->
-		    read_moduli_file(D, I+1, Acc)
-	    end
-    end.
-
-handle_user_pref_pubkey_algs([], Acc) ->
-    {true, lists:reverse(Acc)};
-handle_user_pref_pubkey_algs([H|T], Acc) ->
-    case lists:member(H, ?SUPPORTED_USER_KEYS) of
-	true ->
-	    handle_user_pref_pubkey_algs(T, [H| Acc]);
-
-	false when H==ssh_dsa -> handle_user_pref_pubkey_algs(T, ['ssh-dss'| Acc]);
-	false when H==ssh_rsa -> handle_user_pref_pubkey_algs(T, ['ssh-rsa'| Acc]);
-
-	false ->
-	    false
-    end.
-
 fmt_host({A,B,C,D}) ->
     lists:concat([A,".",B,".",C,".",D]);
 fmt_host(T={_,_,_,_,_,_,_,_}) ->
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 4cd91177f..475534f57 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -73,10 +73,31 @@
 %% Other macros
 -define(to_binary(X), (try iolist_to_binary(X) catch _:_ -> unicode:characters_to_binary(X) end) ).
 
+%% Cipher details
 -define(SSH_CIPHER_NONE, 0).
 -define(SSH_CIPHER_3DES, 3).
 -define(SSH_CIPHER_AUTHFILE, ?SSH_CIPHER_3DES).
 
+%% Option access macros
+-define(do_get_opt(C,K,O),   ssh_options:get_value(C,K,O,  ?MODULE,?LINE)).
+-define(do_get_opt(C,K,O,D), ssh_options:get_value(C,K,O,D,?MODULE,?LINE)).
+
+-define(GET_OPT(Key,Opts),              ?do_get_opt(user_options,    Key,Opts    ) ).
+-define(GET_INTERNAL_OPT(Key,Opts),     ?do_get_opt(internal_options,Key,Opts    ) ).
+-define(GET_INTERNAL_OPT(Key,Opts,Def), ?do_get_opt(internal_options,Key,Opts,Def) ).
+-define(GET_SOCKET_OPT(Key,Opts),       ?do_get_opt(socket_options,  Key,Opts    ) ).
+-define(GET_SOCKET_OPT(Key,Opts,Def),   ?do_get_opt(socket_options,  Key,Opts,Def) ).
+
+-define(do_put_opt(C,KV,O),  ssh_options:put_value(C,KV,O, ?MODULE,?LINE)).
+
+-define(PUT_OPT(KeyVal,Opts),           ?do_put_opt(user_options,    KeyVal,Opts) ).
+-define(PUT_INTERNAL_OPT(KeyVal,Opts),  ?do_put_opt(internal_options,KeyVal,Opts) ).
+-define(PUT_SOCKET_OPT(KeyVal,Opts),    ?do_put_opt(socket_options,  KeyVal,Opts) ).
+
+%% Types
+-type ok_error(SuccessType) :: {ok, SuccessType} | {error, any()} .
+
+%% Records
 -record(ssh,
 	{
 	  role,         %% client | server
@@ -136,7 +157,7 @@
 	  recv_sequence = 0,
 	  keyex_key,
 	  keyex_info,
-	  random_length_padding = 15, % From RFC 4253 section 6.
+	  random_length_padding = ?MAX_RND_PADDING_LEN, % From RFC 4253 section 6.
 	  
 	  %% User auth
 	  user,
diff --git a/lib/ssh/src/ssh_acceptor.erl b/lib/ssh/src/ssh_acceptor.erl
index 13c9d9af4..42be18f2a 100644
--- a/lib/ssh/src/ssh_acceptor.erl
+++ b/lib/ssh/src/ssh_acceptor.erl
@@ -25,56 +25,63 @@
 -include("ssh.hrl").
 
 %% Internal application API
--export([start_link/5,
+-export([start_link/4,
 	 number_of_connections/1,
-	 callback_listen/3,
+	 callback_listen/2,
 	 handle_connection/5]).
 
 %% spawn export  
--export([acceptor_init/6, acceptor_loop/6]).
+-export([acceptor_init/5, acceptor_loop/6]).
 
 -define(SLEEP_TIME, 200).
 
 %%====================================================================
 %% Internal application API
 %%====================================================================
-start_link(Port, Address, SockOpts, Opts, AcceptTimeout) ->
-    Args = [self(), Port, Address, SockOpts, Opts, AcceptTimeout],
+start_link(Port, Address, Options, AcceptTimeout) ->
+    Args = [self(), Port, Address, Options, AcceptTimeout],
     proc_lib:start_link(?MODULE, acceptor_init, Args).
 
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
-acceptor_init(Parent, Port, Address, SockOpts, Opts, AcceptTimeout) ->
-    {_, Callback, _} =  
-	proplists:get_value(transport, Opts, {tcp, gen_tcp, tcp_closed}),
-
-    SockOwner = proplists:get_value(lsock_owner, Opts),
-    LSock = proplists:get_value(lsocket, Opts),
-    UseExistingSocket =
-	case catch inet:sockname(LSock) of
-	    {ok,{_,Port}} -> is_pid(SockOwner);
-	    _ -> false
-	end,
-
-    case UseExistingSocket of
-	true ->
-	    proc_lib:init_ack(Parent, {ok, self()}),
+acceptor_init(Parent, Port, Address, Opts, AcceptTimeout) ->
+    {_, Callback, _} =  ?GET_OPT(transport, Opts),
+    try
+        {LSock0,SockOwner0} = ?GET_INTERNAL_OPT(lsocket, Opts),
+        true = is_pid(SockOwner0),
+        {ok,{_,Port}} = inet:sockname(LSock0),
+        {LSock0, SockOwner0}
+    of
+        {LSock, SockOwner} ->
+            %% Use existing socket
+            proc_lib:init_ack(Parent, {ok, self()}),
 	    request_ownership(LSock, SockOwner),
-	    acceptor_loop(Callback, Port, Address, Opts, LSock, AcceptTimeout);
-
-	false -> 
-	    case (catch do_socket_listen(Callback, Port, SockOpts)) of
-		{ok, ListenSocket} ->
-		    proc_lib:init_ack(Parent, {ok, self()}),
-		    acceptor_loop(Callback, 
-				  Port, Address, Opts, ListenSocket, AcceptTimeout);
-		Error ->
-		    proc_lib:init_ack(Parent, Error),
-		    error
-	    end
+	    acceptor_loop(Callback, Port, Address, Opts, LSock, AcceptTimeout)
+    catch
+        error:{badkey,lsocket} ->
+            %% Open new socket
+            try
+                socket_listen(Port, Opts)
+            of
+                {ok, ListenSocket} ->
+                    proc_lib:init_ack(Parent, {ok, self()}),
+                    {_, Callback, _} = ?GET_OPT(transport, Opts),
+                    acceptor_loop(Callback, 
+                                  Port, Address, Opts, ListenSocket, AcceptTimeout);
+                {error,Error} ->
+                    proc_lib:init_ack(Parent, Error),
+                    {error,Error}
+            catch
+                _:_ ->
+                    {error,listen_socket_failed}
+            end;
+
+        _:_ ->
+            {error,use_existing_socket_failed}
     end.
 
+
 request_ownership(LSock, SockOwner) ->
     SockOwner ! {request_control,LSock,self()},
     receive
@@ -82,23 +89,25 @@ request_ownership(LSock, SockOwner) ->
     end.
     
    
-do_socket_listen(Callback, Port0, Opts) ->
-    Port =
-	case proplists:get_value(fd, Opts) of
-	    undefined -> Port0;
-	    _ -> 0
-	end,
-    callback_listen(Callback, Port, Opts).
-
-callback_listen(Callback, Port, Opts0) ->
-    Opts = [{active, false}, {reuseaddr,true} | Opts0],
-    case Callback:listen(Port, Opts) of
+socket_listen(Port0, Opts) ->
+    Port = case ?GET_SOCKET_OPT(fd, Opts) of
+               undefined -> Port0;
+               _ -> 0
+           end,
+    callback_listen(Port, Opts).
+
+
+callback_listen(Port, Opts0) ->
+    {_, Callback, _} = ?GET_OPT(transport, Opts0),
+    Opts = ?PUT_SOCKET_OPT([{active, false}, {reuseaddr,true}], Opts0),
+    SockOpts = ?GET_OPT(socket_options, Opts),
+    case Callback:listen(Port, SockOpts) of
 	{error, nxdomain} ->
-	    Callback:listen(Port, lists:delete(inet6, Opts));
+	    Callback:listen(Port, lists:delete(inet6, SockOpts));
 	{error, enetunreach} ->
-	    Callback:listen(Port, lists:delete(inet6, Opts));
+	    Callback:listen(Port, lists:delete(inet6, SockOpts));
 	{error, eafnosupport} ->
-	    Callback:listen(Port, lists:delete(inet6, Opts));
+	    Callback:listen(Port, lists:delete(inet6, SockOpts));
 	Other ->
 	    Other
     end.
@@ -120,21 +129,21 @@ acceptor_loop(Callback, Port, Address, Opts, ListenSocket, AcceptTimeout) ->
     end.
 
 handle_connection(Callback, Address, Port, Options, Socket) ->
-    SSHopts = proplists:get_value(ssh_opts, Options, []),
-    Profile =  proplists:get_value(profile, SSHopts, ?DEFAULT_PROFILE),
+    Profile =  ?GET_OPT(profile, Options),
     SystemSup = ssh_system_sup:system_supervisor(Address, Port, Profile),
 
-    MaxSessions = proplists:get_value(max_sessions,SSHopts,infinity),
+    MaxSessions = ?GET_OPT(max_sessions, Options),
     case number_of_connections(SystemSup) < MaxSessions of
 	true ->
 	    {ok, SubSysSup} = ssh_system_sup:start_subsystem(SystemSup, Options),
 	    ConnectionSup = ssh_subsystem_sup:connection_supervisor(SubSysSup),
-	    Timeout = proplists:get_value(negotiation_timeout, SSHopts, 2*60*1000),
+	    NegTimeout = ?GET_OPT(negotiation_timeout, Options),
 	    ssh_connection_handler:start_connection(server, Socket,
-						    [{supervisors, [{system_sup, SystemSup},
-								    {subsystem_sup, SubSysSup},
-								    {connection_sup, ConnectionSup}]}
-						     | Options], Timeout);
+                                                    ?PUT_INTERNAL_OPT(
+                                                       {supervisors, [{system_sup, SystemSup},
+                                                                      {subsystem_sup, SubSysSup},
+                                                                      {connection_sup, ConnectionSup}]},
+                                                       Options), NegTimeout);
 	false ->
 	    Callback:close(Socket),
 	    IPstr = if is_tuple(Address) -> inet:ntoa(Address);
diff --git a/lib/ssh/src/ssh_acceptor_sup.erl b/lib/ssh/src/ssh_acceptor_sup.erl
index 129f85a3e..77f782691 100644
--- a/lib/ssh/src/ssh_acceptor_sup.erl
+++ b/lib/ssh/src/ssh_acceptor_sup.erl
@@ -44,14 +44,13 @@
 start_link(Servers) ->
     supervisor:start_link(?MODULE, [Servers]).
 
-start_child(AccSup, ServerOpts) ->
-    Spec = child_spec(ServerOpts),    
+start_child(AccSup, Options) ->
+    Spec = child_spec(Options),
     case supervisor:start_child(AccSup, Spec) of
 	{error, already_present} ->
-	    Address = proplists:get_value(address, ServerOpts),
-	    Port = proplists:get_value(port, ServerOpts),
-	    Profile = proplists:get_value(profile,  
-					  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+	    Address = ?GET_INTERNAL_OPT(address, Options),
+	    Port = ?GET_INTERNAL_OPT(port, Options),
+	    Profile = ?GET_OPT(profile, Options),  
 	    stop_child(AccSup, Address, Port, Profile),
 	    supervisor:start_child(AccSup, Spec);
 	Reply ->
@@ -70,24 +69,23 @@ stop_child(AccSup, Address, Port, Profile) ->
 %%%=========================================================================
 %%%  Supervisor callback
 %%%=========================================================================
-init([ServerOpts]) ->
+init([Options]) ->
     RestartStrategy = one_for_one,
     MaxR = 10,
     MaxT = 3600,
-    Children = [child_spec(ServerOpts)],
+    Children = [child_spec(Options)],
     {ok, {{RestartStrategy, MaxR, MaxT}, Children}}.
 
 %%%=========================================================================
 %%%  Internal functions
 %%%=========================================================================
-child_spec(ServerOpts) ->
-    Address = proplists:get_value(address, ServerOpts),
-    Port = proplists:get_value(port, ServerOpts),
-    Timeout = proplists:get_value(timeout, ServerOpts, ?DEFAULT_TIMEOUT),
-    Profile = proplists:get_value(profile,  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+child_spec(Options) ->
+    Address = ?GET_INTERNAL_OPT(address, Options),
+    Port = ?GET_INTERNAL_OPT(port, Options),
+    Timeout = ?GET_INTERNAL_OPT(timeout, Options, ?DEFAULT_TIMEOUT),
+    Profile = ?GET_OPT(profile, Options),
     Name = id(Address, Port, Profile),
-    SocketOpts = proplists:get_value(socket_opts, ServerOpts),
-    StartFunc = {ssh_acceptor, start_link, [Port, Address, SocketOpts, ServerOpts, Timeout]},
+    StartFunc = {ssh_acceptor, start_link, [Port, Address, Options, Timeout]},
     Restart = transient, 
     Shutdown = brutal_kill,
     Modules = [ssh_acceptor],
diff --git a/lib/ssh/src/ssh_auth.erl b/lib/ssh/src/ssh_auth.erl
index 9b54ecb2d..88c814406 100644
--- a/lib/ssh/src/ssh_auth.erl
+++ b/lib/ssh/src/ssh_auth.erl
@@ -96,14 +96,14 @@ unique(L) ->
 password_msg([#ssh{opts = Opts, io_cb = IoCb,
 		   user = User, service = Service} = Ssh0]) ->
     {Password,Ssh} = 
-	case proplists:get_value(password, Opts) of
+	case ?GET_OPT(password, Opts) of
 	    undefined when IoCb == ssh_no_io ->
 		{not_ok, Ssh0};
 	    undefined -> 
-		{IoCb:read_password("ssh password: ",Ssh0), Ssh0};
+		{IoCb:read_password("ssh password: ",Opts), 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})}}
+		{PW, Ssh0#ssh{opts = ?PUT_OPT({password,not_ok}, Opts)}}
 	end,
     case Password of
 	not_ok ->
@@ -123,7 +123,7 @@ password_msg([#ssh{opts = Opts, io_cb = IoCb,
 keyboard_interactive_msg([#ssh{user = User,
 			       opts = Opts,
 			       service = Service} = Ssh]) ->
-    case proplists:get_value(password, Opts) of
+    case ?GET_OPT(password, Opts) of
 	not_ok ->
 	    {not_ok,Ssh};       % No need to use a failed pwd once more
 	_ ->
@@ -141,8 +141,9 @@ publickey_msg([Alg, #ssh{user = User,
 		       service = Service,
 		       opts = Opts} = Ssh]) ->
     Hash = ssh_transport:sha(Alg),
-    KeyCb = proplists:get_value(key_cb, Opts, ssh_file),
-    case KeyCb:user_key(Alg, Opts) of
+    {KeyCb,KeyCbOpts} = ?GET_OPT(key_cb, Opts),
+    UserOpts = ?GET_OPT(user_options, Opts),
+    case KeyCb:user_key(Alg, [{key_cb_private,KeyCbOpts}|UserOpts]) of
 	{ok, PrivKey} ->
 	    StrAlgo = atom_to_list(Alg),
             case encode_public_key(StrAlgo, ssh_transport:extract_public_key(PrivKey)) of
@@ -174,13 +175,19 @@ service_request_msg(Ssh) ->
 
 %%%----------------------------------------------------------------
 init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
-    case user_name(Opts) of
-	{ok, User} ->
+    case ?GET_OPT(user, Opts) of
+	undefined ->
+	    ErrStr = "Could not determine the users name",
+	    ssh_connection_handler:disconnect(
+	      #ssh_msg_disconnect{code = ?SSH_DISCONNECT_ILLEGAL_USER_NAME,
+				  description = ErrStr});
+        
+	User ->
 	    Msg = #ssh_msg_userauth_request{user = User,
 					    service = "ssh-connection",
 					    method = "none",
 					    data = <<>>},
-	    Algs0 = proplists:get_value(pref_public_key_algs, Opts, ?SUPPORTED_USER_KEYS),
+	    Algs0 = ?GET_OPT(pref_public_key_algs, Opts),
 	    %% The following line is not strictly correct. The call returns the
 	    %% supported HOST key types while we are interested in USER keys. However,
 	    %% they "happens" to be the same (for now).  This could change....
@@ -194,12 +201,7 @@ init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
 	    ssh_transport:ssh_packet(Msg, Ssh#ssh{user = User,
 						  userauth_preference = Prefs,
 						  userauth_methods = none,
-						  service = "ssh-connection"});
-	{error, no_user} ->
-	    ErrStr = "Could not determine the users name",
-	    ssh_connection_handler:disconnect(
-	      #ssh_msg_disconnect{code = ?SSH_DISCONNECT_ILLEGAL_USER_NAME,
-				  description = ErrStr})
+						  service = "ssh-connection"})
     end.
 
 %%%----------------------------------------------------------------
@@ -342,7 +344,7 @@ handle_userauth_request(#ssh_msg_userauth_request{user = User,
 		       false},
 
 	    {Name, Instruction, Prompt, Echo} =
-		case proplists:get_value(auth_method_kb_interactive_data, Opts) of
+		case ?GET_OPT(auth_method_kb_interactive_data, Opts) of
 		    undefined -> 
 			Default;
 		    {_,_,_,_}=V -> 
@@ -407,9 +409,9 @@ handle_userauth_info_response(#ssh_msg_userauth_info_response{num_responses = 1,
 				   user = User,
 				   userauth_supported_methods = Methods} = Ssh) ->
     SendOneEmpty =
-	(proplists:get_value(tstflg,Opts) == one_empty)
+	(?GET_OPT(tstflg,Opts) == one_empty)
 	orelse 
-	proplists:get_value(one_empty, proplists:get_value(tstflg,Opts,[]), false),
+	proplists:get_value(one_empty, ?GET_OPT(tstflg,Opts), false),
 
     case check_password(User, unicode:characters_to_list(Password), Opts, Ssh) of
 	{true,Ssh1} when SendOneEmpty==true ->
@@ -460,27 +462,8 @@ method_preference(Algs) ->
 	       ],
 	       Algs).
 
-user_name(Opts) ->
-    Env = case os:type() of
-	      {win32, _} -> 
-		  "USERNAME";
-	      {unix, _} -> 
-		  "LOGNAME"
-	  end,
-    case proplists:get_value(user, Opts, os:getenv(Env)) of
-	false ->
-	    case os:getenv("USER") of
-		false -> 
-		    {error, no_user};
-		User -> 
-		    {ok, User}
-	    end;
-	User ->
-	    {ok, User}
-    end.
-
 check_password(User, Password, Opts, Ssh) ->
-    case proplists:get_value(pwdfun, Opts) of
+    case ?GET_OPT(pwdfun, Opts) of
 	undefined ->
 	    Static = get_password_option(Opts, User),
 	    {Password == Static, Ssh};
@@ -510,17 +493,18 @@ check_password(User, Password, Opts, Ssh) ->
     end.
 
 get_password_option(Opts, User) ->
-    Passwords = proplists:get_value(user_passwords, Opts, []),
+    Passwords = ?GET_OPT(user_passwords, Opts),
     case lists:keysearch(User, 1, Passwords) of
 	{value, {User, Pw}} -> Pw;
-	false -> proplists:get_value(password, Opts, false)
+	false -> ?GET_OPT(password, Opts)
     end.
 	    
 pre_verify_sig(User, Alg, KeyBlob, Opts) ->
     try
 	{ok, Key} = decode_public_key_v2(KeyBlob, Alg),
-	KeyCb =  proplists:get_value(key_cb, Opts, ssh_file),
-	KeyCb:is_auth_key(Key, User, Opts)
+        {KeyCb,KeyCbOpts} = ?GET_OPT(key_cb, Opts),
+        UserOpts = ?GET_OPT(user_options, Opts),
+        KeyCb:is_auth_key(Key, User, [{key_cb_private,KeyCbOpts}|UserOpts])
     catch
 	_:_ ->
 	    false
@@ -529,9 +513,10 @@ pre_verify_sig(User, Alg, KeyBlob, Opts) ->
 verify_sig(SessionId, User, Service, Alg, KeyBlob, SigWLen, Opts) ->
     try
 	{ok, Key} = decode_public_key_v2(KeyBlob, Alg),
-	KeyCb =  proplists:get_value(key_cb, Opts, ssh_file),
 
-	case KeyCb:is_auth_key(Key, User, Opts) of
+        {KeyCb,KeyCbOpts} = ?GET_OPT(key_cb, Opts),
+        UserOpts = ?GET_OPT(user_options, Opts),
+        case KeyCb:is_auth_key(Key, User, [{key_cb_private,KeyCbOpts}|UserOpts]) of
 	    true ->
 		PlainText = build_sig_data(SessionId, User,
 					   Service, KeyBlob, Alg),
@@ -565,9 +550,9 @@ decode_keyboard_interactive_prompts(_NumPrompts, Data) ->
 
 keyboard_interact_get_responses(IoCb, Opts, Name, Instr, PromptInfos) ->
     NumPrompts = length(PromptInfos),
-    keyboard_interact_get_responses(proplists:get_value(user_interaction, Opts, true),
-				    proplists:get_value(keyboard_interact_fun, Opts),
-				    proplists:get_value(password, Opts, undefined), IoCb, Name,
+    keyboard_interact_get_responses(?GET_OPT(user_interaction, Opts),
+				    ?GET_OPT(keyboard_interact_fun, Opts),
+				    ?GET_OPT(password, Opts), IoCb, Name,
 				    Instr, PromptInfos, Opts, NumPrompts).
 
 
diff --git a/lib/ssh/src/ssh_cli.erl b/lib/ssh/src/ssh_cli.erl
index 6f8c05048..4c4f61e03 100644
--- a/lib/ssh/src/ssh_cli.erl
+++ b/lib/ssh/src/ssh_cli.erl
@@ -499,14 +499,12 @@ start_shell(ConnectionHandler, State) ->
 						  [peer, user]),
     ShellFun = case is_function(Shell) of
 		   true ->
-		       User = 
-			   proplists:get_value(user, ConnectionInfo),
+		       User = proplists:get_value(user, ConnectionInfo),
 		       case erlang:fun_info(Shell, arity) of
 			   {arity, 1} ->
 			       fun() -> Shell(User) end;
 			   {arity, 2} ->
-			       {_, PeerAddr} =
-				   proplists:get_value(peer, ConnectionInfo),
+			       {_, PeerAddr} = proplists:get_value(peer, ConnectionInfo),
 			       fun() -> Shell(User, PeerAddr) end;
 			   _ ->
 			       Shell
@@ -525,8 +523,7 @@ start_shell(ConnectionHandler, Cmd, #state{exec=Shell} = State) when is_function
 
     ConnectionInfo = ssh_connection_handler:connection_info(ConnectionHandler,
 						 [peer, user]),
-    User = 
-	proplists:get_value(user, ConnectionInfo),
+    User = proplists:get_value(user, ConnectionInfo),
     ShellFun = 
 	case erlang:fun_info(Shell, arity) of
 	    {arity, 1} ->
@@ -534,8 +531,7 @@ start_shell(ConnectionHandler, Cmd, #state{exec=Shell} = State) when is_function
 	    {arity, 2} ->
 		fun() -> Shell(Cmd, User) end;
 	    {arity, 3} ->
-		{_, PeerAddr} =
-		    proplists:get_value(peer, ConnectionInfo),
+		{_, PeerAddr} = proplists:get_value(peer, ConnectionInfo),
 		fun() -> Shell(Cmd, User, PeerAddr) end;
 	    _ ->
 		Shell
diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl
index c7a2c9267..6a48ed581 100644
--- a/lib/ssh/src/ssh_connection.erl
+++ b/lib/ssh/src/ssh_connection.erl
@@ -197,16 +197,16 @@ reply_request(_,false, _, _) ->
 ptty_alloc(ConnectionHandler, Channel, Options) ->
     ptty_alloc(ConnectionHandler, Channel, Options, infinity).
 ptty_alloc(ConnectionHandler, Channel, Options0, TimeOut) ->
-    Options = backwards_compatible(Options0, []),
-    {Width, PixWidth} = pty_default_dimensions(width, Options),
-    {Height, PixHeight} = pty_default_dimensions(height, Options),
+    TermData = backwards_compatible(Options0, []), % FIXME
+    {Width, PixWidth} = pty_default_dimensions(width, TermData),
+    {Height, PixHeight} = pty_default_dimensions(height, TermData),
     pty_req(ConnectionHandler, Channel,
-	    proplists:get_value(term, Options, os:getenv("TERM", ?DEFAULT_TERMINAL)),
-	    proplists:get_value(width, Options, Width),
-	    proplists:get_value(height, Options, Height),
-	    proplists:get_value(pixel_widh, Options, PixWidth),
-	    proplists:get_value(pixel_height, Options, PixHeight),
-	    proplists:get_value(pty_opts, Options, []), TimeOut
+	    proplists:get_value(term, TermData, os:getenv("TERM", ?DEFAULT_TERMINAL)),
+	    proplists:get_value(width, TermData, Width),
+	    proplists:get_value(height, TermData, Height),
+	    proplists:get_value(pixel_widh, TermData, PixWidth),
+	    proplists:get_value(pixel_height, TermData, PixHeight),
+	    proplists:get_value(pty_opts, TermData, []), TimeOut
 	   ).
 %%--------------------------------------------------------------------
 %% Not yet officially supported! The following functions are part of the
@@ -417,7 +417,8 @@ handle_msg(#ssh_msg_channel_open{channel_type = "session" = Type,
 				 maximum_packet_size = PacketSz}, 
 	   #connection{options = SSHopts} = Connection0,
 	   server) ->
-    MinAcceptedPackSz = proplists:get_value(minimal_remote_max_packet_size, SSHopts, 0),
+    MinAcceptedPackSz =
+        ?GET_OPT(minimal_remote_max_packet_size, SSHopts),
     
     if 
 	MinAcceptedPackSz =< PacketSz ->
@@ -574,7 +575,6 @@ handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 		  PixWidth, PixHeight, decode_pty_opts(Modes)},
     
     Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
-    
     handle_cli_msg(Connection, Channel,
 		   {pty, ChannelId, WantReply, PtyRequest});
 
@@ -691,7 +691,6 @@ handle_cli_msg(#connection{channel_cache = Cache} = Connection,
 	       #channel{user = undefined, 
 			remote_id = RemoteId,
 			local_id = ChannelId} = Channel0, Reply0) -> 
-    
     case (catch start_cli(Connection, ChannelId)) of
 	{ok, Pid} ->
 	    erlang:monitor(process, Pid),
@@ -819,7 +818,7 @@ start_channel(Cb, Id, Args, SubSysSup, Exec, Opts) ->
     ssh_channel_sup:start_child(ChannelSup, ChildSpec).
     
 assert_limit_num_channels_not_exceeded(ChannelSup, Opts) ->
-    MaxNumChannels = proplists:get_value(max_channels, Opts, infinity),
+    MaxNumChannels = ?GET_OPT(max_channels, Opts),
     NumChannels = length([x || {_,_,worker,[ssh_channel]} <- 
 				   supervisor:which_children(ChannelSup)]),
     if 
@@ -858,8 +857,8 @@ setup_session(#connection{channel_cache = Cache
 
 
 check_subsystem("sftp"= SsName, Options) ->
-    case proplists:get_value(subsystems, Options, no_subsys) of
-	no_subsys -> 	
+    case ?GET_OPT(subsystems, Options) of
+	no_subsys -> 	% FIXME: Can 'no_subsys' ever be matched?
 	    {SsName, {Cb, Opts}} = ssh_sftpd:subsystem_spec([]),
 	    {Cb, Opts};
 	SubSystems ->
@@ -867,7 +866,7 @@ check_subsystem("sftp"= SsName, Options) ->
     end;
 
 check_subsystem(SsName, Options) ->
-    Subsystems = proplists:get_value(subsystems, Options, []),
+    Subsystems = ?GET_OPT(subsystems, Options),
     case proplists:get_value(SsName, Subsystems, {none, []}) of
 	Fun when is_function(Fun) ->
 	    {Fun, []};
@@ -1022,12 +1021,13 @@ pty_req(ConnectionHandler, Channel, Term, Width, Height,
 				    ?uint32(PixWidth),?uint32(PixHeight),
 				    encode_pty_opts(PtyOpts)], TimeOut).
 
-pty_default_dimensions(Dimension, Options) ->
-    case proplists:get_value(Dimension, Options, 0) of
+pty_default_dimensions(Dimension, TermData) ->
+    case proplists:get_value(Dimension, TermData, 0) of
 	N when is_integer(N), N > 0 ->
 	    {N, 0};
 	_ ->
-	    case proplists:get_value(list_to_atom("pixel_" ++ atom_to_list(Dimension)), Options, 0) of
+            PixelDim = list_to_atom("pixel_" ++ atom_to_list(Dimension)),
+	    case proplists:get_value(PixelDim, TermData, 0) of
 		N when is_integer(N), N > 0 ->
 		    {0, N};
 		_ ->
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index dcf509ca0..706b68d78 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -76,7 +76,7 @@
 %%--------------------------------------------------------------------
 -spec start_link(role(),
 		 inet:socket(),
-		 proplists:proplist()
+                 ssh_options:options()
 		) -> {ok, pid()}.
 %% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
 start_link(Role, Socket, Options) ->
@@ -99,12 +99,10 @@ stop(ConnectionHandler)->
 %% Internal application API
 %%====================================================================
 
--define(DefaultTransport,  {tcp, gen_tcp, tcp_closed} ).
-
 %%--------------------------------------------------------------------
 -spec start_connection(role(),
 		       inet:socket(),
-		       proplists:proplist(),
+                       ssh_options:options(),
 		       timeout()
 		      ) -> {ok, connection_ref()} | {error, term()}.
 %% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
@@ -121,9 +119,8 @@ start_connection(client = Role, Socket, Options, Timeout) ->
     end;
 
 start_connection(server = Role, Socket, Options, Timeout) ->
-    SSH_Opts = proplists:get_value(ssh_opts, Options, []),
     try
-	case proplists:get_value(parallel_login, SSH_Opts, false) of
+	case ?GET_OPT(parallel_login, Options) of
 	    true ->
 		HandshakerPid =
 		    spawn_link(fun() ->
@@ -346,7 +343,7 @@ renegotiate_data(ConnectionHandler) ->
 						 | undefined,
 	  last_size_rekey           = 0         :: non_neg_integer(),
 	  event_queue               = []        :: list(),
-	  opts                                  :: proplists:proplist(),
+	  opts                                  :: ssh_options:options(),
 	  inet_initial_recbuf_size              :: pos_integer()
 						 | undefined
 	 }).
@@ -357,15 +354,14 @@ renegotiate_data(ConnectionHandler) ->
 %%--------------------------------------------------------------------
 -spec init_connection_handler(role(),
 			      inet:socket(),
-			      proplists:proplist()
+			      ssh_options:options()
 			     ) -> no_return().
 %% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
 init_connection_handler(Role, Socket, Opts) ->
     process_flag(trap_exit, true),
     S0 = init_process_state(Role, Socket, Opts),
     try
-	{Protocol, Callback, CloseTag} =
-	    proplists:get_value(transport, Opts, ?DefaultTransport),
+	{Protocol, Callback, CloseTag} = ?GET_OPT(transport, Opts),
 	S0#data{ssh_params = init_ssh_record(Role, Socket, Opts),
 		 transport_protocol = Protocol,
 		 transport_cb = Callback,
@@ -393,7 +389,7 @@ init_process_state(Role, Socket, Opts) ->
 				   port_bindings = [],
 				   requests = [],
 				   options = Opts},
-	       starter = proplists:get_value(user_pid, Opts),
+	       starter = ?GET_INTERNAL_OPT(user_pid, Opts),
 	       socket = Socket,
 	       opts = Opts
 	      },
@@ -409,13 +405,18 @@ init_process_state(Role, Socket, Opts) ->
 
 
 init_connection(server, C = #connection{}, Opts) ->
-    Sups = proplists:get_value(supervisors, Opts),
-    SystemSup = proplists:get_value(system_sup, Sups),
-    SubSystemSup = proplists:get_value(subsystem_sup, Sups),
+    Sups =          ?GET_INTERNAL_OPT(supervisors, Opts),
+
+    SystemSup =     proplists:get_value(system_sup,     Sups),
+    SubSystemSup =  proplists:get_value(subsystem_sup,  Sups),
     ConnectionSup = proplists:get_value(connection_sup, Sups),
-    Shell = proplists:get_value(shell, Opts),
-    Exec = proplists:get_value(exec, Opts),
-    CliSpec = proplists:get_value(ssh_cli, Opts, {ssh_cli, [Shell]}),
+
+    Shell = ?GET_OPT(shell, Opts),
+    Exec = ?GET_OPT(exec, Opts),
+    CliSpec = case ?GET_OPT(ssh_cli, Opts) of
+                  undefined -> {ssh_cli, [Shell]};
+                  Spec -> Spec
+              end,
     C#connection{cli_spec = CliSpec,
 		 exec = Exec,
 		 system_supervisor = SystemSup,
@@ -426,41 +427,38 @@ 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,
-				      case Role of
-					  server -> ?SUPPORTED_AUTH_METHODS;
-					  client -> undefined
-				      end),
+    KeyCb = ?GET_OPT(key_cb, Opts),
+    AuthMethods =
+        case Role of
+            server -> ?GET_OPT(auth_methods, Opts);
+            client -> undefined
+        end,
     S0 = #ssh{role = Role,
 	      key_cb = KeyCb,
 	      opts = Opts,
 	      userauth_supported_methods = AuthMethods,
 	      available_host_keys = supported_host_keys(Role, KeyCb, Opts),
-	      random_length_padding = proplists:get_value(max_random_length_padding,
-							  Opts,
-							  (#ssh{})#ssh.random_length_padding)
+	      random_length_padding = ?GET_OPT(max_random_length_padding, Opts)
 	   },
 
     {Vsn, Version} = ssh_transport:versions(Role, Opts),
     case Role of
 	client ->
-	    PeerName =  proplists:get_value(host, Opts),
+	    PeerName =  ?GET_INTERNAL_OPT(host, Opts),
 	    S0#ssh{c_vsn = Vsn,
 		   c_version = Version,
-		   io_cb = case proplists:get_value(user_interaction, Opts, true) of
+		   io_cb = case ?GET_OPT(user_interaction, Opts) of
 			       true ->  ssh_io;
 			       false -> ssh_no_io
 			   end,
-		   userauth_quiet_mode = proplists:get_value(quiet_mode, Opts, false),
+		   userauth_quiet_mode = ?GET_OPT(quiet_mode, Opts),
 		   peer = {PeerName, PeerAddr}
 		  };
 
 	server ->
 	    S0#ssh{s_vsn = Vsn,
 		   s_version = Version,
-		   io_cb = proplists:get_value(io_cb, Opts, ssh_io),
+		   io_cb = ?GET_INTERNAL_OPT(io_cb, Opts, ssh_io),
 		   userauth_methods = string:tokens(AuthMethods, ","),
 		   kb_tries_left = 3,
 		   peer = {undefined, PeerAddr}
@@ -849,14 +847,12 @@ handle_event(_, Msg = #ssh_msg_userauth_failure{}, {userauth_keyboard_interactiv
 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
+    D = case ?GET_OPT(password, Opts) of
 	    undefined ->
 		D0;
 	    _ ->
 		D0#data{ssh_params =
-			    Ssh0#ssh{opts =
-					 lists:keyreplace(password,1,Opts,
-							  {password,not_ok})}} % FIXME:intermodule dependency
+			    Ssh0#ssh{opts = ?PUT_OPT({password,not_ok}, Opts)}} % FIXME:intermodule dependency
 	end,
     {next_state, {userauth,client}, D, [{next_event, internal, Msg}]};
 
@@ -954,7 +950,7 @@ handle_event(cast, renegotiate, _, _) ->
 handle_event(cast, data_size, {connected,Role}, D) ->
     {ok, [{send_oct,Sent0}]} = inet:getstat(D#data.socket, [send_oct]),
     Sent = Sent0 - D#data.last_size_rekey,
-    MaxSent = proplists:get_value(rekey_limit, D#data.opts, 1024000000),
+    MaxSent = ?GET_OPT(rekey_limit, D#data.opts),
     timer:apply_after(?REKEY_DATA_TIMOUT, gen_statem, cast, [self(), data_size]),
     case Sent >= MaxSent of
 	true ->
@@ -1294,11 +1290,12 @@ handle_event(info, UnexpectedMessage, StateName, D = #data{ssh_params = Ssh}) ->
 		      "Unexpected message '~p' received in state '~p'\n"
 		      "Role: ~p\n"
 		      "Peer: ~p\n"
-		      "Local Address: ~p\n", [UnexpectedMessage,
-					      StateName,
-					      Ssh#ssh.role, 
-					      Ssh#ssh.peer,
-					      proplists:get_value(address, Ssh#ssh.opts)])),
+		      "Local Address: ~p\n",
+                      [UnexpectedMessage,
+                       StateName,
+                       Ssh#ssh.role, 
+                       Ssh#ssh.peer,
+                       ?GET_INTERNAL_OPT(address, Ssh#ssh.opts)])),
 	    error_logger:info_report(Msg),
 	    keep_state_and_data;
 
@@ -1312,11 +1309,12 @@ handle_event(info, UnexpectedMessage, StateName, D = #data{ssh_params = Ssh}) ->
 				  "Message: ~p\n"
 				  "Role: ~p\n"
 				  "Peer: ~p\n"
-				  "Local Address: ~p\n", [Other,
-							  UnexpectedMessage,
-							  Ssh#ssh.role,
-							  element(2,Ssh#ssh.peer),
-							  proplists:get_value(address, Ssh#ssh.opts)]
+				  "Local Address: ~p\n",
+                                  [Other,
+                                   UnexpectedMessage,
+                                   Ssh#ssh.role,
+                                   element(2,Ssh#ssh.peer),
+                                   ?GET_INTERNAL_OPT(address, Ssh#ssh.opts)]
 				 )),
 	    error_logger:error_report(Msg),
 	    keep_state_and_data
@@ -1438,11 +1436,11 @@ code_change(_OldVsn, StateName, State, _Extra) ->
 %%--------------------------------------------------------------------
 %% Starting
 
-start_the_connection_child(UserPid, Role, Socket, Options) ->
-    Sups = proplists:get_value(supervisors, Options),
+start_the_connection_child(UserPid, Role, Socket, Options0) ->
+    Sups = ?GET_INTERNAL_OPT(supervisors, Options0),
     ConnectionSup = proplists:get_value(connection_sup, Sups),
-    Opts = [{supervisors, Sups}, {user_pid, UserPid} | proplists:get_value(ssh_opts, Options, [])],
-    {ok, Pid} = ssh_connection_sup:start_child(ConnectionSup, [Role, Socket, Opts]),
+    Options = ?PUT_INTERNAL_OPT({user_pid,UserPid}, Options0),
+    {ok, Pid} = ssh_connection_sup:start_child(ConnectionSup, [Role, Socket, Options]),
     ok = socket_control(Socket, Pid, Options),
     Pid.
 
@@ -1499,7 +1497,7 @@ supported_host_keys(server, KeyCb, Options) ->
 
 find_sup_hkeys(Options) ->
     case proplists:get_value(public_key,
-                             proplists:get_value(preferred_algorithms,Options,[])
+                             ?GET_OPT(preferred_algorithms,Options)
                             )
     of
         undefined ->
@@ -1512,9 +1510,10 @@ find_sup_hkeys(Options) ->
 
 
 %% Alg :: atom()
-available_host_key(KeyCb, Alg, Opts) ->
-    element(1, catch KeyCb:host_key(Alg, Opts)) == ok.
-
+available_host_key({KeyCb,KeyCbOpts}, Alg, Opts) ->
+    UserOpts = ?GET_OPT(user_options, Opts),
+    element(1,
+            catch KeyCb:host_key(Alg, [{key_cb_private,KeyCbOpts}|UserOpts])) == ok.
 
 send_msg(Msg, State=#data{ssh_params=Ssh0}) when is_tuple(Msg) ->
     {Bytes, Ssh} = ssh_transport:ssh_packet(Msg, Ssh0),
@@ -1773,7 +1772,7 @@ get_repl(X, Acc) ->
 disconnect_fun({disconnect,Msg}, D) ->
     disconnect_fun(Msg, D);
 disconnect_fun(Reason,  #data{opts=Opts}) ->
-    case proplists:get_value(disconnectfun, Opts) of
+    case ?GET_OPT(disconnectfun, Opts) of
 	undefined ->
 	    ok;
 	Fun ->
@@ -1783,7 +1782,7 @@ disconnect_fun(Reason,  #data{opts=Opts}) ->
 unexpected_fun(UnexpectedMessage, #data{opts = Opts,
 					ssh_params = #ssh{peer = {_,Peer} }
 				       } ) ->
-    case proplists:get_value(unexpectedfun, Opts) of
+    case ?GET_OPT(unexpectedfun, Opts) of
 	undefined ->
 	    report;
 	Fun ->
@@ -1795,7 +1794,7 @@ debug_fun(#ssh_msg_debug{always_display = Display,
 			 message = DbgMsg,
 			 language = Lang},
 	  #data{opts = Opts}) ->
-    case proplists:get_value(ssh_msg_debug_fun, Opts) of
+    case ?GET_OPT(ssh_msg_debug_fun, Opts) of
 	undefined ->
 	    ok;
 	Fun ->
@@ -1805,7 +1804,7 @@ debug_fun(#ssh_msg_debug{always_display = Display,
 
 connected_fun(User, Method, #data{ssh_params = #ssh{peer = {_,Peer}},
 				  opts = Opts}) ->
-    case proplists:get_value(connectfun, Opts) of
+    case ?GET_OPT(connectfun, Opts) of
 	undefined ->
 	    ok;
 	Fun ->
@@ -1824,7 +1823,7 @@ retry_fun(User, Reason, #data{ssh_params = #ssh{opts = Opts,
 	    _ ->
 		{infofun, Reason}
 	end,
-    Fun = proplists:get_value(Tag, Opts, fun(_,_)-> ok end),
+    Fun = ?GET_OPT(Tag, Opts),
     try erlang:fun_info(Fun, arity)
     of
 	{arity, 2} -> %% Backwards compatible
@@ -1843,7 +1842,7 @@ retry_fun(User, Reason, #data{ssh_params = #ssh{opts = Opts,
 %%% channels open for a while.
 
 cache_init_idle_timer(D) ->
-    case proplists:get_value(idle_time, D#data.opts, infinity) of
+    case ?GET_OPT(idle_time, D#data.opts) of
 	infinity ->
 	    D#data{idle_timer_value = infinity,
 		   idle_timer_ref = infinity	% A flag used later...
@@ -1906,9 +1905,8 @@ start_channel_request_timer(Channel, From, Time) ->
 %%% Connection start and initialization helpers
 
 socket_control(Socket, Pid, Options) ->
-    {_, TransportCallback, _} =		   % For example {_,gen_tcp,_}
-	proplists:get_value(transport, Options, ?DefaultTransport),
-    case TransportCallback:controlling_process(Socket, Pid) of
+    {_, Callback, _} =	?GET_OPT(transport, Options),
+    case Callback:controlling_process(Socket, Pid) of
 	ok ->
 	    gen_statem:cast(Pid, socket_control);
 	{error, Reason}	->
diff --git a/lib/ssh/src/ssh_file.erl b/lib/ssh/src/ssh_file.erl
index 216f65f33..898b4cc5c 100644
--- a/lib/ssh/src/ssh_file.erl
+++ b/lib/ssh/src/ssh_file.erl
@@ -192,8 +192,8 @@ lookup_user_key(Key, User, Opts) ->
 ssh_dir({remoteuser, User}, Opts) ->
     case proplists:get_value(user_dir_fun, Opts) of
 	undefined ->
-	    case proplists:get_value(user_dir, Opts) of
-		undefined ->
+	    case proplists:get_value(user_dir, Opts, false) of
+		false ->
 		    default_user_dir();
 		Dir ->
 		    Dir
diff --git a/lib/ssh/src/ssh_io.erl b/lib/ssh/src/ssh_io.erl
index 1d8f37088..6828fd476 100644
--- a/lib/ssh/src/ssh_io.erl
+++ b/lib/ssh/src/ssh_io.erl
@@ -27,17 +27,17 @@
 -export([yes_no/2, read_password/2, read_line/2, format/2]).
 -include("ssh.hrl").
 
-read_line(Prompt, Ssh) ->
+read_line(Prompt, Opts) ->
     format("~s", [listify(Prompt)]),
-    proplists:get_value(user_pid, Ssh) ! {self(), question},
+    ?GET_INTERNAL_OPT(user_pid, Opts) ! {self(), question},
     receive
 	Answer when is_list(Answer) ->
 	    Answer
     end.
 
-yes_no(Prompt, Ssh) ->
+yes_no(Prompt, Opts) ->
     format("~s [y/n]?", [Prompt]),
-    proplists:get_value(user_pid, Ssh#ssh.opts) ! {self(), question},
+    ?GET_INTERNAL_OPT(user_pid, Opts) ! {self(), question},
     receive
 	%% I can't see that the atoms y and n are ever received, but it must
 	%% be investigated before removing
@@ -52,15 +52,13 @@ yes_no(Prompt, Ssh) ->
 		"N" -> no;
 		_ ->
 		    format("please answer y or n\n",[]),
-		    yes_no(Prompt, Ssh)
+		    yes_no(Prompt, Opts)
 	    end
     end.
 
-
-read_password(Prompt, #ssh{opts=Opts}) -> read_password(Prompt, Opts);
-read_password(Prompt, Opts) when is_list(Opts) ->
+read_password(Prompt, Opts) ->
     format("~s", [listify(Prompt)]),
-    proplists:get_value(user_pid, Opts) ! {self(), user_password},
+    ?GET_INTERNAL_OPT(user_pid, Opts) ! {self(), user_password},
     receive
 	Answer when is_list(Answer) ->
 	     case trim(Answer) of
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
new file mode 100644
index 000000000..52dea5d18
--- /dev/null
+++ b/lib/ssh/src/ssh_options.erl
@@ -0,0 +1,897 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%
+
+-module(ssh_options).
+
+-include("ssh.hrl").
+-include_lib("kernel/include/file.hrl").
+
+-export([default/1,
+         get_value/5,  get_value/6,
+         put_value/5,
+         handle_options/2
+        ]).
+
+-export_type([options/0
+             ]).
+
+%%%================================================================
+%%% Types
+
+-type options() :: #{socket_options   := socket_options(),
+                     internal_options := internal_options(),
+                     option_key()     => any()
+                    }.
+
+-type socket_options()   :: proplists:proplist().
+-type internal_options() :: #{option_key() => any()}.
+
+-type option_key() :: atom().
+
+-type option_in() :: proplists:property() | proplists:proplist() .
+
+-type option_class() :: internal_options | socket_options | user_options . 
+
+-type option_declaration() :: #{class := user_options,
+                                chk := fun((any) -> boolean() | {true,any()}),
+                                default => any()
+                               }.
+
+-type option_declarations() :: #{ {option_key(),def} := option_declaration() }.
+
+-type role() :: client | server .
+
+-type error() :: {error,{eoptions,any()}} .
+
+%%%================================================================
+%%%
+%%% Get an option
+%%%
+
+-spec get_value(option_class(), option_key(), options(),
+                atom(), non_neg_integer()) -> any() | no_return().
+
+get_value(Class, Key, Opts, _CallerMod, _CallerLine) when is_map(Opts) ->
+    case Class of
+        internal_options -> maps:get(Key, maps:get(internal_options,Opts));
+        socket_options   -> proplists:get_value(Key, maps:get(socket_options,Opts));
+        user_options     -> maps:get(Key, Opts)
+    end;
+get_value(Class, Key, Opts, _CallerMod, _CallerLine) ->
+    io:format("*** Bad Opts GET OPT ~p ~p:~p Key=~p,~n    Opts=~p~n",[Class,_CallerMod,_CallerLine,Key,Opts]),
+    error({bad_options,Class, Key, Opts, _CallerMod, _CallerLine}).
+
+
+-spec get_value(option_class(), option_key(), options(), any(),
+                atom(), non_neg_integer()) -> any() | no_return().
+
+get_value(socket_options, Key, Opts, Def, _CallerMod, _CallerLine) when is_map(Opts) ->
+    proplists:get_value(Key, maps:get(socket_options,Opts), Def);
+get_value(Class, Key, Opts, Def, CallerMod, CallerLine) when is_map(Opts) ->
+    try get_value(Class, Key, Opts, CallerMod, CallerLine)
+    catch
+        error:{badkey,Key} -> Def
+    end;
+get_value(Class, Key, Opts, _Def, _CallerMod, _CallerLine) ->
+    io:format("*** Bad Opts GET OPT ~p ~p:~p Key=~p,~n    Opts=~p~n",[Class,_CallerMod,_CallerLine,Key,Opts]),
+    error({bad_options,Class, Key, Opts, _CallerMod, _CallerLine}).
+
+
+%%%================================================================
+%%%
+%%% Put an option
+%%%
+
+-spec put_value(option_class(), option_in(), options(),
+                atom(), non_neg_integer()) -> options().
+
+put_value(user_options, KeyVal, Opts, _CallerMod, _CallerLine) when is_map(Opts) ->
+    put_user_value(KeyVal, Opts);
+
+put_value(internal_options, KeyVal, Opts, _CallerMod, _CallerLine) when is_map(Opts) ->
+    InternalOpts = maps:get(internal_options,Opts),
+    Opts#{internal_options := put_internal_value(KeyVal, InternalOpts)};
+
+put_value(socket_options, KeyVal, Opts, _CallerMod, _CallerLine) when is_map(Opts) ->
+    SocketOpts = maps:get(socket_options,Opts),
+    Opts#{socket_options := put_socket_value(KeyVal, SocketOpts)}.
+
+
+%%%----------------
+put_user_value(L, Opts) when is_list(L) ->
+    lists:foldl(fun put_user_value/2, Opts, L);
+put_user_value({Key,Value}, Opts) ->
+    Opts#{Key := Value}.
+    
+%%%----------------
+put_internal_value(L, IntOpts) when is_list(L) ->
+    lists:foldl(fun put_internal_value/2, IntOpts, L);
+put_internal_value({Key,Value}, IntOpts) ->
+    IntOpts#{Key => Value}.
+
+%%%----------------
+put_socket_value(L, SockOpts) when is_list(L) ->
+    L ++ SockOpts;
+put_socket_value({Key,Value}, SockOpts) ->
+    [{Key,Value} | SockOpts];
+put_socket_value(A, SockOpts) when is_atom(A) ->
+    [A | SockOpts].
+
+%%%================================================================
+%%%
+%%% Initialize the options
+%%%
+
+-spec handle_options(role(), proplists:proplist()) -> options() | error() .
+
+-spec handle_options(role(), proplists:proplist(), options()) -> options() | error() .
+
+handle_options(Role, PropList0) ->
+    handle_options(Role, PropList0, #{socket_options   => [],
+                                      internal_options => #{},
+                                      user_options     => []
+                                     }).
+
+handle_options(Role, PropList0, Opts0) when is_map(Opts0),
+                                             is_list(PropList0) ->
+    PropList1 = proplists:unfold(PropList0), 
+    try
+        OptionDefinitions = default(Role),
+        InitialMap =
+            maps:fold(
+              fun({K,def}, #{default:=V}, M) -> M#{K=>V};
+                 (_,_,M) -> M
+              end,
+              Opts0#{user_options => 
+                         maps:get(user_options,Opts0) ++ PropList1
+                   },
+              OptionDefinitions),
+        %% Enter the user's values into the map; unknown keys are
+        %% treated as socket options
+        lists:foldl(fun(KV, Vals) ->
+                            save(KV, OptionDefinitions, Vals)
+                    end, InitialMap, PropList1)
+    catch
+        error:{eoptions, KV, undefined} -> 
+            {error, {eoptions,KV}};
+
+        error:{eoptions, KV, Txt} when is_list(Txt) -> 
+            {error, {eoptions,{KV,lists:flatten(Txt)}}};
+
+        error:{eoptions, KV, Extra} ->
+            {error, {eoptions,{KV,Extra}}}
+    end.
+
+
+check_fun(Key, Defs) ->
+    #{chk := Fun} = maps:get({Key,def}, Defs),
+    Fun.
+
+%%%================================================================
+%%%
+%%% Check and save one option
+%%%
+
+
+%%% First some prohibited inet options:
+save({K,V}, _, _) when K == reuseaddr ;
+                       K == active
+                       ->
+    forbidden_option(K, V);
+
+%%% then compatibility conversions:
+save({allow_user_interaction,V}, Opts, Vals) ->
+    save({user_interaction,V}, Opts, Vals);
+
+save({public_key_alg,V}, Defs, Vals) ->         % To remove in OTP-20
+    New = case V of
+              'ssh-rsa' -> ['ssh-rsa', 'ssh-dss'];
+              ssh_rsa   -> ['ssh-rsa', 'ssh-dss'];
+              'ssh-dss' -> ['ssh-dss', 'ssh-rsa'];
+              ssh_dsa   -> ['ssh-dss', 'ssh-rsa'];
+              _ -> error({eoptions, {public_key_alg,V},
+                          "Unknown algorithm, try pref_public_key_algs instead"})
+          end,
+    save({pref_public_key_algs,New}, Defs, Vals);
+
+%% Special case for socket options 'inet' and 'inet6'
+save(Inet, Defs, OptMap) when Inet==inet ; Inet==inet6 ->
+    save({inet,Inet}, Defs, OptMap);
+
+%% Two clauses to prepare for a proplists:unfold
+save({Inet,true}, Defs, OptMap) when Inet==inet ; Inet==inet6 ->  save({inet,Inet}, Defs, OptMap);
+save({Inet,false}, _Defs, OptMap) when Inet==inet ; Inet==inet6 -> OptMap;
+
+%% and finaly the 'real stuff':
+save({Key,Value}, Defs, OptMap) when is_map(OptMap) ->
+    try (check_fun(Key,Defs))(Value)
+    of
+        true ->
+            OptMap#{Key := Value};
+        {true, ModifiedValue} ->
+            OptMap#{Key := ModifiedValue};
+        false ->
+            error({eoptions, {Key,Value}, "Bad value"})
+    catch
+        %% An unknown Key (= not in the definition map) is
+        %% regarded as an inet option:
+        error:{badkey,{inet,def}} ->
+            %% atomic (= non-tuple) options 'inet' and 'inet6':
+            OptMap#{socket_options := [Value | maps:get(socket_options,OptMap)]};
+        error:{badkey,{Key,def}} ->
+            OptMap#{socket_options := [{Key,Value} | maps:get(socket_options,OptMap)]};
+
+        %% But a Key that is known but the value does not validate
+        %% by the check fun will give an error exception:
+        error:{check,{BadValue,Extra}} ->
+            error({eoptions, {Key,BadValue}, Extra})
+    end.
+
+%%%================================================================
+%%%
+%%% Default options
+%%%
+
+-spec default(role() | common) -> option_declarations() .
+
+default(server) ->
+    (default(common))
+        #{
+      {subsystems, def} =>
+          #{default => [ssh_sftpd:subsystem_spec([])],
+            chk => fun(L) ->
+                           is_list(L) andalso
+                               lists:all(fun({Name,{CB,Args}}) ->
+                                                 check_string(Name) andalso
+                                                     is_atom(CB) andalso
+                                                     is_list(Args);
+                                            (_) ->
+                                                 false
+                                         end, L)
+                   end,
+            class => user_options
+           },
+
+      {shell, def} =>
+          #{default => {shell, start, []},
+            chk => fun({M,F,A}) -> is_atom(M) andalso is_atom(F) andalso is_list(A);
+                      (V) -> check_function1(V) orelse check_function2(V)
+                   end,
+            class => user_options
+           },
+
+      {exec, def} =>                 % FIXME: need some archeology....
+          #{default => undefined,
+            chk => fun({M,F,_}) -> is_atom(M) andalso is_atom(F);
+                      (V) -> is_function(V)
+                   end,
+            class => user_options
+           },
+
+      {ssh_cli, def} =>
+          #{default => undefined,
+            chk => fun({Cb, As}) -> is_atom(Cb) andalso is_list(As);
+                      (V) -> V == no_cli
+                   end,
+            class => user_options
+           },
+
+      {system_dir, def} =>
+          #{default => "/etc/ssh",
+            chk => fun(V) -> check_string(V) andalso check_dir(V) end,
+            class => user_options
+           },
+
+      {auth_methods, def} =>
+          #{default => ?SUPPORTED_AUTH_METHODS,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {auth_method_kb_interactive_data, def} =>
+          #{default => undefined, % Default value can be constructed when User is known
+            chk => fun({S1,S2,S3,B}) ->
+                           check_string(S1) andalso
+                               check_string(S2) andalso
+                               check_string(S3) andalso
+                               is_boolean(B);
+                      (F) ->
+                           check_function3(F)
+                   end,
+            class => user_options
+           },
+
+      {user_passwords, def} =>
+          #{default => [],
+            chk => fun(V) ->
+                           is_list(V) andalso
+                               lists:all(fun({S1,S2}) ->
+                                                 check_string(S1) andalso 
+                                                     check_string(S2)   
+                                         end, V)
+                   end,
+            class => user_options
+           },
+
+      {password, def} =>
+          #{default => undefined,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {dh_gex_groups, def} =>
+          #{default => undefined,
+            chk => fun check_dh_gex_groups/1,
+            class => user_options
+           },
+
+      {dh_gex_limits, def} =>
+          #{default => {0, infinity},
+            chk => fun({I1,I2}) ->
+                           check_pos_integer(I1) andalso
+                               check_pos_integer(I2) andalso
+                               I1 < I2;
+                      (_) ->
+                           false
+                   end,
+            class => user_options
+           },
+
+      {pwdfun, def} =>
+          #{default => undefined,
+            chk => fun(V) -> check_function4(V) orelse check_function2(V) end,
+            class => user_options
+           },
+
+      {negotiation_timeout, def} =>
+          #{default => 2*60*1000,
+            chk => fun check_timeout/1,
+            class => user_options
+           },
+
+      {max_sessions, def} =>
+          #{default => infinity,
+            chk => fun check_pos_integer/1,
+            class => user_options
+           },
+
+      {max_channels, def} =>
+          #{default => infinity,
+            chk => fun check_pos_integer/1,
+            class => user_options
+           },
+
+      {parallel_login, def} =>
+          #{default => false,
+            chk => fun erlang:is_boolean/1,
+            class => user_options
+           },
+
+      {minimal_remote_max_packet_size, def} =>
+          #{default => 0,
+            chk => fun check_pos_integer/1,
+            class => user_options
+           },
+
+      {failfun, def} =>
+          #{default => fun(_,_,_) -> void end,
+            chk => fun(V) -> check_function3(V) orelse
+                                 check_function2(V) % Backwards compatibility
+                   end,
+            class => user_options
+           },
+
+      {connectfun, def} =>
+          #{default => fun(_,_,_) -> void end,
+            chk => fun check_function3/1,
+            class => user_options
+           },
+
+%%%%% Undocumented
+      {infofun, def} =>
+          #{default => fun(_,_,_) -> void end,
+            chk => fun(V) -> check_function3(V) orelse
+                                 check_function2(V) % Backwards compatibility
+                   end,
+            class => user_options
+           }
+     };
+
+default(client) ->
+    (default(common))
+        #{
+      {dsa_pass_phrase, def} =>
+          #{default => undefined,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {rsa_pass_phrase, def} =>
+          #{default => undefined,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {silently_accept_hosts, def} =>
+          #{default => false,
+            chk => fun check_silently_accept_hosts/1,
+            class => user_options
+           },
+
+      {user_interaction, def} =>
+          #{default => true,
+            chk => fun erlang:is_boolean/1,
+            class => user_options
+           },
+
+      {pref_public_key_algs, def} =>
+          #{default => 
+                %% Get dynamically supported keys in the order of the ?SUPPORTED_USER_KEYS
+                [A || A <- ?SUPPORTED_USER_KEYS,
+                      lists:member(A, ssh_transport:supported_algorithms(public_key))],
+            chk => 
+                fun check_pref_public_key_algs/1,
+            class =>
+                ssh
+           },
+
+      {dh_gex_limits, def} =>
+          #{default => {1024, 6144, 8192},      % FIXME: Is this true nowadays?
+            chk => fun({Min,I,Max}) ->
+                           lists:all(fun check_pos_integer/1,
+                                     [Min,I,Max]);
+                      (_) -> false
+                   end,
+            class => user_options
+           },
+
+      {connect_timeout, def} =>
+          #{default => infinity,
+            chk => fun check_timeout/1,
+            class => user_options
+           },
+
+      {user, def} =>
+          #{default => 
+                begin
+                    Env = case os:type() of
+                              {win32, _} -> "USERNAME";
+                              {unix, _} -> "LOGNAME"
+                          end,
+                    case os:getenv(Env) of
+                        false ->
+                            case os:getenv("USER") of
+                                false -> undefined;
+                                User -> User
+                            end;
+                        User ->
+                            User
+                    end
+                end,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {password, def} =>
+          #{default => undefined,
+            chk => fun check_string/1,
+            class => user_options
+           },
+
+      {quiet_mode, def} =>
+          #{default => false,
+            chk => fun erlang:is_boolean/1,
+            class => user_options
+           },
+
+      {idle_time, def} =>
+          #{default => infinity,
+            chk => fun check_timeout/1,
+            class => user_options
+           },
+
+%%%%% Undocumented
+      {keyboard_interact_fun, def} =>
+          #{default => undefined,
+            chk => fun check_function3/1,
+            class => user_options
+           }
+     };
+
+default(common) ->
+    #{
+       {user_dir, def} =>
+           #{default => false, % FIXME: TBD ~/.ssh at time of call when user is known
+             chk => fun(V) -> check_string(V) andalso check_dir(V) end,
+             class => user_options
+            },
+
+       {preferred_algorithms, def} =>
+           #{default => ssh:default_algorithms(),
+             chk => fun check_preferred_algorithms/1,
+             class => user_options
+            },
+
+       {id_string, def} => 
+           #{default => undefined, % FIXME: see ssh_transport:ssh_vsn/0
+             chk => fun(random) -> 
+                            {true, {random,2,5}}; % 2 - 5 random characters
+                       ({random,I1,I2}) -> 
+                            %% Undocumented
+                            check_pos_integer(I1) andalso
+                                check_pos_integer(I2) andalso
+                                I1=<I2;
+                       (V) ->
+                            check_string(V)
+                    end,
+             class => user_options
+            },
+
+       {key_cb, def} =>
+           #{default => {ssh_file, []},
+             chk => fun({Mod,Opts}) -> is_atom(Mod) andalso is_list(Opts);
+                       (Mod) when is_atom(Mod) -> {true, {Mod,[]}};
+                       (_) -> false
+                    end,
+             class => user_options
+            },
+
+       {profile, def} =>
+           #{default => ?DEFAULT_PROFILE,
+             chk => fun erlang:is_atom/1,
+             class => user_options
+            },
+
+       %% This is a "SocketOption"...
+       %% {fd, def} =>
+       %%     #{default => undefined,
+       %%       chk => fun erlang:is_integer/1,
+       %%       class => user_options
+       %%      },
+
+       {disconnectfun, def} =>
+           #{default => fun(_) -> void end,
+             chk => fun check_function1/1,
+             class => user_options
+            },
+
+       {unexpectedfun, def} => 
+           #{default => fun(_,_) -> report end,
+             chk => fun check_function2/1,
+             class => user_options
+            },
+
+       {ssh_msg_debug_fun, def} =>
+           #{default => fun(_,_,_,_) -> void end,
+             chk => fun check_function4/1,
+             class => user_options
+            },
+
+      {rekey_limit, def} =>                     % FIXME: Why not common?
+          #{default => 1024000000,
+            chk => fun check_non_neg_integer/1,
+            class => user_options
+           },
+
+%%%%% Undocumented
+       {transport, def} =>
+           #{default => ?DEFAULT_TRANSPORT,
+             chk => fun({A,B,C}) ->
+                            is_atom(A) andalso is_atom(B) andalso is_atom(C)
+                    end,
+             class => user_options
+            },
+
+       {vsn, def} =>
+           #{default => {2,0},
+             chk => fun({Maj,Min}) -> check_non_neg_integer(Maj) andalso check_non_neg_integer(Min);
+                       (_) -> false
+                    end,
+             class => user_options
+            },
+    
+       {tstflg, def} =>
+           #{default => [],
+             chk => fun erlang:is_list/1,
+             class => user_options
+            },
+
+       {user_dir_fun, def} =>
+           #{default => undefined,
+             chk => fun check_function1/1,
+             class => user_options
+            },
+
+       {max_random_length_padding, def} =>
+          #{default => ?MAX_RND_PADDING_LEN,
+            chk => fun check_non_neg_integer/1,
+            class => user_options
+           }
+    }.
+
+
+%%%================================================================
+%%%================================================================
+%%%================================================================
+
+%%%
+%%% check_*/1 -> true | false | error({check,Spec})
+%%% See error_in_check/2,3
+%%%
+
+%%% error_in_check(BadValue) -> error_in_check(BadValue, undefined).
+
+error_in_check(BadValue, Extra) -> error({check,{BadValue,Extra}}).
+
+
+%%%----------------------------------------------------------------
+check_timeout(infinity) -> true;
+check_timeout(I) -> check_pos_integer(I).
+
+%%%----------------------------------------------------------------
+check_pos_integer(I) -> is_integer(I) andalso I>0.
+
+%%%----------------------------------------------------------------
+check_non_neg_integer(I) -> is_integer(I) andalso I>=0.
+
+%%%----------------------------------------------------------------
+check_function1(F) -> is_function(F,1).
+check_function2(F) -> is_function(F,2).
+check_function3(F) -> is_function(F,3).
+check_function4(F) -> is_function(F,4).
+     
+%%%----------------------------------------------------------------
+check_pref_public_key_algs(V) -> 
+    %% Get the dynamically supported keys, that is, thoose
+    %% that are stored
+    PKs = ssh_transport:supported_algorithms(public_key),
+    CHK = fun(A, Ack) ->
+                  case lists:member(A, PKs) of
+                      true ->
+                          [A|Ack];
+                      false -> 
+                          %% Check with the documented options, that is,
+                          %% the one we can handle
+                          case lists:member(A,?SUPPORTED_USER_KEYS) of
+                              false ->
+                                  %% An algorithm ssh never can handle
+                                  error_in_check(A, "Not supported public key");
+                              true ->
+                                  %% An algorithm ssh can handle, but not in
+                                  %% this very call
+                                  Ack
+                          end
+                  end
+          end,
+    case lists:foldr(
+          fun(ssh_dsa, Ack) -> CHK('ssh-dss', Ack); % compatibility
+             (ssh_rsa, Ack) -> CHK('ssh-rsa', Ack); % compatibility
+             (X, Ack) -> CHK(X, Ack)
+          end, [], V)
+    of
+        V -> true;
+        [] -> false;
+        V1 -> {true,V1}
+    end.
+
+
+%%%----------------------------------------------------------------
+%% Check that it is a directory and is readable
+check_dir(Dir) -> 
+    case file:read_file_info(Dir) of
+	{ok, #file_info{type = directory,
+			access = Access}} ->
+	    case Access of
+		read -> true;
+		read_write -> true;
+		_ -> error_in_check(Dir, eacces)
+	    end;
+
+	{ok, #file_info{}}->
+            error_in_check(Dir, enotdir);
+
+	{error, Error} ->
+            error_in_check(Dir, Error)
+    end.
+
+%%%----------------------------------------------------------------
+check_string(S) -> is_list(S).                  % FIXME: stub
+                
+%%%----------------------------------------------------------------
+check_dh_gex_groups({file,File}) when is_list(File) ->
+    case file:consult(File) of
+        {ok, GroupDefs} ->
+            check_dh_gex_groups(GroupDefs);
+        {error, Error} ->
+            error_in_check({file,File},Error)
+    end;
+
+check_dh_gex_groups({ssh_moduli_file,File})  when is_list(File) ->
+    case file:open(File,[read]) of
+        {ok,D} ->
+            try
+                read_moduli_file(D, 1, [])
+            of
+                {ok,Moduli} ->
+                    check_dh_gex_groups(Moduli);
+                {error,Error} ->
+                    error_in_check({ssh_moduli_file,File}, Error)
+            catch
+                _:_ ->
+                    error_in_check({ssh_moduli_file,File}, "Bad format in file "++File)
+            after
+                file:close(D)
+            end;
+
+        {error, Error} ->
+            error_in_check({ssh_moduli_file,File}, Error)
+    end;
+
+check_dh_gex_groups(L0) when is_list(L0), is_tuple(hd(L0)) ->
+    {true,
+     collect_per_size(
+       lists:foldl(
+	 fun({N,G,P}, Acc) when is_integer(N),N>0,
+				is_integer(G),G>0,
+				is_integer(P),P>0 ->
+		 [{N,{G,P}} | Acc];
+	    ({N,{G,P}}, Acc) when is_integer(N),N>0,
+				  is_integer(G),G>0,
+				  is_integer(P),P>0 ->
+		 [{N,{G,P}} | Acc];
+	    ({N,GPs}, Acc) when is_list(GPs) ->
+		 lists:foldr(fun({Gi,Pi}, Acci) when is_integer(Gi),Gi>0,
+						     is_integer(Pi),Pi>0 ->
+				     [{N,{Gi,Pi}} | Acci]
+			     end, Acc, GPs)
+	 end, [], L0))};
+
+check_dh_gex_groups(_) ->
+    false.
+
+
+
+collect_per_size(L) ->
+    lists:foldr(
+      fun({Sz,GP}, [{Sz,GPs}|Acc]) -> [{Sz,[GP|GPs]}|Acc];
+	 ({Sz,GP}, Acc) -> [{Sz,[GP]}|Acc]
+      end, [], lists:sort(L)).
+
+read_moduli_file(D, I, Acc) ->
+    case io:get_line(D,"") of
+	{error,Error} ->
+	    {error,Error};
+	eof ->
+	    {ok, Acc};
+	"#" ++ _ -> read_moduli_file(D, I+1, Acc);
+	<<"#",_/binary>> ->  read_moduli_file(D, I+1, Acc);
+	Data ->
+	    Line = if is_binary(Data) -> binary_to_list(Data);
+		      is_list(Data) -> Data
+		   end,
+	    try
+		[_Time,_Class,_Tests,_Tries,Size,G,P] = string:tokens(Line," \r\n"),
+		M = {list_to_integer(Size),
+		     {list_to_integer(G), list_to_integer(P,16)}
+		    },
+		read_moduli_file(D, I+1, [M|Acc])
+	    catch
+		_:_ ->
+		    read_moduli_file(D, I+1, Acc)
+	    end
+    end.
+
+%%%----------------------------------------------------------------
+-define(SHAs, [md5, sha, sha224, sha256, sha384, sha512]).
+
+check_silently_accept_hosts(B) when is_boolean(B) -> true;
+check_silently_accept_hosts(F) when is_function(F,2) -> true;
+check_silently_accept_hosts({S,F}) when is_atom(S),
+                                        is_function(F,2) -> 
+    lists:member(S, ?SHAs) andalso
+        lists:member(S, proplists:get_value(hashs,crypto:supports()));
+check_silently_accept_hosts({L,F}) when is_list(L),
+                                        is_function(F,2) -> 
+    lists:all(fun(S) ->
+                      lists:member(S, ?SHAs) andalso
+                          lists:member(S, proplists:get_value(hashs,crypto:supports()))
+              end, L);
+check_silently_accept_hosts(_) -> false.
+
+%%%----------------------------------------------------------------
+check_preferred_algorithms(Algs) ->
+    try alg_duplicates(Algs, [], [])
+    of
+	[] ->
+	    {true,
+	     [try ssh_transport:supported_algorithms(Key)
+	      of
+		  DefAlgs -> handle_pref_alg(Key,Vals,DefAlgs)
+	      catch
+		  _:_ -> error_in_check(Key,"Bad preferred_algorithms key")
+	      end  || {Key,Vals} <- Algs]
+	    };
+
+	Dups ->
+	    error_in_check(Dups, "Duplicates")
+    catch
+	_:_ ->
+	    false
+    end.
+
+alg_duplicates([{K,V}|KVs], Ks, Dups0) ->
+    Dups =
+	case lists:member(K,Ks) of
+	    true ->  [K|Dups0];
+	    false -> Dups0
+	end,
+    case V--lists:usort(V) of
+	[] -> alg_duplicates(KVs, [K|Ks], Dups);
+	Ds -> alg_duplicates(KVs, [K|Ks], Dups++Ds)
+    end;
+alg_duplicates([], _Ks, Dups) ->
+    Dups.
+
+handle_pref_alg(Key,
+		Vs=[{client2server,C2Ss=[_|_]},{server2client,S2Cs=[_|_]}],
+		[{client2server,Sup_C2Ss},{server2client,Sup_S2Cs}]
+	       ) ->
+    chk_alg_vs(Key, C2Ss, Sup_C2Ss),
+    chk_alg_vs(Key, S2Cs, Sup_S2Cs),
+    {Key, Vs};
+
+handle_pref_alg(Key,
+		Vs=[{server2client,[_|_]},{client2server,[_|_]}],
+		Sup=[{client2server,_},{server2client,_}]
+	       ) ->
+    handle_pref_alg(Key, lists:reverse(Vs), Sup);
+
+handle_pref_alg(Key,
+		Vs=[V|_],
+		Sup=[{client2server,_},{server2client,_}]
+	       ) when is_atom(V) ->
+    handle_pref_alg(Key, [{client2server,Vs},{server2client,Vs}], Sup);
+
+handle_pref_alg(Key,
+		Vs=[V|_],
+		Sup=[S|_]
+	       ) when is_atom(V), is_atom(S) ->
+    chk_alg_vs(Key, Vs, Sup),
+    {Key, Vs};
+
+handle_pref_alg(Key, Vs, _) ->
+    error_in_check({Key,Vs}, "Badly formed list").
+
+chk_alg_vs(OptKey, Values, SupportedValues) ->
+    case (Values -- SupportedValues) of
+	[] -> Values;
+	Bad -> error_in_check({OptKey,Bad}, "Unsupported value(s) found")
+    end.
+
+%%%----------------------------------------------------------------
+forbidden_option(K,V) ->
+    Txt = io_lib:format("The option '~s' is used internally. The "
+                        "user is not allowed to specify this option.",
+                        [K]),
+    error({eoptions, {K,V}, Txt}).
+
+%%%----------------------------------------------------------------
diff --git a/lib/ssh/src/ssh_sftp.erl b/lib/ssh/src/ssh_sftp.erl
index 8d994cdb4..140856c8e 100644
--- a/lib/ssh/src/ssh_sftp.erl
+++ b/lib/ssh/src/ssh_sftp.erl
@@ -100,18 +100,14 @@ start_channel(Socket) when is_port(Socket) ->
 start_channel(Host) when is_list(Host) ->
     start_channel(Host, []).
 
-start_channel(Socket, Options) when is_port(Socket) ->
-    Timeout =
-	%% A mixture of ssh:connect and ssh_sftp:start_channel:
-	case proplists:get_value(connect_timeout, Options, undefined) of
-	    undefined ->
-		proplists:get_value(timeout, Options, infinity);
-	    TO ->
-		TO
-	end,
-    case ssh:connect(Socket, Options, Timeout) of
+start_channel(Socket, UserOptions) when is_port(Socket) ->
+    {SshOpts, _ChanOpts, SftpOpts} = handle_options(UserOptions),
+    Timeout =   % A mixture of ssh:connect and ssh_sftp:start_channel:
+        proplists:get_value(connect_timeout, SshOpts,
+                            proplists:get_value(timeout, SftpOpts, infinity)),
+    case ssh:connect(Socket, SshOpts, Timeout) of
 	{ok,Cm} ->
-	    case start_channel(Cm, Options) of
+	    case start_channel(Cm, UserOptions) of
 		{ok, Pid} ->
 		    {ok, Pid, Cm};
 		Error ->
@@ -120,9 +116,9 @@ start_channel(Socket, Options) when is_port(Socket) ->
 	Error ->
 	    Error
     end;
-start_channel(Cm, Opts) when is_pid(Cm) ->
-    Timeout = proplists:get_value(timeout, Opts, infinity),
-    {_, ChanOpts, SftpOpts} = handle_options(Opts, [], [], []),
+start_channel(Cm, UserOptions) when is_pid(Cm) ->
+    Timeout = proplists:get_value(timeout, UserOptions, infinity),
+    {_SshOpts, ChanOpts, SftpOpts} = handle_options(UserOptions),
     case ssh_xfer:attach(Cm, [], ChanOpts) of
 	{ok, ChannelId, Cm} ->
 	    case ssh_channel:start(Cm, ChannelId,
@@ -143,15 +139,17 @@ start_channel(Cm, Opts) when is_pid(Cm) ->
 	    Error
     end;
 
-start_channel(Host, Opts) ->
-    start_channel(Host, 22, Opts).
-start_channel(Host, Port, Opts) ->
-    {SshOpts, ChanOpts, SftpOpts} = handle_options(Opts, [], [], []),
-    Timeout = proplists:get_value(timeout, SftpOpts, infinity),
+start_channel(Host, UserOptions) ->
+    start_channel(Host, 22, UserOptions).
+
+start_channel(Host, Port, UserOptions) ->
+    {SshOpts, ChanOpts, SftpOpts} = handle_options(UserOptions),
+    Timeout =   % A mixture of ssh:connect and ssh_sftp:start_channel:
+        proplists:get_value(connect_timeout, SshOpts,
+                            proplists:get_value(timeout, SftpOpts, infinity)),
     case ssh_xfer:connect(Host, Port, SshOpts, ChanOpts, Timeout) of
 	{ok, ChannelId, Cm} ->
-	    case ssh_channel:start(Cm, ChannelId, ?MODULE, [Cm,
-							    ChannelId, SftpOpts]) of
+	    case ssh_channel:start(Cm, ChannelId, ?MODULE, [Cm,ChannelId,SftpOpts]) of
 		{ok, Pid} ->
 		    case wait_for_version_negotiation(Pid, Timeout) of
 			ok ->
@@ -865,6 +863,9 @@ terminate(_Reason, State) ->
 %%====================================================================
 %% Internal functions
 %%====================================================================
+handle_options(UserOptions) ->
+    handle_options(UserOptions, [], [], []).
+
 handle_options([], Sftp, Chan, Ssh) ->
     {Ssh, Chan, Sftp};
 handle_options([{timeout, _} = Opt | Rest], Sftp, Chan, Ssh) ->
diff --git a/lib/ssh/src/ssh_subsystem_sup.erl b/lib/ssh/src/ssh_subsystem_sup.erl
index 637f5f398..cf82db458 100644
--- a/lib/ssh/src/ssh_subsystem_sup.erl
+++ b/lib/ssh/src/ssh_subsystem_sup.erl
@@ -26,6 +26,8 @@
 
 -behaviour(supervisor).
 
+-include("ssh.hrl").
+
 -export([start_link/1,
 	 connection_supervisor/1,
 	 channel_supervisor/1
@@ -37,8 +39,8 @@
 %%%=========================================================================
 %%%  API
 %%%=========================================================================
-start_link(Opts) ->
-    supervisor:start_link(?MODULE, [Opts]).
+start_link(Options) ->
+    supervisor:start_link(?MODULE, [Options]).
 
 connection_supervisor(SupPid) ->
     Children = supervisor:which_children(SupPid),
@@ -53,42 +55,42 @@ channel_supervisor(SupPid) ->
 %%%=========================================================================
 -spec init( [term()] ) -> {ok,{supervisor:sup_flags(),[supervisor:child_spec()]}} | ignore .
 
-init([Opts]) ->
+init([Options]) ->
     RestartStrategy = one_for_all,
     MaxR = 0,
     MaxT = 3600,
-    Children = child_specs(Opts),
+    Children = child_specs(Options),
     {ok, {{RestartStrategy, MaxR, MaxT}, Children}}.
 
 %%%=========================================================================
 %%%  Internal functions
 %%%=========================================================================
-child_specs(Opts) ->
-    case proplists:get_value(role, Opts) of
+child_specs(Options) ->
+    case ?GET_INTERNAL_OPT(role, Options) of
 	client ->		
 	    [];
 	server ->
-	    [ssh_channel_child_spec(Opts), ssh_connectinon_child_spec(Opts)]
+	    [ssh_channel_child_spec(Options), ssh_connectinon_child_spec(Options)]
     end.
   
-ssh_connectinon_child_spec(Opts) ->
-    Address = proplists:get_value(address, Opts),
-    Port = proplists:get_value(port, Opts),
-    Role = proplists:get_value(role, Opts),
+ssh_connectinon_child_spec(Options) ->
+    Address = ?GET_INTERNAL_OPT(address, Options),
+    Port = ?GET_INTERNAL_OPT(port, Options),
+    Role = ?GET_INTERNAL_OPT(role, Options),
     Name = id(Role, ssh_connection_sup, Address, Port),
-    StartFunc = {ssh_connection_sup, start_link, [Opts]},
+    StartFunc = {ssh_connection_sup, start_link, [Options]},
     Restart = temporary,
     Shutdown = 5000,
      Modules = [ssh_connection_sup],
     Type = supervisor,
     {Name, StartFunc, Restart, Shutdown, Type, Modules}.
 
-ssh_channel_child_spec(Opts) ->
-    Address = proplists:get_value(address, Opts),
-    Port = proplists:get_value(port, Opts),
-    Role = proplists:get_value(role, Opts),
+ssh_channel_child_spec(Options) ->
+    Address = ?GET_INTERNAL_OPT(address, Options),
+    Port = ?GET_INTERNAL_OPT(port, Options),
+    Role = ?GET_INTERNAL_OPT(role, Options),
     Name = id(Role, ssh_channel_sup, Address, Port),
-    StartFunc = {ssh_channel_sup, start_link, [Opts]},
+    StartFunc = {ssh_channel_sup, start_link, [Options]},
     Restart = temporary,
     Shutdown = infinity,
     Modules = [ssh_channel_sup],
diff --git a/lib/ssh/src/ssh_system_sup.erl b/lib/ssh/src/ssh_system_sup.erl
index e97ac7b01..b0bbd3aae 100644
--- a/lib/ssh/src/ssh_system_sup.erl
+++ b/lib/ssh/src/ssh_system_sup.erl
@@ -45,12 +45,12 @@
 %%%=========================================================================
 %%% Internal  API
 %%%=========================================================================
-start_link(ServerOpts) ->
-    Address = proplists:get_value(address, ServerOpts),
-    Port = proplists:get_value(port, ServerOpts),
-    Profile = proplists:get_value(profile,  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+start_link(Options) ->
+    Address = ?GET_INTERNAL_OPT(address, Options),
+    Port =    ?GET_INTERNAL_OPT(port, Options),
+    Profile = ?GET_OPT(profile, Options),
     Name = make_name(Address, Port, Profile),
-    supervisor:start_link({local, Name}, ?MODULE, [ServerOpts]).
+    supervisor:start_link({local, Name}, ?MODULE, [Options]).
 
 stop_listener(SysSup) ->
     stop_acceptor(SysSup). 
@@ -127,12 +127,12 @@ restart_acceptor(Address, Port, Profile) ->
 %%%=========================================================================
 -spec init( [term()] ) -> {ok,{supervisor:sup_flags(),[supervisor:child_spec()]}} | ignore .
 
-init([ServerOpts]) ->
+init([Options]) ->
     RestartStrategy = one_for_one,
     MaxR = 0,
     MaxT = 3600,
-    Children = case proplists:get_value(asocket,ServerOpts) of
-		   undefined -> child_specs(ServerOpts);
+    Children = case ?GET_INTERNAL_OPT(asocket,Options,undefined) of
+		   undefined -> child_specs(Options);
 		   _ -> []
 	       end,
     {ok, {{RestartStrategy, MaxR, MaxT}, Children}}.
@@ -140,24 +140,24 @@ init([ServerOpts]) ->
 %%%=========================================================================
 %%%  Internal functions
 %%%=========================================================================
-child_specs(ServerOpts) ->
-    [ssh_acceptor_child_spec(ServerOpts)]. 
+child_specs(Options) ->
+    [ssh_acceptor_child_spec(Options)]. 
   
-ssh_acceptor_child_spec(ServerOpts) ->
-    Address = proplists:get_value(address, ServerOpts),
-    Port = proplists:get_value(port, ServerOpts),
-    Profile = proplists:get_value(profile,  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+ssh_acceptor_child_spec(Options) ->
+    Address = ?GET_INTERNAL_OPT(address, Options),
+    Port =    ?GET_INTERNAL_OPT(port, Options),
+    Profile = ?GET_OPT(profile, Options),
     Name = id(ssh_acceptor_sup, Address, Port, Profile),
-    StartFunc = {ssh_acceptor_sup, start_link, [ServerOpts]},
+    StartFunc = {ssh_acceptor_sup, start_link, [Options]},
     Restart = transient, 
     Shutdown = infinity,
     Modules = [ssh_acceptor_sup],
     Type = supervisor,
     {Name, StartFunc, Restart, Shutdown, Type, Modules}.
 
-ssh_subsystem_child_spec(ServerOpts) ->
+ssh_subsystem_child_spec(Options) ->
     Name = make_ref(),
-    StartFunc = {ssh_subsystem_sup, start_link, [ServerOpts]},
+    StartFunc = {ssh_subsystem_sup, start_link, [Options]},
     Restart = temporary,
     Shutdown = infinity,
     Modules = [ssh_subsystem_sup],
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index a17ad560d..02c995399 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -153,14 +153,14 @@ supported_algorithms(compression) ->
 
 %%%----------------------------------------------------------------------------
 versions(client, Options)->
-    Vsn = proplists:get_value(vsn, Options, ?DEFAULT_CLIENT_VERSION),
+    Vsn = ?GET_INTERNAL_OPT(vsn, Options, ?DEFAULT_CLIENT_VERSION),
     {Vsn, format_version(Vsn, software_version(Options))};
 versions(server, Options) ->
-    Vsn = proplists:get_value(vsn, Options, ?DEFAULT_SERVER_VERSION),
+    Vsn = ?GET_INTERNAL_OPT(vsn, Options, ?DEFAULT_SERVER_VERSION),
     {Vsn, format_version(Vsn, software_version(Options))}.
 
 software_version(Options) -> 
-    case proplists:get_value(id_string, Options) of
+    case ?GET_OPT(id_string, Options) of
 	undefined ->
 	    "Erlang"++ssh_vsn();
 	{random,Nlo,Nup} ->
@@ -171,7 +171,7 @@ software_version(Options) ->
 
 ssh_vsn() ->
     try {ok,L} = application:get_all_key(ssh),
-	 proplists:get_value(vsn,L,"")
+	 proplists:get_value(vsn, L, "")
     of 
 	"" -> "";
 	VSN when is_list(VSN) -> "/" ++ VSN;
@@ -232,13 +232,7 @@ key_exchange_init_msg(Ssh0) ->
 
 kex_init(#ssh{role = Role, opts = Opts, available_host_keys = HostKeyAlgs}) ->
     Random = ssh_bits:random(16),
-    PrefAlgs =
-	case proplists:get_value(preferred_algorithms,Opts) of
-	    undefined -> 
-		default_algorithms();
-	    Algs0 ->
-		Algs0
-	end,
+    PrefAlgs = ?GET_OPT(preferred_algorithms, Opts),
     kexinit_message(Role, Random, PrefAlgs, HostKeyAlgs).
 
 key_init(client, Ssh, Value) ->
@@ -341,10 +335,7 @@ key_exchange_first_msg(Kex, Ssh0) when Kex == 'diffie-hellman-group1-sha1' ;
 
 key_exchange_first_msg(Kex, Ssh0=#ssh{opts=Opts}) when Kex == 'diffie-hellman-group-exchange-sha1' ;
 						       Kex == 'diffie-hellman-group-exchange-sha256' ->
-    {Min,NBits0,Max} = 
-	proplists:get_value(dh_gex_limits, Opts, {?DEFAULT_DH_GROUP_MIN,
-						  ?DEFAULT_DH_GROUP_NBITS,
-						  ?DEFAULT_DH_GROUP_MAX}),
+    {Min,NBits0,Max} = ?GET_OPT(dh_gex_limits, Opts),
     DhBits = dh_bits(Ssh0#ssh.algorithms),
     NBits1 = 
         %% NIST Special Publication 800-57 Part 1 Revision 4: Recommendation for Key Management
@@ -458,7 +449,7 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request{min = Min0,
     %% server
     {Min, Max} = adjust_gex_min_max(Min0, Max0, Opts),
     case public_key:dh_gex_group(Min, NBits, Max,
-				 proplists:get_value(dh_gex_groups,Opts)) of
+				 ?GET_OPT(dh_gex_groups,Opts)) of
 	{ok, {_, {G,P}}} ->
 	    {SshPacket, Ssh} = 
 		ssh_packet(#ssh_msg_kex_dh_gex_group{p = P, g = G}, Ssh0),
@@ -492,7 +483,7 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request_old{n = NBits},
     Max0 = 8192,
     {Min, Max} = adjust_gex_min_max(Min0, Max0, Opts),
     case public_key:dh_gex_group(Min, NBits, Max,
-				 proplists:get_value(dh_gex_groups,Opts)) of
+				 ?GET_OPT(dh_gex_groups,Opts)) of
 	{ok, {_, {G,P}}} ->
 	    {SshPacket, Ssh} = 
 		ssh_packet(#ssh_msg_kex_dh_gex_group{p = P, g = G}, Ssh0),
@@ -517,22 +508,18 @@ handle_kex_dh_gex_request(_, _) ->
 
 
 adjust_gex_min_max(Min0, Max0, Opts) ->
-    case proplists:get_value(dh_gex_limits, Opts) of
-	undefined ->
-	    {Min0, Max0};
-	{Min1, Max1} ->
-	    Min2 = max(Min0, Min1),
-	    Max2 = min(Max0, Max1),
-	    if
-		Min2 =< Max2 ->
-		    {Min2, Max2};
-		Max2 < Min2 ->
-		    ssh_connection_handler:disconnect(
-		      #ssh_msg_disconnect{
-			 code = ?SSH_DISCONNECT_PROTOCOL_ERROR,
-			 description = "No possible diffie-hellman-group-exchange group possible"
-			})
-	    end
+    {Min1, Max1} = ?GET_OPT(dh_gex_limits, Opts),
+    Min2 = max(Min0, Min1),
+    Max2 = min(Max0, Max1),
+    if
+        Min2 =< Max2 ->
+            {Min2, Max2};
+        Max2 < Min2 ->
+            ssh_connection_handler:disconnect(
+              #ssh_msg_disconnect{
+                 code = ?SSH_DISCONNECT_PROTOCOL_ERROR,
+                 description = "No possible diffie-hellman-group-exchange group possible"
+                })
     end.
 		    
 
@@ -719,9 +706,9 @@ sid(#ssh{session_id = Id}, _) ->
 %% The host key should be read from storage
 %%
 get_host_key(SSH) ->
-    #ssh{key_cb = Mod, opts = Opts, algorithms = ALG} = SSH,
-
-    case Mod:host_key(ALG#alg.hkey, Opts) of
+    #ssh{key_cb = {KeyCb,KeyCbOpts}, opts = Opts, algorithms = ALG} = SSH,
+    UserOpts = ?GET_OPT(user_options, Opts),
+    case KeyCb:host_key(ALG#alg.hkey, [{key_cb_private,KeyCbOpts}|UserOpts]) of
 	{ok, #'RSAPrivateKey'{} = Key} ->  Key;
 	{ok, #'DSAPrivateKey'{} = Key} ->  Key;
 	{ok, #'ECPrivateKey'{}  = Key} ->  Key;
@@ -767,7 +754,7 @@ public_algo({#'ECPoint'{},{namedCurve,OID}}) ->
 
 
 accepted_host(Ssh, PeerName, Public, Opts) ->
-    case proplists:get_value(silently_accept_hosts, Opts, false) of
+    case ?GET_OPT(silently_accept_hosts, Opts) of
 	F when is_function(F,2) ->
 	    true == (catch F(PeerName, public_key:ssh_hostkey_fingerprint(Public)));
 	{DigestAlg,F} when is_function(F,2) ->
@@ -778,15 +765,16 @@ accepted_host(Ssh, PeerName, Public, Opts) ->
 	    yes == yes_no(Ssh, "New host " ++ PeerName ++ " accept")
     end.
 
-known_host_key(#ssh{opts = Opts, key_cb = Mod, peer = {PeerName,_}} = Ssh, 
+known_host_key(#ssh{opts = Opts, key_cb = {KeyCb,KeyCbOpts}, peer = {PeerName,_}} = Ssh, 
 	       Public, Alg) ->
-    case Mod:is_host_key(Public, PeerName, Alg, Opts) of
+    UserOpts = ?GET_OPT(user_options, Opts),
+    case KeyCb:is_host_key(Public, PeerName, Alg, [{key_cb_private,KeyCbOpts}|UserOpts]) of
 	true ->
 	    ok;
 	false ->
 	    case accepted_host(Ssh, PeerName, Public, Opts) of
 		true ->
-		    Mod:add_host_key(PeerName, Public, Opts);
+		    KeyCb:add_host_key(PeerName, Public, [{key_cb_private,KeyCbOpts}|UserOpts]);
 		false ->
 		    {error, rejected}
 	    end
@@ -1822,10 +1810,6 @@ len_supported(Name, Len) ->
 
 same(Algs) ->  [{client2server,Algs}, {server2client,Algs}].
 
-
-%% default_algorithms(kex) -> % Example of how to disable an algorithm
-%%     supported_algorithms(kex, ['ecdh-sha2-nistp521']);
-
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%
 %% Other utils
diff --git a/lib/ssh/src/sshd_sup.erl b/lib/ssh/src/sshd_sup.erl
index 04d2df30f..14f1937ab 100644
--- a/lib/ssh/src/sshd_sup.erl
+++ b/lib/ssh/src/sshd_sup.erl
@@ -41,13 +41,13 @@
 start_link(Servers) ->
     supervisor:start_link({local, ?MODULE}, ?MODULE, [Servers]).
 
-start_child(ServerOpts) ->
-    Address = proplists:get_value(address, ServerOpts),
-    Port = proplists:get_value(port, ServerOpts),    
-    Profile = proplists:get_value(profile,  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+start_child(Options) ->
+    Address = ?GET_INTERNAL_OPT(address,  Options),
+    Port =    ?GET_INTERNAL_OPT(port,     Options),    
+    Profile = ?GET_OPT(profile,  Options),
     case ssh_system_sup:system_supervisor(Address, Port, Profile) of
        undefined ->
-	    Spec =  child_spec(Address, Port, ServerOpts),    
+	    Spec = child_spec(Address, Port, Options),
 	    case supervisor:start_child(?MODULE, Spec) of
 		{error, already_present} ->
 		    Name = id(Address, Port, Profile),
@@ -58,7 +58,7 @@ start_child(ServerOpts) ->
 	    end;
 	Pid ->
 	    AccPid = ssh_system_sup:acceptor_supervisor(Pid),
-	    ssh_acceptor_sup:start_child(AccPid, ServerOpts)
+	    ssh_acceptor_sup:start_child(AccPid, Options)
     end.
 
 stop_child(Name) ->
@@ -82,8 +82,8 @@ init([Servers]) ->
     MaxR = 10,
     MaxT = 3600,
     Fun = fun(ServerOpts) -> 
-		  Address = proplists:get_value(address, ServerOpts),
-		  Port = proplists:get_value(port, ServerOpts),
+		  Address = ?GET_INTERNAL_OPT(address, ServerOpts),
+		  Port =    ?GET_INTERNAL_OPT(port, ServerOpts),
 		  child_spec(Address, Port, ServerOpts) 
 	  end,
     Children = lists:map(Fun, Servers),
@@ -92,10 +92,10 @@ init([Servers]) ->
 %%%=========================================================================
 %%%  Internal functions
 %%%=========================================================================
-child_spec(Address, Port, ServerOpts) ->
-    Profile = proplists:get_value(profile,  proplists:get_value(ssh_opts, ServerOpts), ?DEFAULT_PROFILE),
+child_spec(Address, Port, Options) ->
+    Profile = ?GET_OPT(profile, Options),
     Name = id(Address, Port,Profile),
-    StartFunc = {ssh_system_sup, start_link, [ServerOpts]},
+    StartFunc = {ssh_system_sup, start_link, [Options]},
     Restart = temporary, 
     Shutdown = infinity,
     Modules = [ssh_system_sup],
diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl
index 0fa0f0c0e..261239c15 100644
--- a/lib/ssh/test/ssh_trpt_test_lib.erl
+++ b/lib/ssh/test/ssh_trpt_test_lib.erl
@@ -85,18 +85,18 @@ exec(Op, S0=#s{}) ->
 
 	throw:Term ->
 	    report_trace(throw, Term, S1),
-	    throw(Term);
+	    throw({Term,Op});
 
 	error:Error ->
 	    report_trace(error, Error, S1),
-	    error(Error);
+	    error({Error,Op});
 
 	exit:Exit ->
 	    report_trace(exit, Exit, S1),
-	    exit(Exit);
+	    exit({Exit,Op});
         Cls:Err ->
             ct:pal("Class=~p, Error=~p", [Cls,Err]),
-            error("fooooooO")
+            error({"fooooooO",Op})
     end;
 exec(Op, {ok,S=#s{}}) -> exec(Op, S);
 exec(_, Error) -> Error.
@@ -114,20 +114,20 @@ op({accept,Opts}, S) when ?role(S) == server ->
     {ok,Socket} = gen_tcp:accept(S#s.listen_socket, S#s.timeout),
     {Host,_Port} = ok(inet:sockname(Socket)),
     S#s{socket = Socket,
-	ssh = init_ssh(server,Socket,[{host,host(Host)}|Opts]),
+	ssh = init_ssh(server, Socket, host(Host), Opts),
 	return_value = ok};
 
 %%%---- Client ops
 op({connect,Host,Port,Opts}, S) when ?role(S) == undefined -> 
     Socket = ok(gen_tcp:connect(host(Host), Port, mangle_opts([]))),
     S#s{socket = Socket,
-	ssh = init_ssh(client, Socket, [{host,host(Host)}|Opts]),
+	ssh = init_ssh(client, Socket, host(Host), Opts),
 	return_value = ok};
 
 %%%---- ops for both client and server
 op(close_socket, S) ->
-    catch tcp_gen:close(S#s.socket),
-    catch tcp_gen:close(S#s.listen_socket),
+    catch gen_tcp:close(S#s.socket),
+    catch gen_tcp:close(S#s.listen_socket),
     S#s{socket = undefined,
 	listen_socket = undefined,
 	return_value = ok};
@@ -296,12 +296,14 @@ instantiate(X, _S) ->
 
 %%%================================================================
 %%%
-init_ssh(Role, Socket, Options0) ->
-    Options = [{user_interaction, false},
-	       {vsn, {2,0}},
-	       {id_string, "ErlangTestLib"}
-	       | Options0],
-    ssh_connection_handler:init_ssh_record(Role, Socket, Options).
+init_ssh(Role, Socket, Host, UserOptions0) ->
+    UserOptions = [{user_interaction, false},
+                   {vsn, {2,0}},
+                   {id_string, "ErlangTestLib"}
+                   | UserOptions0],
+    Opts = ?PUT_INTERNAL_OPT({host,Host},
+                             ssh_options:handle_options(Role, UserOptions)),
+    ssh_connection_handler:init_ssh_record(Role, Socket, Opts).
 
 mangle_opts(Options) ->
     SysOpts = [{reuseaddr, true},
-- 
2.12.0

openSUSE Build Service is sponsored by