The library(socket) provides TCP and UDP inet-domain sockets from SWI-Prolog, both client and server-side communication. The interface of this library is very close to the Unix socket interface, also supported by the MS-Windows winsock API. SWI-Prolog applications that wish to communicate with multiple sources have two options:
Using this library to establish a TCP connection to a server is as simple as opening a file. See also http_open/3.
dump_swi_homepage :- setup_call_cleanup( tcp_connect('www.swi-prolog.org':http, Stream, []), ( format(Stream, 'GET / HTTP/1.1~n\c Host: www.swi-prolog.org~n\c Connection: close~n~n', []), flush_output(Stream), copy_stream_data(Stream, current_output) ), close(Stream)).
To deal with timeouts and multiple connections, threads, wait_for_input/3 and/or non-blocking streams (see tcp_fcntl/3) can be used.
The typical sequence for generating a server application is given below. To close the server, use close/1 on the StreamPair.
create_server(Port) :- tcp_socket(Socket), tcp_bind(Socket, Port), tcp_listen(Socket, 5), tcp_open_socket(Socket, StreamPair), stream_pair(StreamPair, AcceptFd, _), <dispatch>
There are various options for <dispatch>. The most commonly used option is to start a Prolog thread to handle the connection. Alternatively, input from multiple clients can be handled in a single thread by listening to these clients using wait_for_input/3. Finally, on Unix systems, we can use fork/1 to handle the connection in a new process. Note that fork/1 and threads do not cooperate well. Combinations can be realised but require good understanding of POSIX thread and fork-semantics.
Below is the typical example using a thread. Note the use of setup_call_cleanup/3 to guarantee that all resources are reclaimed, also in case of failure or exceptions.
dispatch(AcceptFd) :- tcp_accept(AcceptFd, Socket, Peer), thread_create(process_client(Socket, Peer), _, [ detached(true) ]), dispatch(AcceptFd). process_client(Socket, Peer) :- setup_call_cleanup( tcp_open_socket(Socket, StreamPair), handle_service(StreamPair), close(StreamPair)). handle_service(StreamPair) :- ...
Errors that are trapped by the low-level library are mapped to an
exception of the shape below. In this term, Code is a lower case atom
that corresponds to the C macro name, e.g., epipe
for a broken pipe.
Message is the human readable string for the error code returned by
the OS or the same as Code if the OS does not provide this
functionality. Note that Code is derived from a static set of macros
that may or may not be defines for the target OS. If the macro name is
not known, Code is ERROR_nnn
, where nnn is an integer.
error(socket_error(Code, Message), _)
Note that on Windows Code is a wsa*
code which makes it hard to
write portable code that handles specific socket errors. Even on POSIX
systems the exact set of errors produced by the network stack is not
defined.
The library supports both IP4 and IP6 addresses. On Unix systems it also
supports Unix domain sockets (AF_UNIX
). The address of a Unix
domain sockets is a file name. Unix domain sockets are created using
socket_create/2 or unix_domain_socket/1.
IP4 or IP6 sockets can be created using socket_create/2 or tcp_connect/3
with the inet
(default, IP3) or inet6
domain option. Some of the
predicates produce or consume IP addresses as a Prolog term. The format
of this term is one of:
The predicate ip_name/2 translates between the canonical textual representation and the above defined address terms.
inet
(default), inet6
, unix
or local
(same
as unix
)stream
(default) to create a TCP connection or
dgram
to create a UDP socket.This predicate subsumes tcp_socket/1, udp_socket/1 and unix_domain_socket/1.
socket_create(SocketId, [])
or, explicit,
socket_create(SocketId, [domain(inet), type(stream)])
.socket_create(SocketId, [domain(unix)])
or,
explicit, socket_create(SocketId, [domain(unix), type(stream)])
Unix domain socket affect tcp_connect/2 (for clients) and
tcp_bind/2 and tcp_accept/3 (for servers). The address is an atom
or string that is handled as a file name. On most systems the
length of this file name is limited to 128 bytes (including null
terminator), but according to the Linux documentation (unix(7)
),
portable applications must keep the address below 92 bytes. Note
that these lengths are in bytes. Non-ascii characters may be
represented as multiple bytes. If the length limit is exceeded a
representation_error(af_unix_name)
exception is raised.
The following predicates are exported, but not or incorrectly documented.