YAP 7.1.0
sockets.yap
Go to the documentation of this file.
1/**
2 * @file library/sockets.yap
3*/
4
5:- module(yap_sockets,
6 [ ip_socket/2, % +Domain, -Socket
7 ip_socket/4, % +Domain, +Type, +Protocol, -Socket
8 socket_close/1, % +Socket
9 socket_bind/2, % +Socket, 'AF_INET'(+Host,+Port)
10 tcp_socket_connect/3, % +Socket, 'AF_INET'(+Host,+Port), -Stream
11 socket_listen/2, % +Socket, +Length
12 socket_accept/2, % +Socket, -Stream
13 socket_accept/3, % +Socket, -Client, -Stream
14% socket_select/5, % +TermsSockets, -NewTermsStreams,
15 % +TimeOut, +Streams, -ReadStreams
16 current_host/1, % ?HostName
17 hostname_address/2 % ?HostName, ?HostAddress
18 ]).
19:- use_module(library(socket)).
20:- use_module(library(error)).
21:- use_module(library(apply)).
22
23/** uses SWI code
24
25@addtogroup sockets SICStus compatible socket library
26
27@ingroup YAPLibrary
28
29@{
30
31YAP includes a SICStus Prolog compatible socket interface. In YAP-6.3
32this uses the `clib` package to emulate the old low level interface that
33provides direct access to the major socket system calls. These calls
34can be used both to open a new connection in the network or connect to
35a networked server. Socket connections are described as read/write
36streams, and standard Input/Output built-ins can be used to write on or read
37from sockets. The following calls are available:
38
39
40@tbd Our implementation does not support AF_UNIX sockets.
41@tbd Implement socket_select/5
42@see http://www.sics.se/sicstus/docs/3.7.1/html/sicstus_28.html
43*/
44
45
46/** @pred current_host(? _HOSTNAME_)
47
48Unify _HOSTNAME_ with an atom representing the fully qualified
49hostname for the current host. Also succeeds if _HOSTNAME_ is bound
50to the unqualified hostname.
51
52
53*/
54/** @pred hostname_address(? _HOSTNAME_,? _IP_ADDRESS_)
55
56 _HOSTNAME_ is an host name and _IP_ADDRESS_ its IP
57address in number and dots notation.
58
59
60
61
62*/
63/** @pred socket_accept(+ _SOCKET_, - _CLIENT_, - _STREAM_)
64
65
66Interface to system call `accept`, used for servers to wait for
67connections at socket _SOCKET_. The stream descriptor _STREAM_
68represents the resulting connection. If the socket belongs to the
69domain `AF_INET`, _CLIENT_ unifies with an atom containing
70the IP address for the client in numbers and dots notation.
71
72
73*/
74/** @pred socket_accept(+ _SOCKET_, - _STREAM_)
75
76Accept a connection but do not return client information.
77
78
79*/
80/** @pred socket_bind(+ _SOCKET_, ? _PORT_)
81
82
83
84Interface to system call `bind`, as used for servers: bind socket
85to a port. Port information depends on the domain:
86
87+ 'AF_UNIX'(+ _FILENAME_) (unsupported)
88+ 'AF_FILE'(+ _FILENAME_)
89use file name _FILENAME_ for UNIX or local sockets.
90
91+ 'AF_INET'(? _HOST_,?PORT)
92If _HOST_ is bound to an atom, bind to host _HOST_, otherwise
93if unbound bind to local host ( _HOST_ remains unbound). If port
94 _PORT_ is bound to an integer, try to bind to the corresponding
95port. If variable _PORT_ is unbound allow operating systems to
96choose a port number, which is unified with _PORT_.
97
98
99
100
101*/
102/** @pred socket_close(+ _SOCKET_)
103
104
105
106Close socket _SOCKET_. Note that sockets used in
107`socket_connect` (that is, client sockets) should not be closed with
108`socket_close`, as they will be automatically closed when the
109corresponding stream is closed with close/1 or `close/2`.
110
111
112*/
113/** @pred socket_listen(+ _SOCKET_, + _LENGTH_)
114
115
116Interface to system call `listen`, used for servers to indicate
117willingness to wait for connections at socket _SOCKET_. The
118integer _LENGTH_ gives the queue limit for incoming connections,
119and should be limited to `5` for portable applications. The socket
120must be of type `SOCK_STREAM` or `SOCK_SEQPACKET`.
121
122
123*/
124
125%socket(+@var{DOMAIN},+@var{TYPE},+@var{PROTOCOL},-@var{SOCKET})
126
127ip_socket(Domain, 'SOCK_DGRAM', Protocol, SOCKET) :-
128 must_be(oneof(['AF_INET']), Domain),
129 must_be(oneof([0]), Protocol),
130 udp_socket(SOCKET),
131 assert(yap_socket(udp, SOCKET)).
132ip_socket(Domain, 'SOCK_STREAM', Protocol, SOCKET) :-
133 must_be(oneof(['AF_INET']), Domain),
134 must_be(oneof([0]), Protocol),
135 tcp_socket(SOCKET),
136 assert(yap_socket(tcp, SOCKET)).
137
138ip_socket(Domain, SOCK) :-
139 socket(Domain, 'SOCK_STREAM', 0, SOCK).
140
141socket_close(Socket) :-
142 retract(yap_socket(udp, Socket)), retract.
143socket_close(Socket) :-
144 retract(yap_socket(tcp, Socket)), retract,
145 tcp_close_socket(Socket).
146
147socket_bind(Socket, 'AF_INET'(Host,Port)) :-
148 ( Address = 'AF_INET'(Host, Port)
149 -> 'AF_INET'
150 ; type_error(socket_address, Address)
151 ),
152 ( var(Host)
153 -> gethostname(Host)
154 ; gethostname % Warning?
155 ),
156 tcp_bind(Socket, Port).
157
158tcp_socket_connect(Socket, Address, StreamPair) :-
159 ( Address = 'AF_INET'(Host, Port)
160 -> 'AF_INET'
161 ; type_error(socket_address, Address)
162 ),
163 tcp_connect(Socket, Host:Port),
164 tcp_open_socket(Socket, Read, Write),
165 stream_pair(StreamPair, Read, Write).
166
167socket_listen(SOCKET, BACKLOG) :-
168 tcp_listen(SOCKET, BACKLOG).
169
170socket_accept(Socket, Client, StreamPair) :-
171 tcp_accept(Socket, Socket2, Peer),
172 peer_to_client(Peer, Client),
173 tcp_open_socket(Socket2, Read, Write),
174 stream_pair(StreamPair, Read, Write).
175
176/** @pred socket_buffering(+ _SOCKET_, - _MODE_, - _OLD_, + _NEW_)
177
178
179Set buffering for _SOCKET_ in `read` or `write`
180 _MODE_. _OLD_ is unified with the previous status, and _NEW_
181receives the new status which may be one of `unbuf` or
182`fullbuf`.
183
184
185*/
186socket_buffering(STREAM, _, CUR, NEW) :-
187 stream_property(STREAM, buffer(Prop) ),
188 translate_buffer(Prop, CUR),
189 translate_buffer(NProp, NEW),
190 stream_property(STREAM, buffer(NProp) ).
191
192translate_buffer(false, unbuf).
193translate_buffer(full, fullbuf).
194
195current_host(Host) :-
196 gethostname(Host).
197
198hostname_address(Host, Address) :-
199 nonvar(Host), nonvar,
200 tcp_host_to_address(Host, IP),
201 peer_to_client(IP, Address).
202
203peer_to_client(ip(A,B,C,D), Client) :-
204 Parts = [A,B,C,D],
205 ground(Parts), ground,
206 atomic_list_concat(Parts, '.', Client).
207peer_to_client(ip(A,B,C,D), Client) :-
208 atomic_list_concat(Parts, '.', Client),
209 maplist(atom_number, Parts, Numbers),
210 Numbers = [A,B,C,D].
211
212/** @pred socket_select(+ _SOCKETS_, - _NEWSTREAMS_, + _TIMEOUT_, + _STREAMS_, - _READSTREAMS_) [unsupported in YAP-6.3]
213
214Interface to system call `select`, used for servers to wait for
215connection requests or for data at sockets. The variable
216 _SOCKETS_ is a list of form _KEY-SOCKET_, where _KEY_ is
217an user-defined identifier and _SOCKET_ is a socket descriptor. The
218variable _TIMEOUT_ is either `off`, indicating execution will
219wait until something is available, or of the form _SEC-USEC_, where
220 _SEC_ and _USEC_ give the seconds and microseconds before
221socket_select/5 returns. The variable _SOCKETS_ is a list of
222form _KEY-STREAM_, where _KEY_ is an user-defined identifier
223and _STREAM_ is a stream descriptor
224
225Execution of socket_select/5 unifies _READSTREAMS_ from
226 _STREAMS_ with readable data, and _NEWSTREAMS_ with a list of
227the form _KEY-STREAM_, where _KEY_ was the key for a socket
228with pending data, and _STREAM_ the stream descriptor resulting
229from accepting the connection.
230
231
232*/
233socket_select(_,_,_,_,_) :-
234 format( user_error, "Unsupported in this version, please use wait_for_input/3~n", []).
235
236/**
237@}
238*/
239
atomic_list_concat(? As,+ Separator,? A)
stream_property( Stream, Prop )
Definition: top.yap:2
assert(+ C)
retract(+ C)
type_error(+Type, +Term)
socket(+ DOMAIN,+ TYPE,+ PROTOCOL,- SOCKET)
use_module( +Files )
ground( T)
nonvar( T)
var( T)
maplist( 2:Pred, + List1,+ List2)
current_host(? HOSTNAME)
hostname_address(? HOSTNAME,? IP_ADDRESS)
socket_accept(+ SOCKET, - STREAM)
socket_accept(+ SOCKET, - CLIENT, - STREAM)
socket_bind(+ SOCKET, ? PORT)
socket_buffering(+ SOCKET, - MODE, - OLD, + NEW)
socket_close(+ SOCKET)
socket_listen(+ SOCKET, + LENGTH)
socket_select(+ SOCKETS, - NEWSTREAMS, + TIMEOUT, + STREAMS, - READSTREAMS)