diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl index 1914f11119f1..d1a292f88539 100644 --- a/lib/ssh/src/ssh.erl +++ b/lib/ssh/src/ssh.erl @@ -135,7 +135,7 @@ The directory could be changed with the option [{type,<<"Client Options">>}, {type,<<"Daemon Options">>}, {type,<<"Common Options">>}, - {type,<<"Other data types">>}]}). + {type,<<"Deprecated">>}]}). -include("ssh.hrl"). -include("ssh_connect.hrl"). @@ -174,8 +174,11 @@ The directory could be changed with the option %%% "Deprecated" types export: -export_type([ssh_daemon_ref/0, ssh_connection_ref/0, ssh_channel_id/0]). +-doc(#{title => <<"Deprecated">>}). -opaque ssh_daemon_ref() :: daemon_ref(). +-doc(#{title => <<"Deprecated">>}). -opaque ssh_connection_ref() :: connection_ref(). +-doc(#{title => <<"Deprecated">>}). -opaque ssh_channel_id() :: channel_id(). @@ -208,7 +211,6 @@ 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. @@ -216,7 +218,6 @@ 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 @@ -225,7 +226,6 @@ Opaque data type representing a connection between a client and a server 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 %%-------------------------------------------------------------------- @@ -427,13 +427,9 @@ close(ConnectionRef) -> %%-------------------------------------------------------------------- %% Description: Retrieves information about a connection. %%--------------------------------------------------------------------- --doc(#{title => <<"Other data types">>}). -type version() :: {protocol_version(), software_version()}. --doc(#{title => <<"Other data types">>}). -type protocol_version() :: {Major::pos_integer(), Minor::non_neg_integer()}. --doc(#{title => <<"Other data types">>}). -type software_version() :: string(). --doc(#{title => <<"Other data types">>}). -type conn_info_algs() :: [{kex, kex_alg()} | {hkey, pubkey_alg()} | {encrypt, cipher_alg()} @@ -445,16 +441,14 @@ close(ConnectionRef) -> | {send_ext_info, boolean()} | {recv_ext_info, boolean()} ]. +-type conn_info_channels() :: [proplists:proplist()]. + -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 +In the `options` 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">>}). -type connection_info_tuple() :: {client_version, version()} | {server_version, version()} @@ -691,7 +685,6 @@ 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()} diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl index 46d93a166212..7f2a477b1fd4 100644 --- a/lib/ssh/src/ssh.hrl +++ b/lib/ssh/src/ssh.hrl @@ -122,16 +122,17 @@ %% Types +-doc(#{title => <<"Other Data Types">>}). -type role() :: client | server . --doc(#{title => <<"Other data types">>}). +-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">>}). +-doc(#{title => <<"Other Data Types">>}). -type open_socket() :: gen_tcp:socket(). -doc """ @@ -514,7 +515,7 @@ protocol). Opaque types that define experimental options that are not to be used in products. """. --doc(#{title => <<"Other data types">>}). +-doc(#{title => <<"Other Data Types">>}). -type opaque_common_options() :: {transport, {atom(),atom(),atom()} } | {vsn, {non_neg_integer(),non_neg_integer()} } @@ -547,7 +548,7 @@ risk. | gen_tcp:connect_option() | ?COMMON_OPTION . --doc(#{title => <<"Other data types">>}). +-doc(#{title => <<"Other Data Types">>}). -type opaque_client_options() :: {keyboard_interact_fun, fun((Name::iodata(), Instruction::iodata(), @@ -1149,17 +1150,17 @@ in the User's Guide chapter. {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">>}). +-doc(#{title => <<"Other Data Types">>}). -type opaque_daemon_options() :: {infofun, fun()} | opaque_common_options(). --doc(#{title => <<"Other data types">>}). +-doc(#{title => <<"Other Data Types">>}). -type ip_port() :: {inet:ip_address(), inet:port_number()} . --doc(#{title => <<"Other data types">>}). +-doc(#{title => <<"Other Data Types">>}). -type mod_args() :: {Module::atom(), Args::list()} . --doc(#{title => <<"Other data types">>}). +-doc(#{title => <<"Other Data Types">>}). -type mod_fun_args() :: {Module::atom(), Function::atom(), Args::list()} . diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl index cef81e56a57d..d77989273705 100644 --- a/lib/ssh/src/ssh_connection.erl +++ b/lib/ssh/src/ssh_connection.erl @@ -417,6 +417,12 @@ request is a one-time execution that closes the channel when it is done. See the User's Guide section on [One-Time Execution](using_ssh.md#one-time-execution) for examples. + +> #### Note {: .info } +> +> In case when command generates large amount of output data, manual +> window adjustment might be necessary in order to receive it. +> see [`ssh_connectino:adjust_window/3`](`adjust_window/3`) """. -spec exec(ConnectionRef, ChannelId, Command, Timeout) -> result() when ConnectionRef :: ssh:connection_ref(), diff --git a/lib/ssh/src/ssh_sftp.erl b/lib/ssh/src/ssh_sftp.erl index e2ce584f2d34..a0af7a1fb897 100644 --- a/lib/ssh/src/ssh_sftp.erl +++ b/lib/ssh/src/ssh_sftp.erl @@ -130,38 +130,38 @@ The `t:tuple/0` reason are other errors like for example `{exit_status,1}`. %%==================================================================== %% API %%==================================================================== - - -%%%================================================================ -%%% - -%%%---------------------------------------------------------------- -%%% start_channel/1 --doc(#{equiv => start_channel/3}). +-doc(#{equiv => start_channel/2}). -spec start_channel(ssh:open_socket() | ssh:connection_ref() | ssh:host()) -> {ok, pid()} | {ok, pid(), ssh:connection_ref()} | {error, reason()}. start_channel(Dest) -> start_channel(Dest, []). - -%%%---------------------------------------------------------------- -%%% start_channel/2 + %%% -spec:s are as if Dialyzer handled signatures for separate %%% function clauses. --doc(#{equiv => start_channel/3}). --spec start_channel(ssh:open_socket(), - [ssh:client_option() | sftp_option()] - ) - -> {ok,pid(),ssh:connection_ref()} | {error,reason()}; +-doc """ +Starts new ssh channel for communicating with the SFTP server. - (ssh:connection_ref(), - [sftp_option()] - ) - -> {ok,pid()} | {ok,pid(),ssh:connection_ref()} | {error,reason()}; +Starts an ssh channel when first argument is a connection reference. - (ssh:host(), - [ssh:client_option() | sftp_option()] - ) - -> {ok,pid(),ssh:connection_ref()} | {error,reason()} . +Equivalent to [start_channel(Host, 22, UserOptions)](`start_channel/3`) when +first argument is recognized as network host. + +Otherwise, first argument is treated as a network socket which will be used for +establishing new SSH connection. New connection reference will be used for +starting an SSH channel. + +The returned `pid` for this process is to be used as input to all other API +functions in this module. + +See also (`start_channel/3`). + +""". +-spec start_channel(ssh:open_socket(), [ssh:client_option() | sftp_option()]) -> + {ok,pid(),ssh:connection_ref()} | {error,reason()}; + (ssh:connection_ref(), [sftp_option()]) -> + {ok,pid()} | {ok,pid(),ssh:connection_ref()} | {error,reason()}; + (ssh:host(), [ssh:client_option() | sftp_option()]) -> + {ok,pid(),ssh:connection_ref()} | {error,reason()}. start_channel(Cm, UserOptions0) when is_pid(Cm) -> UserOptions = legacy_timeout(UserOptions0), Timeout = proplists:get_value(timeout, UserOptions, infinity), @@ -209,14 +209,10 @@ start_channel(Dest, UserOptions0) -> end end. -%%%---------------------------------------------------------------- -%%% start_channel/3 -doc """ -start_channel(Host, Port, Options) -> +Starts new ssh connection and channel for communicating with the SFTP server. -If no connection reference is provided, a connection is set up, and the new -connection is returned. An SSH channel process is started to handle the -communication with the SFTP server. The returned `pid` for this process is to be +The returned `pid` for this process is to be used as input to all other API functions in this module. Options: