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-2018, 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:- use_module(library(shlib)).   63:- use_module(library(debug)).   64:- use_module(library(lists)).   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(In, 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%!  tcp_socket(-SocketId) is det.
  186%
  187%   Creates an INET-domain stream-socket and   unifies an identifier
  188%   to it with SocketId. On MS-Windows, if the socket library is not
  189%   yet initialised, this will also initialise the library.
  190
  191%!  tcp_close_socket(+SocketId) is det.
  192%
  193%   Closes the indicated socket, making  SocketId invalid. Normally,
  194%   sockets are closed by closing both   stream  handles returned by
  195%   open_socket/3. There are two cases   where tcp_close_socket/1 is
  196%   used because there are no stream-handles:
  197%
  198%     - If, after tcp_accept/3, the server uses fork/1 to handle the
  199%       client in a sub-process. In this case the accepted socket is
  200%       not longer needed from the main server and must be discarded
  201%       using tcp_close_socket/1.
  202%     - If, after discovering the connecting client with
  203%       tcp_accept/3, the server does not want to accept the
  204%       connection, it should discard the accepted socket
  205%       immediately using tcp_close_socket/1.
  206
  207%!  tcp_open_socket(+SocketId, -StreamPair) is det.
  208%
  209%   Create streams to communicate to  SocketId.   If  SocketId  is a
  210%   master socket (see tcp_bind/2), StreamPair   should  be used for
  211%   tcp_accept/3. If SocketId is a  connected (see tcp_connect/2) or
  212%   accepted socket (see tcp_accept/3), StreamPair   is unified to a
  213%   stream pair (see stream_pair/3) that can be used for reading and
  214%   writing. The stream or pair must   be closed with close/1, which
  215%   also closes SocketId.
  216
  217tcp_open_socket(Socket, Stream) :-
  218    tcp_open_socket(Socket, In, Out),
  219    (   var(Out)
  220    ->  Stream = In
  221    ;   stream_pair(Stream, In, Out)
  222    ).
  223
  224%!  tcp_open_socket(+SocketId, -InStream, -OutStream) is det.
  225%
  226%   Similar to tcp_open_socket/2, but creates   two separate sockets
  227%   where tcp_open_socket/2 would have created a stream pair.
  228%
  229%   @deprecated New code should use tcp_open_socket/2 because
  230%   closing a stream pair is much easier to perform safely.
  231
  232%!  tcp_bind(SocketId, ?Address) is det.
  233%
  234%   Bind  the  socket  to  Address  on  the  current  machine.  This
  235%   operation, together with tcp_listen/2 and tcp_accept/3 implement
  236%   the _server-side_ of the socket interface.  Address is either an
  237%   plain `Port` or a term HostPort. The first form binds the socket
  238%   to the given port on all interfaces, while the second only binds
  239%   to the matching interface. A typical   example is below, causing
  240%   the socket to listen only on port   8080  on the local machine's
  241%   network.
  242%
  243%     ==
  244%       tcp_bind(Socket, localhost:8080)
  245%     ==
  246%
  247%   If `Port` is unbound, the system   picks  an arbitrary free port
  248%   and unifies `Port` with the  selected   port  number.  `Port` is
  249%   either an integer or the name of  a registered service. See also
  250%   tcp_connect/4.
  251
  252%!  tcp_listen(+SocketId, +BackLog) is det.
  253%
  254%   Tells, after tcp_bind/2,  the  socket   to  listen  for incoming
  255%   requests for connections. Backlog  indicates   how  many pending
  256%   connection requests are allowed. Pending   requests are requests
  257%   that  are  not  yet  acknowledged  using  tcp_accept/3.  If  the
  258%   indicated number is exceeded,  the   requesting  client  will be
  259%   signalled  that  the  service  is  currently  not  available.  A
  260%   commonly used default value for Backlog is 5.
  261
  262%!  tcp_accept(+Socket, -Slave, -Peer) is det.
  263%
  264%   This predicate waits on a server socket for a connection request
  265%   by a client. On success, it creates  a new socket for the client
  266%   and binds the  identifier  to  Slave.   Peer  is  bound  to  the
  267%   IP-address of the client.
  268
  269%!  tcp_connect(+SocketId, +HostAndPort) is det.
  270%
  271%   Connect SocketId. After successful completion, tcp_open_socket/3
  272%   can be used to create  I/O-Streams   to  the remote socket. This
  273%   predicate is part of the low level client API. A connection to a
  274%   particular host and port is realised using these steps:
  275%
  276%     ==
  277%         tcp_socket(Socket),
  278%         tcp_connect(Socket, Host:Port),
  279%         tcp_open_socket(Socket, StreamPair)
  280%     ==
  281%
  282%   Typical client applications should use  the high level interface
  283%   provided by tcp_connect/3 which  avoids   resource  leaking if a
  284%   step in the process fails, and can  be hooked to support proxies.
  285%   For example:
  286%
  287%     ==
  288%         setup_call_cleanup(
  289%             tcp_connect(Host:Port, StreamPair, []),
  290%             talk(StreamPair),
  291%             close(StreamPair))
  292%     ==
  293
  294
  295                 /*******************************
  296                 *      HOOKABLE CONNECT        *
  297                 *******************************/
  298
  299%!  tcp_connect(+Socket, +Address, -Read, -Write) is det.
  300%
  301%   Connect a (client) socket to Address and return a bi-directional
  302%   connection through the  stream-handles  Read   and  Write.  This
  303%   predicate may be hooked   by  defining socket:tcp_connect_hook/4
  304%   with the same signature. Hooking can be  used to deal with proxy
  305%   connections. E.g.,
  306%
  307%       ==
  308%       :- multifile socket:tcp_connect_hook/4.
  309%
  310%       socket:tcp_connect_hook(Socket, Address, Read, Write) :-
  311%           proxy(ProxyAdress),
  312%           tcp_connect(Socket, ProxyAdress),
  313%           tcp_open_socket(Socket, Read, Write),
  314%           proxy_connect(Address, Read, Write).
  315%       ==
  316%
  317%   @deprecated New code should use tcp_connect/3 called as
  318%   tcp_connect(+Address, -StreamPair, +Options).
  319
  320tcp_connect(Socket, Address, Read, Write) :-
  321    tcp_connect_hook(Socket, Address, Read, Write),
  322    !.
  323tcp_connect(Socket, Address, Read, Write) :-
  324    tcp_connect(Socket, Address),
  325    tcp_open_socket(Socket, Read, Write).
  326
  327
  328
  329%!  tcp_connect(+Address, -StreamPair, +Options) is det.
  330%!  tcp_connect(+Socket, +Address, -StreamPair) is det.
  331%
  332%   Establish a TCP communication as a client. The +,-,+ mode is the
  333%   preferred way for a  client  to   establish  a  connection. This
  334%   predicate can be hooked to  support   network  proxies. To use a
  335%   proxy, the hook  proxy_for_url/3  must   be  defined.  Permitted
  336%   options are:
  337%
  338%      * bypass_proxy(+Boolean)
  339%        Defaults to =false=. If =true=, do not attempt to use any
  340%        proxies to obtain the connection
  341%
  342%      * nodelay(+Boolean)
  343%        Defaults to =false=. If =true=, set nodelay on the
  344%        resulting socket using tcp_setopt(Socket, nodelay)
  345%
  346%   The +,+,- mode is deprecated and   does  not support proxies. It
  347%   behaves like tcp_connect/4,  but  creates   a  stream  pair (see
  348%   stream_pair/3).
  349%
  350%   @error proxy_error(tried(ResultList)) is raised  by mode (+,-,+)
  351%   if proxies are defines  by  proxy_for_url/3   but  no  proxy can
  352%   establsh the connection. `ResultList` contains one or more terms
  353%   of the form false(Proxy)  for  a   hook  that  simply  failed or
  354%   error(Proxy, ErrorTerm) for a hook that raised an exception.
  355%
  356%   @see library(http/http_proxy) defines a  hook   that  allows  to
  357%   connect through HTTP proxies that support the =CONNECT= method.
  358
  359% Main mode: +,-,+
  360tcp_connect(Address, StreamPair, Options) :-
  361    var(StreamPair),
  362    !,
  363    (   memberchk(bypass_proxy(true), Options)
  364    ->  tcp_connect_direct(Address, Socket, StreamPair)
  365    ;   findall(Result,
  366                try_a_proxy(Address, Result),
  367                ResultList),
  368        last(ResultList, Status)
  369    ->  (   Status = true(_Proxy, Socket, StreamPair)
  370        ->  true
  371        ;   throw(error(proxy_error(tried(ResultList)), _))
  372        )
  373    ;   tcp_connect_direct(Address, Socket, StreamPair)
  374    ),
  375    (   memberchk(nodelay(true), Options)
  376    ->  tcp_setopt(Socket, nodelay)
  377    ;   true
  378    ).
  379% backward compatibility mode +,+,-
  380tcp_connect(Socket, Address, StreamPair) :-
  381    tcp_connect_hook(Socket, Address, StreamPair0),
  382    !,
  383    StreamPair = StreamPair0.
  384tcp_connect(Socket, Address, StreamPair) :-
  385    tcp_connect(Socket, Address, Read, Write),
  386    stream_pair(StreamPair, Read, Write).
  387
  388
  389tcp_connect_direct(Address, Socket, StreamPair):-
  390    tcp_socket(Socket),
  391    catch(tcp_connect(Socket, Address, StreamPair),
  392          Error,
  393          ( tcp_close_socket(Socket),
  394            throw(Error)
  395          )).
  396
  397%!  tcp_select(+ListOfStreams, -ReadyList, +TimeOut)
  398%
  399%   Same as the built-in wait_for_input/3. Used  to allow for interrupts
  400%   and timeouts on Windows. A redesign  of the Windows socket interface
  401%   makes  it  impossible  to  do  better  than  Windows  select()  call
  402%   underlying wait_for_input/3. As input multiplexing typically happens
  403%   in a background thread anyway we  accept   the  loss of timeouts and
  404%   interrupts.
  405%
  406%   @deprecated Use wait_for_input/3
  407
  408tcp_select(ListOfStreams, ReadyList, TimeOut) :-
  409    wait_for_input(ListOfStreams, ReadyList, TimeOut).
  410
  411
  412                 /*******************************
  413                 *        PROXY SUPPORT         *
  414                 *******************************/
  415
  416try_a_proxy(Address, Result) :-
  417    format(atom(URL), 'socket://~w', [Address]),
  418    (   Address = Host:_
  419    ->  true
  420    ;   Host = Address
  421    ),
  422    proxy_for_url(URL, Host, Proxy),
  423    debug(socket(proxy), 'Socket connecting via ~w~n', [Proxy]),
  424    (   catch(try_proxy(Proxy, Address, Socket, Stream), E, true)
  425    ->  (   var(E)
  426        ->  !, Result = true(Proxy, Socket, Stream)
  427        ;   Result = error(Proxy, E)
  428        )
  429    ;   Result = false(Proxy)
  430    ),
  431    debug(socket(proxy), 'Socket: ~w: ~p', [Proxy, Result]).
  432
  433%!  try_proxy(+Proxy, +TargetAddress, -Socket, -StreamPair) is semidet.
  434%
  435%   Attempt  a  socket-level  connection  via  the  given  proxy  to
  436%   TargetAddress. The Proxy argument must match the output argument
  437%   of proxy_for_url/3. The predicate tcp_connect/3 (and http_open/3
  438%   from the library(http/http_open)) collect the  results of failed
  439%   proxies and raise an exception no  proxy is capable of realizing
  440%   the connection.
  441%
  442%   The default implementation  recognises  the   values  for  Proxy
  443%   described    below.    The      library(http/http_proxy)    adds
  444%   proxy(Host,Port)  which  allows  for  HTTP   proxies  using  the
  445%   =CONNECT= method.
  446%
  447%     - direct
  448%     Do not use any proxy
  449%     - socks(Host, Port)
  450%     Use a SOCKS5 proxy
  451
  452:- multifile
  453    try_proxy/4.  454
  455try_proxy(direct, Address, Socket, StreamPair) :-
  456    !,
  457    tcp_connect_direct(Address, Socket, StreamPair).
  458try_proxy(socks(Host, Port), Address, Socket, StreamPair) :-
  459    !,
  460    tcp_connect_direct(Host:Port, Socket, StreamPair),
  461    catch(negotiate_socks_connection(Address, StreamPair),
  462          Error,
  463          ( close(StreamPair, [force(true)]),
  464            throw(Error)
  465          )).
  466
  467%!  proxy_for_url(+URL, +Hostname, -Proxy) is nondet.
  468%
  469%   This hook can be implemented  to  return   a  proxy  to try when
  470%   connecting to URL. Returned proxies are   tried  in the order in
  471%   which they are  returned  by   the  multifile  hook try_proxy/4.
  472%   Pre-defined proxy methods are:
  473%
  474%      * direct
  475%        connect directly to the resource
  476%      * proxy(Host, Port)
  477%        Connect to the resource using an HTTP proxy. If the
  478%        resource is not an HTTP URL, then try to connect using the
  479%        CONNECT verb, otherwise, use the GET verb.
  480%      * socks(Host, Port)
  481%        Connect to the resource via a SOCKS5 proxy
  482%
  483%   These correspond to the proxy  methods   defined  by  PAC [Proxy
  484%   auto-config](http://en.wikipedia.org/wiki/Proxy_auto-config).
  485%   Additional methods can  be  returned   if  suitable  clauses for
  486%   http:http_connection_over_proxy/6 or try_proxy/4 are defined.
  487
  488:- multifile
  489    proxy_for_url/3.  490
  491
  492                 /*******************************
  493                 *            OPTIONS           *
  494                 *******************************/
  495
  496%!  tcp_setopt(+SocketId, +Option) is det.
  497%
  498%   Set options on the socket.  Defined options are:
  499%
  500%     - reuseaddr
  501%     Allow servers to reuse a port without the system being
  502%     completely sure the port is no longer in use.
  503%
  504%     - bindtodevice(+Device)
  505%     Bind the socket to Device (an atom). For example, the code
  506%     below binds the socket to the _loopback_ device that is
  507%     typically used to realise the _localhost_. See the manual
  508%     pages for setsockopt() and the socket interface (e.g.,
  509%     socket(7) on Linux) for details.
  510%
  511%       ==
  512%       tcp_socket(Socket),
  513%       tcp_setopt(Socket, bindtodevice(lo))
  514%       ==
  515%
  516%     - nodelay
  517%     - nodelay(true)
  518%     If =true=, disable the Nagle optimization on this socket,
  519%     which is enabled by default on almost all modern TCP/IP
  520%     stacks. The Nagle optimization joins small packages, which is
  521%     generally desirable, but sometimes not. Please note that the
  522%     underlying TCP_NODELAY setting to setsockopt() is not
  523%     available on all platforms and systems may require additional
  524%     privileges to change this option. If the option is not
  525%     supported, tcp_setopt/2 raises a domain_error exception. See
  526%     [Wikipedia](http://en.wikipedia.org/wiki/Nagle's_algorithm)
  527%     for details.
  528%
  529%     - broadcast
  530%     UDP sockets only: broadcast the package to all addresses
  531%     matching the address. The address is normally the address of
  532%     the local subnet (i.e. 192.168.1.255).  See udp_send/4.
  533%
  534%     - ip_add_membership(+MultiCastGroup)
  535%     - ip_add_membership(+MultiCastGroup, +LocalInterface)
  536%     - ip_add_membership(+MultiCastGroup, +LocalInterface, +InterfaceIndex)
  537%     - ip_drop_membership(+MultiCastGroup)
  538%     - ip_drop_membership(+MultiCastGroup, +LocalInterface)
  539%     - ip_drop_membership(+MultiCastGroup, +LocalInterface, +InterfaceIndex)
  540%     Join/leave a multicast group.  Calls setsockopt() with the
  541%     corresponding arguments.
  542%
  543%     - dispatch(+Boolean)
  544%     In GUI environments (using XPCE or the Windows =swipl-win.exe=
  545%     executable) this flags defines whether or not any events are
  546%     dispatched on behalf of the user interface. Default is
  547%     =true=. Only very specific situations require setting
  548%     this to =false=.
  549
  550%!  tcp_fcntl(+Stream, +Action, ?Argument) is det.
  551%
  552%   Interface to the fcntl() call. Currently   only suitable to deal
  553%   switch stream to non-blocking mode using:
  554%
  555%     ==
  556%       tcp_fcntl(Stream, setfl, nonblock),
  557%     ==
  558%
  559%   An attempt to read from a non-blocking  stream while there is no
  560%   data available returns -1  (or   =end_of_file=  for read/1), but
  561%   at_end_of_stream/1    fails.    On      actual     end-of-input,
  562%   at_end_of_stream/1 succeeds.
  563
  564tcp_fcntl(Socket, setfl, nonblock) :-
  565    !,
  566    tcp_setopt(Socket, nonblock).
  567
  568%!  tcp_getopt(+Socket, ?Option) is semidet.
  569%
  570%   Get  information  about  Socket.  Defined    properties  are  below.
  571%   Requesting an unknown option results in a `domain_error` exception.
  572%
  573%     - file_no(-File)
  574%     Get the OS file handle as an integer.  This may be used for
  575%     debugging and integration.
  576
  577%!  tcp_host_to_address(?HostName, ?Address) is det.
  578%
  579%   Translate between a machines host-name and it's (IP-)address. If
  580%   HostName is an atom, it is  resolved using getaddrinfo() and the
  581%   IP-number is unified to  Address  using   a  term  of the format
  582%   ip(Byte1,Byte2,Byte3,Byte4). Otherwise, if Address   is bound to
  583%   an  ip(Byte1,Byte2,Byte3,Byte4)  term,   it    is   resolved  by
  584%   gethostbyaddr() and the  canonical  hostname   is  unified  with
  585%   HostName.
  586%
  587%   @tbd This function should support more functionality provided by
  588%   gethostbyaddr, probably by adding an option-list.
  589
  590%!  gethostname(-Hostname) is det.
  591%
  592%   Return the canonical fully qualified name  of this host. This is
  593%   achieved by calling gethostname() and  return the canonical name
  594%   returned by getaddrinfo().
  595
  596
  597                 /*******************************
  598                 *            SOCKS             *
  599                 *******************************/
  600
  601%!  negotiate_socks_connection(+DesiredEndpoint, +StreamPair) is det.
  602%
  603%   Negotiate  a  connection  to  DesiredEndpoint  over  StreamPair.
  604%   DesiredEndpoint should be in the form of either:
  605%
  606%      * hostname : port
  607%      * ip(A,B,C,D) : port
  608%
  609%   @error socks_error(Details) if the SOCKS negotiation failed.
  610
  611negotiate_socks_connection(Host:Port, StreamPair):-
  612    format(StreamPair, '~s', [[0x5,    % Version 5
  613                               0x1,    % 1 auth method supported
  614                               0x0]]), % which is 'no auth'
  615    flush_output(StreamPair),
  616    get_byte(StreamPair, ServerVersion),
  617    get_byte(StreamPair, AuthenticationMethod),
  618    (   ServerVersion =\= 0x05
  619    ->  throw(error(socks_error(invalid_version(5, ServerVersion)), _))
  620    ;   AuthenticationMethod =:= 0xff
  621    ->  throw(error(socks_error(invalid_authentication_method(
  622                                    0xff,
  623                                    AuthenticationMethod)), _))
  624    ;   true
  625    ),
  626    (   Host = ip(A,B,C,D)
  627    ->  AddressType = 0x1,                  % IPv4 Address
  628        format(atom(Address), '~s', [[A, B, C, D]])
  629    ;   AddressType = 0x3,                  % Domain
  630        atom_length(Host, Length),
  631        format(atom(Address), '~s~w', [[Length], Host])
  632    ),
  633    P1 is Port /\ 0xff,
  634    P2 is Port >> 8,
  635    format(StreamPair, '~s~w~s', [[0x5,   % Version 5
  636                                   0x1,   % Please establish a connection
  637                                   0x0,   % reserved
  638                                   AddressType],
  639                                  Address,
  640                                  [P2, P1]]),
  641    flush_output(StreamPair),
  642    get_byte(StreamPair, _EchoedServerVersion),
  643    get_byte(StreamPair, Status),
  644    (   Status =:= 0                        % Established!
  645    ->  get_byte(StreamPair, _Reserved),
  646        get_byte(StreamPair, EchoedAddressType),
  647        (   EchoedAddressType =:= 0x1
  648        ->  get_byte(StreamPair, _),        % read IP4
  649            get_byte(StreamPair, _),
  650            get_byte(StreamPair, _),
  651            get_byte(StreamPair, _)
  652        ;   get_byte(StreamPair, Length),   % read host name
  653            forall(between(1, Length, _),
  654                   get_byte(StreamPair, _))
  655        ),
  656        get_byte(StreamPair, _),            % read port
  657        get_byte(StreamPair, _)
  658    ;   throw(error(socks_error(negotiation_rejected(Status)), _))
  659    ).
  660
  661
  662                 /*******************************
  663                 *             MESSAGES         *
  664                 *******************************/
  665
  666/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  667The C-layer generates exceptions of the  following format, where Message
  668is extracted from the operating system.
  669
  670        error(socket_error(Code, Message), _)
  671- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  672
  673:- multifile
  674    prolog:error_message//1.  675
  676prolog:error_message(socket_error(_Code, Message)) -->
  677    [ 'Socket error: ~w'-[Message] ].
  678prolog:error_message(socks_error(Error)) -->
  679    socks_error(Error).
  680prolog:error_message(proxy_error(tried(Tried))) -->
  681    [ 'Failed to connect using a proxy.  Tried:'-[], nl],
  682    proxy_tried(Tried).
  683
  684socks_error(invalid_version(Supported, Got)) -->
  685    [ 'SOCKS: unsupported version: ~p (supported: ~p)'-
  686      [ Got, Supported ] ].
  687socks_error(invalid_authentication_method(Supported, Got)) -->
  688    [ 'SOCKS: unsupported authentication method: ~p (supported: ~p)'-
  689      [ Got, Supported ] ].
  690socks_error(negotiation_rejected(Status)) -->
  691    [ 'SOCKS: connection failed: ~p'-[Status] ].
  692
  693proxy_tried([]) --> [].
  694proxy_tried([H|T]) -->
  695    proxy_tried(H),
  696    proxy_tried(T).
  697proxy_tried(error(Proxy, Error)) -->
  698    [ '~w: '-[Proxy] ],
  699    '$messages':translate_message(Error).
  700proxy_tried(false(Proxy)) -->
  701    [ '~w: failed with unspecified error'-[Proxy] ]