ssh (ssh v5.2.9)
View SourceMain 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 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.
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 or
daemon/3. Possible channel handlers (subsystems) are declared with
the subsystem 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. 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.
To write your own client channel handler, use the behaviour
ssh_client_channel. For server channel handlers use ssh_server_channel
behaviour (replaces ssh_daemon_channel).
Both clients and daemons accept options that control the exact behaviour. Some options are common to both. The three sets are called Client Options, Daemon Options and Common Options.
The descriptions of the options uses the Erlang Type Language with explaining text.
Note
See also SSH Application Reference and Examples 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. Keys could be
generated with the ssh-keygen program from OpenSSH. See the
User's Guide.
The paths could easily be changed by options:
user_dir and
system_dir.
A completely different storage could be interfaced by writing callback modules
using the behaviours ssh_client_key_api and/or ssh_server_key_api. A
callback module is installed with the option
key_cb 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/sshin the files- ssh_host_dsa_keyand- ssh_host_dsa_key.pub
- ssh_host_rsa_keyand- ssh_host_rsa_key.pub
- ssh_host_ecdsa_keyand- ssh_host_ecdsa_key.pub
 - The host keys directory could be changed with the option - system_dir.
- Optional: one or more User's public key in case of - publickeyauthorization. Default is to store them concatenated in the file- .ssh/authorized_keysin the user's home directory.- The user keys directory could be changed with the option - user_dir.
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.
- 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 - host_accepting_client_options/0are associated with this list of keys.
- Optional: one or more User's private key(s) in case of - publickeyauthorization. The default files are- id_dsaand- id_dsa.pub
- id_rsaand- id_rsa.pub
- id_ecdsaand- id_ecdsa.pub
 
Summary
Types: Other data types
Opaque data type representing a channel inside a connection.
Return values from the connection_info/1 and connection_info/2 functions.
Opaque data type representing a connection between a client and a server (daemon).
Return values from the daemon_info/1 and daemon_info/2 functions.
Opaque data type representing a daemon.
Opaque types that define experimental options that are not to be used in products.
The socket is supposed to be result of a gen_tcp:connect
or a gen_tcp:accept. The socket must be in passive mode
(that is, opened with the option {active,false}).
Functions
Closes an SSH connection.
Equivalent to connect/4.
Connects to an SSH server at the Host on Port.
Equivalent to connection_info/2.
Returns information about a connection intended for e.g debugging or logging.
Equivalent to daemon/3.
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.
Equivalent to daemon_info/2.
Returns information about a daemon intended for e.g debugging or logging.
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.
Returns a key-value list, where the keys are the different types of algorithms and the values are the algorithms themselves.
Get tcp socket option values of the tcp-socket below an ssh connection.
Equivalent to hostkey_fingerprint/2.
hostkey_fingerprint([DigestType], HostKey) -> [string()]hostkey_fingerprint(DigestType, HostKey) -> string()
Sets tcp socket options on the tcp-socket below an ssh connection.
Equivalent to shell/3.
Connects to an SSH server at Host and Port (defaults to 22) and starts an
interactive shell on that remote host.
Utility function that starts the applications crypto, public_key, and ssh.
Default type is temporary. For more information, see the application
manual page in Kernel.
Stops the ssh application. For more information, see the application
manual page in Kernel.
Equivalent to stop_daemon/3.
Equivalent to stop_daemon/3.
Stops the listener and all connections started by the listener.
Equivalent to stop_listener/3.
Equivalent to stop_listener/3.
Stops the listener, but leaves existing connections started by the listener operational.
Equivalent to tcpip_tunnel_from_server/6.
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.
Equivalent to tcpip_tunnel_to_server/6.
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.
Types: Client Options
Types: Daemon Options
Types: Common Options
Types: Other data types
-opaque channel_id()
      Opaque data type representing a channel inside a connection.
Returned by the functions ssh_connection:session_channel/2,4.
-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()}].
-type conn_info_channels() :: [proplists:proplist()].
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.
-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()}.
-type connection_ref() :: pid().
Opaque data type representing a connection between a client and a server (daemon).
Returned by the functions connect/2,3,4 and
ssh_sftp:start_channel/2,3.
-type daemon_info_tuple() :: {port, inet:port_number()} | {ip, inet:ip_address()} | {profile, atom()} | {options, daemon_options()}.
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.
-opaque daemon_ref()
      Opaque data type representing a daemon.
