1/*  Author:        Jan Wielemaker
    2    E-mail:        J.Wielemaker@cs.vu.nl
    3    WWW:           http://www.swi-prolog.org
    4    Copyright (C): 2012, VU University Amsterdam
    5
    6    This program is free software; you can redistribute it and/or
    7    modify it under the terms of the GNU General Public License
    8    as published by the Free Software Foundation; either version 2
    9    of the License, or (at your option) any later version.
   10
   11    This program is distributed in the hope that it will be useful,
   12    but WITHOUT ANY WARRANTY; without even the implied warranty of
   13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14    GNU General Public License for more details.
   15
   16    You should have received a copy of the GNU General Public
   17    License along with this library; if not, write to the Free Software
   18    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   19
   20    As a special exception, if you link this library with other files,
   21    compiled with a Free Software compiler, to produce an executable, this
   22    library does not by itself cause the resulting executable to be covered
   23    by the GNU General Public License. This exception does not however
   24    invalidate any other reasons why the executable file might be covered by
   25    the GNU General Public License.
   26*/
   27
   28:- module(webconsole,
   29	  [ wc_start/0,
   30	    wc_start/1,			% +Options
   31
   32	    wc_format/2,		% +Format, +Args
   33	    wc_format/3,		% +WCId, +Format, +Args
   34	    wc_format/4,		% +WCId, +Format, +Args, +Options
   35	    wc_html/1,			% :HTML
   36	    wc_html/2,			% +WCId, :HTML
   37	    wc_html/3,			% +WCId, :HTML, +Options
   38	    wc_ask/2,			% -Bindings, +Question
   39	    wc_ask/4,			% +InputId, -Bindings, +Question, +Options
   40
   41	    wc_output_area//1,		% +Options
   42	    wc_form_area//1,		% +Options
   43	    wc_error_area//0
   44	  ]).

Use a browser as HTML console

The library(webconsole) allows for writing classical query/reply programs that use a web-browser for I/O. In the typical user scenarion, the application calls wc_start/0 to open a browser. Next, it calls one of wc_format/2,3,4 or wc_html/1,2 to send output to the browser and or calls wc_ask/2,4 to request data from the user.

The home-page can be customized by defining a handler for wc_home. See wc_home/1 for the default page.

Here is an example run:

?- [library(webconsole)].
?- wc_start.				% opens browser
?- wc_format('Hello ~w', [world]).
?- wc_html(p(['Hello ', b(world)])).
?- wc_ask([age(Age)], [p('How old are you'), input([name(age)])]).
Age = 24.				% type 24 <enter>

*/

   70:- use_module(library(http/thread_httpd)).   71:- use_module(library(http/http_dispatch)).   72:- use_module(library(http/http_path), []).   73:- use_module(library(http/http_server_files), []).   74:- use_module(library(http/http_parameters)).   75:- use_module(library(http/html_head)).   76:- use_module(library(http/html_write)).   77:- use_module(library(option)).   78
   79:- multifile http:location/3.   80:- dynamic   http:location/3.   81
   82http:location(webconsole, root(webconsole), []).
   83
   84:- http_handler(webconsole('wc_home'),    wc_home,    [priority(-10)]).   85:- http_handler(webconsole('wc_message'), wc_message, []).   86:- http_handler(webconsole('wc_reply'),   wc_reply,   []).   87
   88:- html_resource(jquery,
   89		 [ virtual(true),
   90		   requires(js('jquery-1.7.1.js'))
   91		 ]).   92:- html_resource(js('jquery.form.js'),
   93		 [ requires(jquery)
   94		 ]).   95:- html_resource(js('webconsole.js'),
   96		 [ requires(jquery),
   97		   requires(js('jquery.form.js'))
   98		 ]).   99:- html_resource(webconsole,
  100		 [ virtual(true),
  101		   requires(js('webconsole.js'))
  102		 ]).  103
  104:- html_meta
  105	wc_html(html),
  106	wc_html(+, html),
  107	wc_html(+, html, +).
  108
  109
  110		 /*******************************
  111		 *	  SIMPLE SERVER		*
  112		 *******************************/
  113
  114:- dynamic
  115	wc_option/1.  116
  117wc_option(Option, Default) :-
  118	Option =.. [Name,Value],
  119	GenOption =.. [Name,Gen],
  120	(   wc_option(GenOption)
  121	->  Value = Gen
  122	;   Value = Default
  123	).
 wc_start is det
 wc_start(+Options) is det
