Did you know ... Search Documentation:
ssh_server.pl -- Embedded SSH server
PublicShow source

This module defines an embedded SSH server for SWI-Prolog on top of libssh. This module allows for a safe secondary access point to a running Prolog process. A typical use case is to provide a safe channal or inspection and maintenance of servers or embedded Prolog instances.

If possible, a login to the Prolog process uses a pseudo terminal to realise normal terminal interaction, including processing of ^C to interrupt running queries. If libedit (editline) is used as the command line editor this is installed (see el_wrap/0), providing advanced command line editing and history.

The library currently support login to the Prolog process. Future versions may also use the client access and exploit the SSH subsystem interface to achieve safe interaction between Prolog peers.

The client session

A new connection creates a Prolog thread that handles the connection. The new thread's standard streams (user_input, user_output, user_error, current_input and current_output) are attached to the new connection. Some of the environment is shared as Prolog flags. The following flags are defined:

ssh_tty
Provides the name of the pseudo terminal if such a terminal us allocated for this connection.
ssh_term
Provides the TERM environment variable passed from the client.
ssh_user
Provides the name of the user logged on.

If a pseudo terminal is used and the ssh_term flag is not dump, library(ansi_term) is connected to provide colorized output.

If a pseudo terminal is used and library(editline) is available, this library is used to enable command line editing.

Executing commands

Using ssh <options> <server> <command>, <command> is executed without a terminal (unless the -t option is given to ssh to force a terminal) and otherwise as a single Prolog toplevel command. For example:

ssh -p 2020 localhost "writeln('Hello world')"
Hello world
true.

If the query is nondeterministic alternative answers can be requested in the same way as using the interactive toplevel. The exit code is defined as follows:

0
The query succeeded
1
The query failed
2
The query produced an exception (the system prints a backtrace)
3
The query itself was not syntactically correct.

Aborting the server

If a Prolor process with an embedded ssh server misbehaves it can be forcefully aborted using the abort command. This calls C abort() as soon as possible and thus should function even if Prolog is, for example, stuck in a deadlock.

ssh -p 2020 localhost abort
To be done
- Currently only supports Unix. A Windows port is probably doable. It mostly requires finding a sensible replacement for the Unix pseudo terminal.
- Implement running other commands than the Prolog toplevel.
Source ssh_server is det
Source ssh_server(+PortOrOptions) is det
Create an embedded SSH server in the current Prolog process. If the argument is an integer it is interpreted as ssh_server([port(Integer)]). Options:
name(+Atom)
Name the server. Passed as first argument to verify_password/3 to identify multiple servers.
port(+Integer)
Port to listen on. Default is 2020.
bind_address(+Name)
Interface to listen to. Default is localhost. Use * to grant acccess from all network interfaces.
host_key_file(+File)
File name for the host private key. If omitted it searches for etc/ssh below the current directory and user_app_config('etc/ssh') (normally ~/.config/swi-prolog/etc/ssh). On failure it creates, a directory etc/ssh with default host keys and uses these.
auth_methods(+ListOfMethod)
Set allowed authentication methods. ListOfMethod is a list of
password
Allow password login (see verify_password/3)
public_key
Allow key based login (see authorized_keys_file below) The default is derived from the authorized_keys_file option and whether or not verify_password/3 is defined.
authorized_keys_file(+File)
File name for a file holding the public keys for users that are allows to login. Activates auth_methods([public_key]). This file is in OpenSSH format and contains a certificate per line in the format
<type> <base64-key> <comment>

The the file `~/.ssh/authorized_keys` is present, this will be used as default, granting anyone with access to this account to access the server with the same keys. If the option is present with value [] (empty list), no key file is used.

Source ensure_host_keys(+Options0, -Options) is det[private]
Provide a host key:
  1. If the key file is given, use it.
  2. If there is a key in etc/ssh, use it.
  3. If there is a key in user_app_config('etc/ssh'), use it.
  4. Try to create a key in user_app_config('etc/ssh')
  5. Try to create a key in etc/ssh
Source setup_signals(+Options)[private]
Re-installs the int signal to start the debugger. Notably library(http/http_unix_daemon) binds this to terminates the process.
Source run_client(+Server, +In, +Out, +Err, +Command, -RetCode) is det
Run Command using I/O from the triple <In, Out, Err> and bind RetCode to the ssh shell return code.
Source enable_colors is det[private]
Enable ANSI colors on the remote shell. This is controlled by the setting color_term. Note that we do not wish to inherit this as the server may have different preferences.
 enable_line_editing is det[private]
Enable line editing for the SSH session. We can do this if the SSH session uses a pseudo terminal and we are using library(editline) as command line editor (GNU readline uses global variables and thus can only handle a single tty in the process).
Source verify_password(+ServerName, +User:atom, +Passwd:string) is semidet[multifile]
Hook that can be used to accept password based logins. This predicate must succeeds to accept the User/Passwd combination.
Arguments:
ServerName- is the name provided with the name(Name) option when creating the server or the empty list.
Source load_history(+EditMode, +Server, -Cleanup) is det[private]
Load command line history for Server, binding Cleanup to the required command for save_history/1
Source save_history(+Action) is det[private]
Save the history information according to action.
Source ssh_toplevel(+Command, -RetCode)[private]
Run the toplevel goal for the SSH session. The default is prolog, running the toplevel. Otherwise the argument is processed as a single toplevel goal.
Source capture_messages(+Level) is det
Redirect all messages of the indicated level to the console of the current thread. This is part of the SSH library as it is notably practical when connected through SSH. Consider using trace/1 on some predicate. We catch capture the output using:
?- capture_messages(debug).
?- trace(p/1).

Re-exported predicates

The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

Source ssh_server is det
Source ssh_server(+PortOrOptions) is det
Create an embedded SSH server in the current Prolog process. If the argument is an integer it is interpreted as ssh_server([port(Integer)]). Options:
name(+Atom)
Name the server. Passed as first argument to verify_password/3 to identify multiple servers.
port(+Integer)
Port to listen on. Default is 2020.
bind_address(+Name)
Interface to listen to. Default is localhost. Use * to grant acccess from all network interfaces.
host_key_file(+File)
File name for the host private key. If omitted it searches for etc/ssh below the current directory and user_app_config('etc/ssh') (normally ~/.config/swi-prolog/etc/ssh). On failure it creates, a directory etc/ssh with default host keys and uses these.
auth_methods(+ListOfMethod)
Set allowed authentication methods. ListOfMethod is a list of
password
Allow password login (see verify_password/3)
public_key
Allow key based login (see authorized_keys_file below) The default is derived from the authorized_keys_file option and whether or not verify_password/3 is defined.
authorized_keys_file(+File)
File name for a file holding the public keys for users that are allows to login. Activates auth_methods([public_key]). This file is in OpenSSH format and contains a certificate per line in the format
<type> <base64-key> <comment>

The the file `~/.ssh/authorized_keys` is present, this will be used as default, granting anyone with access to this account to access the server with the same keys. If the option is present with value [] (empty list), no key file is used.