File 3547-compiler-fix-nondeterministic-behaviour.patch of Package erlang

From 07c3ddc6d2fdedf670145019a29eeb4b5926cd48 Mon Sep 17 00:00:00 2001
From: Igor Goryachev <igor@goryachev.org>
Date: Wed, 19 Jun 2024 00:25:16 +0300
Subject: [PATCH 1/2] compiler: fix nondeterministic behaviour

---
 lib/compiler/src/compile.erl                  |   28 +-
 lib/compiler/test/compile_SUITE.erl           |   25 +
 lib/compiler/test/compile_SUITE_data/ssh.erl  | 1431 +++++++++++++++++
 lib/compiler/test/compile_SUITE_data/ssh.hrl  | 1342 ++++++++++++++++
 .../test/compile_SUITE_data/ssh_connect.hrl   |  273 ++++
 5 files changed, 3092 insertions(+), 7 deletions(-)
 create mode 100644 lib/compiler/test/compile_SUITE_data/ssh.erl
 create mode 100644 lib/compiler/test/compile_SUITE_data/ssh.hrl
 create mode 100644 lib/compiler/test/compile_SUITE_data/ssh_connect.hrl

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 5bbb84286c..04f13f3080 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -1905,7 +1905,8 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
 -define(META_USED_FEATURES, enabled_features).
 -define(META_CHUNK_NAME, <<"Meta">>).
 
-metadata_add_features(Ftrs, #compile{extra_chunks = Extra} = St) ->
+metadata_add_features(Ftrs, #compile{options = CompOpts,
+                                     extra_chunks = Extra} = St) ->
     MetaData =
         case proplists:get_value(?META_CHUNK_NAME, Extra) of
             undefined ->
@@ -1918,11 +1919,21 @@ metadata_add_features(Ftrs, #compile{extra_chunks = Extra} = St) ->
     MetaData1 =
         proplists:from_map(maps:put(?META_USED_FEATURES, NewFtrs,
                                     proplists:to_map(MetaData))),
-    Extra1 = proplists:from_map(maps:put(?META_CHUNK_NAME,
-                                         erlang:term_to_binary(MetaData1),
-                                         proplists:to_map(Extra))),
+    Extra1 = proplists:from_map(
+               maps:put(?META_CHUNK_NAME,
+                        term_to_binary(MetaData1,
+                                       ensure_deterministic(CompOpts, [])),
+                        proplists:to_map(Extra))),
     St#compile{extra_chunks = Extra1}.
 
+ensure_deterministic(CompOpts, Opts) ->
+    case member(deterministic, CompOpts) of
+        true ->
+            [deterministic | Opts];
+        false ->
+            Opts
+    end.
+
 with_columns(Opts) ->
     case proplists:get_value(error_location, Opts, column) of
         column -> true;
@@ -2466,8 +2480,8 @@ debug_info_chunk(#compile{mod_options=ModOpts0,
             false ->
                 {erl_abstract_code,{none,AbstOpts},ModOpts0}
         end,
-    DebugInfo = erlang:term_to_binary({debug_info_v1,Backend,Metadata},
-                                      [compressed]),
+    DebugInfo = term_to_binary({debug_info_v1,Backend,Metadata},
+                               ensure_deterministic(CompOpts, [compressed])),
     {DebugInfo, ModOpts}.
 
 encrypt_debug_info(DebugInfo, Key, Opts) ->
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index 2467c6bfe2..e0791172c4 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -38,6 +38,7 @@
 	 sys_pre_attributes/1, dialyzer/1, no_core_prepare/1,
 	 warnings/1, pre_load_check/1, env_compiler_options/1,
          bc_options/1, deterministic_include/1, deterministic_paths/1,
+         deterministic_docs/1,
          compile_attribute/1, message_printing/1, other_options/1,
          transforms/1, erl_compile_api/1, types_pp/1
 	]).
@@ -60,6 +61,7 @@ all() ->
      sys_pre_attributes, dialyzer, warnings, pre_load_check,
      env_compiler_options, custom_debug_info, bc_options,
      custom_compile_info, deterministic_include, deterministic_paths,
+     deterministic_docs,
      compile_attribute, message_printing, other_options, transforms,
      erl_compile_api, types_pp].
 
@@ -1803,6 +1805,29 @@ deterministic_paths_1(DataDir, Name, Opts) ->
         file:set_cwd(Cwd)
     end.
 
