ssh_connection
This module provides API functions to send SSH Connection Protocol
events to the other side of an SSH channel.
The SSH Connection Protocol is used by clients and servers
(i.e. SSH channels) to communicate over the SSH connection. The
API functions in this module sends SSH Connection Protocol events
that are received as messages by the remote channel.
In the case that the receiving channel is an Erlang process the
message will be on the following format
{ssh_cm, ssh_connection_ref(), ssh_event_msg()}
. If the ssh_channel behavior is used to
implement the channel process these will be handled by
handle_ssh_msg/2 .
DATA TYPES
Type definitions that are used more than once in this module and/or abstractions to indicate the intended use of the data type:
boolean() = true | false
string() = list of ASCII characters
timeout() = infinity | integer() - in milliseconds.
ssh_connection_ref() - opaque to the user returned by
ssh:connect/3 or sent to an SSH channel processes
ssh_channel_id() = integer()
ssh_data_type_code() = 1 ("stderr") | 0 ("normal") are
currently valid values see
ssh_request_status() = success | failure
event() = {ssh_cm, ssh_connection_ref(), ssh_event_msg()}
ssh_event_msg() = data_events() | status_events() | terminal_events()
{data, ssh_channel_id(), ssh_data_type_code(), binary() = Data}
{eof, ssh_channel_id()}
{signal, ssh_channel_id(), ssh_signal()}
{exit_signal, ssh_channel_id(), string() = ExitSignal, string() = ErrorMsg,
string() = LanguageString}
{exit_status, ssh_channel_id(), integer() = ExitStatus}
{closed, ssh_channel_id()}
Channels implementing a shell and command execution on the server side should handle the following messages that may be sent by client channel processes.
Note!
Events that includes a WantReply
expects the event handling
process to call ssh_connection:reply_request/4
with the boolean value of WantReply
as the second
argument.
{env, ssh_channel_id(), boolean() = WantReply,
string() = Var, string() = Value}
{pty, ssh_channel_id(),
boolean() = WantReply, {string() = Terminal, integer() = CharWidth,
integer() = RowHeight, integer() = PixelWidth, integer() = PixelHight,
[{atom() | integer() = Opcode,
integer() = Value}] = TerminalModes}}
Opcode
in the
TerminalModes
list is the mnemonic name, represented
as an lowercase erlang atom, defined in
OP code: 53, mnemonic name ECHO erlang atom:
echo
. There is currently no API function to generate this
event.{shell, boolean() = WantReply}
{window_change, ssh_channel_id(), integer() = CharWidth,
integer() = RowHeight, integer() = PixWidth, integer() = PixHeight}
{exec, ssh_channel_id(),
boolean() = WantReply, string() = Cmd}
Functions
adjust_window(ConnectionRef, ChannelId, NumOfBytes) -> ok
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
NumOfBytes = integer()
Adjusts the SSH flowcontrol window. This shall be done by both client and server side channel processes.
Note!
Channels implemented with the ssh_channel behavior will normaly not need to call this function as flow control will be handled by the behavior. The behavior will adjust the window every time the callback handle_ssh_msg/2 has returned after processing channel data
close(ConnectionRef, ChannelId) -> ok
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
A server or client channel process can choose to close their session by sending a close event.
Note!
This function will be called by the ssh_channel behavior when the channel is terminated see ssh_channel(3) so channels implemented with the behavior should not call this function explicitly.
exec(ConnectionRef, ChannelId, Command, TimeOut) -> ssh_request_status()
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Command = string()
Timeout = timeout()
Should be called by a client channel process to request that the server starts execution of the given command, the result will be several messages according to the following pattern. Note that the last message will be a channel close message, as the exec request is a one time execution that closes the channel when it is done.
N x {ssh_cm, ssh_connection_ref(),
{data, ssh_channel_id(), ssh_data_type_code(), binary() = Data}}
0 or 1 x {ssh_cm, ssh_connection_ref(), {eof, ssh_channel_id()}}
0 or 1 x {ssh_cm,
ssh_connection_ref(), {exit_signal,
ssh_channel_id(), string() = ExitSignal, string() = ErrorMsg, string() = LanguageString}}
0 or 1 x {ssh_cm, ssh_connection_ref(), {exit_status,
ssh_channel_id(), integer() = ExitStatus}}
ssh connection protocol
that this
message shall be sent, but that may not always be the case. 1 x {ssh_cm, ssh_connection_ref(),
{closed, ssh_channel_id()}}
exit_status(ConnectionRef, ChannelId, Status) -> ok
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Status = integer()
Should be called by a server channel process to sends the exit status of a command to the client.
reply_request(ConnectionRef, WantReply, Status, ChannelId) -> ok
ConnectionRef = ssh_connection_ref()
WantReply = boolean()
Status = ssh_request_status()
ChannelId = ssh_channel_id()
Sends status replies to requests where the requester has
stated that they want a status report e.i . WantReply = true
,
if WantReply
is false calling this function will be a
"noop". Should be called while handling an ssh connection
protocol message containing a WantReply
boolean
value.
send(ConnectionRef, ChannelId, Data) ->
send(ConnectionRef, ChannelId, Data, Timeout) ->
send(ConnectionRef, ChannelId, Type, Data) ->
send(ConnectionRef, ChannelId, Type, Data, TimeOut) -> ok | {error, timeout} | {error, closed}
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Data = binary()
Type = ssh_data_type_code()
Timeout = timeout()
Should be called by client- and server channel processes to send data to each other.
send_eof(ConnectionRef, ChannelId) -> ok | {error, closed}
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Sends eof on the channel ChannelId
.
session_channel(ConnectionRef, Timeout) ->
session_channel(ConnectionRef, InitialWindowSize, MaxPacketSize, Timeout) -> {ok, ssh_channel_id()} | {error, Reason}
ConnectionRef = ssh_connection_ref()
InitialWindowSize = integer()
MaxPacketSize = integer()
Timeout = timeout()
Reason = term()
Opens a channel for an SSH session. The channel id returned from this function is the id used as input to the other funtions in this module.
setenv(ConnectionRef, ChannelId, Var, Value, TimeOut) -> ssh_request_status()
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Var = string()
Value = string()
Timeout = timeout()
Environment variables may be passed before starting the shell/command. Should be called by a client channel processes.
shell(ConnectionRef, ChannelId) -> ssh_request_status()
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Should be called by a client channel process to request that the user's default shell (typically defined in /etc/passwd in UNIX systems) shall be executed at the server end.
subsystem(ConnectionRef, ChannelId, Subsystem, Timeout) -> ssh_request_status()
ConnectionRef = ssh_connection_ref()
ChannelId = ssh_channel_id()
Subsystem = string()
Timeout = timeout()
Should be called by a client channel process for requesting to execute a predefined subsystem on the server.