1:- module(ciao_sockets,
    2	  [ connect_to_socket/3,	% Host, +Port, -Stream
    3	    socket_recv/2,		% +Stream, ?String
    4	    hostname_address/2,		% +HostName, -Address
    5	    socket_shutdown/2,		% +Stream, +How
    6	    socket_recv_code/3,		% +Stream, ?String, ?Length
    7	    socket_send/2,		% +Stream, +String
    8%	    select_socket/5,
    9	    socket_accept/2,		% +Sock, -Stream
   10	    bind_socket/3		% ?Port, +Length, -Socket
   11%	    connect_to_socket_type/4
   12	  ]).   13:- use_module(library(socket)).

CIAO Compatible socket interface

This library emulates library(sockets) from CIAO Prolog. One of the problems we are faced with here is that CIAO streams appear to be read/write, while SWI-Prolog streams are either input or output. For this reason, SWI-Prolog introduced stream_pair/3. */

Calls connect_to_socket_type/4 with SOCK_STREAM connection type. This is the connection type you want in order to use the write/2 and read/2 predicates (and other stream IO related predicates).
   29connect_to_socket(Host, Port, StreamPair) :-
   30	tcp_socket(Socket),
   31	tcp_connect(Socket, Host:Port),
   32	tcp_open_socket(Socket, Read, Write),
   33	stream_pair(StreamPair, Read, Write).
 hostname_address(+HostName, -Address) is det
Translate between HostName and Address. Address is an atom of the form XX.XX.XX.XX.
   41hostname_address(HostName, Address) :-
   42	tcp_host_to_address(HostName, Addr0),
   43	address_to_atom(Addr0, Address).
   44
   45address_to_atom(ip(A,B,C,D), Address) :-
   46	atomic_list_concat([A,B,C,D], '.', Address).
 socket_shutdown(+Stream, +How)
Shut down a duplex communication socket with which Stream is associated. All or part of the communication can be shutdown, depending on the value of How. The atoms read, write, or read_write should be used to denote the type of closing required.
   56socket_shutdown(StreamPair, How) :-
   57	stream_pair(StreamPair, Read, Write),
   58	must_be(oneof([read,write,read_write]), How),
   59	(   How == read
   60	->  close(Read)
   61	;   How == write
   62	->  close(Write)
   63	;   catch(close(Write), E, true),
   64	    close(Read),
   65	    (	nonvar(E)
   66	    ->	throw(E)
   67	    ;	true
   68	    )
   69	).
 socket_recv_code(+Stream, ?String)
As socket_recv_code/3, but the return code is ignored.
   76socket_recv(Stream, String) :-
   77	socket_recv_code(Stream, String, _).
 socket_recv_code(+Stream, ?String, ?Length)
Receives a String from the socket associated to Stream, and returns its Length. If Length is -1, no more data is available.
   84socket_recv_code(StreamPair, String, Length) :-
   85	(   at_end_of_stream(StreamPair)
   86	->  String = "",
   87	    Length = -1
   88	;   read_pending_codes(StreamPair, String, []),
   89	    length(String, Length)
   90	).
 socket_send(+Stream, +String)
Sends String to the socket associated to Stream. The socket has to be in connected state. String is not supposed to be NULL terminated, since it is a Prolog string. If a NULL terminated string is needed at the other side, it has to be explicitly created in Prolog.
  101socket_send(StreamPair, String) :-
  102	format(StreamPair, '~s', [String]),
  103	flush_output(StreamPair).
 bind_socket(?Port, +Length, -Socket) is det
Returs an AF_INET Socket bound to Port (which may be assigned by the OS or defined by the caller), and listens to it (hence no listen call in this set of primitives). Length specifies the maximum number of pending connections.
  112bind_socket(Port, Length, Socket) :-
  113	tcp_socket(Socket),
  114	tcp_setopt(Socket, reuseaddr),
  115	tcp_bind(Socket, Port),
  116	tcp_listen(Socket, Length).
 socket_accept(+Sock, -Stream) is det
Creates a new Stream connected to Sock.
  122socket_accept(Socket, StreamPair) :-
  123	tcp_accept(Socket, Client, _Peer),
  124	tcp_open_socket(Client, Read, Write),
  125	stream_pair(StreamPair, Read, Write)