+%% The test case uses ssh.erl from ssh application.
+deterministic_docs(Config) when is_list(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    Filepath = filename:join(DataDir, "ssh"),
+    false = deterministic_docs_1(Filepath, [binary], 25),
+    true = deterministic_docs_1(Filepath, [binary, deterministic], 25),
+    ok.
+
+deterministic_docs_1(Filepath, Opts, Checks) ->
+    {ok, _, Reference} = compile:file(Filepath, Opts),
+    lists:all(
+      fun(_) ->
+              {ok, Peer, Node} = ?CT_PEER(#{}),
+              {ok, _, Testing} =
+                  erpc:call(
+                    Node,
+                    fun() ->
+                            compile:file(Filepath, Opts)
+                    end),
+              peer:stop(Peer),
+              Testing =:= Reference
+      end, lists:seq(1, Checks)).
+
 %% ERL-1058: -compile(debug_info) had no effect
 compile_attribute(Config) when is_list(Config) ->
     DataDir = proplists:get_value(data_dir, Config),
diff --git a/lib/compiler/test/compile_SUITE_data/ssh.erl b/lib/compiler/test/compile_SUITE_data/ssh.erl
new file mode 100644
index 0000000000..2bc1bb4621
--- /dev/null
+++ b/lib/compiler/test/compile_SUITE_data/ssh.erl
@@ -0,0 +1,1431 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2004-2024. 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).
+-moduledoc """
+Main API of the ssh application
+
+This is the interface module for the `SSH` application. The Secure Shell (SSH)
+Protocol is a protocol for secure remote login and other secure network services
+over an insecure network. See [ssh](ssh_app.md#supported) for details of
+supported RFCs, versions, algorithms and unicode handling.
+
+With the SSH application it is possible to start _clients_ and to start
+_daemons_ (servers).
+
+Clients are started with `connect/2`, `connect/3` or `connect/4`. They open an
+encrypted connection on top of TCP/IP. In that encrypted connection one or more
+channels could be opened with
+[ssh_connection:session_channel/2,4](`ssh_connection:session_channel/2`).
+
+Each channel is an isolated "pipe" between a client-side process and a
+server-side process. Those process pairs could handle for example file transfers
+(sftp) or remote command execution (shell, exec and/or cli). If a custom shell
+is implemented, the user of the client could execute the special commands
+remotely. Note that the user is not necessarily a human but probably a system
+interfacing the SSH app.
+
+A server-side subssystem (channel) server is requested by the client with
+`ssh_connection:subsystem/4`.
+
+A server (daemon) is started with [daemon/1](`daemon/2`), `daemon/2` or
+[daemon/3](`daemon/2`). Possible channel handlers (subsystems) are declared with
+the [subsystem](`t:subsystem_daemon_option/0`) option when the daemon is
+started.
+
+To just run a shell on a remote machine, there are functions that bundles the
+needed three steps needed into one: [shell/1,2,3](`shell/1`). Similarly, to just
+open an sftp (file transfer) connection to a remote machine, the simplest way is
+to use [ssh_sftp:start_channel/1,2,3](`ssh_sftp:start_channel/1`).
+
+To write your own client channel handler, use the behaviour
+`m:ssh_client_channel`. For server channel handlers use `m:ssh_server_channel`
+behaviour (replaces ssh_daemon_channel).
+
+Both clients and daemons accepts options that controls the exact behaviour. Some
+options are common to both. The three sets are called
+[Client Options](`t:client_options/0`), [Daemon Options](`t:daemon_options/0`)
+and [Common Options](`t:common_options/0`).
+
+The descriptions of the options uses the
+[Erlang Type Language](`e:system:typespec.md`) with explaining text.
+
+> #### Note {: .info }
+>
+> See also [SSH Application Reference](index.html) and [Examples](using_ssh.md) section.
+
+## Keys and files
+
+A number of objects must be present for the SSH application to work. Those
+objects are per default stored in files. The default names, paths and file
+formats are the same as for [OpenSSH](http://www.openssh.com). Keys could be
+generated with the `ssh-keygen` program from OpenSSH. See the
+[User's Guide](using_ssh.md#running-an-erlang-ssh-daemon).
+
+The paths could easily be changed by options:
+[`user_dir`](`t:ssh_file:user_dir_common_option/0`) and
+[`system_dir`](`t:ssh_file:system_dir_daemon_option/0`).
+
+A completely different storage could be interfaced by writing callback modules
+using the behaviours `m:ssh_client_key_api` and/or `m:ssh_server_key_api`. A
+callback module is installed with the option
+[`key_cb`](`t:key_cb_common_option/0`) to the client and/or the daemon.
+
+### Daemons
+
+The keys are by default stored in files:
+
+- Mandatory: one or more _Host key(s)_, both private and public. Default is to
+  store them in the directory `/etc/ssh` in the files
+
+  - `ssh_host_dsa_key` and `ssh_host_dsa_key.pub`
+  - `ssh_host_rsa_key` and `ssh_host_rsa_key.pub`
+  - `ssh_host_ecdsa_key` and `ssh_host_ecdsa_key.pub`
+
+  The host keys directory could be changed with the option
+  [`system_dir`](`t:ssh_file:system_dir_daemon_option/0`).
+
+- Optional: one or more _User's public key_ in case of `publickey`
+  authorization. Default is to store them concatenated in the file
+  `.ssh/authorized_keys` in the user's home directory.
+
+  The user keys directory could be changed with the option
+  [`user_dir`](`t:ssh_file:user_dir_common_option/0`).
+
+### Clients
+
+The keys and some other data are by default stored in files in the directory
+`.ssh` in the user's home directory.
+
+The directory could be changed with the option
+[`user_dir`](`t:ssh_file:user_dir_common_option/0`).
+
+- Optional: a list of _Host public key(s)_ for previously connected hosts. This
+  list is handled by the SSH application without any need of user assistance.
+  The default is to store them in the file `known_hosts`.
+
+  The `t:host_accepting_client_options/0` are associated with this list of keys.
+
+- Optional: one or more _User's private key(s)_ in case of `publickey`
+  authorization. The default files are
+  - `id_dsa` and `id_dsa.pub`
+  - `id_rsa` and `id_rsa.pub`
+  - `id_ecdsa` and `id_ecdsa.pub`
+""".
+-moduledoc(#{titles =>
+                 [{type,<<"Client Options">>},
+                  {type,<<"Daemon Options (Server Options)">>},
+                  {type,<<"Common Options">>},
+                  {type,<<"Other data types">>}]}).
+
+-include("ssh.hrl").
+-include("ssh_connect.hrl").
+-include_lib("public_key/include/public_key.hrl").
+-include_lib("kernel/include/file.hrl").
+-include_lib("kernel/include/inet.hrl").
+
+-export([start/0, start/1, stop/0,
+	 connect/2, connect/3, connect/4,
+	 close/1, connection_info/2,
+         connection_info/1,
+	 channel_info/3,
+	 daemon/1, daemon/2, daemon/3,
+	 daemon_info/1, daemon_info/2,
+         daemon_replace_options/2,
+         set_sock_opts/2, get_sock_opts/2,
+	 default_algorithms/0,
+         chk_algos_opts/1,
+	 stop_listener/1, stop_listener/2,  stop_listener/3,
+	 stop_daemon/1, stop_daemon/2, stop_daemon/3,
+	 shell/1, shell/2, shell/3,
+         tcpip_tunnel_from_server/5, tcpip_tunnel_from_server/6,
+         tcpip_tunnel_to_server/5, tcpip_tunnel_to_server/6
+	]).
+
+%% In move from public_key
+-export([hostkey_fingerprint/1, hostkey_fingerprint/2
+        ]).
+         
+
+%%% Internal export
+-export([is_host/2]).
+
+-behaviour(ssh_dbg).
+-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1, ssh_dbg_format/2, ssh_dbg_format/3]).
+
+%%% "Deprecated" types export:
+-export_type([ssh_daemon_ref/0, ssh_connection_ref/0, ssh_channel_id/0]).
+-opaque ssh_daemon_ref()     :: daemon_ref().
+-opaque ssh_connection_ref() :: connection_ref().
+-opaque ssh_channel_id()     :: channel_id().
+
+
+%%% Type exports
+-export_type([daemon_ref/0,
+              connection_ref/0,
+	      channel_id/0,
+              client_options/0, client_option/0,
+              daemon_options/0, daemon_option/0,
+              common_options/0,
+              role/0,
+              subsystem_spec/0,
+              algs_list/0,
+              double_algs/1,
+              modify_algs_list/0,
+              alg_entry/0,
+              kex_alg/0,
+              pubkey_alg/0,
+              cipher_alg/0,
+              mac_alg/0,
+              compression_alg/0,
+              host/0,
+              open_socket/0,
+              ip_port/0
+	     ]).
+
+
+-doc """
+Opaque data type representing a daemon.
+
+Returned by the functions [`daemon/1,2,3`](`daemon/1`).
+""".
+-doc(#{title => <<"Other data types">>}).
+-opaque daemon_ref()         :: pid() .
+-doc """
+Opaque data type representing a channel inside a connection.
+
+Returned by the functions
+[ssh_connection:session_channel/2,4](`ssh_connection:session_channel/2`).
+""".
+-doc(#{title => <<"Other data types">>}).
+-opaque channel_id()     :: non_neg_integer().
+-doc """
+Opaque data type representing a connection between a client and a server
+(daemon).
+
+Returned by the functions [`connect/2,3,4`](`connect/3`) and
+[`ssh_sftp:start_channel/2,3`](`ssh_sftp:start_channel/2`).
+""".
+-doc(#{title => <<"Other data types">>}).
+-type connection_ref()       :: pid().  % should be -opaque, but that gives problems
+
+%%--------------------------------------------------------------------
+%% Description: Starts the ssh application. Default type
+%% is temporary. see application(3)
+%%--------------------------------------------------------------------
+-doc(#{equiv => start/1}).
+-spec start() -> ok | {error, term()}.
+
+start() ->
+    start(temporary).
+
+-doc """
+Utility function that starts the applications `crypto`, `public_key`, and `ssh`.
+Default type is `temporary`. For more information, see the `m:application`
+manual page in Kernel.
+""".
+-spec start(Type) -> ok | {error, term()} when
+      Type :: permanent | transient | temporary .
+
+start(Type) ->
+    case application:ensure_all_started(ssh, Type) of
+        {ok, _} ->
+            %% Clear cached default_algorithms (if exists) ...
+            ssh_transport:clear_default_algorithms_env(),
+            %% ... and rebuild them taking configure options in account
+            ssh_transport:default_algorithms(),
+            ok;
+        Other ->
+            Other
+    end.
+
+%%--------------------------------------------------------------------
+%% Description: Stops the ssh application.
+%%--------------------------------------------------------------------
+-doc """
+Stops the `ssh` application. For more information, see the `m:application`
+manual page in Kernel.
+""".
+-spec stop() -> ok | {error, term()}.
+
+stop() ->
+    application:stop(ssh).
+
+%%--------------------------------------------------------------------
+%% Description: Starts an ssh connection.
+%%--------------------------------------------------------------------
+-define(IS_VALID_OPTIONS(Options), is_list(Options)).
+-define(IS_VALID_PORT(Port), (is_integer(Port) andalso Port > 0)).
+-define(IS_VALID_TIMEOUT(Timeout),
+        (Timeout == infinity
+         orelse (is_integer(Timeout)
+                 andalso Timeout >= 0))).
+
+-doc(#{equiv => connect/4}).
+-doc(#{since => <<"OTP 19.0">>}).
+-spec connect(OpenTcpSocket, Options)
+             -> {ok, connection_ref()}
+              | {error, term()} when
+      OpenTcpSocket :: open_socket(),
+      Options :: client_options().
+
+connect(OpenTcpSocket, Options) when ?IS_VALID_OPTIONS(Options) ->
+    connect(OpenTcpSocket, Options, infinity);
+connect(_OpenTcpSocket, Options) ->
+    bad_arg([{options, Options}]).
+
+-doc(#{equiv => connect/4}).
+-spec connect(open_socket(), client_options(), timeout()) ->
+                     {ok, connection_ref()} | {error, term()}
+           ; (host(), inet:port_number(), client_options()) ->
+                     {ok, connection_ref()} | {error, term()}.
+
+connect(Host, Port, Options) when ?IS_VALID_PORT(Port),
+                                  ?IS_VALID_OPTIONS(Options) ->
+    Timeout = proplists:get_value(connect_timeout, Options, infinity),
+    connect(Host, Port, Options, Timeout);
+connect(Socket, UserOptions, NegotiationTimeout)
+  when ?IS_VALID_OPTIONS(UserOptions),
+       ?IS_VALID_TIMEOUT(NegotiationTimeout) ->
+    case ssh_options:handle_options(client, UserOptions) of
+	{error, Error} ->
+	    {error, Error};
+
+	Options = #{} ->
+            case valid_socket_to_use(Socket, ?GET_OPT(transport,Options)) of
+                ok ->
+                    continue_connect(Socket, Options, NegotiationTimeout);
+                {error,SockError} ->
+                    {error,SockError}
+            end
+    end;
+connect(_HostOrSocket, PortOrOptions, OptionsOrTimeout) ->
+    bad_arg(PortOrOptions, OptionsOrTimeout).
+
+-doc """
+connect(Host, Port, Options, NegotiationTimeout) -> Result
+
+Connects to an SSH server at the `Host` on `Port`.
+
+As an alternative, an already open TCP socket could be passed to the function in
+`TcpSocket`. The SSH initiation and negotiation will be initiated on that one
+with the SSH that should be at the other end.
+
+No channel is started. This is done by calling
+[ssh_connection:session_channel/2,4](`ssh_connection:session_channel/2`).
+
+The `NegotiationTimeout` is in milli-seconds. The default value is `infinity` or
+the value of the [`connect_timeout`](`t:connect_timeout_client_option/0`)
+option, if present. For connection timeout, use the option
+[`connect_timeout`](`t:connect_timeout_client_option/0`).
+""".
+-spec connect(Host, Port, Options, NegotiationTimeout)
+             -> {ok, connection_ref()}
+              | {error, term()} when
+      Host :: host(),
+      Port :: inet:port_number(),
+      Options :: client_options(),
+      NegotiationTimeout :: timeout().
+
+connect(Host0, Port, UserOptions, NegotiationTimeout)
+  when ?IS_VALID_PORT(Port),
+       ?IS_VALID_OPTIONS(UserOptions),
+       ?IS_VALID_TIMEOUT(NegotiationTimeout) ->
+    case ssh_options:handle_options(client, UserOptions) of
+	{error, Reason} ->
+            {error, Reason};
+
+        Options ->
+            SocketOpts = [{active,false} | ?GET_OPT(socket_options,Options)],
+            Host = mangle_connect_address(Host0, Options),
+            try
+                transport_connect(Host, Port, SocketOpts, Options)
+            of
+                {ok, Socket} ->
+                    continue_connect(Socket, Options, NegotiationTimeout);
+                {error, Reason} ->
+                    {error, Reason}
+            catch
+                _:badarg -> {error, {options,?GET_OPT(socket_options,Options)}};
+                _:{error,Reason} -> {error,Reason};
+                error:Error -> {error,Error};
+                Class:Error -> {error, {Class,Error}}
+            end
+    end;
+connect(_Host, Port, UserOptions, NegotiationTimeout) ->
+    bad_arg([{port, Port},
+             {options, UserOptions},
+             {timeout, NegotiationTimeout}]).
+
+bad_arg(Args) ->
+    hd(bad_args(Args)).
+
+%% Special handling for finding the incorrect args for connect/3,
+%% which has two distinctly different signatures.
+bad_arg(Arg2, Arg3) ->
+    E0 = bad_args([{port, Arg2}, {options, Arg3}]),
+    E1 = bad_args([{options, Arg2}, {timeout, Arg3}]),
+    %% Select the case with only one error
+    case {E0, E1} of
+        {[Error], _}    -> Error;
+        {_, [Error]}    -> Error;
+        {[Error, _], _} -> Error
+    end.
+
+%% Return list of errors
+-spec bad_args([{'options' | 'port' | 'timeout', any()}]) ->
+          [{'error', term()}].
+bad_args(Args) ->
+    IsErr = fun(true, _) -> false;
+               (false, Error) -> {true, {error, Error}}
+            end,
+    Check =
+        fun({options, Arg}) -> IsErr(?IS_VALID_OPTIONS(Arg), invalid_options);
+           ({timeout, Arg}) -> IsErr(?IS_VALID_TIMEOUT(Arg), invalid_timeout);
+           ({port, Arg})    -> IsErr(?IS_VALID_PORT(Arg), invalid_port)
+        end,
+
+    lists:filtermap(Check, Args).
+
+%%%----------------
+continue_connect(Socket, Options0, NegTimeout) ->
+    {ok, {SockHost,SockPort}} = inet:sockname(Socket),
+    Options = ?PUT_INTERNAL_OPT([{negotiation_timeout,NegTimeout}], Options0),
+    Address = #address{address = SockHost,
+                       port = SockPort,
+                       profile = ?GET_OPT(profile,Options)
+                      },
+    ssh_system_sup:start_subsystem(client, Address, Socket, Options).
+
+%%--------------------------------------------------------------------
+-doc "Closes an SSH connection.".
+-spec close(ConnectionRef) -> ok | {error,term()} when
+      ConnectionRef :: connection_ref() .
+%%
+%% Description: Closes an ssh connection.
+%%--------------------------------------------------------------------
+close(ConnectionRef) ->
+    ssh_connection_handler:stop(ConnectionRef).
+
+%%--------------------------------------------------------------------
+%% Description: Retrieves information about a connection.
+%%---------------------------------------------------------------------
+-doc(#{title => <<"Other data types">>,equiv => conn_info_channels/0}).
+-type version() :: {protocol_version(), software_version()}.
+-doc(#{title => <<"Other data types">>,equiv => conn_info_channels/0}).
+-type protocol_version() :: {Major::pos_integer(), Minor::non_neg_integer()}.
+-doc(#{title => <<"Other data types">>,equiv => conn_info_channels/0}).
+-type software_version() :: string().
+-doc(#{title => <<"Other data types">>,equiv => conn_info_channels/0}).
+-type conn_info_algs() :: [{kex, kex_alg()}
+                           | {hkey, pubkey_alg()}
+                           | {encrypt, cipher_alg()}
+                           | {decrypt, cipher_alg()}
+                           | {send_mac, mac_alg()}
+                           | {recv_mac, mac_alg()}
+                           | {compress, compression_alg()}
+                           | {decompress, compression_alg()}
+                           | {send_ext_info, boolean()}
+                           | {recv_ext_info, boolean()}
+                          ].
+-doc """
+Return values from the `connection_info/1` and `connection_info/2` functions.
+
+In the `option` info tuple are only the options included that differs from the
+default values.
+""".
+-doc(#{title => <<"Other data types">>}).
+-type conn_info_channels() :: [proplists:proplist()].
+
+-doc(#{title => <<"Other data types">>,equiv => conn_info_channels/0}).
+-type connection_info_tuple() ::
+        {client_version, version()}
+      | {server_version, version()}
+      | {user, string()}
+      | {peer, {inet:hostname(), ip_port()}}
+      | {sockname, ip_port()}
+      | {options, client_options()}
+      | {algorithms, conn_info_algs()}
+      | {channels, conn_info_channels()}.
+        
+-doc(#{equiv => connection_info/2}).
+-doc(#{since => <<"OTP 22.1">>}).
+-spec connection_info(ConnectionRef) -> InfoTupleList when
+      ConnectionRef :: connection_ref(),
+      InfoTupleList :: [InfoTuple],
+      InfoTuple :: connection_info_tuple().
+
+connection_info(ConnectionRef) ->                                      
+    connection_info(ConnectionRef, []).
+
+-doc """
+Returns information about a connection intended for e.g debugging or logging.
+
+When the `Key` is a single `Item`, the result is a single `InfoTuple`
+""".
+-spec connection_info(ConnectionRef, ItemList|Item) ->  InfoTupleList|InfoTuple when
+      ConnectionRef :: connection_ref(),
+      ItemList :: [Item],
+      Item :: client_version | server_version | user | peer | sockname | options | algorithms | sockname,
+      InfoTupleList :: [InfoTuple],
+      InfoTuple :: connection_info_tuple().
+
+connection_info(ConnectionRef, Key) ->
+    ssh_connection_handler:connection_info(ConnectionRef, Key).
+
+%%--------------------------------------------------------------------
+-doc false.
+-spec channel_info(connection_ref(), channel_id(), [atom()]) -> proplists:proplist().
+%%
+%% Description: Retrieves information about a connection.
+%%--------------------------------------------------------------------
+channel_info(ConnectionRef, ChannelId, Options) ->
+    ssh_connection_handler:channel_info(ConnectionRef, ChannelId, Options).
+
+%%--------------------------------------------------------------------
+%% Description: Starts a server listening for SSH connections
+%% on the given port.
+%%--------------------------------------------------------------------
+-doc(#{equiv => daemon/3}).
+-spec daemon(inet:port_number()) ->  {ok,daemon_ref()} | {error,term()}.
+
+daemon(Port) ->
+    daemon(Port, []).
+
+
+-doc(#{equiv => daemon/3}).
+-spec daemon(inet:port_number()|open_socket(), daemon_options()) -> {ok,daemon_ref()} | {error,term()}.
+
+daemon(Port, UserOptions) when 0 =< Port,Port =< 65535 ->
+    daemon(any, Port, UserOptions);
+
+daemon(Socket, UserOptions) ->
+    case ssh_options:handle_options(server, UserOptions) of
+        #{} = Options0 ->
+            case valid_socket_to_use(Socket, ?GET_OPT(transport,Options0)) of
+                ok ->
+                    try
+                        %% throws error:Error if no usable hostkey is found
+                        ssh_connection_handler:available_hkey_algorithms(server, Options0),
+                        {ok, {SockHost,SockPort}} = inet:sockname(Socket),
+                        Address = #address{address = SockHost,
+                                           port = SockPort,
+                                           profile = ?GET_OPT(profile,Options0)
+                                          },
+                        Options = ?PUT_INTERNAL_OPT({connected_socket, Socket}, Options0),
+                        case ssh_system_sup:start_subsystem(server, Address, Socket, Options) of
+                            {ok,Pid} ->
+                                {ok,Pid};
+                            {error, {already_started, _}} ->
+                                {error, eaddrinuse};
+                            {error, Error} ->
+                                {error, Error}
+                        end
+                    catch
+                        error:{shutdown,Err} ->
+                            {error,Err};
+                        exit:{noproc, _} ->
+                            {error, ssh_not_started};
+                        C:R ->
+                            {error,{could_not_start_connection,{C,R}}}
+                    end;
+
+                {error,SockError} ->
+                    {error,SockError}
+            end;
+
+        {error,OptionError} ->
+            {error,OptionError}
+    end.
+
+
+
+-doc """
+daemon(HostAddress, Port, Options) -> Result
+
+Starts a server listening for SSH connections on the given port. If the `Port`
+is 0, a random free port is selected. See `daemon_info/1` about how to find the
+selected port number.
+
+As an alternative, an already open TCP socket could be passed to the function in
+`TcpSocket`. The SSH initiation and negotiation will be initiated on that one
+when an SSH starts at the other end of the TCP socket.
+
+For a description of the options, see [Daemon Options](`t:daemon_options/0`).
+
+Please note that by historical reasons both the `HostAddress` argument and the
+[gen_tcp connect_option() `{ip,Address}`](`t:gen_tcp:connect_option/0`) set the
+listening address. This is a source of possible inconsistent settings.
+
+The rules for handling the two address passing options are:
+
+- if `HostAddress` is an IP-address, that IP-address is the listening address.
+  An 'ip'-option will be discarded if present.
+- if `HostAddress` is the atom `loopback`, the listening address is `loopback`
+  and an loopback address will be chosen by the underlying layers. An
+  'ip'-option will be discarded if present.
+- if `HostAddress` is the atom `any` and no 'ip'-option is present, the
+  listening address is `any` and the socket will listen to all addresses
+- if `HostAddress` is `any` and an 'ip'-option is present, the listening address
+  is set to the value of the 'ip'-option
+""".
+-spec daemon(any | inet:ip_address(), inet:port_number(), daemon_options()) -> {ok,daemon_ref()} | {error,term()}
+           ;(socket, open_socket(), daemon_options()) -> {ok,daemon_ref()} | {error,term()}
+            .
+
+daemon(Host0, Port0, UserOptions0) when 0 =< Port0, Port0 =< 65535,
+                                        Host0 == any ; Host0 == loopback ; is_tuple(Host0) ->
+    try
+        {Host1, UserOptions} = handle_daemon_args(Host0, UserOptions0),
+        #{} = Options0 = ssh_options:handle_options(server, UserOptions),
+        %% We need to open the listen socket here before start of the system supervisor. That
+        %% is because Port0 might be 0, or if an FD is provided in the Options0, in which case
+        %% the real listening port will be known only after the gen_tcp:listen call.
+        maybe_open_listen_socket(Host1, Port0, Options0)
+    of
+        {Host, Port, ListenSocket, Options1} ->
+            try
+                %% Now Host,Port is what to use for the supervisor to register its name,
+                %% and ListenSocket, if provided,  is for listening on connections. But
+                %% it is still owned by self()...
+
+                %% throws error:Error if no usable hostkey is found
+                ssh_connection_handler:available_hkey_algorithms(server, Options1),
+                ssh_system_sup:start_system(server,
+                                            #address{address = Host,
+                                                     port = Port,
+                                                     profile = ?GET_OPT(profile,Options1)},
+                                            Options1)
+            of
+                {ok,DaemonRef} when ListenSocket == undefined ->
+                    {ok,DaemonRef};
+                {ok,DaemonRef} ->
+                    receive
+                        {request_control, ListenSocket, ReqPid} ->
+                            ok = controlling_process(ListenSocket, ReqPid, Options1),
+                            ReqPid ! {its_yours,ListenSocket}
+                    end,
+                    {ok,DaemonRef};
+                {error, {already_started, _}} ->
+                    close_listen_socket(ListenSocket, Options1),
+                    {error, eaddrinuse};
+                {error, Error} ->
+                    close_listen_socket(ListenSocket, Options1),
+                    {error, Error}
+            catch
+                error:{shutdown,Err} ->
+                    close_listen_socket(ListenSocket, Options1),
+                    {error,Err};
+                exit:{noproc, _} ->
+                    close_listen_socket(ListenSocket, Options1),
+                    {error, ssh_not_started};
+                error:Error ->
+                    close_listen_socket(ListenSocket, Options1),
+                    error(Error);
+                exit:Exit ->
+                    close_listen_socket(ListenSocket, Options1),
+                    exit(Exit)
+            end
+    catch
+        throw:bad_fd ->
+            {error,bad_fd};
+        throw:bad_socket ->
+            {error,bad_socket};
+        error:{badmatch,{error,Error}} ->
+            {error,Error};
+        error:Error ->
+            {error,Error};
+        _C:_E ->
+            {error,{cannot_start_daemon,_C,_E}}
+    end;
+
+daemon(_, _, _) ->
+    {error, badarg}.
+
+%%--------------------------------------------------------------------
+-doc """
+Replaces the options in a running daemon with the options in `NewUserOptions`.
+Only connections established after this call are affected, already established
+connections are not.
+
+> #### Note {: .info }
+>
+> In the final phase of this function, the listening process is restarted.
+> Therfore a connection attempt to the daemon in this final phase could fail.
+
+The handling of Erlang configurations is described in the User's Guide; see
+chapters [Configuration in SSH](configurations.md) and
+[Configuring algorithms in SSH](configure_algos.md).
+""".
+-doc(#{since => <<"OTP 25.1">>}).
+-spec daemon_replace_options(DaemonRef, NewUserOptions) -> {ok,daemon_ref()}
+                                                         | {error,term()} when
+      DaemonRef :: daemon_ref(),
+      NewUserOptions :: daemon_options().
+
+daemon_replace_options(DaemonRef, NewUserOptions) ->
+    {ok,Os0} = ssh_system_sup:get_acceptor_options(DaemonRef),
+    Os1 = ssh_options:merge_options(server, NewUserOptions, Os0),
+    ssh_system_sup:replace_acceptor_options(DaemonRef, Os1).
+
+%%--------------------------------------------------------------------
+-doc """
+Return values from the `daemon_info/1` and `daemon_info/2` functions.
+
+In the `option` info tuple are only the options included that differs from the
+default values.
+""".
+-doc(#{title => <<"Other data types">>}).
+-type daemon_info_tuple() ::
+        {port, inet:port_number()}
+      | {ip, inet:ip_address()}
+      | {profile, atom()}
+      | {options, daemon_options()}.
+
+-doc(#{equiv => daemon_info/2}).
+-doc(#{since => <<"OTP 19.0">>}).
+-spec daemon_info(DaemonRef) -> {ok,InfoTupleList} | {error,bad_daemon_ref} when
+      DaemonRef :: daemon_ref(),
+      InfoTupleList :: [InfoTuple],
+      InfoTuple :: daemon_info_tuple().
+
+daemon_info(DaemonRef) ->
+    case ssh_system_sup:get_daemon_listen_address(DaemonRef) of
+        {ok,A} ->
+            Address =
+                case inet:parse_strict_address(A#address.address) of
+                    {ok,IP} -> A#address{address=IP};
+                    _ -> A
+                end,
+            Opts =
+                %% Pick a subset of the Options to present:
+                case ssh_system_sup:get_options(DaemonRef, Address) of
+                    {ok, OptMap} ->
+                        lists:sort(
+                          maps:to_list(
+                            ssh_options:keep_set_options(
+                              server,
+                              ssh_options:keep_user_options(server,OptMap))));
+                    _ ->
+                        []
+                end,
+            
+	    {ok, [{port,    Address#address.port},
+                  {ip,      Address#address.address},
+                  {profile, Address#address.profile},
+                  {options, Opts}
+                 ]};
+        
+	_ ->
+	    {error,bad_daemon_ref}
+    end.
+
+-doc """
+Returns information about a daemon intended for e.g debugging or logging.
+
+When the `Key` is a single `Item`, the result is a single `InfoTuple`
+
+Note that [`daemon_info/1`](`daemon_info/1`) and
+[`daemon_info/2`](`daemon_info/2`) returns different types due to compatibility
+reasons.
+""".
+-doc(#{since => <<"OTP 22.1">>}).
+-spec daemon_info(DaemonRef, ItemList|Item) ->  InfoTupleList|InfoTuple | {error,bad_daemon_ref} when
+      DaemonRef :: daemon_ref(),
+      ItemList :: [Item],
+      Item :: ip | port | profile | options,
+      InfoTupleList :: [InfoTuple],
+      InfoTuple :: daemon_info_tuple().
+
+daemon_info(DaemonRef, Key) when is_atom(Key) ->
+    case daemon_info(DaemonRef, [Key]) of
+        [{Key,Val}] -> {Key,Val};
+        Other -> Other
+    end;
+daemon_info(DaemonRef, Keys) ->
+    case daemon_info(DaemonRef) of
+        {ok,KVs} ->
+            [{Key,proplists:get_value(Key,KVs)} || Key <- Keys,
+                                                   lists:keymember(Key,1,KVs)];
+        _ ->
+            []
+    end.
+
+%%--------------------------------------------------------------------
+%% Description: Stops the listener, but leaves
+%% existing connections started by the listener up and running.
+%%--------------------------------------------------------------------
+-doc(#{equiv => stop_listener/3}).
+-spec stop_listener(daemon_ref()) -> ok.
+
+stop_listener(SysSup) ->
+    ssh_system_sup:stop_listener(SysSup).
+
+
+-doc(#{equiv => stop_listener/3}).
+-spec stop_listener(inet:ip_address(), inet:port_number()) -> ok.
+
+stop_listener(Address, Port) ->
+    stop_listener(Address, Port, ?DEFAULT_PROFILE).
+
+
+-doc """
+Stops the listener, but leaves existing connections started by the listener
+operational.
+""".
+-doc(#{since => <<"OTP 21.0">>}).
+-spec stop_listener(any|inet:ip_address(), inet:port_number(), term()) -> ok.
+
+stop_listener(Address, Port, Profile) ->
+    lists:foreach(fun({Sup,_Addr}) ->
+                          stop_listener(Sup)
+                  end,
+                  ssh_system_sup:addresses(server,
+                                           #address{address=Address,
+                                                    port=Port,
+                                                    profile=Profile})).
+
+-doc(#{equiv => stop_daemon/3}).
+-spec stop_daemon(DaemonRef::daemon_ref()) -> ok.
+
+stop_daemon(SysSup) ->
+    ssh_system_sup:stop_system(server, SysSup).
+
+
+-doc(#{equiv => stop_daemon/3}).
+-spec stop_daemon(inet:ip_address(), inet:port_number()) -> ok.
+
+stop_daemon(Address, Port) ->
+    stop_daemon(Address, Port, ?DEFAULT_PROFILE).
+
+
+-doc "Stops the listener and all connections started by the listener.".
+-doc(#{since => <<"OTP 21.0">>}).
+-spec stop_daemon(any|inet:ip_address(), inet:port_number(), atom()) -> ok.
+
+stop_daemon(Address, Port, Profile) ->
+    lists:foreach(fun({Sup,_Addr}) ->
+                          stop_daemon(Sup)
+                  end,
+                  ssh_system_sup:addresses(server,
+                                           #address{address=Address,
+                                                    port=Port,
+                                                    profile=Profile})).
+
+%%--------------------------------------------------------------------
+%% Description: Starts an interactive shell to an SSH server on the
+%% given <Host>. The function waits for user input,
+%% and will not return until the remote shell is ended.(e.g. on
+%% exit from the shell)
+%%--------------------------------------------------------------------
+-doc(#{equiv => shell/3}).
+-spec shell(open_socket() | host() | connection_ref()) ->  _.
+
+shell(ConnectionRef) when is_pid(ConnectionRef) ->
+    case ssh_connection:session_channel(ConnectionRef, infinity) of
+	{ok,ChannelId}  ->
+	    success = ssh_connection:ptty_alloc(ConnectionRef, ChannelId,
+                                                [{pty_opts, [{echo,0}]}
+                                                ]),
+            success = ssh_connection:send_environment_vars(ConnectionRef, ChannelId,
+                                                           ["LANG", "LC_ALL"]),
+	    Args = [{channel_cb, ssh_shell},
+		    {init_args,[ConnectionRef, ChannelId]},
+		    {cm, ConnectionRef}, {channel_id, ChannelId}],
+	    {ok, State} = ssh_client_channel:init([Args]),
+            try
+                ssh_client_channel:enter_loop(State)
+            catch
+                exit:normal ->
+                    ok
+            end;
+	Error ->
+	    Error
+    end;
+
+shell(Dest) ->
+    case is_host(Dest, []) of
+        true ->
+            shell(Dest, ?SSH_DEFAULT_PORT, []);
+        false ->
+            %% Maybe socket
+            shell_socket(Dest, [])
+    end.
+
+
+
+-doc(#{equiv => shell/3}).
+-spec shell(open_socket() | host(), client_options()) ->  _.
+
+shell(Dest, Options) ->
+    case is_host(Dest, Options) of
+        true ->
+            shell(Dest, ?SSH_DEFAULT_PORT, Options);
+        false ->
+            %% Maybe socket
+            shell_socket(Dest, Options)
+    end.
+
+shell_socket(Socket, Options) ->
+    case connect(Socket, Options) of
+        {ok,ConnectionRef} ->
+            shell(ConnectionRef),
+            close(ConnectionRef);
+        Error ->
+            Error
+    end.
+    
+
+
+-doc """
+shell(Host, Port, Options) -> Result
+
+Connects to an SSH server at `Host` and `Port` (defaults to 22) and starts an
+interactive shell on that remote host.
+
+As an alternative, an already open TCP socket could be passed to the function in
+`TcpSocket`. The SSH initiation and negotiation will be initiated on that one
+and finally a shell will be started on the host at the other end of the TCP
+socket.
+
+For a description of the options, see [Client Options](`t:client_options/0`).
+
+The function waits for user input, and does not return until the remote shell is
+ended (that is, exit from the shell).
+""".
+-spec shell(Host, Port, Options) -> _ when
+      Host :: host(),
+      Port :: inet:port_number(),
+      Options :: client_options() .
+
+shell(Host, Port, Options) ->
+    case connect(Host, Port, Options) of
+        {ok,ConnectionRef} ->
+            shell(ConnectionRef),
+            close(ConnectionRef);
+        Error ->
+            Error
+    end.
+
+%%--------------------------------------------------------------------
+-doc """
+Returns a key-value list, where the keys are the different types of algorithms
+and the values are the algorithms themselves.
+
+See the [User's Guide](configure_algos.md#example_default_algorithms) for an
+example.
+""".
+-doc(#{since => <<"OTP 18.0">>}).
+-spec default_algorithms() -> algs_list() .
+%%--------------------------------------------------------------------
+default_algorithms() ->
+    ssh_transport:default_algorithms().
+
+%%--------------------------------------------------------------------
+-doc false.
+-spec chk_algos_opts(client_options()|daemon_options()) -> internal_options() | {error,term()}.
+%%--------------------------------------------------------------------
+chk_algos_opts(Opts) ->
+    case lists:foldl(
+           fun({preferred_algorithms,_}, Acc) -> Acc;
+              ({modify_algorithms,_}, Acc) -> Acc;
+              (KV, Acc) -> [KV|Acc]
+           end, [], Opts)
+    of
+        [] ->
+            case ssh_options:handle_options(client, Opts) of
+                M when is_map(M) ->
+                    maps:get(preferred_algorithms, M);
+                Others ->
+                    Others
+            end;
+        OtherOps ->
+            {error, {non_algo_opts_found,OtherOps}}
+    end.
+
+
+%%--------------------------------------------------------------------
+-doc """
+Sets tcp socket options on the tcp-socket below an ssh connection.
+
+This function calls the `inet:setopts/2`, read that documentation and for
+`t:gen_tcp:option/0`.
+
+All gen_tcp socket options except
+
+- `active`
+- `deliver`
+- `mode` and
+- `packet`
+
+are allowed. The excluded options are reserved by the SSH application.
+
+> #### Warning {: .warning }
+>
+> This is an extremely dangerous function. You use it on your own risk.
+>
+> Some options are OS and OS version dependent. Do not use it unless you know
+> what effect your option values will have on an TCP stream.
+>
+> Some values may destroy the functionality of the SSH protocol.
+""".
+-doc(#{since => <<"OTP 22.3">>}).
+-spec set_sock_opts(ConnectionRef, SocketOptions) ->
+                           ok | {error, inet:posix()}  when
+      ConnectionRef :: connection_ref(),
+      SocketOptions :: [gen_tcp:option()] .
+%%--------------------------------------------------------------------
+set_sock_opts(ConnectionRef, SocketOptions) ->
+    ssh_connection_handler:set_sock_opts(ConnectionRef, SocketOptions).
+
+%%--------------------------------------------------------------------
+-doc """
+Get tcp socket option values of the tcp-socket below an ssh connection.
+
+This function calls the `inet:getopts/2`, read that documentation.
+""".
+-doc(#{since => <<"OTP 22.3">>}).
+-spec get_sock_opts(ConnectionRef, SocketGetOptions) ->
+                           ok | {error, inet:posix()}  when
+      ConnectionRef :: connection_ref(),
+      SocketGetOptions :: [gen_tcp:option_name()] .
+%%--------------------------------------------------------------------
+get_sock_opts(ConnectionRef, SocketGetOptions) ->
+    ssh_connection_handler:get_sock_opts(ConnectionRef, SocketGetOptions).
+
+%%--------------------------------------------------------------------
+%% Ask local client to listen to ListenHost:ListenPort.  When someone
+%% connects that address, connect to ConnectToHost:ConnectToPort from
+%% the server.
+%%--------------------------------------------------------------------
+-doc(#{equiv => tcpip_tunnel_to_server/6}).
+-doc(#{since => <<"OTP 23.0">>}).
+-spec tcpip_tunnel_to_server(ConnectionRef,
+                             ListenHost, ListenPort,
+                             ConnectToHost, ConnectToPort
+                          ) ->
+                                  {ok,TrueListenPort} | {error, term()} when
+      ConnectionRef :: connection_ref(),
+      ListenHost :: host(),
+      ListenPort :: inet:port_number(),
+      ConnectToHost :: host(),
+      ConnectToPort :: inet:port_number(),
+      TrueListenPort :: inet:port_number().
+
+tcpip_tunnel_to_server(ConnectionHandler, ListenHost, ListenPort, ConnectToHost, ConnectToPort) ->
+    tcpip_tunnel_to_server(ConnectionHandler, ListenHost, ListenPort, ConnectToHost, ConnectToPort, infinity).
+
+
+-doc """
+Tells the local client to listen to `ListenHost:ListenPort`. When someone
+connects to that address, the connection is forwarded in an encrypted channel to
+the peer server of `ConnectionRef`. That server then connects to
+`ConnectToHost:ConnectToPort`.
+
+The returned `TrueListenPort` is the port that is listened to. It is the same as
+`ListenPort`, except when `ListenPort = 0`. In that case a free port is selected
+by the underlying OS.
+
+Note that in case of an Erlang/OTP SSH server (daemon) as peer, that server must
+have been started with the option
+[tcpip_tunnel_in](`t:tcpip_tunnel_in_daemon_option/0`) to allow the connection.
+""".
+-doc(#{since => <<"OTP 23.0">>}).
+-spec tcpip_tunnel_to_server(ConnectionRef,
+                             ListenHost, ListenPort,
+                             ConnectToHost, ConnectToPort,
+                             Timeout) ->
+                                  {ok,TrueListenPort} | {error, term()} when
+      ConnectionRef :: connection_ref(),
+      ListenHost :: host(),
+      ListenPort :: inet:port_number(),
+      ConnectToHost :: host(),
+      ConnectToPort :: inet:port_number(),
+      Timeout :: timeout(),
+      TrueListenPort :: inet:port_number().
+
+tcpip_tunnel_to_server(ConnectionHandler, ListenHost, ListenPort, ConnectToHost0, ConnectToPort, Timeout) ->
+    SockOpts = [],
+    try
+        list_to_binary(
+          case mangle_connect_address(ConnectToHost0,SockOpts) of
+              IP when is_tuple(IP) -> inet_parse:ntoa(IP);
+              _ when is_list(ConnectToHost0) -> ConnectToHost0
+          end)
+    of
+        ConnectToHost ->
+            ssh_connection_handler:handle_direct_tcpip(ConnectionHandler,
+                                                       mangle_tunnel_address(ListenHost), ListenPort,
+                                                       ConnectToHost, ConnectToPort,
+                                                       Timeout)
+    catch
+        _:_ ->
+            {error, bad_connect_to_address}
+    end.
+
+%%--------------------------------------------------------------------
+%% Ask remote server to listen to ListenHost:ListenPort.  When someone
+%% connects that address, connect to ConnectToHost:ConnectToPort from
+%% the client.
+%%--------------------------------------------------------------------
+-doc(#{equiv => tcpip_tunnel_from_server/6}).
+-doc(#{since => <<"OTP 23.0">>}).
+-spec tcpip_tunnel_from_server(ConnectionRef,
+                               ListenHost, ListenPort,
+                               ConnectToHost, ConnectToPort
+                              ) ->
+                                    {ok,TrueListenPort} | {error, term()} when
+      ConnectionRef :: connection_ref(),
+      ListenHost :: host(),
+      ListenPort :: inet:port_number(),
+      ConnectToHost :: host(),
+      ConnectToPort :: inet:port_number(),
+      TrueListenPort :: inet:port_number().
+
+tcpip_tunnel_from_server(ConnectionRef, ListenHost, ListenPort, ConnectToHost, ConnectToPort) ->
+    tcpip_tunnel_from_server(ConnectionRef, ListenHost, ListenPort, ConnectToHost, ConnectToPort, infinity).
+
+-doc """
+Asks the remote server of `ConnectionRef` to listen to `ListenHost:ListenPort`.
+When someone connects that address, the connection is forwarded in an encrypted
+channel from the server to the client. The client (that is, at the node that
+calls this function) then connects to `ConnectToHost:ConnectToPort`.
+
+The returned `TrueListenPort` is the port that is listened to. It is the same as
+`ListenPort`, except when `ListenPort = 0`. In that case a free port is selected
+by the underlying OS.
+
+Note that in case of an Erlang/OTP SSH server (daemon) as peer, that server must
+have been started with the option
+[tcpip_tunnel_out](`t:tcpip_tunnel_out_daemon_option/0`) to allow the
+connection.
+""".
+-doc(#{since => <<"OTP 23.0">>}).
+-spec tcpip_tunnel_from_server(ConnectionRef,
+                               ListenHost, ListenPort,
+                               ConnectToHost, ConnectToPort,
+                               Timeout) ->
+                                    {ok,TrueListenPort} | {error, term()} when
+      ConnectionRef :: connection_ref(),
+      ListenHost :: host(),
+      ListenPort :: inet:port_number(),
+      ConnectToHost :: host(),
+      ConnectToPort :: inet:port_number(),
+      Timeout :: timeout(),
+      TrueListenPort :: inet:port_number().
+
+tcpip_tunnel_from_server(ConnectionRef, ListenHost0, ListenPort, ConnectToHost0, ConnectToPort, Timeout) ->
+    SockOpts = [],
+    ListenHost = mangle_tunnel_address(ListenHost0),
+    ConnectToHost = mangle_connect_address(ConnectToHost0, SockOpts),
+    case ssh_connection_handler:global_request(ConnectionRef, "tcpip-forward", true, 
+                                               {ListenHost,ListenPort,ConnectToHost,ConnectToPort},
+                                               Timeout) of
+        {success,<<>>} ->
+            {ok, ListenPort};
+        {success,<<TruePort:32/unsigned-integer>>} when ListenPort==0 ->
+            {ok, TruePort};
+        {success,_} = Res ->
+            {error, {bad_result,Res}};
+        {failure,<<>>} ->
+            {error,not_accepted};
+        {failure,Error} ->
+            {error,Error};
+        Other ->
+            Other
+    end.
+
+%%--------------------------------------------------------------------
+%% In move from public_key
+%%--------------------------------------------------------------------
+-doc(#{equiv => hostkey_fingerprint/2}).
+-doc(#{since => <<"OTP 24.0">>}).
+-spec hostkey_fingerprint(public_key:public_key()) -> string().
+
+hostkey_fingerprint(Key) ->
+    sshfp_string(md5, ssh_message:ssh2_pubkey_encode(Key) ).
+
+-doc """
+hostkey_fingerprint([DigestType], HostKey) ->
+[string()]hostkey_fingerprint(DigestType, HostKey) -> string()
+
+Calculates a ssh fingerprint from a public host key as openssh does.
+
+The algorithm in [`hostkey_fingerprint/1`](`hostkey_fingerprint/1`) is md5 to be
+compatible with older ssh-keygen commands. The string from the second variant is
+prepended by the algorithm name in uppercase as in newer ssh-keygen commands.
+
+Examples:
+
+```erlang
+ 2> ssh:hostkey_fingerprint(Key).
+ "f5:64:a6:c1:5a:cb:9f:0a:10:46:a2:5c:3e:2f:57:84"
+
+ 3> ssh:hostkey_fingerprint(md5,Key).
+ "MD5:f5:64:a6:c1:5a:cb:9f:0a:10:46:a2:5c:3e:2f:57:84"
+
+ 4> ssh:hostkey_fingerprint(sha,Key).
+ "SHA1:bSLY/C4QXLDL/Iwmhyg0PGW9UbY"
+
+ 5> ssh:hostkey_fingerprint(sha256,Key).
+ "SHA256:aZGXhabfbf4oxglxltItWeHU7ub3Dc31NcNw2cMJePQ"
+
+ 6> ssh:hostkey_fingerprint([sha,sha256],Key).
+ ["SHA1:bSLY/C4QXLDL/Iwmhyg0PGW9UbY",
+  "SHA256:aZGXhabfbf4oxglxltItWeHU7ub3Dc31NcNw2cMJePQ"]
+```
+""".
+-doc(#{since => <<"OTP 24.0">>}).
+-spec hostkey_fingerprint(TypeOrTypes, Key) -> StringOrString
+                                                   when
+      TypeOrTypes :: public_key:digest_type() | [public_key:digest_type()],
+      Key :: public_key:public_key(),
+      StringOrString :: string() | [string()] .
+
+hostkey_fingerprint(HashAlgs, Key) when is_list(HashAlgs) ->
+    EncKey = ssh_message:ssh2_pubkey_encode(Key),
+    [sshfp_full_string(HashAlg,EncKey) || HashAlg <- HashAlgs];
+hostkey_fingerprint(HashAlg, Key) when is_atom(HashAlg) ->
+    EncKey = ssh_message:ssh2_pubkey_encode(Key),
+    sshfp_full_string(HashAlg, EncKey).
+
+
+sshfp_string(HashAlg, EncodedKey) ->
+    %% Other HashAlgs than md5 will be printed with
+    %% other formats than hextstr by
+    %%    ssh-keygen -E <alg> -lf <file>
+    fp_fmt(sshfp_fmt(HashAlg), crypto:hash(HashAlg, EncodedKey)).
+
+sshfp_full_string(HashAlg, EncKey) ->
+    lists:concat([sshfp_alg_name(HashAlg),
+		  [$: | sshfp_string(HashAlg, EncKey)]
+		 ]).
+
+sshfp_alg_name(sha) -> "SHA1";
+sshfp_alg_name(Alg) -> string:to_upper(atom_to_list(Alg)).
+
+sshfp_fmt(md5) -> hexstr;
+sshfp_fmt(_) -> b64.
+
+fp_fmt(hexstr, Bin) ->
+    lists:flatten(string:join([io_lib:format("~2.16.0b",[C1]) || <<C1>> <= Bin], ":"));
+fp_fmt(b64, Bin) ->
+    %% This function clause *seems* to be
+    %%    [C || C<-base64:encode_to_string(Bin), C =/= $=]
+    %% but I am not sure. Must be checked.
+    B64Chars = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/",
+    BitsInLast = 8*byte_size(Bin) rem 6,
+    Padding = (6-BitsInLast) rem 6, % Want BitsInLast = [1:5] to map to padding [5:1] and 0 -> 0
+    [lists:nth(C+1,B64Chars) || <<C:6>> <= <<Bin/binary,0:Padding>> ].
+
+%%--------------------------------------------------------------------
+%%% Internal functions
+%%--------------------------------------------------------------------
+%% The handle_daemon_args/2 function basically only sets the ip-option in Opts
+%% so that it is correctly set when opening the listening socket.
+
+handle_daemon_args(any, Opts) ->
+    case proplists:get_value(ip, Opts) of
+        undefined -> {any, Opts};
+        IP -> {IP, Opts}
+    end;
+
+handle_daemon_args(IPaddr, Opts) when is_tuple(IPaddr) ; IPaddr == loopback ->
+    case proplists:get_value(ip, Opts) of
+        undefined -> {IPaddr, [{ip,IPaddr}|Opts]};
+        IPaddr -> {IPaddr, Opts};
+        IP -> {IPaddr, [{ip,IPaddr}|Opts--[{ip,IP}]]} %% Backward compatibility
+    end.
+
+%%%----------------------------------------------------------------
+valid_socket_to_use(Socket, {tcp,_,_}) ->
+    %% Is this tcp-socket a valid socket?
+    try {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}
+    catch
+        _:_ ->           {error, bad_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.
+
+%%%----------------------------------------------------------------
+maybe_open_listen_socket(Host, Port, Options) ->
+    Opened =
+        case ?GET_SOCKET_OPT(fd, Options) of
+            undefined when Port == 0 ->
+                ssh_acceptor:listen(0, Options);
+            Fd when is_integer(Fd) ->
+                %% Do gen_tcp:listen with the option {fd,Fd}:
+                ssh_acceptor:listen(0, Options);
+            undefined ->
+                open_later
+        end,
+    case Opened of
+        {ok,LSock} ->
+            {ok,{LHost,LPort}} = inet:sockname(LSock),
+            {LHost, LPort, LSock, ?PUT_INTERNAL_OPT({lsocket,{LSock,self()}}, Options)};
+        open_later ->
+            {Host, Port, undefined, Options};
+        Others ->
+            Others
+    end.
+
+%%%----------------------------------------------------------------
+close_listen_socket(ListenSocket, Options) ->
+    try
+        {_, Callback, _} = ?GET_OPT(transport, Options),
+        Callback:close(ListenSocket)
+    catch
+        _C:_E -> ok
+    end.
+
+controlling_process(ListenSocket, ReqPid, Options) ->
+    {_, Callback, _} = ?GET_OPT(transport, Options),
+    Callback:controlling_process(ListenSocket, ReqPid).
+
+transport_connect(Host, Port, SocketOpts, Options) ->
+    {_, Callback, _} = ?GET_OPT(transport, Options),
+    Callback:connect(Host, Port, SocketOpts, ?GET_OPT(connect_timeout,Options)).
+    
+%%%----------------------------------------------------------------
+-doc false.
+is_host(X, Opts) ->
+    try is_host1(mangle_connect_address(X, Opts))
+    catch
+        _:_ -> false
+    end.
+            
+
+is_host1(L) when is_list(L) -> true; %% "string()"
+is_host1(T) when tuple_size(T)==4 -> lists:all(fun(I) -> 0=<I andalso I=<255 end,
+                                               tuple_to_list(T));
+is_host1(T) when tuple_size(T)==16 -> lists:all(fun(I) -> 0=<I andalso I=<65535 end,
+                                                tuple_to_list(T));
+is_host1(loopback) -> true.
+
+%%%----------------------------------------------------------------
+mangle_connect_address(A,  #{socket_options := SockOpts}) ->
+    mangle_connect_address(A, SockOpts);
+mangle_connect_address(A, SockOpts) ->
+    mangle_connect_address1(A, proplists:get_value(inet6,SockOpts,false)).
+
+loopback(true) -> {0,0,0,0,0,0,0,1};
+loopback(false) ->      {127,0,0,1}.
+
+mangle_connect_address1( loopback,     V6flg) -> loopback(V6flg);
+mangle_connect_address1(      any,     V6flg) -> loopback(V6flg);
+mangle_connect_address1({0,0,0,0},         _) -> loopback(false);
+mangle_connect_address1({0,0,0,0,0,0,0,0}, _) -> loopback(true);
+mangle_connect_address1(       IP,     _) when is_tuple(IP) -> IP;
+mangle_connect_address1(A, _) ->
+    case catch inet:parse_address(A) of
+        {ok,         {0,0,0,0}} -> loopback(false);
+        {ok, {0,0,0,0,0,0,0,0}} -> loopback(true);
+        _ -> A
+    end.
+
+%%%----------------------------------------------------------------
+mangle_tunnel_address(any) -> <<"">>;
+mangle_tunnel_address(loopback) -> <<"localhost">>;
+mangle_tunnel_address({0,0,0,0}) -> <<"">>;
+mangle_tunnel_address({0,0,0,0,0,0,0,0}) -> <<"">>;
+mangle_tunnel_address(IP) when is_tuple(IP) -> list_to_binary(inet_parse:ntoa(IP));
+mangle_tunnel_address(A) when is_atom(A) -> mangle_tunnel_address(atom_to_list(A));
+mangle_tunnel_address(X) when is_list(X) -> case catch inet:parse_address(X) of
+                                     {ok, {0,0,0,0}} -> <<"">>;
+                                     {ok, {0,0,0,0,0,0,0,0}} -> <<"">>;
+                                     _ -> list_to_binary(X)
+                                 end.
+
+
+%%%################################################################
+%%%#
+%%%# Tracing
+%%%#
+
+-doc false.
+ssh_dbg_trace_points() -> [tcp].
+
+-doc false.
+ssh_dbg_flags(tcp) -> [c].
+
+-doc false.
+ssh_dbg_on(tcp) -> dbg:tpl(?MODULE, controlling_process, 3, x),
+                   dbg:tpl(?MODULE, transport_connect, 4, x),
+                   dbg:tpl(?MODULE, close_listen_socket, 2, x).
+                   
+-doc false.
+ssh_dbg_off(tcp) ->dbg:ctpl(?MODULE, controlling_process, 3),
+                   dbg:ctpl(?MODULE, transport_connect, 4),
+                   dbg:ctpl(?MODULE, close_listen_socket, 2).
+
+-doc false.
+ssh_dbg_format(tcp, {call, {?MODULE,controlling_process, [ListenSocket, ReqPid, _Opts]}}) ->
+    ["TCP socket transferred to\n",
+     io_lib:format("Sock: ~p~n"
+                   "ToPid: ~p~n", [ListenSocket, ReqPid])
+    ];
+ssh_dbg_format(tcp, {return_from, {?MODULE,controlling_process,3}, _Result}) ->
+    skip;
+
+ssh_dbg_format(tcp, {call, {?MODULE,close_listen_socket, [ListenSocket, _Opts]}}) ->
+    ["TCP socket listening closed\n",
+     io_lib:format("Sock: ~p~n", [ListenSocket])
+    ];
+ssh_dbg_format(tcp, {return_from, {?MODULE,close_listen_socket,2}, _Result}) ->
+    skip.
+
+
+-doc false.
+ssh_dbg_format(tcp, {call, {?MODULE,transport_connect, [Host,Port,SockOpts,_Opts]}}, Stack) ->
+    {skip, [{transport_connect,Host,Port,SockOpts}|Stack]};
+ssh_dbg_format(tcp, {return_from, {?MODULE,transport_connect,4}, {ok,Sock}},
+               [{transport_connect,Host,Port,SockOpts}|Stack]) ->
+    {["TCP connected to\n",
+      io_lib:format("Host: ~p~n"
+                    "Port: ~p~n"
+                    "SockOpts: ~p~n"
+                    "Socket: ~p~n", [Host,Port,SockOpts,Sock])
+     ],
+     Stack};
+ssh_dbg_format(tcp, {return_from, {?MODULE,transport_connect,4}, Result},
+               [{transport_connect,Host,Port,SockOpts}|Stack]) ->
+    {["TCP connected FAILED to\n",
+      io_lib:format("Host: ~p~n"
+                    "Port: ~p~n"
+                    "SockOpts: ~p~n"
+                    "Result: ~p~n", [Host,Port,SockOpts,Result])
+     ],
+     Stack}.
diff --git a/lib/compiler/test/compile_SUITE_data/ssh.hrl b/lib/compiler/test/compile_SUITE_data/ssh.hrl
new file mode 100644
index 0000000000..f78a6e4cea
--- /dev/null
+++ b/lib/compiler/test/compile_SUITE_data/ssh.hrl
@@ -0,0 +1,1342 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2004-2024. 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%
+%%
+
+%%
+
+%%
+%% SSH definitions
+%%
+
+-ifndef(SSH_HRL).
+-define(SSH_HRL, 1).
+
+-define(SSH_DEFAULT_PORT, 22).
+-define(SSH_MAX_PACKET_SIZE, (256*1024)).
+-define(REKEY_DATA_TIMOUT, 60000).
+-define(DEFAULT_PROFILE, default).
+
+-define(DEFAULT_TRANSPORT,  {tcp, gen_tcp, tcp_closed} ).
+
+-define(DEFAULT_SHELL, {shell, start, []} ).
+
+-define(DEFAULT_TIMEOUT, 5000).
+
+-define(MAX_RND_PADDING_LEN, 15).
+
+-define(SUPPORTED_AUTH_METHODS, "publickey,keyboard-interactive,password").
+
+-define(FALSE, 0).
+-define(TRUE,  1).
+%% basic binary constructors
+-define(BOOLEAN(X),  (X):8/unsigned-big-integer).
+-define(BYTE(X),     (X):8/unsigned-big-integer).
+-define(UINT16(X),   (X):16/unsigned-big-integer).
+-define(UINT32(X),   (X):32/unsigned-big-integer).
+-define(UINT64(X),   (X):64/unsigned-big-integer).
+-define(STRING(X),   ?UINT32((byte_size(X))), (X)/binary).
+
+-define(DEC_BIN(X,Len),   ?UINT32(Len), X:Len/binary ).
+-define(DEC_INT(I,Len),   ?UINT32(Len), I:Len/big-signed-integer-unit:8 ).
+-define(DEC_MPINT(I,Len), ?UINT32(Len), I:Len/big-signed-integer-unit:8 ).
+
+%% building macros
+-define(boolean(X),
+	case X of
+	    true -> <<?BOOLEAN(1)>>;
+	    false -> (<<?BOOLEAN(0)>>)
+	end).
+
+-define(byte(X),   << ?BYTE(X) >> ).
+-define(uint16(X), << ?UINT16(X) >> ).
+-define(uint32(X), << ?UINT32(X) >> ).
+-define(uint64(X), << ?UINT64(X) >> ).
+-define(string_utf8(X), << ?STRING(unicode:characters_to_binary(X)) >> ).
+-define(string(X), ?string_utf8(X)).
+-define(binary(X), << ?STRING(X) >>).
+
+-define('2bin'(X), (if is_binary(X) -> X;
+		       is_list(X) -> list_to_binary(X);
+		       X==undefined -> <<>>
+		    end) ).
+
+%% encoding macros
+-define('E...'(X),    ?'2bin'(X)/binary ).
+-define(Eboolean(X),  ?BOOLEAN(case X of
+				   true -> ?TRUE;
+				   false -> ?FALSE
+			       end) ).
+-define(Ebyte(X),        ?BYTE(X) ).
+-define(Euint32(X),      ?UINT32(X) ).
+-define(Estring(X),      ?STRING(?'2bin'(X)) ).
+-define(Estring_utf8(X), ?string_utf8(X)/binary ).
+-define(Ename_list(X),   ?STRING(ssh_bits:name_list(X)) ).
+-define(Empint(X),       (ssh_bits:mpint(X))/binary ).
+-define(Ebinary(X),      ?STRING(X) ).
+
+%% 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,?LAZY(D),?MODULE,?LINE)).
+
+-define(LAZY(D), fun()-> D end).
+
+-define(GET_OPT(Key,Opts),              ?do_get_opt(user_options,    Key,Opts    ) ).
+-define(GET_OPT(Key,Opts,Def),          ?do_get_opt(user_options,    Key,Opts,Def) ).
+-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) ).
+
+-define(do_del_opt(C,K,O),  ssh_options:delete_key(C,K,O, ?MODULE,?LINE)).
+-define(DELETE_INTERNAL_OPT(Key,Opts),  ?do_del_opt(internal_options,Key,Opts) ).
+
+
+%% Types
+-type role()                  :: client | server .
+
+-doc(#{title => <<"Other data types">>}).
+-type host()                  :: string() | inet:ip_address() | loopback .
+-doc """
+The socket is supposed to be result of a [gen_tcp:connect](`gen_tcp:connect/3`)
+or a [gen_tcp:accept](`gen_tcp:accept/1`). The socket must be in passive mode
+(that is, opened with the option `{active,false})`.
+""".
+-doc(#{title => <<"Other data types">>}).
+-type open_socket()           :: gen_tcp:socket().
+
+-doc """
+Defines a subsystem in the daemon.
+
+The `subsystem_name` is the name that a client requests to start with for
+example `ssh_connection:subsystem/4`.
+
+The `channel_callback` is the module that implements the `m:ssh_server_channel`
+(replaces ssh_daemon_channel) behaviour in the daemon. See the section
+[Creating a Subsystem](using_ssh.md#usersguide_creating_a_subsystem) in the
+User's Guide for more information and an example.
+
+If the subsystems option is not present, the value of
+`ssh_sftpd:subsystem_spec([])` is used. This enables the sftp subsystem by
+default. The option can be set to the empty list if you do not want the daemon
+to run any subsystems.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type subsystem_spec()        :: {Name::string(), mod_args()} .
+                              
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type algs_list()             :: list( alg_entry() ).
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type alg_entry()             :: {kex, [kex_alg()]} 
+                               | {public_key, [pubkey_alg()]}
+                               | {cipher, double_algs(cipher_alg())}
+                               | {mac, double_algs(mac_alg())}
+                               | {compression, double_algs(compression_alg())} .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type kex_alg()          :: 'curve25519-sha256' |
+                            'curve25519-sha256@libssh.org' |
+                            'curve448-sha512' |
+                            'ecdh-sha2-nistp521' |
+                            'ecdh-sha2-nistp384' |
+                            'ecdh-sha2-nistp256' |
+                            'diffie-hellman-group-exchange-sha256' |
+                            'diffie-hellman-group16-sha512' |
+                            'diffie-hellman-group18-sha512' |
+                            'diffie-hellman-group14-sha256' |
+                            'diffie-hellman-group14-sha1' |
+                            'diffie-hellman-group-exchange-sha1' |
+                            'diffie-hellman-group1-sha1'
+                            .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type pubkey_alg()       :: 'ssh-ed25519' |
+                            'ssh-ed448' |
+                            'ecdsa-sha2-nistp521' |
+                            'ecdsa-sha2-nistp384' |
+                            'ecdsa-sha2-nistp256' |
+                            'rsa-sha2-512' |
+                            'rsa-sha2-256' |
+                            'ssh-rsa' |
+                            'ssh-dss'
+                            .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type cipher_alg()       :: 'aes256-gcm@openssh.com' |
+                            'aes256-ctr' |
+                            'aes192-ctr' |
+                            'aes128-gcm@openssh.com' |
+                            'aes128-ctr' |
+                            'AEAD_AES_256_GCM' |
+                            'AEAD_AES_128_GCM' |
+                            'chacha20-poly1305@openssh.com' |
+                            'aes256-cbc' |
+                            'aes192-cbc' |
+                            'aes128-cbc' |
+                            '3des-cbc'
+                            .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type mac_alg()          :: 'hmac-sha2-512-etm@openssh.com' |
+                            'hmac-sha2-256-etm@openssh.com' |
+                            'hmac-sha2-512' |
+                            'hmac-sha2-256' |
+                            'hmac-sha1-etm@openssh.com' |
+                            'hmac-sha1' |
+                            'hmac-sha1-96' |
+                            'AEAD_AES_256_GCM' |
+                            'AEAD_AES_128_GCM'
+                            .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type compression_alg()  :: 'none' |
+                            'zlib' |
+                            'zlib@openssh.com'
+                            .
+
+-doc """
+List of algorithms to use in the algorithm negotiation. The default
+`t:algs_list/0` can be obtained from `default_algorithms/0`.
+
+If an alg_entry() is missing in the algs_list(), the default value is used for
+that entry.
+
+Here is an example of this option:
+
+```erlang
+	  {preferred_algorithms,
+	  [{public_key,['ssh-rsa','ssh-dss']},
+	  {cipher,[{client2server,['aes128-ctr']},
+          {server2client,['aes128-cbc','3des-cbc']}]},
+	  {mac,['hmac-sha2-256','hmac-sha1']},
+	  {compression,[none,zlib]}
+	  ]
+	  }
+```
+
+The example specifies different algorithms in the two directions (client2server
+and server2client), for cipher but specifies the same algorithms for mac and
+compression in both directions. The kex (key exchange) is implicit but
+public_key is set explicitly.
+
+For background and more examples see the
+[User's Guide](configure_algos.md#introduction).
+
+If an algorithm name occurs more than once in a list, the behaviour is
+undefined. The tags in the property lists are also assumed to occur at most one
+time.
+
+> #### Warning {: .warning }
+>
+> Changing the values can make a connection less secure. Do not change unless
+> you know exactly what you are doing. If you do not understand the values then
+> you are not supposed to change them.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type double_algs(AlgType)  :: list( {client2server,[AlgType]} | {server2client,[AlgType]} )
+                             | [AlgType].
+
+-doc """
+Modifies the list of algorithms to use in the algorithm negotiation. The
+modifications are applied after the option `preferred_algorithms` (if existing)
+is applied.
+
+The algorithm for modifications works like this:
+
+- Input is the `t:modify_algs_list/0` and a set of algorithms `A` obtained from
+  the `preferred_algorithms` option if existing, or else from the
+  [ssh:default_algorithms/0](`default_algorithms/0`).
+- The head of the `t:modify_algs_list/0` modifies `A` giving the result `A'`.
+
+  The possible modifications are:
+
+  - Append or prepend supported but not enabled algorithm(s) to the list of
+    algorithms. If the wanted algorithms already are in `A` they will first be
+    removed and then appended or prepended,
+  - Remove (rm) one or more algorithms from `A`.
+
+- Repeat the modification step with the tail of `t:modify_algs_list/0` and the
+  resulting `A'`.
+
+If an unsupported algorithm is in the `t:modify_algs_list/0`, it will be
+silently ignored
+
+If there are more than one modify_algorithms options, the result is undefined.
+
+Here is an example of this option:
+
+```text
+	  {modify_algorithms,
+	  [{prepend, [{kex, ['diffie-hellman-group1-sha1']}],
+	  {rm,      [{compression, [none]}]}
+	  ]
+	  }
+```
+
+The example specifies that:
+
+- the old key exchange algorithm 'diffie-hellman-group1-sha1' should be the main
+  alternative. It will be the main alternative since it is prepened to the list
+- The compression algorithm none (= no compression) is removed so compression is
+  enforced
+
+For background and more examples see the
+[User's Guide](configure_algos.md#introduction).
+""".
+-doc(#{title => <<"Common Options">>}).
+-type modify_algs_list()      :: list( {append,algs_list()} | {prepend,algs_list()} | {rm,algs_list()} ) .
+
+-type internal_options()      :: ssh_options:private_options().
+-type socket_options()        :: [gen_tcp:connect_option() | gen_tcp:listen_option()].
+                              
+-doc(#{title => <<"Client Options">>,equiv => client_option/0}).
+-type client_options()        :: [ client_option() ] .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => daemon_option/0}).
+-type daemon_options()        :: [ daemon_option() ].
+                              
+
+-doc(#{title => <<"Common Options">>,
+       equiv => common_option/0}).
+-type common_options() :: [ common_option() ].
+-doc """
+The options above can be used both in clients and in daemons (servers). They are
+further explained below.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type common_option() :: 
+        ssh_file:user_dir_common_option()
+      | profile_common_option()
+      | max_idle_time_common_option()
+      | max_log_item_len_common_option()
+      | key_cb_common_option()
+      | disconnectfun_common_option()
+      | unexpectedfun_common_option()
+      | ssh_msg_debug_fun_common_option()
+      | rekey_limit_common_option()
+      | id_string_common_option()
+      | pref_public_key_algs_common_option()
+      | preferred_algorithms_common_option()
+      | modify_algorithms_common_option()
+      | auth_methods_common_option()
+      | inet_common_option()
+      | fd_common_option()
+        .
+
+-define(COMMON_OPTION, common_option()).
+
+-doc """
+Used together with `ip-address` and `port` to uniquely identify a ssh daemon.
+This can be useful in a virtualized environment, where there can be more that
+one server that has the same `ip-address` and `port`. If this property is not
+explicitly set, it is assumed that the the `ip-address` and `port` uniquely
+identifies the SSH daemon.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type profile_common_option()       :: {profile,   atom() }.
+-doc """
+Sets a time-out on a connection when no channels are open. Defaults to
+`infinity`. The unit is milliseconds.
+
+The timeout is not active until channels are started, so it does not limit the
+time from the connection creation to the first channel opening.
+
+For more information about timeouts, see the
+[Timeouts section ](hardening.md#timeouts)in the User's Guide
+[Hardening](hardening.md) chapter.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type max_idle_time_common_option() :: {idle_time, timeout()}.
+-doc(#{title => <<"Common Options">>,
+       equiv => limit_time/0}).
+-type rekey_limit_common_option()   :: {rekey_limit, Bytes::limit_bytes() |
+                                                     {Minutes::limit_time(), Bytes::limit_bytes()}
+                                       }.
+-doc """
+Sets a limit for the size of a logged item excluding a header. The unit is bytes
+and the value defaults to 500.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type max_log_item_len_common_option() :: {max_log_item_len, limit_bytes()} .
+
+-doc(#{title => <<"Common Options">>,
+       equiv => limit_time/0}).
+-type limit_bytes() :: non_neg_integer() | infinity .  % non_neg_integer due to compatibility
+-doc """
+Sets the limit when rekeying is to be initiated. Both the max time and max
+amount of data could be configured:
+
+- `{Minutes, Bytes}` initiate rekeying when any of the limits are reached.
+- `Bytes` initiate rekeying when `Bytes` number of bytes are transferred, or at
+  latest after one hour.
+
+When a rekeying is done, both the timer and the byte counter are restarted.
+Defaults to one hour and one GByte.
+
+If `Minutes` is set to `infinity`, no rekeying will ever occur due to that max
+time has passed. Setting `Bytes` to `infinity` will inhibit rekeying after a
+certain amount of data has been transferred. If the option value is set to
+`{infinity, infinity}`, no rekeying will be initiated. Note that rekeying
+initiated by the peer will still be performed.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type limit_time()  :: pos_integer() | infinity .
+
+-doc """
+Module implementing the behaviour `m:ssh_client_key_api` and/or
+`m:ssh_server_key_api`. Can be used to customize the handling of public keys. If
+callback options are provided along with the module name, they are made
+available to the callback module via the options passed to it under the key
+'key_cb_private'.
+
+The `Opts` defaults to `[]` when only the `Module` is specified.
+
+The default value of this option is `{ssh_file, []}`. See also the manpage of
+`m:ssh_file`.
+
+A call to the call-back function `F` will be
+
+```text
+	  Module:F(..., [{key_cb_private,Opts}|UserOptions])
+```
+
+where `...` are arguments to `F` as in `m:ssh_client_key_api` and/or
+`m:ssh_server_key_api`. The `UserOptions` are the options given to
+[ssh:connect](`connect/3`), [ssh:shell](`shell/1`) or [ssh:daemon](`daemon/2`).
+""".
+-doc(#{title => <<"Common Options">>}).
+-type key_cb_common_option()            :: {key_cb,  Module::atom() | {Module::atom(),Opts::[term()]} } .
+-doc "Provides a fun to implement your own logging or other handling at disconnects.".
+-doc(#{title => <<"Common Options">>}).
+-type disconnectfun_common_option()     ::
+        {disconnectfun, fun((Reason::term()) -> void | any()) }.
+-doc """
+Provides a fun to implement your own logging or other action when an unexpected
+message arrives. If the fun returns `report` the usual info report is issued but
+if `skip` is returned no report is generated.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type unexpectedfun_common_option()     ::
+        {unexpectedfun, fun((Message::term(),{Host::term(),Port::term()}) -> report | skip ) }.
+-doc """
+Provide a fun to implement your own logging of the SSH message SSH_MSG_DEBUG.
+The last three parameters are from the message, see
+[RFC 4253, section 11.3](https://tools.ietf.org/html/rfc4253#section-11.3). The
+`t:connection_ref/0` is the reference to the connection on which the message
+arrived. The return value from the fun is not checked.
+
+The default behaviour is ignore the message. To get a printout for each message
+with `AlwaysDisplay = true`, use for example
+`{ssh_msg_debug_fun, fun(_,true,M,_)-> io:format("DEBUG: ~p~n", [M]) end}`
+""".
+-doc(#{title => <<"Common Options">>}).
+-type ssh_msg_debug_fun_common_option() ::
+        {ssh_msg_debug_fun, fun((ssh:connection_ref(),AlwaysDisplay::boolean(),Msg::binary(),LanguageTag::binary()) -> any()) } .
+
+-doc """
+The string the daemon will present to a connecting peer initially. The default
+value is "Erlang/VSN" where VSN is the ssh application version number.
+
+The value `random` will cause a random string to be created at each connection
+attempt. This is to make it a bit more difficult for a malicious peer to find
+the ssh software brand and version.
+
+The value `{random, Nmin, Nmax}` will make a random string with at least `Nmin`
+characters and at most `Nmax` characters.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type id_string_common_option()           :: {id_string,  string() | random | {random,Nmin::pos_integer(),Nmax::pos_integer()} }.
+-doc """
+List of user (client) public key algorithms to try to use.
+
+The default value is the `public_key` entry in the list returned by
+[ssh:default_algorithms/0](`default_algorithms/0`).
+
+If there is no public key of a specified type available, the corresponding entry
+is ignored. Note that the available set is dependent on the underlying cryptolib
+and current user's public keys.
+
+See also the option [`user_dir`](`t:ssh_file:user_dir_common_option/0`) for
+specifying the path to the user's keys.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type pref_public_key_algs_common_option() :: {pref_public_key_algs, [pubkey_alg()] } .
+-doc(#{title => <<"Common Options">>,
+       equiv => double_algs/1}).
+-type preferred_algorithms_common_option():: {preferred_algorithms, algs_list()}.
+-doc(#{title => <<"Common Options">>,
+       equiv => modify_algs_list/0}).
+-type modify_algorithms_common_option()   :: {modify_algorithms,    modify_algs_list()}.
+-doc """
+Comma-separated string that determines which authentication methods that the
+client shall support and in which order they are tried. Defaults to
+`"publickey,keyboard-interactive,password"`
+
+Note that the client is free to use any order and to exclude methods.
+""".
+-doc(#{title => <<"Common Options">>}).
+-type auth_methods_common_option()        :: {auth_methods,         string() }.
+
+-doc "IP version to use when the host address is specified as `any`.".
+-doc(#{title => <<"Common Options">>}).
+-type inet_common_option() :: {inet, inet | inet6} .
+-doc """
+Allows an existing file-descriptor to be used (passed on to the transport
+protocol).
+""".
+-doc(#{title => <<"Common Options">>}).
+-type fd_common_option() :: {fd, gen_tcp:socket()} .
+
+
+-doc """
+Opaque types that define experimental options that are not to be used in
+products.
+""".
+-doc(#{title => <<"Other data types">>}).
+-type opaque_common_options() ::
+        {transport, {atom(),atom(),atom()} }
+      | {vsn, {non_neg_integer(),non_neg_integer()} }
+      | {tstflg, list(term())}
+      | ssh_file:user_dir_fun_common_option()
+      | {max_random_length_padding, non_neg_integer()} .
+
+
+
+-doc """
+Options for [clients](`connect/3`). The individual options are further explained
+below or by following the hyperlinks.
+
+Note that not every `t:gen_tcp:connect_option/0` is accepted. See
+`set_sock_opts/2` for a list of prohibited options.
+
+Also note that setting a `t:gen_tcp:connect_option/0` could change the socket in
+a way that impacts the ssh client's behaviour negatively. You use it on your own
+risk.
+""".
+-doc(#{title => <<"Client Options">>}).
+-type client_option()         ::
+        ssh_file:pubkey_passphrase_client_options()
+      | host_accepting_client_options()
+      | authentication_client_options()
+      | diffie_hellman_group_exchange_client_option()
+      | connect_timeout_client_option()
+      | recv_ext_info_client_option()
+      | opaque_client_options()
+      | gen_tcp:connect_option()
+      | ?COMMON_OPTION .
+
+-doc(#{title => <<"Other data types">>,
+       equiv => opaque_common_options/0}).
+-type opaque_client_options() ::
+        {keyboard_interact_fun, fun((Name::iodata(),
+                                     Instruction::iodata(),
+                                     Prompts::[{Prompt::iodata(),Echo::boolean()}]
+                                    ) ->
+                                      [Response::iodata()]
+                                   )} 
+        | opaque_common_options().
+
+-doc(#{title => <<"Client Options">>,equiv => fingerprint/0}).
+-type host_accepting_client_options() ::
+        {silently_accept_hosts, accept_hosts()}
+      | {user_interaction,     boolean()}
+      | {save_accepted_host,   boolean()}
+      | {quiet_mode,           boolean()} .
+
+-doc(#{title => <<"Client Options">>,equiv => fingerprint/0}).
+-type accept_hosts() :: boolean() 
+                      | accept_callback()
+                      | {HashAlgoSpec::fp_digest_alg(), accept_callback()}.
+
+-doc(#{title => <<"Client Options">>,equiv => fingerprint/0}).
+-type fp_digest_alg() :: 'md5' | crypto:sha1() | crypto:sha2() .
+
+-doc(#{title => <<"Client Options">>,equiv => fingerprint/0}).
+-type accept_callback() :: fun((PeerName::string(), fingerprint() ) -> boolean()) % Old style
+                         | fun((PeerName::string(), Port::inet:port_number(), fingerprint() ) -> boolean()) % New style
+                           .
+-doc """
+- **`silently_accept_hosts`{: #hardening_client_options-silently_accept_hosts
+  }** - This option guides the `connect` function on how to act when the
+  connected server presents a Host Key that the client has not seen before. The
+  default is to ask the user with a question on stdio of whether to accept or
+  reject the new Host Key. See the option
+  [`user_dir`](`t:ssh_file:user_dir_common_option/0`) for specifying the path to
+  the file `known_hosts` where previously accepted Host Keys are recorded. See
+  also the option [key_cb](`t:key_cb_common_option/0`) for the general way to
+  handle keys.
+
+  The option can be given in three different forms as seen
+  [above](`t:accept_hosts/0`):
+
+  - The value is a `t:boolean/0`. The value `true` will make the client accept
+    any unknown Host Key without any user interaction. The value `false`
+    preserves the default behaviour of asking the user on stdio.
+  - An `t:accept_callback/0` will be called and the boolean return value `true`
+    will make the client accept the Host Key. A return value of `false` will
+    make the client to reject the Host Key and as a result the connection will
+    be closed. The arguments to the fun are:
+    - `PeerName` \- a string with the name or address of the remote host.
+    - `FingerPrint` \- the fingerprint of the Host Key as
+      `hostkey_fingerprint/1` calculates it.
+  - A tuple `{HashAlgoSpec, accept_callback}`. The `HashAlgoSpec` specifies
+    which hash algorithm shall be used to calculate the fingerprint used in the
+    call of the `t:accept_callback/0`. The `HashALgoSpec` is either an atom or a
+    list of atoms as the first argument in `hostkey_fingerprint/2`. If it is a
+    list of hash algorithm names, the `FingerPrint` argument in the
+    `t:accept_callback/0` will be a list of fingerprints in the same order as
+    the corresponding name in the `HashAlgoSpec` list.
+
+- **`user_interaction`** - If `false`, disables the client to connect to the
+  server if any user interaction is needed, such as accepting the server to be
+  added to the `known_hosts` file, or supplying a password.
+
+  Even if user interaction is allowed it can be suppressed by other options,
+  such as `silently_accept_hosts` and `password`. However, those options are not
+  always desirable to use from a security point of view.
+
+  Defaults to `true`.
+
+- **`save_accepted_host`** - If `true`, the client saves an accepted host key to
+  avoid the accept question the next time the same host is connected. If the
+  option [`key_cb`](`t:key_cb_common_option/0`) is not present, the key is saved
+  in the file "known_hosts". See option
+  [`user_dir`](`t:ssh_file:user_dir_common_option/0`) for the location of that
+  file.
+
+  If `false`, the key is not saved and the key will still be unknown at the next
+  access of the same host.
+
+  Defaults to `true`
+
+- **`quiet_mode`** - If `true`, the client does not print anything on
+  authorization.
+
+  Defaults to `false`
+""".
+-doc(#{title => <<"Client Options">>}).
+-type fingerprint() :: string() | [string()].
+
+-doc """
+- **`user`** - Provides the username. If this option is not given, `ssh` reads
+  from the environment (`LOGNAME` or `USER` on UNIX, `USERNAME` on Windows).
+
+- **`password`** - Provides a password for password authentication. If this
+  option is not given, the user is asked for a password, if the password
+  authentication method is attempted.
+""".
+-doc(#{title => <<"Client Options">>}).
+-type authentication_client_options() ::
+        {user,                 string()}
+      | {password,             string()} .
+
+-doc """
+Sets the three diffie-hellman-group-exchange parameters that guides the
+connected server in choosing a group. See
+[RFC 4419](https://tools.ietf.org/html/rfc4419) for the details. The default
+value is `{1024, 6144, 8192}`.
+""".
+-doc(#{title => <<"Client Options">>}).
+-type diffie_hellman_group_exchange_client_option() ::
+        {dh_gex_limits,        {Min::pos_integer(), I::pos_integer(), Max::pos_integer()} } .
+
+-doc """
+Sets a timeout on the transport layer connect time. For `m:gen_tcp` the time is
+in milli-seconds and the default value is `infinity`.
+
+See the parameter `Timeout` in `connect/4` for a timeout of the negotiation
+phase.
+""".
+-doc(#{title => <<"Client Options">>}).
+-type connect_timeout_client_option() :: {connect_timeout, timeout()} .
+
+-doc """
+Make the client tell the server that the client accepts extension negotiation,
+that is, include `ext-info-c` in the kexinit message sent. See
+[RFC 8308](https://tools.ietf.org/html/rfc8308) for details and
+[ssh](ssh_app.md#supported-ext-info) for a list of currently implemented
+extensions.
+
+Default value is `true` which is compatible with other implementations not
+supporting ext-info.
+""".
+-doc(#{title => <<"Client Options">>}).
+-type recv_ext_info_client_option() :: {recv_ext_info, boolean()} .
+
+
+
+-doc """
+Options for [daemons](`daemon/1`). The individual options are further explained
+below or by following the hyperlinks.
+
+Note that not every `t:gen_tcp:listen_option/0` is accepted. See
+`set_sock_opts/2` for a list of prohibited options.
+
+Also note that setting a `t:gen_tcp:listen_option/0` could change the socket in
+a way that impacts the ssh deamon's behaviour negatively. You use it on your own
+risk.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type daemon_option()         ::
+        subsystem_daemon_option()
+      | shell_daemon_option()
+      | exec_daemon_option()
+      | ssh_cli_daemon_option()
+      | tcpip_tunnel_out_daemon_option()
+      | tcpip_tunnel_in_daemon_option()
+      | authentication_daemon_options()
+      | diffie_hellman_group_exchange_daemon_option()
+      | max_initial_idle_time_daemon_option()
+      | negotiation_timeout_daemon_option()
+      | hello_timeout_daemon_option()
+      | hardening_daemon_options()
+      | callbacks_daemon_options()
+      | send_ext_info_daemon_option()
+      | opaque_daemon_options()
+      | gen_tcp:listen_option()
+      | ?COMMON_OPTION .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => subsystem_spec/0}).
+-type subsystem_daemon_option() :: {subsystems, subsystem_specs()}.
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => subsystem_spec/0}).
+-type subsystem_specs() :: [ subsystem_spec() ].
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'shell_fun/2'/0}).
+-type shell_daemon_option()     :: {shell, shell_spec()} .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'shell_fun/2'/0}).
+-type shell_spec() :: mod_fun_args() | shell_fun() | disabled .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'shell_fun/2'/0}).
+-type shell_fun() :: 'shell_fun/1'()  | 'shell_fun/2'() .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'shell_fun/2'/0}).
+-type 'shell_fun/1'() :: fun((User::string()) -> pid()) .
+-doc """
+Defines the read-eval-print loop used in a daemon when a shell is requested by
+the client. The default is to use the Erlang shell: `{shell, start, []}`
+
+See the option [`exec-option`](`t:exec_daemon_option/0`) for a description of
+how the daemon executes shell-requests and exec-requests depending on the shell-
+and exec-options.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type 'shell_fun/2'() :: fun((User::string(),  PeerAddr::inet:ip_address()) -> pid()).
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => exec_spec/0}).
+-type exec_daemon_option()      :: {exec, exec_spec()} .
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type exec_spec()               :: {direct, exec_fun()} | disabled | deprecated_exec_opt().
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type exec_fun()                :: 'exec_fun/1'() | 'exec_fun/2'() | 'exec_fun/3'().
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'exec_fun/3'/0}).
+-type 'exec_fun/1'() :: fun((Cmd::string()) -> exec_result()) .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => 'exec_fun/3'/0}).
+-type 'exec_fun/2'() :: fun((Cmd::string(), User::string()) -> exec_result()) .
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type 'exec_fun/3'() :: fun((Cmd::string(), User::string(), ClientAddr::ip_port()) -> exec_result()) .
+-doc """
+This option changes how the daemon executes exec-requests from clients. The term
+in the return value is formatted to a string if it is a non-string type. No
+trailing newline is added in the ok-case.
+
+See the User's Guide section on
+[One-Time Execution](using_ssh.md#one-time-execution) for examples.
+
+Error texts are returned on channel-type 1 which usually is piped to `stderr` on
+e.g Linux systems. Texts from a successful execution are returned on
+channel-type 0 and will in similar manner be piped to `stdout`. The exit-status
+code is set to 0 for success and 255 for errors. The exact results presented on
+the client side depends on the client and the client's operating system.
+
+In case of the `{direct, exec_fun()}` variant or no exec-option at all, all
+reads from `standard_input` will be from the received data-events of type 0.
+Those are sent by the client. Similarly all writes to `standard_output` will be
+sent as data-events to the client. An OS shell client like the command 'ssh'
+will usually use stdin and stdout for the user interface.
+
+The option cooperates with the daemon-option
+[`shell`](`t:shell_daemon_option/0`) in the following way:
+
+- **1\. If neither the [`exec-option`](`t:exec_daemon_option/0`) nor the
+  [`shell-option`](`t:shell_daemon_option/0`) is present:** - The default Erlang
+  evaluator is used both for exec and shell requests. The result is returned to
+  the client.
+
+- **2\. If the [`exec_spec`](`t:exec_daemon_option/0`)'s value is `disabled`
+  (the [`shell-option`](`t:shell_daemon_option/0`) may or may not be
+  present):** - No exec-requests are executed but shell-requests are not
+  affected, they follow the [`shell_spec`](`t:shell_daemon_option/0`)'s value.
+
+- **3\. If the [`exec-option`](`t:exec_daemon_option/0`) is present and the
+  [`exec_spec`](`t:exec_daemon_option/0`) value =/= `disabled` (the
+  [`shell-option`](`t:shell_daemon_option/0`) may or may not be present):** -
+  The [`exec_spec`](`t:exec_daemon_option/0`) `fun()` is called with the same
+  number of parameters as the arity of the fun, and the result is returned to
+  the client. Shell-requests are not affected, they follow the
+  [`shell_spec`](`t:shell_daemon_option/0`)'s value.
+
+- **4\. If the [`exec-option`](`t:exec_daemon_option/0`) is absent, and the
+  [`shell-option`](`t:shell_daemon_option/0`) is present with the default Erlang
+  shell as the [`shell_spec`](`t:shell_daemon_option/0`)'s value:** - The
+  default Erlang evaluator is used both for exec and shell requests. The result
+  is returned to the client.
+
+- **5\. If the [`exec-option`](`t:exec_daemon_option/0`) is absent, and the
+  [`shell-option`](`t:shell_daemon_option/0`) is present with a value that is
+  neither the default Erlang shell nor the value `disabled`:** - The
+  exec-request is not evaluated and an error message is returned to the client.
+  Shell-requests are executed according to the value of the
+  [`shell_spec`](`t:shell_daemon_option/0`).
+
+- **6\. If the [`exec-option`](`t:exec_daemon_option/0`) is absent, and the
+  [`shell_spec`](`t:shell_daemon_option/0`)'s value is `disabled`:** - Exec
+  requests are executed by the default shell, but shell-requests are not
+  executed.
+
+If a custom CLI is installed (see the option
+[`ssh_cli`](`t:ssh_cli_daemon_option/0`)) the rules above are replaced by thoose
+implied by the custom CLI.
+
+> #### Note {: .info }
+>
+> The [`exec-option`](`t:exec_daemon_option/0`) has existed for a long time but
+> has not previously been documented. The old definition and behaviour are
+> retained but obey the rules 1-6 above if conflicting. The old and undocumented
+> style should not be used in new programs.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type exec_result()  :: {ok,Result::term()} | {error,Reason::term()} .
+-doc """
+Old-style exec specification that are kept for compatibility, but should not be
+used in new programs
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type deprecated_exec_opt() :: fun() | mod_fun_args() .
+
+-doc """
+Provides your own CLI implementation in a daemon.
+
+It is a channel callback module that implements a shell and command execution.
+The shell's read-eval-print loop can be customized, using the option
+[`shell`](`t:shell_daemon_option/0`). This means less work than implementing an
+own CLI channel. If `ssh_cli` is set to `no_cli`, the CLI channels like
+[`shell`](`t:shell_daemon_option/0`) and [`exec`](`t:exec_daemon_option/0`) are
+disabled and only subsystem channels are allowed.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type ssh_cli_daemon_option()   :: {ssh_cli, mod_args() | no_cli }.
+
+-doc """
+Enables (`true`) or disables (`false`) the possibility to tunnel a TCP/IP
+connection out of a [server](`daemon/2`). Disabled per default.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type tcpip_tunnel_out_daemon_option() :: {tcpip_tunnel_out, boolean()} .
+-doc """
+Enables (`true`) or disables (`false`) the possibility to tunnel a TCP/IP
+connection in to a [server](`daemon/2`). Disabled per default.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type tcpip_tunnel_in_daemon_option() :: {tcpip_tunnel_in, boolean()} .
+
+-doc """
+Make the server (daemon) tell the client that the server accepts extension
+negotiation, that is, include `ext-info-s` in the kexinit message sent. See
+[RFC 8308](https://tools.ietf.org/html/rfc8308) for details and
+[ssh](ssh_app.md#supported-ext-info) for a list of currently implemented
+extensions.
+
+Default value is `true` which is compatible with other implementations not
+supporting ext-info.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type send_ext_info_daemon_option() :: {send_ext_info, boolean()} .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type authentication_daemon_options() ::
+        ssh_file:system_dir_daemon_option()
+      | {auth_method_kb_interactive_data, prompt_texts() }
+      | {user_passwords, [{UserName::string(),Pwd::string()}]}
+      | {pk_check_user, boolean()}  
+      | {password, string()}
+      | {pwdfun, pwdfun_2() | pwdfun_4()}
+      | {no_auth_needed, boolean()}
+        .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type prompt_texts() ::
+        kb_int_tuple()
+      | kb_int_fun_3()
+      | kb_int_fun_4()
+      .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type kb_int_fun_3() :: fun((Peer::ip_port(), User::string(), Service::string()) -> kb_int_tuple()).
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type kb_int_fun_4() :: fun((Peer::ip_port(), User::string(), Service::string(), State::any()) -> kb_int_tuple()).
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type kb_int_tuple() :: {Name::string(), Instruction::string(), Prompt::string(), Echo::boolean()}.
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => pwdfun_4/0}).
+-type pwdfun_2() :: fun((User::string(), Password::string()|pubkey) -> boolean()) .
+-doc """
+- **`auth_method_kb_interactive_data`** - Sets the text strings that the daemon
+  sends to the client for presentation to the user when using
+  `keyboard-interactive` authentication.
+
+  If the fun/3 or fun/4 is used, it is called when the actual authentication
+  occurs and may therefore return dynamic data like time, remote ip etc.
+
+  The parameter `Echo` guides the client about need to hide the password.
+
+  The default value is:
+  `{auth_method_kb_interactive_data, {"SSH server", "Enter password for \""++User++"\"", "password: ", false}>`
+
+- **`user_passwords`{: #option-user_passwords }** - Provides passwords for
+  password authentication. The passwords are used when someone tries to connect
+  to the server and public key user-authentication fails. The option provides a
+  list of valid usernames and the corresponding passwords.
+
+  > #### Warning {: .warning }
+  >
+  > Note that this is very insecure due to the plain-text passwords; it is
+  > intended for test purposes. Use the [`pwdfun`](`m:ssh#option-pwdfun`) option
+  > to handle the password checking instead.
+
+- **`pk_check_user`{: #option-pk_check_user }** - Enables checking of the
+  [client's user name](`t:authentication_client_options/0`) in the server when
+  doing public key authentication. It is disabled by default.
+
+  The term "user" is used differently in OpenSSH and SSH in Erlang/OTP: see more
+  in the [User's Guide](terminology.md#the-term-user).
+
+  If the option is enabled, and no [`pwdfun`](`m:ssh#option-pwdfun`) is present,
+  the user name must present in the
+  [user_passwords](`m:ssh#option-user_passwords`) for the check to succeed but
+  the value of the password is not checked.
+
+  In case of a [`pwdfun`](`m:ssh#option-pwdfun`) checking the user, the atom
+  `pubkey` is put in the password argument.
+
+- **`password`{: #option-password }** - Provides a global password that
+  authenticates any user.
+
+  > #### Warning {: .warning }
+  >
+  > Intended to facilitate testing.
+  >
+  > From a security perspective this option makes the server very vulnerable.
+
+- **`pwdfun`{: #option-pwdfun } with `t:pwdfun_4/0`** - Provides a function for
+  password validation. This could used for calling an external system or
+  handling passwords stored as hash values.
+
+  This fun can also be used to make delays in authentication tries for example
+  by calling `timer:sleep/1`.
+
+  To facilitate for instance counting of failed tries, the `State` variable
+  could be used. This state is per connection only. The first time the pwdfun is
+  called for a connection, the `State` variable has the value `undefined`.
+
+  The fun should return:
+
+  - `true` if the user and password is valid
+  - `false` if the user or password is invalid
+  - `disconnect` if a SSH_MSG_DISCONNECT message should be sent immediately. It
+    will be followed by a close of the underlying tcp connection.
+  - `{true, NewState:any()}` if the user and password is valid
+  - `{false, NewState:any()}` if the user or password is invalid
+
+  A third usage is to block login attempts from a missbehaving peer. The `State`
+  described above can be used for this. The return value `disconnect` is useful
+  for this.
+
+  In case of the [`pk_check_user`](`m:ssh#option-pk_check_user`) is set, the
+  atom `pubkey` is put in the password argument when validating a public key
+  login. The pwdfun is then responsible to check that the user name is valid.
+
+- **`pwdfun` with `t:pwdfun_2/0`** - Provides a function for password
+  validation. This function is called with user and password as strings, and
+  returns:
+
+  - `true` if the user and password is valid
+  - `false` if the user or password is invalid
+
+  In case of the [`pk_check_user`](`m:ssh#option-pk_check_user`) is set, the
+  atom `pubkey` is put in the password argument when validating a public key
+  login. The pwdfun is then responsible to check that the user name is valid.
+
+  This variant is kept for compatibility.
+
+- **`no_auth_needed`{: #option-no_auth_needed }** - If `true`, a client is
+  authenticated without any need of providing any password or key.
+
+  This option is only intended for very special applications due to the high
+  risk of accepting any connecting client.
+
+  The default value is `false`.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type pwdfun_4() :: fun((User::string(),
+                         Password::string()|pubkey,
+                         PeerAddress::ip_port(),
+                         State::any()) ->
+                               boolean() | disconnect | {boolean(),NewState::any()}
+                       ) .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => ssh_moduli_file/0}).
+-type diffie_hellman_group_exchange_daemon_option() ::
+        {dh_gex_groups, [explicit_group()] | explicit_group_file() | ssh_moduli_file()}
+      | {dh_gex_limits, {Min::pos_integer(), Max::pos_integer()} } .
+
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => ssh_moduli_file/0}).
+-type explicit_group() :: {Size::pos_integer(),G::pos_integer(),P::pos_integer()} .
+-doc(#{title => <<"Daemon Options (Server Options)">>,
+       equiv => ssh_moduli_file/0}).
+-type explicit_group_file() :: {file,string()} .
+-doc """
+- **`dh_gex_groups`** - Defines the groups the server may choose among when
+  diffie-hellman-group-exchange is negotiated. See
+  [RFC 4419](https://tools.ietf.org/html/rfc4419) for details. The three
+  variants of this option are:
+
+  - **`{Size=integer(),G=integer(),P=integer()}`** - The groups are given
+    explicitly in this list. There may be several elements with the same `Size`.
+    In such a case, the server will choose one randomly in the negotiated Size.
+
+  - **`{file,filename()}`** - The file must have one or more three-tuples
+    `{Size=integer(),G=integer(),P=integer()}` terminated by a dot. The file is
+    read when the daemon starts.
+
+  - **`{ssh_moduli_file,filename()}`** - The file must be in
+    [ssh-keygen moduli file format](`public_key:dh_gex_group/4`). The file is
+    read when the daemon starts.
+
+  The default list is fetched from the [public_key](`public_key:dh_gex_group/4`)
+  application.
+
+- **`dh_gex_limits`** - Limits what a client can ask for in
+  diffie-hellman-group-exchange. The limits will be
+  `{MaxUsed = min(MaxClient,Max), MinUsed = max(MinClient,Min)}` where
+  `MaxClient` and `MinClient` are the values proposed by a connecting client.
+
+  The default value is `{0,infinity}`.
+
+  If `MaxUsed < MinUsed` in a key exchange, it will fail with a disconnect.
+
+  See [RFC 4419](https://tools.ietf.org/html/rfc4419) for the function of the
+  Max and Min values.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type ssh_moduli_file() :: {ssh_moduli_file,string()}.
+
+-doc """
+Maximum time in milliseconds for the first channel start after completion of the
+authentication negotiation. Defaults to `infinity`.
+
+For more information about timeouts, see the
+[Timeouts section ](hardening.md#timeouts)in the User's Guide
+[Hardening](hardening.md) chapter.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type max_initial_idle_time_daemon_option() :: {max_initial_idle_time, timeout()} .
+-doc """
+Maximum time in milliseconds for the authentication negotiation. Defaults to
+120000 ms (2 minutes). If the client fails to log in within this time, the
+connection is closed.
+
+For more information about timeouts, see the
+[Timeouts section ](hardening.md#timeouts)in the User's Guide
+[Hardening](hardening.md) chapter.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type negotiation_timeout_daemon_option() :: {negotiation_timeout, timeout()} .
+-doc """
+Maximum time in milliseconds for the first part of the ssh session setup, the
+hello message exchange. Defaults to 30000 ms (30 seconds). If the client fails
+to send the first message within this time, the connection is closed.
+
+For more information about timeouts, see the
+[Timeouts section ](hardening.md#timeouts)in the User's Guide
+[Hardening](hardening.md) chapter.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type hello_timeout_daemon_option() :: {hello_timeout, timeout()} .
+
+-doc """
+For more information about hardening, see the [Hardening](hardening.md) section
+in the User's Guide chapter.
+
+- **`max_sessions`{: #hardening_daemon_options-max_sessions }** - The maximum
+  number of simultaneous sessions that are accepted at any time for this daemon.
+  This includes sessions that are being authorized. Thus, if set to `N`, and `N`
+  clients have connected but not started the login process, connection attempt
+  `N+1` is aborted. If `N` connections are authenticated and still logged in, no
+  more logins are accepted until one of the existing ones log out.
+
+  The counter is per listening port. Thus, if two daemons are started, one with
+  `{max_sessions,N}` and the other with `{max_sessions,M}`, in total `N+M`
+  connections are accepted for the whole `ssh` application.
+
+  Notice that if `parallel_login` is `false`, only one client at a time can be
+  in the authentication phase.
+
+  By default, this option is not set. This means that the number is not limited.
+
+- **`max_channels`{: #hardening_daemon_options-max_channels }** - The maximum
+  number of channels with active remote subsystem that are accepted for each
+  connection to this daemon
+
+  By default, this option is not set. This means that the number is not limited.
+
+- **`parallel_login`{: #hardening_daemon_options-parallel_login }** - If set to
+  false (the default value), only one login is handled at a time. If set to
+  true, an unlimited number of login attempts are allowed simultaneously.
+
+  If the `max_sessions` option is set to `N` and `parallel_login` is set to
+  `true`, the maximum number of simultaneous login attempts at any time is
+  limited to `N-K`, where `K` is the number of authenticated connections present
+  at this daemon.
+
+  > #### Warning {: .warning }
+  >
+  > Do not enable `parallel_logins` without protecting the server by other
+  > means, for example, by the `max_sessions` option or a firewall
+  > configuration. If set to `true`, there is no protection against DOS attacks.
+
+- **`minimal_remote_max_packet_size`{:
+  #hardening_daemon_options-minimal_remote_max_packet_size }** - The least
+  maximum packet size that the daemon will accept in channel open requests from
+  the client. The default value is 0.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type hardening_daemon_options() ::
+        {max_sessions, pos_integer()}
+      | {max_channels, pos_integer()}
+      | {parallel_login, boolean()}
+      | {minimal_remote_max_packet_size, pos_integer()}.
+
+-doc """
+- **`connectfun`** - Provides a fun to implement your own logging when a user
+  authenticates to the server.
+
+- **`failfun`** - Provides a fun to implement your own logging when a user fails
+  to authenticate.
+""".
+-doc(#{title => <<"Daemon Options (Server Options)">>}).
+-type callbacks_daemon_options() ::
+        {failfun, fun((User::string(), PeerAddress::inet:ip_address(), Reason::term()) -> _)}
+      | {connectfun, fun((User::string(), PeerAddress::inet:ip_address(), Method::string()) ->_)} .
+
+-doc(#{title => <<"Other data types">>,
+       equiv => opaque_common_options/0}).
+-type opaque_daemon_options()  ::
+        {infofun, fun()}
+      | opaque_common_options().
+
+-doc(#{title => <<"Other data types">>}).
+-type ip_port() :: {inet:ip_address(), inet:port_number()} .
+
+-doc(#{title => <<"Other data types">>}).
+-type mod_args() :: {Module::atom(), Args::list()} .
+-doc(#{title => <<"Other data types">>}).
+-type mod_fun_args() :: {Module::atom(), Function::atom(), Args::list()} .
+
+
+%% Records
+-record(address, {address,
+                  port,
+                  profile
+                 }).
+
+-record(ssh,
+	{
+	  role :: client | role(),
+	  peer :: undefined | 
+                  {inet:hostname(),ip_port()},         %% string version of peer address 
+
+          local,        %% Local sockname. Need this AFTER a socket is closed by i.e. a crash
+
+	  c_vsn,        %% client version {Major,Minor}
+	  s_vsn,        %% server version {Major,Minor}
+
+	  c_version,    %% client version string
+	  s_version,    %% server version string
+
+	  c_keyinit,    %% binary payload of kexinit packet
+	  s_keyinit,    %% binary payload of kexinit packet
+
+          send_ext_info, %% May send ext-info to peer
+          recv_ext_info, %% Expect ext-info from peer
+
+          kex_strict_negotiated = false,
+
+	  algorithms,   %% #alg{}
+	  
+	  send_mac = none, %% send MAC algorithm
+	  send_mac_key,  %% key used in send MAC algorithm
+	  send_mac_size = 0,
+
+	  recv_mac = none, %% recv MAC algorithm
+	  recv_mac_key,  %% key used in recv MAC algorithm
+	  recv_mac_size = 0,
+
+	  encrypt = none,       %% encrypt algorithm
+          encrypt_cipher,       %% cipher. could be different from the algorithm
+	  encrypt_keys,         %% encrypt keys
+	  encrypt_block_size = 8,
+	  encrypt_ctx,
+
+	  decrypt = none,       %% decrypt algorithm
+          decrypt_cipher,       %% cipher. could be different from the algorithm
+	  decrypt_keys,         %% decrypt keys
+	  decrypt_block_size = 8,
+	  decrypt_ctx,          %% Decryption context   
+
+	  compress = none,
+	  compress_ctx,
+	  decompress = none,
+	  decompress_ctx,
+
+	  c_lng=none,   %% client to server languages
+	  s_lng=none,   %% server to client languages
+
+	  user_ack    = true,   %% client
+	  timeout     = infinity,
+
+	  shared_secret,        %% K from key exchange
+	  exchanged_hash,       %% H from key exchange
+	  session_id,           %% same as FIRST exchanged_hash
+	  
+	  opts = [],
+	  send_sequence = 0,
+	  recv_sequence = 0,
+	  keyex_key,
+	  keyex_info,
+	  random_length_padding = ?MAX_RND_PADDING_LEN, % From RFC 4253 section 6.
+	  
+	  %% User auth
+	  user,
+	  service,
+	  userauth_quiet_mode,              %  boolean()
+	  userauth_methods,                 %  list( string() )  eg ["keyboard-interactive", "password"]
+	  userauth_supported_methods,       %  string() eg "keyboard-interactive,password"
+          userauth_pubkeys,
+	  kb_tries_left = 0,                %  integer(), num tries left for "keyboard-interactive"
+	  userauth_preference,
+	  available_host_keys,
+	  pwdfun_user_state,
+	  authenticated = false
+	 }).
+
+-record(alg,
+	{
+	  kex,
+	  hkey,
+	  send_mac,
+	  recv_mac,
+	  encrypt,
+	  decrypt,
+	  compress,
+	  decompress,
+	  c_lng,
+	  s_lng,
+          send_ext_info,
+          recv_ext_info,
+          kex_strict_negotiated = false
+	 }).
+
+-record(ssh_pty, {c_version = "", % client version string, e.g "SSH-2.0-Erlang/4.10.5"
+                  term = "",      % e.g. "xterm"
+		  width = 80,
+		  height = 25,
+		  pixel_width = 1024,
+		  pixel_height = 768,
+		  modes = <<>>}).
+
+
+%% dbg help macros
+-define(wr_record(N,BlackList),
+        wr_record(R=#N{}) ->  ssh_dbg:wr_record(R, record_info(fields,N), BlackList)
+        ).
+
+-define(wr_record(N), ?wr_record(N, [])).
+
+
+%% Circular trace buffer macros
+
+-record(circ_buf_entry,
+        {
+          module,
+          line,
+          function,
+          pid = self(),
+          value
+        }).
+
+-define(CIRC_BUF_IN(VALUE),
+        ssh_dbg:cbuf_in(
+          #circ_buf_entry{module = ?MODULE,
+                          line = ?LINE,
+                          function = {?FUNCTION_NAME,?FUNCTION_ARITY},
+                          pid = self(),
+                          value = (VALUE)
+                         })
+       ).
+
+-define(CIRC_BUF_IN_ONCE(VALUE),
+        ((fun(V) -> ?CIRC_BUF_IN(V), V end)(VALUE))
+       ).
+                 
+-endif. % SSH_HRL defined
diff --git a/lib/compiler/test/compile_SUITE_data/ssh_connect.hrl b/lib/compiler/test/compile_SUITE_data/ssh_connect.hrl
new file mode 100644
index 0000000000..3bd53d5912
--- /dev/null
+++ b/lib/compiler/test/compile_SUITE_data/ssh_connect.hrl
@@ -0,0 +1,273 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2005-2021. 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%
+%%
+
+%%
+
+%%% Description : SSH connection protocol 
+
+-define(DEFAULT_PACKET_SIZE, 65536).
+-define(DEFAULT_WINDOW_SIZE, 10*?DEFAULT_PACKET_SIZE).
+
+-define(MAX_PROTO_VERSION, 255).      % Max length of the hello string
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%
+%% CONNECT messages
+%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%%%----------------------------------------------------------------------
+%%% #   SSH_MSG_xxx
+%%% Description: Packet types used by the connection protocol.
+%%%----------------------------------------------------------------------
+-define(SSH_MSG_GLOBAL_REQUEST,  80).
+-define(SSH_MSG_REQUEST_SUCCESS,  81).
+-define(SSH_MSG_REQUEST_FAILURE,  82).
+-define(SSH_MSG_CHANNEL_OPEN,  90).
+-define(SSH_MSG_CHANNEL_OPEN_CONFIRMATION,  91).
+-define(SSH_MSG_CHANNEL_OPEN_FAILURE,  92).
+-define(SSH_MSG_CHANNEL_WINDOW_ADJUST,  93).
+-define(SSH_MSG_CHANNEL_DATA,  94).
+-define(SSH_MSG_CHANNEL_EXTENDED_DATA,  95).
+-define(SSH_MSG_CHANNEL_EOF,  96).
+-define(SSH_MSG_CHANNEL_CLOSE,  97).
+-define(SSH_MSG_CHANNEL_REQUEST,  98).
+-define(SSH_MSG_CHANNEL_SUCCESS,  99).
+-define(SSH_MSG_CHANNEL_FAILURE,  100).
+
+-record(ssh_msg_global_request,
+	{
+	  name,
+	  want_reply,
+	  data %% ...
+	 }).
+
+-record(ssh_msg_request_success,
+	{
+	  data  %% ...
+	 }).
+
+-record(ssh_msg_request_failure,
+	{
+	 }).
+
+
+-record(ssh_msg_channel_open,
+	{
+	  channel_type,
+	  sender_channel,
+	  initial_window_size,
+	  maximum_packet_size,
+	  data %% ...
+	 }).
+
+-record(ssh_msg_channel_open_confirmation,
+	{
+	  recipient_channel,
+	  sender_channel,
+	  initial_window_size,
+	  maximum_packet_size,
+	  data  %% ...
+	 }).
+
+
+%%%----------------------------------------------------------------------
+%%% #   SSH_OPEN_xxx
+%%% Description: Reason codes for SSH_MSG_OPEN_FAILURE packages.
+%%%----------------------------------------------------------------------
+
+-define(SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,	1).
+-define(SSH_OPEN_CONNECT_FAILED,		2).
+-define(SSH_OPEN_UNKNOWN_CHANNEL_TYPE,		3).
+-define(SSH_OPEN_RESOURCE_SHORTAGE,		4).
+
+-record(ssh_msg_channel_open_failure,
+	{
+	  recipient_channel,
+	  reason,
+	  description,
+	  lang
+	 }).
+
+	 
+-record(ssh_msg_channel_window_adjust,
+	{
+	  recipient_channel,
+	  bytes_to_add
+	 }).
+
+-record(ssh_msg_channel_data,
+	{
+	  recipient_channel,
+	  data
+	 }).
+
+%%%----------------------------------------------------------------------
+%%% #   SSH_EXTENDED_DATA_xxx
+%%% Description: Type codes for SSH_MSG_CHANNEL_EXTENDED_DATA packages
+%%%----------------------------------------------------------------------
+-define(SSH_EXTENDED_DATA_DEFAULT, 0).
+-define(SSH_EXTENDED_DATA_STDERR,  1).
+
+-record(ssh_msg_channel_extended_data,
+	{
+	  recipient_channel,
+	  data_type_code,
+	  data
+	 }).
+
+-record(ssh_msg_channel_eof,
+	{
+	  recipient_channel
+	 }).
+
+-record(ssh_msg_channel_close,
+	{
+	  recipient_channel
+	 }).
+
+
+-record(ssh_msg_channel_request,
+	{
+	  recipient_channel,
+	  request_type,
+	  want_reply,
+	  data         %% ...
+	 }).
+
+
+-record(ssh_msg_channel_success,
+	{
+	  recipient_channel
+	 }).
+
+
+-record(ssh_msg_channel_failure,
+	{
+	  recipient_channel
+	 }).
+
+-define(TERMINAL_WIDTH, 80).
+-define(TERMINAL_HEIGHT, 24).
+-define(DEFAULT_TERMINAL, "vt100").
+
+-define(TTY_OP_END,0).  %% Indicates end of options.
+-define(VINTR,1).       %% Interrupt character; 255 if none. Similarly for the
+			%% other characters. Not all of these characters are
+                        %% supported on all systems.
+-define(VQUIT,2).       %% The quit character (sends SIGQUIT signal on POSIX
+                        %%                    systems).
+-define(VERASE,3).      %% Erase the character to left of the cursor.
+-define(VKILL,4).       %% Kill the current input line.
+-define(VEOF,5).        %% End-of-file character (sends EOF from the terminal).
+-define(VEOL,6).        %% End-of-line character in addition to carriage return
+                        %% or,and). linefeed.
+-define(VEOL2,7).       %% Additional end-of-line character.
+-define(VSTART,8).      %% Continues paused output (normally control-Q).
+-define(VSTOP,9).       %% Pauses output (normally control-S).
+-define(VSUSP,10).      %% Suspends the current program.
+-define(VDSUSP,11).     %% Another suspend character.
+-define(VREPRINT,12).   %% Reprints the current input line.
+-define(VWERASE,13).    %% Erases a word left of cursor.
+-define(VLNEXT,14).     %% Enter the next character typed literally, even if it
+                        %% is a special character
+-define(VFLUSH,15).     %% Character to flush output.
+-define(VSWTCH,16).     %% Switch to a different shell layer.
+-define(VSTATUS,17).    %% Prints system status line (load, command, pid etc).
+-define(VDISCARD,18).   %% Toggles the flushing of terminal output.
+-define(IGNPAR,30).     %% The ignore parity flag.  The parameter SHOULD be 0 if
+                        %% this flag is FALSE set, and 1 if it is TRUE.
+-define(PARMRK,31).     %% Mark parity and framing errors.
+-define(INPCK,32).      %% Enable checking of parity errors.
+-define(ISTRIP,33).     %% Strip 8th bit off characters.
+-define(INLCR,34).      %% Map NL into CR on input.
+-define(IGNCR,35).      %% Ignore CR on input.
+-define(ICRNL,36).      %% Map CR to NL on input.
+-define(IUCLC,37).      %% Translate uppercase characters to lowercase.
+-define(IXON,38).       %% Enable output flow control.
+-define(IXANY,39).      %% Any char will restart after stop.
+-define(IXOFF,40).      %% Enable input flow control.
+-define(IMAXBEL,41).    %% Ring bell on input queue full.
+-define(IUTF8,42).      %% Terminal input and output is assumed to be encoded in UTF-8.
+-define(ISIG,50).       %% Enable signals INTR, QUIT, [D]SUSP.
+-define(ICANON,51).     %% Canonicalize input lines.
+-define(XCASE,52).      %% Enable input and output of uppercase characters by
+                        %% preceding their lowercase equivalents with `\'.
+-define(ECHO,53).       %% Enable echoing.
+-define(ECHOE,54).      %% Visually erase chars.
+-define(ECHOK,55).      %% Kill character discards current line.
+-define(ECHONL,56).     %% Echo NL even if ECHO is off.
+-define(NOFLSH,57).     %% Don't flush after interrupt.
+-define(TOSTOP,58).     %% Stop background jobs from output.
+-define(IEXTEN,59).     %% Enable extensions.
+-define(ECHOCTL,60).    %% Echo control characters as ^(Char).
+-define(ECHOKE,61).     %% Visual erase for line kill.
+-define(PENDIN,62).     %% Retype pending input.
+-define(OPOST,70).      %% Enable output processing.
+-define(OLCUC,71).      %% Convert lowercase to uppercase.
+-define(ONLCR,72).      %% Map NL to CR-NL.
+-define(OCRNL,73).      %% Translate carriage return to newline (output).
+-define(ONOCR,74).      %% Translate newline to carriage return-newline
+                        %% (output).
+-define(ONLRET,75).     %% Newline performs a carriage return (output).
+-define(CS7,90).        %% 7 bit mode.
+-define(CS8,91).        %% 8 bit mode.
+-define(PARENB,92).     %% Parity enable.
+-define(PARODD,93).     %% Odd parity, else even.
+
+%%  Specifies the input baud rate in bits per second.
+-define(TTY_OP_ISPEED,128).
+%%  Specifies the output baud rate in bits per second.
+-define(TTY_OP_OSPEED,129).  
+
+-record(channel,
+	{
+	  type,          %% "session"
+	  sys,           %% "none", "shell", "exec" "subsystem"
+	  user,          %% "user" process id (default to cm user)
+	  flow_control, 
+
+	  local_id,           %% local channel id
+
+	  recv_window_size,
+	  recv_window_pending = 0, %% Sum of window size updates that has not
+	                           %% yet been sent. This limits the number
+	                           %% of sent update msgs.
+	  recv_packet_size,
+	  recv_close = false,
+
+	  remote_id,          %% remote channel id
+	  send_window_size,
+	  send_packet_size,
+	  sent_close = false,
+	  send_buf = []
+	 }).
+
+-record(connection, {
+	  requests = [], %% [{ChannelId, Pid}...] awaiting reply on request,
+	  channel_cache,
+	  channel_id_seed,
+	  cli_spec,
+	  options,
+          suggest_window_size,
+          suggest_packet_size,
+	  exec,
+	  sub_system_supervisor
+	 }).
-- 
2.35.3

openSUSE Build Service is sponsored by