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