Start the webconsole. This opens your browser using www_open_url/1. Options processed:
title(+Title)
Title for window and h1 header
allow(+IP)
Only allow connections whose peer unify to IP. IP is a term IP(A,B,C,D), where A,B,C,D are integers in the range 0..255.

The user can customize the output page by defining an HTTP handler with the id wc_home (see http_handler/3). The predicate wc_home/1 provides the simple default page.

  141wc_start :-
  142	wc_start([]).
  143
  144wc_start(Options) :-
  145	retractall(wc_option(_)),
  146	forall(member(Option, Options), assertz(wc_option(Option))),
  147	wc_server(Port),
  148	wc_browser(Port).
  149
  150wc_server(Port) :-
  151	http_server_property(Port, goal(_)), !.
  152wc_server(Port) :-
  153	wc_option(port(Port), _),
  154	http_server(http_dispatch, [port(Port)]).
  155
  156wc_browser(Port) :-
  157	http_link_to_id(wc_home, [], Home),
  158	format(atom(URL), 'http://localhost:~w~w', [Port, Home]),
  159	www_open_url(URL).
 wc_home(+Request) is det
HTTP Handler for the default webconsole console layout
  165wc_home(Request) :-
  166	wc_allowed(Request),
  167	wc_option(title(Title), 'SWI-Prolog webconsole'),
  168	reply_html_page(title(Title),
  169			[ \html_requires(css('webconsole.css')),
  170			  h1(Title),
  171			  \wc_error_area,
  172			  \wc_output_area([]),
  173			  \wc_form_area([])
  174			]).
  175
  176
  177wc_allowed(Request) :-
  178	memberchk(peer(Peer), Request),
  179	debug(wc(authorise), 'Peer = ~q', [Peer]),
  180	wc_option(allow(Allow), ip(127,0,0,_)),
  181	Peer = Allow.
  182
  183
  184		 /*******************************
  185		 *	     LIBRARY		*
  186		 *******************************/
 wc_output_area(+Options)// is det
Creates a webconsole div element. Multiple output areas can be created, each with their own id. The default id is wc_output.
  194wc_output_area(Options) -->
  195	{ option(id(Id), Options, wc_output)
  196	},
  197	html_requires(webconsole),
  198	html([ div(id(Id), [])
  199	     ]).
 wc_message(+Request)
HTTP handler that is queried from webconsole.js, waiting for the next message to execute. Time out after 30 seconds, which is indicated with X-Timeout: true in the header.
  208wc_message(_Request) :-
  209	(   thread_get_message(wc_queue,
  210			       message(QueueId, Message, Options),
  211			       [timeout(30)])
  212	->  reply_message(QueueId, Message, Options)
  213	;   format('X-Timeout: true~n', []),
  214	    format('Content-type: text/plain~n~n'),
  215	    format('timeout~n')
  216	).
  217
  218reply_message(Id, format(Format, Args), Options) :-
  219	format('X-Id: ~w~n', [Id]),
  220	maplist(x_header, Options),
  221	format('Content-type: text/plain\n\n'),
  222	format(Format, Args).
  223reply_message(Id, html(HTML), Options) :-
  224	format('X-Id: ~w~n', [Id]),
  225	maplist(x_header, Options),
  226	format('Content-type: text/html\n\n'),
  227	phrase(html(HTML), Tokens),
  228	print_html(Tokens).
  229
  230x_header(clear(Bool)) :-
  231	format('X-Clear: ~w~n', [Bool]).
 wc_format(+Format, +Args) is det
 wc_format(+WCId, +Format, +Args) is det
 wc_format(+WCId, +Format, +Args, +Options) is det
Formats a string (like format/3) to the web console. For example:
?- wc_format('Hello ~w', [world]).

Options:

clear(Boolean)
If true, clear the output area before adding the new content.
Arguments:
WCId- is the identifier of the output area. Default is wc_output.
Format- and Args are passed to format/3.
  253wc_format(Format, Args) :-
  254	wc_format(wc_output, Format, Args).
  255
  256wc_format(WCId, Format, Args) :-
  257	wc_format(WCId, Format, Args, []).
  258
  259wc_format(WCId, Format, Args, Options) :-
  260	thread_send_message(
  261	    wc_queue,
  262	    message(WCId, format(Format, Args), Options)).
 wc_html(+HTML) is det
 wc_html(+WCId, +HTML) is det
 wc_html(+WCId, +HTML, +Options) is det
Adds an HTML element to the output area. HTML must be valid input for html//1 from library(http/html_write). For example:
?- wc_write([p(['Hello ', b(world)])]).

Options:

