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)  2010-2012, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(sicstus_sockets,
   37	  [ socket/2,			% +Domain, -Socket
   38	    socket_close/1,		% +Socket
   39	    socket_bind/2,		% +Socket, 'AF_INET'(+Host,+Port)
   40	    socket_connect/3,		% +Socket, 'AF_INET'(+Host,+Port), -Stream
   41	    socket_listen/2,		% +Socket, +Length
   42	    socket_accept/2,		% +Socket, -Stream
   43	    socket_accept/3,		% +Socket, -Client, -Stream
   44	    socket_select/5,		% +TermsSockets, -NewTermsStreams,
   45					% +TimeOut, +Streams, -ReadStreams
   46	    current_host/1,		% ?HostName
   47	    hostname_address/2		% ?HostName, ?HostAddress
   48	  ]).   49:- use_module(library(socket)).   50:- use_module(library(error)).   51:- use_module(library(apply)).   52:- use_module(library(pairs)).   53:- use_module(library(lists)).   54
   55:- multifile sicstus:rename_module/2.   56
   57sicstus:rename_module(sockets, sicstus_sockets).
   58
   59/** <module> SICStus 3-compatible library(sockets).
   60
   61@tbd Our implementation does not support AF_UNIX sockets.
   62@see https://sicstus.sics.se/sicstus/docs/3.12.11/html/sicstus/Sockets.html
   63*/
   64
   65socket(Domain, Socket) :-
   66	must_be(oneof(['AF_INET']), Domain),
   67	tcp_socket(Socket).
   68
   69socket_close(Socket) :-
   70	tcp_close_socket(Socket).
   71
   72socket_bind(Socket, Address) :-
   73	(   Address = 'AF_INET'(Host, Port)
   74	->  true
   75	;   type_error(socket_address, Address)
   76	),
   77	(   var(Host)
   78	->  gethostname(Host)
   79	;   true			% Warning?
   80	),
   81	tcp_bind(Socket, Port).
   82
   83socket_connect(Socket, Address, StreamPair) :-
   84	(   Address = 'AF_INET'(Host, Port)
   85	->  true
   86	;   type_error(socket_address, Address)
   87	),
   88	tcp_connect(Socket, Host:Port),
   89	tcp_open_socket(Socket, Read, Write),
   90	stream_pair(StreamPair, Read, Write).
   91
   92socket_listen(Socket, Length) :-
   93	tcp_listen(Socket, Length).
   94
   95socket_accept(Socket, Client, StreamPair) :-
   96	tcp_accept(Socket, Socket2, Peer),
   97	peer_to_client(Peer, Client),
   98	tcp_open_socket(Socket2, Read, Write),
   99	stream_pair(StreamPair, Read, Write).
  100
  101socket_accept(Socket, Stream) :-
  102	socket_accept(Socket, _Client, Stream).
  103
  104
  105peer_to_client(ip(A,B,C,D), Client) :-
  106	Parts = [A,B,C,D],
  107	ground(Parts), !,
  108	atomic_list_concat(Parts, '.', Client).
  109peer_to_client(ip(A,B,C,D), Client) :-
  110	atomic_list_concat(Parts, '.', Client),
  111	maplist(atom_number, Parts, Numbers),
  112	length(Numbers, 4), !,
  113	Numbers = [A,B,C,D].
  114peer_to_client(_, Client) :-
  115	domain_error(ip_address, Client).
  116
  117
  118%%	socket_select(+TermsSockets, -NewTermsStreams,
  119%%		      +TimeOut, +Streams, -ReadStreams) is det.
  120%
  121%	The  list  of  streams  in  Streams   is  checked  for  readable
  122%	characters. A stream can be any   stream  associated with an I/O
  123%	descriptor.  The  list  ReadStreams  returns  the  streams  with
  124%	readable data. socket_select/5 also waits for connections to the
  125%	sockets specified by TermsSockets.  This   argument  should be a
  126%	list of Term-Socket pairs, where Term, which can be any term, is
  127%	used  as  an  identifier.   NewTermsStreams    is   a   list  of
  128%	Term-connection(Client,Stream) pairs, where  Stream   is  a  new
  129%	stream open for communicating with a   process connecting to the
  130%	socket identified with Term, Client is   the client host address
  131%	(see socket_accept/3). If TimeOut is   instantiated  to off, the
  132%	predicate waits until something is available.  If TimeOut is S:U
  133%	the predicate waits at most S seconds and U microseconds. Both S
  134%	and U must be integers >=0. If   there is a timeout, ReadStreams
  135%	and NewTermsStreams are [].
  136
  137socket_select(TermsSockets, NewTermsStreams, SicsTimeOut, Streams, ReadStreams) :-
  138	pairs_values(TermsSockets, Sockets),
  139	append(Sockets, Streams, AllStream),
  140	map_timeout(SicsTimeOut, TimeOut),
  141	wait_for_input(AllStream, ReadyStream, TimeOut),
  142	process_ready(ReadyStream, TermsSockets, NewTermsStreams, ReadStreams).
  143
  144map_timeout(off, infinite) :- !.
  145map_timeout(S:U, Seconds) :- !,
  146	Seconds is S+U/1000000.
  147map_timeout(SicsTimeOut, _) :-
  148	type_error(sicstus_timeout, SicsTimeOut).
  149
  150process_ready([], _, [], []).
  151process_ready([H|T], TermsSockets, NewTermsStreams, ReadStreams) :-
  152	memberchk(Term-H, TermsSockets), !,
  153	socket_accept(H, Client, Stream),
  154	NewTermsStreams = [Term-connection(Client,Stream)|NewTSTail],
  155	process_ready(T, TermsSockets, NewTSTail, ReadStreams).
  156process_ready([H|T], TermsSockets, NewTermsStreams, [H|ReadStreams]) :-
  157	process_ready(T, TermsSockets, NewTermsStreams, ReadStreams).
  158
  159
  160%%	current_host(-Host) is det.
  161%
  162%	True when Host is an atom that denotes the name of the host.
  163%
  164current_host(Host) :-
  165	gethostname(Host).
  166
  167%%	hostname_address(+Host:atom, -Address:atom) is det.
  168%
  169%	True when Address is the IP address of Host.
  170
  171hostname_address(Host, Address) :-
  172	nonvar(Host), !,
  173	tcp_host_to_address(Host, IP),
  174	peer_to_client(IP, Address)