View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2000-2020, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(socket,
   38          [ tcp_socket/1,               % -Socket
   39            tcp_close_socket/1,         % +Socket
   40            tcp_open_socket/3,          % +Socket, -Read, -Write
   41            tcp_connect/2,              % +Socket, +Address
   42            tcp_connect/3,              % +Socket, +Address, -StreamPair
   43            tcp_connect/4,              % +Socket, +Address, -Read, -Write)
   44            tcp_bind/2,                 % +Socket, +Address
   45            tcp_accept/3,               % +Master, -Slave, -PeerName
   46            tcp_listen/2,               % +Socket, +BackLog
   47            tcp_fcntl/3,                % +Socket, +Command, ?Arg
   48            tcp_setopt/2,               % +Socket, +Option
   49            tcp_getopt/2,               % +Socket, ?Option
   50            tcp_host_to_address/2,      % ?HostName, ?Ip-nr
   51            tcp_select/3,               % +Inputs, -Ready, +Timeout
   52            gethostname/1,              % -HostName
   53
   54            tcp_open_socket/2,          % +Socket, -StreamPair
   55
   56            udp_socket/1,               % -Socket
   57            udp_receive/4,              % +Socket, -Data, -Sender, +Options
   58            udp_send/4,                 % +Socket, +Data, +Sender, +Options
   59
   60            negotiate_socks_connection/2% +DesiredEndpoint, +StreamPair
   61          ]).   62:- autoload(library(debug),[debug/3]).   63:- autoload(library(lists),[last/2]).   64
   65
   66/** <module> Network socket (TCP and UDP) library
   67
   68The library(socket) provides  TCP  and   UDP  inet-domain  sockets  from
   69SWI-Prolog, both client and server-side  communication. The interface of
   70this library is very close to the  Unix socket interface, also supported
   71by the MS-Windows _winsock_ API. SWI-Prolog   applications  that wish to
   72communicate with multiple sources have three options:
   73
   74  - Use I/O multiplexing based on wait_for_input/3.  On Windows
   75    systems this can only be used for sockets, not for general
   76    (device-) file handles.
   77  - Use multiple threads, handling either a single blocking socket
   78    or a pool using I/O multiplexing as above.
   79  - Using XPCE's class `socket` which synchronises socket
   80    events in the GUI event-loop.
   81
   82## Client applications  {#socket-server}
   83
   84Using this library to establish  a  TCP   connection  to  a server is as
   85simple as opening a file.  See also http_open/3.
   86
   87==
   88dump_swi_homepage :-
   89    setup_call_cleanup(
   90        tcp_connect(www.swi-prolog.org:http, Stream, []),
   91        ( format(Stream,
   92                 'GET / HTTP/1.1~n\c
   93                  Host: www.swi-prolog.org~n\c
   94                  Connection: close~n~n', []),
   95          flush_output(Stream),
   96          copy_stream_data(Stream, current_output)
   97        ),
   98        close(S)).
   99==
  100
  101To   deal   with   timeouts   and     multiple   connections,   threads,
  102wait_for_input/3 and/or non-blocking streams (see   tcp_fcntl/3)  can be
  103used.
  104
  105## Server applications  {#socket-client}
  106
  107The typical sequence for generating a server application is given below.
  108To close the server, use close/1 on `AcceptFd`.
  109
  110  ==
  111  create_server(Port) :-
  112        tcp_socket(Socket),
  113        tcp_bind(Socket, Port),
  114        tcp_listen(Socket, 5),
  115        tcp_open_socket(Socket, AcceptFd, _),
  116        <dispatch>
  117  ==
  118
  119There are various options for <dispatch>.  The most commonly used option
  120is to start a Prolog  thread   to  handle the connection. Alternatively,
  121input from multiple clients  can  be  handled   in  a  single  thread by
  122listening to these clients  using   wait_for_input/3.  Finally,  on Unix
  123systems, we can use fork/1 to handle   the  connection in a new process.
  124Note that fork/1 and threads do not  cooperate well. Combinations can be
  125realised  but  require  good   understanding    of   POSIX   thread  and
  126fork-semantics.
  127
  128Below  is  the  typical  example  using  a   thread.  Note  the  use  of
  129setup_call_cleanup/3 to guarantee that all resources are reclaimed, also
  130in case of failure or exceptions.
  131
  132  ==
  133  dispatch(AcceptFd) :-
  134          tcp_accept(AcceptFd, Socket, Peer),
  135          thread_create(process_client(Socket, Peer), _,
  136                        [ detached(true)
  137                        ]),
  138          dispatch(AcceptFd).
  139
  140  process_client(Socket, Peer) :-
  141          setup_call_cleanup(
  142              tcp_open_socket(Socket, StreamPair),
  143              handle_service(StreamPair),
  144              close(StreamPair)).
  145
  146  handle_service(StreamPair) :-
  147          ...
  148  ==
  149
  150## Socket exceptions			{#socket-exceptions}
  151
  152Errors that are trapped by  the  low-level   library  are  mapped  to an
  153exception of the shape below. In this term,  `Code` is a lower case atom
  154that corresponds to the C macro name,   e.g., `epipe` for a broken pipe.
  155`Message` is the human readable string for   the  error code returned by
  156the OS or  the  same  as  `Code`  if   the  OS  does  not  provide  this
  157functionality. Note that `Code` is derived from   a static set of macros
  158that may or may not be defines for the   target OS. If the macro name is
  159not known, `Code` is =|ERROR_nnn|=, where _nnn_ is an integer.
  160
  161    error(socket_error(Code, Message), _)
  162
  163Note that on Windows `Code` is a ``wsa*``   code  which makes it hard to
  164write portable code that handles specific   socket errors. Even on POSIX
  165systems the exact set of errors  produced   by  the network stack is not
  166defined.
  167
  168## TCP socket predicates                {#socket-predicates}
  169*/
  170
  171:- multifile
  172    tcp_connect_hook/3,             % +Socket, +Addr, -In, -Out
  173    tcp_connect_hook/4,             % +Socket, +Addr, -Stream
  174    proxy_for_url/3,                % +URL, +Host, -ProxyList
  175    try_proxy/4.                    % +Proxy, +Addr, -Socket, -Stream
  176
  177:- predicate_options(tcp_connect/3, 3,
  178                     [ bypass_proxy(boolean),
  179                       nodelay(boolean)
  180                     ]).  181
  182:- use_foreign_library(foreign(socket), install_socket).  183:- public tcp_debug/1.                  % set debugging.
  184
  185:- if(current_predicate(unix_domain_socket/1)).  186:- export(unix_domain_socket/1).  % -Socket
  187:- endif.  188
  189%!  tcp_socket(-SocketId) is det.
  190%
  191%   Creates an INET-domain stream-socket and   unifies an identifier
  192%   to it with SocketId. On MS-Windows, if the socket library is not
  193%   yet initialised, this will also initialise the library.
  194
  195%!  tcp_close_socket(+SocketId) is det.
  196%
  197%   Closes the indicated socket, making  SocketId invalid. Normally,
  198%   sockets are closed by closing both   stream  handles returned by
  199%   open_socket/3. There are two cases   where tcp_close_socket/1 is
  200%   used because there are no stream-handles:
  201%
  202%     - If, after tcp_accept/3, the server uses fork/1 to handle the
  203%       client in a sub-process. In this case the accepted socket is
  204%       not longer needed from the main server and must be discarded
  205%       using tcp_close_socket/1.
  206%     - If, after discovering the connecting client with
  207%       tcp_accept/3, the server does not want to accept the
  208%       connection, it should discard the accepted socket
  209%       immediately using tcp_close_socket/1.
  210
  211%!  tcp_open_socket(+SocketId, -StreamPair) is det.
  212%
  213%   Create streams to communicate to  SocketId.   If  SocketId  is a
  214%   master socket (see tcp_bind/2), StreamPair   should  be used for
  215%   tcp_accept/3. If SocketId is a  connected (see tcp_connect/2) or
  216%   accepted socket (see tcp_accept/3), StreamPair   is unified to a
  217%   stream pair (see stream_pair/3) that can be used for reading and
  218%   writing. The stream or pair must   be closed with close/1, which
  219%   also closes SocketId.
  220
  221tcp_open_socket(Socket, Stream) :-
  222    tcp_open_socket(Socket, In, Out),
  223    (   var(Out)
  224    ->  Stream = In
  225    ;   stream_pair(Stream, In, Out)
  226    ).
  227
  228%!  tcp_open_socket(+SocketId, -InStream, -OutStream) is det.
  229%
  230%   Similar to tcp_open_socket/2, but creates   two separate sockets
  231%   where tcp_open_socket/2 would have created a stream pair.
  232%
  233%   @deprecated New code should use tcp_open_socket/2 because
  234%   closing a stream pair is much easier to perform safely.
  235
  236%!  tcp_bind(SocketId, ?Address) is det.
  237%
  238%   Bind  the  socket  to  Address  on  the  current  machine.  This
  239%   operation, together with tcp_listen/2 and tcp_accept/3 implement
  240%   the _server-side_ of the socket interface.  Address is either an
  241%   plain `Port` or a term HostPort. The first form binds the socket
  242%   to the given port on all interfaces, while the second only binds
  243%   to the matching interface. A typical   example is below, causing
  244%   the socket to listen only on port   8080  on the local machine's
  245%   network.
  246%
  247%     ==
  248%       tcp_bind(Socket, localhost:8080)
  249%     ==
  250%
  251%   If `Port` is unbound, the system   picks  an arbitrary free port
  252%   and unifies `Port` with the  selected   port  number.  `Port` is
  253%   either an integer or the name of  a registered service. See also
  254%   tcp_connect/4.
  255
  256%!  tcp_listen(+SocketId, +BackLog) is det.
  257%
  258%   Tells, after tcp_bind/2,  the  socket   to  listen  for incoming
  259%   requests for connections. Backlog  indicates   how  many pending
  260%   connection requests are allowed. Pending   requests are requests
  261%   that  are  not  yet  acknowledged  using  tcp_accept/3.  If  the
  262%   indicated number is exceeded,  the   requesting  client  will be
  263%   signalled  that  the  service  is  currently  not  available.  A
  264%   commonly used default value for Backlog is 5.
  265
  266%!  tcp_accept(+Socket, -Slave, -Peer) is det.
  267%
  268%   This predicate waits on a server socket  for a connection request by
  269%   a client. On success, it creates  a   new  socket for the client and
  270%   binds the identifier to Slave. Peer is   bound  to the IP-address of
  271%   the client or the atom `af_unix` if Socket is an AF_UNIX socket (see
  272%   unix_domain_socket/1).
  273
  274%!  tcp_connect(+SocketId, +Address) is det.
  275%
  276%   Connect SocketId. After successful completion, tcp_open_socket/3
  277%   can be used to create  I/O-Streams   to  the remote socket. This
  278%   predicate is part of the low level client API. A connection to a
  279%   particular host and port is realised using these steps:
  280%
  281%     ==
  282%         tcp_socket(Socket),
  283%         tcp_connect(Socket, Host:Port),
  284%         tcp_open_socket(Socket, StreamPair)
  285%     ==
  286%
  287%   Typical client applications should use  the high level interface
  288%   provided by tcp_connect/3 which  avoids   resource  leaking if a
  289%   step in the process fails, and can  be hooked to support proxies.
  290%   For example:
  291%
  292%     ==
  293%         setup_call_cleanup(
  294%             tcp_connect(Host:Port, StreamPair, []),
  295%             talk(StreamPair),
  296%             close(StreamPair))
  297%     ==
  298%
  299%   If SocketId is an AF_UNIX socket (see unix_domain_socket/1), Address
  300%   is an atom or string denoting a file name.
  301
  302
  303                 /*******************************
  304                 *      HOOKABLE CONNECT        *
  305                 *******************************/
  306
  307%!  tcp_connect(+Socket, +Address, -Read, -Write) is det.
  308%
  309%   Connect a (client) socket to Address and return a bi-directional
  310%   connection through the  stream-handles  Read   and  Write.  This
  311%   predicate may be hooked   by  defining socket:tcp_connect_hook/4
  312%   with the same signature. Hooking can be  used to deal with proxy
  313%   connections. E.g.,
  314%
  315%       ==
  316%       :- multifile socket:tcp_connect_hook/4.
  317%
  318%       socket:tcp_connect_hook(Socket, Address, Read, Write) :-
  319%           proxy(ProxyAdress),
  320%           tcp_connect(Socket, ProxyAdress),
  321%           tcp_open_socket(Socket, Read, Write),
  322%           proxy_connect(Address, Read, Write).
  323%       ==
  324%
  325%   @deprecated New code should use tcp_connect/3 called as
  326%   tcp_connect(+Address, -StreamPair, +Options).
  327
  328tcp_connect(Socket, Address, Read, Write) :-
  329    tcp_connect_hook(Socket, Address, Read, Write),
  330    !.
  331tcp_connect(Socket, Address, Read, Write) :-
  332    tcp_connect(Socket, Address),
  333    tcp_open_socket(Socket, Read, Write).
  334
  335
  336
  337%!  tcp_connect(+Address, -StreamPair, +Options) is det.
  338%!  tcp_connect(+Socket, +Address, -StreamPair) is det.
  339%
  340%   Establish a TCP communication as a  client.   The  +,-,+ mode is the
  341%   preferred way for a client to establish a connection. This predicate
  342%   can be hooked to support network proxies.   To use a proxy, the hook
  343%   proxy_for_url/3 must be defined. Permitted options are:
  344%
  345%      * bypass_proxy(+Boolean)
  346%        Defaults to =false=. If =true=, do not attempt to use any
  347%        proxies to obtain the connection
  348%
  349%      * nodelay(+Boolean)
  350%        Defaults to =false=. If =true=, set nodelay on the
  351%        resulting socket using tcp_setopt(Socket, nodelay)
  352%
  353%   The +,+,- mode is  deprecated  and   does  not  support  proxies. It
  354%   behaves  like  tcp_connect/4,  but  creates    a  stream  pair  (see
  355%   stream_pair/3).
  356%
  357%   @arg Address is either a Host:Port  term   or  a  file name (atom or
  358%   string). The latter connects  to  an   AF_UNIX  socket  and requires
  359%   unix_domain_socket/1.
  360%
  361%   @error proxy_error(tried(ResultList)) is raised by   mode (+,-,+) if
  362%   proxies are defines by proxy_for_url/3 but no proxy can establsh the
  363%   connection. `ResultList` contains one or  more   terms  of  the form
  364%   false(Proxy)  for  a  hook  that    simply  failed  or  error(Proxy,
  365%   ErrorTerm) for a hook that raised an exception.
  366%
  367%   @see library(http/http_proxy) defines a hook  that allows to connect
  368%   through HTTP proxies that support the =CONNECT= method.
  369
  370% Main mode: +,-,+
  371tcp_connect(Address, StreamPair, Options) :-
  372    var(StreamPair),
  373    !,
  374    (   memberchk(bypass_proxy(true), Options)
  375    ->  tcp_connect_direct(Address, Socket, StreamPair)
  376    ;   findall(Result,
  377                try_a_proxy(Address, Result),
  378                ResultList),
  379        last(ResultList, Status)
  380    ->  (   Status = true(_Proxy, Socket, StreamPair)
  381        ->  true
  382        ;   throw(error(proxy_error(tried(ResultList)), _))
  383        )
  384    ;   tcp_connect_direct(Address, Socket, StreamPair)
  385    ),
  386    (   memberchk(nodelay(true), Options)
  387    ->  tcp_setopt(Socket, nodelay)
  388    ;   true
  389    ).
  390% backward compatibility mode +,+,-
  391tcp_connect(Socket, Address, StreamPair) :-
  392    tcp_connect_hook(Socket, Address, StreamPair0),
  393    !,
  394    StreamPair = StreamPair0.
  395tcp_connect(Socket, Address, StreamPair) :-
  396    tcp_connect(Socket, Address, Read, Write),
  397    stream_pair(StreamPair, Read, Write).
  398
  399
  400tcp_connect_direct(Address, Socket, StreamPair):-
  401    make_socket(Address, Socket),
  402    catch(tcp_connect(Socket, Address, StreamPair),
  403          Error,
  404          ( tcp_close_socket(Socket),
  405            throw(Error)
  406          )).
  407
  408:- if(current_predicate(unix_domain_socket/1)).  409make_socket(Address, Socket) :-
  410    (   atom(Address)
  411    ;   string(Address)
  412    ),
  413    !,
  414    unix_domain_socket(Socket).
  415:- endif.  416make_socket(_Address, Socket) :-
  417    tcp_socket(Socket).
  418
  419
  420%!  tcp_select(+ListOfStreams, -ReadyList, +TimeOut)
  421%
  422%   Same as the built-in wait_for_input/3. Used  to allow for interrupts
  423%   and timeouts on Windows. A redesign  of the Windows socket interface
  424%   makes  it  impossible  to  do  better  than  Windows  select()  call
  425%   underlying wait_for_input/3. As input multiplexing typically happens
  426%   in a background thread anyway we  accept   the  loss of timeouts and
  427%   interrupts.
  428%
  429%   @deprecated Use wait_for_input/3
  430
  431tcp_select(ListOfStreams, ReadyList, TimeOut) :-
  432    wait_for_input(ListOfStreams, ReadyList, TimeOut).
  433
  434
  435                 /*******************************
  436                 *        PROXY SUPPORT         *
  437                 *******************************/
  438
  439try_a_proxy(Address, Result) :-
  440    format(atom(URL), 'socket://~w', [Address]),
  441    (   Address = Host:_
  442    ->  true
  443    ;   Host = Address
  444    ),
  445    proxy_for_url(URL, Host, Proxy),
  446    debug(socket(proxy), 'Socket connecting via ~w~n', [Proxy]),
  447    (   catch(try_proxy(Proxy, Address, Socket, Stream), E, true)
  448    ->  (   var(E)
  449        ->  !, Result = true(Proxy, Socket, Stream)
  450        ;   Result = error(Proxy, E)
  451        )
  452    ;   Result = false(Proxy)
  453    ),
  454    debug(socket(proxy), 'Socket: ~w: ~p', [Proxy, Result]).
  455
  456%!  try_proxy(+Proxy, +TargetAddress, -Socket, -StreamPair) is semidet.
  457%
  458%   Attempt  a  socket-level  connection  via  the  given  proxy  to
  459%   TargetAddress. The Proxy argument must match the output argument
  460%   of proxy_for_url/3. The predicate tcp_connect/3 (and http_open/3
  461%   from the library(http/http_open)) collect the  results of failed
  462%   proxies and raise an exception no  proxy is capable of realizing
  463%   the connection.
  464%
  465%   The default implementation  recognises  the   values  for  Proxy
  466%   described    below.    The      library(http/http_proxy)    adds
  467%   proxy(Host,Port)  which  allows  for  HTTP   proxies  using  the
  468%   =CONNECT= method.
  469%
  470%     - direct
  471%     Do not use any proxy
  472%     - socks(Host, Port)
  473%     Use a SOCKS5 proxy
  474
  475:- multifile
  476    try_proxy/4.  477
  478try_proxy(direct, Address, Socket, StreamPair) :-
  479    !,
  480    tcp_connect_direct(Address, Socket, StreamPair).
  481try_proxy(socks(Host, Port), Address, Socket, StreamPair) :-
  482    !,
  483    tcp_connect_direct(Host:Port, Socket, StreamPair),
  484    catch(negotiate_socks_connection(Address, StreamPair),
  485          Error,
  486          ( close(StreamPair, [force(true)]),
  487            throw(Error)
  488          )).
  489
  490%!  proxy_for_url(+URL, +Hostname, -Proxy) is nondet.
  491%
  492%   This hook can be implemented  to  return   a  proxy  to try when
  493%   connecting to URL. Returned proxies are   tried  in the order in
  494%   which they are  returned  by   the  multifile  hook try_proxy/4.
  495%   Pre-defined proxy methods are:
  496%
  497%      * direct
  498%        connect directly to the resource
  499%      * proxy(Host, Port)
  500%        Connect to the resource using an HTTP proxy. If the
  501%        resource is not an HTTP URL, then try to connect using the
  502%        CONNECT verb, otherwise, use the GET verb.
  503%      * socks(Host, Port)
  504%        Connect to the resource via a SOCKS5 proxy
  505%
  506%   These correspond to the proxy  methods   defined  by  PAC [Proxy
  507%   auto-config](http://en.wikipedia.org/wiki/Proxy_auto-config).
  508%   Additional methods can  be  returned   if  suitable  clauses for
  509%   http:http_connection_over_proxy/6 or try_proxy/4 are defined.
  510
  511:- multifile
  512    proxy_for_url/3.  513
  514
  515                 /*******************************
  516                 *            OPTIONS           *
  517                 *******************************/
  518
  519%!  tcp_setopt(+SocketId, +Option) is det.
  520%
  521%   Set options on the socket.  Defined options are:
  522%
  523%     - reuseaddr
  524%     Allow servers to reuse a port without the system being
  525%     completely sure the port is no longer in use.
  526%
  527%     - bindtodevice(+Device)
  528%     Bind the socket to Device (an atom). For example, the code
  529%     below binds the socket to the _loopback_ device that is
  530%     typically used to realise the _localhost_. See the manual
  531%     pages for setsockopt() and the socket interface (e.g.,
  532%     socket(7) on Linux) for details.
  533%
  534%       ==
  535%       tcp_socket(Socket),
  536%       tcp_setopt(Socket, bindtodevice(lo))
  537%       ==
  538%
  539%     - nodelay
  540%     - nodelay(true)
  541%     If =true=, disable the Nagle optimization on this socket,
  542%     which is enabled by default on almost all modern TCP/IP
  543%     stacks. The Nagle optimization joins small packages, which is
  544%     generally desirable, but sometimes not. Please note that the
  545%     underlying TCP_NODELAY setting to setsockopt() is not
  546%     available on all platforms and systems may require additional
  547%     privileges to change this option. If the option is not
  548%     supported, tcp_setopt/2 raises a domain_error exception. See
  549%     [Wikipedia](http://en.wikipedia.org/wiki/Nagle's_algorithm)
  550%     for details.
  551%
  552%     - broadcast
  553%     UDP sockets only: broadcast the package to all addresses
  554%     matching the address. The address is normally the address of
  555%     the local subnet (i.e. 192.168.1.255).  See udp_send/4.
  556%
  557%     - ip_add_membership(+MultiCastGroup)
  558%     - ip_add_membership(+MultiCastGroup, +LocalInterface)
  559%     - ip_add_membership(+MultiCastGroup, +LocalInterface, +InterfaceIndex)
  560%     - ip_drop_membership(+MultiCastGroup)
  561%     - ip_drop_membership(+MultiCastGroup, +LocalInterface)
  562%     - ip_drop_membership(+MultiCastGroup, +LocalInterface, +InterfaceIndex)
  563%     Join/leave a multicast group.  Calls setsockopt() with the
  564%     corresponding arguments.
  565%
  566%     - dispatch(+Boolean)
  567%     In GUI environments (using XPCE or the Windows =swipl-win.exe=
  568%     executable) this flags defines whether or not any events are
  569%     dispatched on behalf of the user interface. Default is
  570%     =true=. Only very specific situations require setting
  571%     this to =false=.
  572%
  573%     - sndbuf(+Integer)
  574%     Sets the send buffer size to Integer (bytes). On Windows this defaults
  575%     (now) to 64kb. Higher latency links may benefit from increasing this
  576%     further since the maximum theoretical throughput on a link is given by
  577%     buffer-size / latency.
  578%     See https://support.microsoft.com/en-gb/help/823764/slow-performance-occurs-when-you-copy-data-to-a-tcp-server-by-using-a
  579%     for Microsoft's discussion
  580
  581%!  tcp_fcntl(+Stream, +Action, ?Argument) is det.
  582%
  583%   Interface to the fcntl() call. Currently   only suitable to deal
  584%   switch stream to non-blocking mode using:
  585%
  586%     ==
  587%       tcp_fcntl(Stream, setfl, nonblock),
  588%     ==
  589%
  590%   An attempt to read from a non-blocking  stream while there is no
  591%   data available returns -1  (or   =end_of_file=  for read/1), but
  592%   at_end_of_stream/1    fails.    On      actual     end-of-input,
  593%   at_end_of_stream/1 succeeds.
  594
  595tcp_fcntl(Socket, setfl, nonblock) :-
  596    !,
  597    tcp_setopt(Socket, nonblock).
  598
  599%!  tcp_getopt(+Socket, ?Option) is semidet.
  600%
  601%   Get  information  about  Socket.  Defined    properties  are  below.
  602%   Requesting an unknown option results in a `domain_error` exception.
  603%
  604%     - file_no(-File)
  605%     Get the OS file handle as an integer.  This may be used for
  606%     debugging and integration.
  607
  608%!  tcp_host_to_address(?HostName, ?Address) is det.
  609%
  610%   Translate between a machines host-name and it's (IP-)address. If
  611%   HostName is an atom, it is  resolved using getaddrinfo() and the
  612%   IP-number is unified to  Address  using   a  term  of the format
  613%   ip(Byte1,Byte2,Byte3,Byte4). Otherwise, if Address   is bound to
  614%   an  ip(Byte1,Byte2,Byte3,Byte4)  term,   it    is   resolved  by
  615%   gethostbyaddr() and the  canonical  hostname   is  unified  with
  616%   HostName.
  617%
  618%   @tbd This function should support more functionality provided by
  619%   gethostbyaddr, probably by adding an option-list.
  620
  621%!  gethostname(-Hostname) is det.
  622%
  623%   Return the canonical fully qualified name  of this host. This is
  624%   achieved by calling gethostname() and  return the canonical name
  625%   returned by getaddrinfo().
  626
  627
  628                 /*******************************
  629                 *            SOCKS             *
  630                 *******************************/
  631
  632%!  negotiate_socks_connection(+DesiredEndpoint, +StreamPair) is det.
  633%
  634%   Negotiate  a  connection  to  DesiredEndpoint  over  StreamPair.
  635%   DesiredEndpoint should be in the form of either:
  636%
  637%      * hostname : port
  638%      * ip(A,B,C,D) : port
  639%
  640%   @error socks_error(Details) if the SOCKS negotiation failed.
  641
  642negotiate_socks_connection(Host:Port, StreamPair):-
  643    format(StreamPair, '~s', [[0x5,    % Version 5
  644                               0x1,    % 1 auth method supported
  645                               0x0]]), % which is 'no auth'
  646    flush_output(StreamPair),
  647    get_byte(StreamPair, ServerVersion),
  648    get_byte(StreamPair, AuthenticationMethod),
  649    (   ServerVersion =\= 0x05
  650    ->  throw(error(socks_error(invalid_version(5, ServerVersion)), _))
  651    ;   AuthenticationMethod =:= 0xff
  652    ->  throw(error(socks_error(invalid_authentication_method(
  653                                    0xff,
  654                                    AuthenticationMethod)), _))
  655    ;   true
  656    ),
  657    (   Host = ip(A,B,C,D)
  658    ->  AddressType = 0x1,                  % IPv4 Address
  659        format(atom(Address), '~s', [[A, B, C, D]])
  660    ;   AddressType = 0x3,                  % Domain
  661        atom_length(Host, Length),
  662        format(atom(Address), '~s~w', [[Length], Host])
  663    ),
  664    P1 is Port /\ 0xff,
  665    P2 is Port >> 8,
  666    format(StreamPair, '~s~w~s', [[0x5,   % Version 5
  667                                   0x1,   % Please establish a connection
  668                                   0x0,   % reserved
  669                                   AddressType],
  670                                  Address,
  671                                  [P2, P1]]),
  672    flush_output(StreamPair),
  673    get_byte(StreamPair, _EchoedServerVersion),
  674    get_byte(StreamPair, Status),
  675    (   Status =:= 0                        % Established!
  676    ->  get_byte(StreamPair, _Reserved),
  677        get_byte(StreamPair, EchoedAddressType),
  678        (   EchoedAddressType =:= 0x1
  679        ->  get_byte(StreamPair, _),        % read IP4
  680            get_byte(StreamPair, _),
  681            get_byte(StreamPair, _),
  682            get_byte(StreamPair, _)
  683        ;   get_byte(StreamPair, Length),   % read host name
  684            forall(between(1, Length, _),
  685                   get_byte(StreamPair, _))
  686        ),
  687        get_byte(StreamPair, _),            % read port
  688        get_byte(StreamPair, _)
  689    ;   throw(error(socks_error(negotiation_rejected(Status)), _))
  690    ).
  691
  692
  693                 /*******************************
  694                 *             MESSAGES         *
  695                 *******************************/
  696
  697/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  698The C-layer generates exceptions of the  following format, where Message
  699is extracted from the operating system.
  700
  701        error(socket_error(Code, Message), _)
  702- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  703
  704:- multifile
  705    prolog:error_message//1.  706
  707prolog:error_message(socket_error(_Code, Message)) -->
  708    [ 'Socket error: ~w'-[Message] ].
  709prolog:error_message(socks_error(Error)) -->
  710    socks_error(Error).
  711prolog:error_message(proxy_error(tried(Tried))) -->
  712    [ 'Failed to connect using a proxy.  Tried:'-[], nl],
  713    proxy_tried(Tried).
  714
  715socks_error(invalid_version(Supported, Got)) -->
  716    [ 'SOCKS: unsupported version: ~p (supported: ~p)'-
  717      [ Got, Supported ] ].
  718socks_error(invalid_authentication_method(Supported, Got)) -->
  719    [ 'SOCKS: unsupported authentication method: ~p (supported: ~p)'-
  720      [ Got, Supported ] ].
  721socks_error(negotiation_rejected(Status)) -->
  722    [ 'SOCKS: connection failed: ~p'-[Status] ].
  723
  724proxy_tried([]) --> [].
  725proxy_tried([H|T]) -->
  726    proxy_tried(H),
  727    proxy_tried(T).
  728proxy_tried(error(Proxy, Error)) -->
  729    [ '~w: '-[Proxy] ],
  730    '$messages':translate_message(Error).
  731proxy_tried(false(Proxy)) -->
  732    [ '~w: failed with unspecified error'-[Proxy] ]