Returned by the functions daemon/1,2,3.
-type host() :: string() | inet:ip_address() | loopback.
-type ip_port() :: {inet:ip_address(), inet:port_number()}.
-type opaque_common_options() :: {transport, {atom(), atom(), atom()}} | {vsn, {non_neg_integer(), non_neg_integer()}} | {tstflg, [term()]} | ssh_file:user_dir_fun_common_option() | {max_random_length_padding, non_neg_integer()}.
Opaque types that define experimental options that are not to be used in products.
-type opaque_daemon_options() :: {infofun, fun()} | opaque_common_options().
-type open_socket() :: gen_tcp:socket().
The socket is supposed to be result of a gen_tcp:connect
or a gen_tcp:accept. The socket must be in passive mode
(that is, opened with the option {active,false}).
-type protocol_version() :: {Major :: pos_integer(), Minor :: non_neg_integer()}.
-type software_version() :: string().
-type version() :: {protocol_version(), software_version()}.
Types
Functions
-spec close(ConnectionRef) -> ok | {error, term()} when ConnectionRef :: connection_ref().
Closes an SSH connection.
-spec connect(OpenTcpSocket, Options) -> {ok, connection_ref()} | {error, term()} when OpenTcpSocket :: open_socket(), Options :: client_options().
Equivalent to 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()}.
Equivalent to connect/4.
-spec connect(Host, Port, Options, NegotiationTimeout) -> {ok, connection_ref()} | {error, term()} when Host :: host(), Port :: inet:port_number(), Options :: client_options(), NegotiationTimeout :: timeout().
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.
The NegotiationTimeout is in milli-seconds. The default value is infinity or
the value of the connect_timeout
option, if present. For connection timeout, use the option
connect_timeout.
-spec connection_info(ConnectionRef) -> InfoTupleList | {error, term()} when ConnectionRef :: connection_ref(), InfoTupleList :: [InfoTuple], InfoTuple :: connection_info_tuple().
Equivalent to connection_info/2.
-spec connection_info(ConnectionRef, ItemList | Item) -> InfoTupleList | InfoTuple | {error, term()} when ConnectionRef :: connection_ref(), ItemList :: [Item], Item :: client_version | server_version | user | peer | sockname | options | algorithms | sockname, InfoTupleList :: [InfoTuple], InfoTuple :: connection_info_tuple().
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 daemon(inet:port_number()) -> {ok, daemon_ref()} | {error, term()}.
Equivalent to daemon/3.
-spec daemon(inet:port_number() | open_socket(), daemon_options()) -> {ok, daemon_ref()} | {error, term()}.
Equivalent to daemon/3.
-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()}.
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.
Please note that by historical reasons both the HostAddress argument and the
gen_tcp connect_option() {ip,Address} set the
listening address. This is a source of possible inconsistent settings.
The rules for handling the two address passing options are:
- if HostAddressis an IP-address, that IP-address is the listening address. An 'ip'-option will be discarded if present.
- if HostAddressis the atomloopback, the listening address isloopbackand an loopback address will be chosen by the underlying layers. An 'ip'-option will be discarded if present.
- if HostAddressis the atomanyand no 'ip'-option is present, the listening address isanyand the socket will listen to all addresses
- if HostAddressisanyand an 'ip'-option is present, the listening address is set to the value of the 'ip'-option
-spec daemon_info(DaemonRef) -> {ok, InfoTupleList} | {error, bad_daemon_ref} when DaemonRef :: daemon_ref(), InfoTupleList :: [InfoTuple], InfoTuple :: daemon_info_tuple().
Equivalent to daemon_info/2.
-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().
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 and
daemon_info/2 returns different types due to compatibility
reasons.
-spec daemon_replace_options(DaemonRef, NewUserOptions) -> {ok, daemon_ref()} | {error, term()} when DaemonRef :: daemon_ref(), NewUserOptions :: daemon_options().
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
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 and Configuring algorithms in SSH.
-spec default_algorithms() -> algs_list().
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 for an example.
-spec get_sock_opts(ConnectionRef, SocketGetOptions) -> ok | {error, inet:posix()} when ConnectionRef :: connection_ref(), SocketGetOptions :: [gen_tcp:option_name()].
Get tcp socket option values of the tcp-socket below an ssh connection.
This function calls the inet:getopts/2, read that documentation.
-spec hostkey_fingerprint(public_key:public_key()) -> string().
Equivalent to hostkey_fingerprint/2.
-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([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 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:
 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"]-spec set_sock_opts(ConnectionRef, SocketOptions) -> ok | {error, inet:posix()} when ConnectionRef :: connection_ref(), SocketOptions :: [gen_tcp:option()].
Sets tcp socket options on the tcp-socket below an ssh connection.
This function calls the inet:setopts/2, read that documentation and for
gen_tcp:option/0.
All gen_tcp socket options except
- active
- deliver
- modeand
- packet
are allowed. The excluded options are reserved by the SSH application.
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.
-spec shell(open_socket() | host() | connection_ref()) -> _.
Equivalent to shell/3.
-spec shell(open_socket() | host(), client_options()) -> _.
Equivalent to shell/3.
-spec shell(Host, Port, Options) -> _ when Host :: host(), Port :: inet:port_number(), Options :: client_options().
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.
The function waits for user input, and does not return until the remote shell is ended (that is, exit from the shell).
-spec start() -> ok | {error, term()}.
Equivalent to start/1.
-spec start(Type) -> ok | {error, term()} when Type :: permanent | transient | temporary.
Utility function that starts the applications crypto, public_key, and ssh.
Default type is temporary. For more information, see the application
manual page in Kernel.
-spec stop() -> ok | {error, term()}.
Stops the ssh application. For more information, see the application
manual page in Kernel.
-spec stop_daemon(DaemonRef :: daemon_ref()) -> ok.
Equivalent to stop_daemon/3.
-spec stop_daemon(inet:ip_address(), inet:port_number()) -> ok.
Equivalent to stop_daemon/3.
-spec stop_daemon(any | inet:ip_address(), inet:port_number(), atom()) -> ok.
Stops the listener and all connections started by the listener.
-spec stop_listener(daemon_ref()) -> ok.
Equivalent to stop_listener/3.
-spec stop_listener(inet:ip_address(), inet:port_number()) -> ok.
Equivalent to stop_listener/3.
-spec stop_listener(any | inet:ip_address(), inet:port_number(), term()) -> ok.
Stops the listener, but leaves existing connections started by the listener operational.
-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().
Equivalent to tcpip_tunnel_from_server/6.
-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().
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 to allow the connection.
-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().
Equivalent to tcpip_tunnel_to_server/6.
-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().
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 to allow the connection.