infinite
, wait_for_input/3
waits indefinitely. (31)
This predicate can be used to implement timeout while reading and to
handle input from multiple sources. The following example will wait for
input from the user and an explicitly opened second terminal. On return,
Inputs may hold user
or P4 or both.
?- open('/dev/ttyp4', read, P4), wait_for_input([user, P4], Inputs, 0). |
This predicate relies on the select() call on most operating systems.
On Unix this call is implemented for any stream referring to a
file-handle, which implies all OS-based streams: sockets, terminals,
pipes, etc. On non-Unix systems select() is generally only implemented
for socket-based streams. See also library(socket)
from the clib
package.
Note that wait_for_input/3
returns streams that have data waiting. This does not mean you can, for
example, call read/2
on the stream without blocking as the stream might hold an incomplete
term. The predicate
set_stream/2
using the option timeout(Seconds)
can be used to make the
stream generate an exception if no new data arrives for within the
timeout. Suppose two processes communicate by exchanging Prolog terms.
The following code makes the server immune for clients that write an
incomplete term:
..., tcp_accept(Server, Socket, _Peer), tcp_open(Socket, In, Out), set_stream(In, timeout(10)), catch(read(In, Term), _, (close(Out), close(In), fail)), ..., |
on
(default) and off
.
First Old is unified with the current value. Then the new
value is set to New. (32)
With the introduction of exception-handling, it is adviced to use
catch/3
to catch possibly file-errors and act accordingly. Note that if fileerrors
is off
, no exception is generated.