1/*  Part of SWI-Prolog
2
3    Author:        Jan Wielemaker & Steve Prior
4    E-mail:        J.Wielemaker@vu.nl
5    WWW:           http://www.swi-prolog.org
6    Copyright (c)  2004-2020, 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(prolog_server,
38          [ prolog_server/2             % +Port, +Options
39          ]).
40
41:- autoload(library(lists),[member/2]).
42:- autoload(library(socket),
43	    [ tcp_socket/1,
44	      tcp_setopt/2,
45	      tcp_bind/2,
46	      tcp_listen/2,
47	      tcp_accept/3,
48	      tcp_open_socket/3,
49	      tcp_host_to_address/2
50	    ]).
51
52
53%!  prolog_server(?Port, +Options)
54%
55%   Create a TCP/IP based server  on  the   given  Port,  so you can
56%   telnet into Prolog and run an  interactive session. This library
57%   is intended to provide access for   debugging  and management of
58%   embedded servers.
59%
60%   Currently defined options are:
61%
62%           * allow(IP)
63%           Allow access from IP, a term of the format ip(A,B,C,D).
64%           Multiple of such terms can exist and access is granted
65%           if the peer IP address unifies to one of them.  If no
66%           allow option is provided access is only granted from
67%           ip(127,0,0,1) (localhost).
68%
69%   For example:
70%
71%           ==
72%           ?- prolog_server(4000, []).
73%
74%           % telnet localhost 4000
75%           Welcome to the SWI-Prolog server on thread 3
76%
77%           1 ?-
78%           ==
79%
80%   @bug As the connection does not involve a terminal, command history
81%   and completion are not provided. Neither are interrupts
82%   (Control-C).  To terminate the Prolog shell one must enter the
83%   command "end_of_file."
84
85
86prolog_server(Port, Options) :-
87    tcp_socket(ServerSocket),
88    tcp_setopt(ServerSocket, reuseaddr),
89    tcp_bind(ServerSocket, Port),
90    tcp_listen(ServerSocket, 5),
91    thread_create(server_loop(ServerSocket, Options), _,
92                  [ alias(prolog_server)
93                  ]).
94
95server_loop(ServerSocket, Options) :-
96    tcp_accept(ServerSocket, Slave, Peer),
97    tcp_open_socket(Slave, InStream, OutStream),
98    set_stream(InStream, close_on_abort(false)),
99    set_stream(OutStream, close_on_abort(false)),
100    tcp_host_to_address(Host, Peer),
101    (   Postfix = []
102    ;   between(2, 1000, Num),
103        Postfix = [-, Num]
104    ),
105    atomic_list_concat(['client@', Host | Postfix], Alias),
106    catch(thread_create(
107              service_client(InStream, OutStream, Peer, Options),
108              _,
109              [ alias(Alias)
110              ]),
111          error(permission_error(create, thread, Alias), _),
112          fail),
113    !,
114    server_loop(ServerSocket, Options).
115
116service_client(InStream, OutStream, Peer, Options) :-
117    allow(Peer, Options),
118    !,
119    thread_self(Id),
120    set_prolog_IO(InStream, OutStream, OutStream),
121    set_stream(InStream, tty(true)),
122    set_prolog_flag(tty_control, false),
123    current_prolog_flag(encoding, Enc),
124    set_stream(user_input, encoding(Enc)),
125    set_stream(user_output, encoding(Enc)),
126    set_stream(user_error, encoding(Enc)),
127    set_stream(user_input, newline(detect)),
128    set_stream(user_output, newline(dos)),
129    set_stream(user_error, newline(dos)),
130    format(user_error,
131           'Welcome to the SWI-Prolog server on thread ~w~n~n',
132           [Id]),
133    call_cleanup(prolog,
134                 ( close(InStream),
135                   close(OutStream),
136                   thread_detach(Id))).
137service_client(InStream, OutStream, _, _):-
138    thread_self(Id),
139    format(OutStream, 'Go away!!~n', []),
140    close(InStream),
141    close(OutStream),
142    thread_detach(Id).
143
144
145allow(Peer, Options) :-
146    (   member(allow(Allow), Options)
147    *-> Peer = Allow,
148        !
149    ;   Peer = ip(127,0,0,1)
150    ).
151