clear(Boolean)
If true, clear the output area before adding the new content.
  281wc_html(HTML) :-
  282	wc_html(wc_output, HTML).
  283
  284wc_html(WCId, HTML) :-
  285	wc_html(WCId, HTML, []).
  286
  287wc_html(WCId, HTML, Options) :-
  288	thread_send_message(
  289	    wc_queue,
  290	    message(WCId, html(HTML), Options)).
  291
  292
  293		 /*******************************
  294		 *	       ERRORS		*
  295		 *******************************/
 wc_error_area//
Create an output area for errors and warnings. This is a normal output area, using the identifier ic_error.
  302wc_error_area -->
  303	wc_output_area([id(wc_error)]).
  304
  305
  306		 /*******************************
  307		 *	      INPUT		*
  308		 *******************************/
 wc_form_area(+Options)//
Create a form-area. This is a div holding a form with ID wc_form. A form-area is used with wc_ask/3 and wc_ask/4.
  315wc_form_area(Options) -->
  316	{ option(id(Id), Options, wc_form),
  317	  http_link_to_id(wc_reply, [], HREF)
  318	},
  319	html_requires(webconsole),
  320	form_script(Id),
  321	html([ div(class(form),
  322		   [ form([id(Id), action(HREF)], [])
  323		   ]),
  324	       div(id(preview), [])
  325	     ]).
  326
  327form_script(Id) -->
  328	html(script(type('text/javascript'),
  329		    \[ '$("#~w").ajaxForm({\n\c
  330			   target: "#preview",\n\c
  331			   success: function(respText, statusText, xhr, el) {\n\c
  332			     $("#~w").addClass("inactive");\n\c
  333			     $("#~w input").prop("disabled", true);\n\c
  334			   },\n\c
  335			   error: function(xhr, textStatus, errorThrown) {\n\c
  336                             $("#preview").empty();\n\c
  337			     $("#preview").addClass("error");\n\c
  338			     $("#preview").append(xhr.responseText);\n\c
  339			   }\n\c
  340		        });'-[Id, Id, Id]
  341		     ])).
 wc_ask(-Result, +Specification) is det
 wc_ask(+InputId, -Result, +Specification, +Options) is det
Ask a question. Result is a list Name(Value). Specification is an HTML specification (as wc_html/1, see also html//1) which is used as the content for a form element. Each Name in the Result list must be covered by an equally named input element in the form.
?- wc_ask([ age(Age)
          ],
          [ p('How old are you?'),
            input([name(age)])
          ]).
Age = 24.
Arguments:
Options- is currently ignored
See also
- We need a form that doesn't submit. Generic code I found sofar is http://www.9lessons.info/2011/09/submit-form-without-refreshing-page.html
  365:- dynamic
  366	form_result/2.				% Id, Result
  367
  368wc_ask(Result, Question) :-
  369	wc_ask(wc_form, Result, Question, []).
  370wc_ask(InputId, Result, Question, _Options) :-
  371	Id is random(1<<63),
  372	(   is_list(Question)
  373	->  QuestionList = Question
  374	;   QuestionList = [Question]
  375	),
  376	asserta(form_result(Id, Result)),
  377	wc_html(InputId,
  378		[ input([type(hidden), name(id), value(Id)])
  379		| QuestionList
  380		],
  381		[ clear(true)
  382		]),
  383	thread_get_message(reply_queue, Id-Result).
 wc_reply(+Request)
HTTP handler than processed the answer after the user completes an input form.
  390wc_reply(Request) :-
  391	http_parameters(Request,
  392			[ id(Id, [integer])
  393			],
  394			[ form_data(Form)
  395			]),
  396	form_result(Id, Result),
  397	bind_form(Result, Form),
  398	thread_send_message(reply_queue, Id-Result),
  399	format('Content-type: text/plain\n\n'),
  400	format('Thank you\n').
  401
  402bind_form([], _).
  403bind_form([H|T], Form) :-
  404	(   H =.. [Name,Value|Options]
  405	->  memberchk(Name=Raw, Form),
  406	    http_convert_parameter(Options, Name, Raw, Value)
  407	;   true
  408	),
  409	bind_form(T, Form).
  410
  411
  412		 /*******************************
  413		 *	      RESOURCES		*
  414		 *******************************/
  415
  416:- initialization (
  417       catch(message_queue_create(wc_queue),
  418	     error(permission_error(_,_,_),_),
  419	     true),
  420       catch(message_queue_create(reply_queue),
  421	     error(permission_error(_,_,_),_),
  422	     true)
  423       ).