View source with formatted comments or as raw
    1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(html_messages,
   31	  [ call_showing_messages/2
   32	  ]).   33:- use_module(library(http/html_write)).   34:- use_module(library(http/html_head)).   35:- use_module(library(option)).   36
   37/** <module> Run goals that produce messages
   38
   39This module allows executing (long  running)   Prolog  goals and see the
   40messages appear in the browser.
   41*/
   42
   43:- meta_predicate
   44	call_showing_messages(0, +).   45
   46%%	call_showing_messages(:Goal, +Options) is det.
   47%
   48%	Execute  Goal,  showing  the  feedback   in  the  browser.  This
   49%	predicate builds a default application   page with a placeholder
   50%	for the messages. It then sends   all  HTML upto the placeholder
   51%	and flushes the output to  the   browser.  During execution, all
   52%	output from Goal emitted through   print_message/2  is caught in
   53%	the message-box. After completion of Goal the page is completed.
   54%
   55%	This predicate is intended for action such as loading RDF files,
   56%	while providing feedback on  files   loaded  and  possible error
   57%	messages. Note that this call creates a complete page.
   58%
   59%	@bug	This call uses =chunked= transfer encoding to send the
   60%		page in parts.  Not all browsers support this and not
   61%		all browsers update the page incrementally.
   62
   63:- create_prolog_flag(html_messages, false, [type(boolean)]).   64
   65assert_message_hook :-
   66	Head = message_hook(_Term, Level, Lines),
   67	Body = send_message(Level, Lines),
   68	(   clause(user:Head, Body)
   69	->  true
   70	;   asserta((user:Head :- Body))
   71	).
   72
   73:- initialization
   74	assert_message_hook.   75
   76call_showing_messages(Goal, Options) :-
   77	option(style(Style), Options, default),
   78	option(head(Head), Options, title('SWI-Prolog -- make')),
   79	option(header(Header), Options,
   80	       div(class(msg_header),
   81		   h4('Messages ...'))),
   82	(   option(footer(Footer), Options)
   83	->  true
   84	;   (   option(return_to(ReturnURI), Options)
   85	    ->  FooterRest = [ p(['Go ', a(href(ReturnURI), 'back'),
   86				  ' to the previous page']) ]
   87	    ;	FooterRest = []
   88	    ),
   89	    Footer = div(class(msg_footer), [ h4('Done') | FooterRest ])
   90	),
   91	format('Content-Type: text/html~n'),
   92	format('Transfer-Encoding: chunked~n~n'),
   93	header(Style, Head, Header, Footer, FooterTokens),
   94	setup_call_cleanup(
   95	    set_prolog_flag(html_messages, true),
   96	    catch(Goal, E, print_message(error, E)),
   97	    set_prolog_flag(html_messages, false)), !,
   98	footer(FooterTokens).
   99
  100send_message(Level, Lines) :-
  101	current_prolog_flag(html_messages, true),
  102	level_css_class(Level, Class),
  103	phrase(html(pre(class(Class), \html_message_lines(Lines))), Tokens),
  104	with_mutex(html_messages, print_html(Tokens)),
  105	flush_output,
  106	fail.
  107
  108level_css_class(informational, msg_informational).
  109level_css_class(warning,       msg_warning).
  110level_css_class(error,	       msg_error).
  111
  112html_message_lines([]) -->
  113	[].
  114html_message_lines([nl|T]) --> !,
  115	html('\n'),			% we are in a <pre> environment
  116	html_message_lines(T).
  117html_message_lines([flush]) -->
  118	[].
  119html_message_lines([H|T]) --> !,
  120	html(H),
  121	html_message_lines(T).
  122
  123
  124%%	header(+Style, +Head, +Header, +Footer, -FooterTokens)
  125%
  126%	Emit all tokens upto the placeholder for the actual messages and
  127%	return the remaining page-tokens in FooterTokens. Style and Head
  128%	are passed
  129
  130header(Style, Head, Header, Footer, FooterTokens) :-
  131	Magic = '$$$MAGIC$$$',
  132	Body = [ Header,
  133		 \(html_messages:html_requires(css('messages.css'))),
  134		 div(class(messages), Magic),
  135		 Footer
  136	       ],
  137	phrase(html_write:page(Style, Head, Body), Tokens),
  138	html_write:mailman(Tokens),
  139	append(HeaderTokens, [Magic|FooterTokens], Tokens), !,
  140	current_output(Out),
  141	html_write:write_html(HeaderTokens, Out),
  142	flush_output(Out).
  143
  144footer(Footer) :-
  145	current_output(Out),
  146	html_write:write_html(Footer, Out)