View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010, University of Amsterdam,
    7		   VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(rdfql_queries,
   32	  [ query_form//1,		% +Options
   33	    store_recall//2,		% +Type, +ColsStore-CollsRecall
   34	    query_script//0,		%
   35	    store_query/3		% +Type, +Id, +Query
   36	  ]).   37:- use_module(library(http/http_session)).   38:- use_module(library(http/html_write)).   39:- use_module(library(http/html_head)).   40:- use_module(basics).

Forms for entering SPARQL and SeRQL queries.

This module implements the forms for entering SPARQL and SeRQL queries with a simple query-history mechanism for user-submitted SPARQL queries. */

 query_form(+Options)//
HTMP component for an interactive (SPARQL) query-form. This calls to the handler with id evaluate_query. Options is an option list:
query_languages(+List)
Query languages supported. Default is ['SPARQL', 'SeRQL']. Specifying only one removes the query-language menu.
   58query_form(Options) -->
   59	html([ form([ class(query),
   60		      name(query),
   61		      action(location_by_id(evaluate_query)),
   62		      method('GET')
   63		    ],
   64		    [ \hidden(repository, default),
   65		      \hidden(serialization, rdfxml),
   66		      h3([ 'Interactive ',
   67			   \query_language(Options, Hidden),
   68			   ' query'
   69			 ]),
   70		      Hidden,
   71		      table([ class(query)
   72			    ],
   73			    [ \store_recall(_, 3-2),
   74			      tr([ td(colspan(5),
   75				      textarea(name(query), ''))
   76				 ]),
   77			      tr([ td([ span(class(label), 'Result format: '),
   78					\result_format
   79				      ]),
   80				   td([ span(class(label), 'Resource: '),
   81					\resource_menu
   82				      ]),
   83				   td([ span(class(label), 'Entailment: '),
   84					\entailment
   85				      ]),
   86				   td(align(right),
   87				      [ input([ type(reset),
   88						value('Clear')
   89					      ]),
   90					input([ type(submit),
   91						value('Go!')
   92					      ])
   93				      ])
   94				 ])
   95			    ])
   96		    ]),
   97	       \query_script
   98	     ]).
   99
  100
  101result_format -->
  102	html(select(name(resultFormat),
  103		    [ option([], xml),
  104		      option([selected], html),
  105		      option([], json),
  106		      option([], csv)
  107		    ])).
  108
  109query_language(Options, Hidden) -->
  110	{ option(query_languages(LangList), Options, ['SPARQL', 'SeRQL'])
  111	},
  112	(   { LangList = [Lang] }
  113	->  html([Lang]),
  114	    { Hidden = \hidden(queryLanguage, Lang) }
  115	;   { LangList = [DefLang|More] },
  116	    html(select(name(queryLanguage),
  117			[ option([selected], DefLang)
  118			| \options(More)
  119			])),
  120	    { Hidden = '' }
  121	).
  122
  123options([]) --> [].
  124options([Value|T]) -->
  125	html(option([], Value)),
  126	options(T).
  127
  128
  129resource_menu -->
  130	html(select(name(resourceFormat),
  131		    [ option([value(plain)],		plain),
  132		      option([value(ns), selected],	'ns:local'),
  133		      option([value(nslabel)],		'ns:label')
  134		    ])).
  135
  136entailment -->
  137	{ findall(E, cliopatria:entailment(E, _), Es)
  138	},
  139	html(select(name(entailment),
  140		    \entailments(Es))).
  141
  142entailments([]) -->
  143	[].
  144entailments([E|T]) -->
  145	(   { setting(cliopatria:default_entailment, E)
  146	    }
  147	->  html(option([selected], E))
  148	;   html(option([], E))
  149	),
  150	entailments(T).
 store_recall(+Type, +ColsSpec)// is det
Creates a table-row (tr) holding a `store' and `recall' element. ColsSpec is a term SpanLeft-SpanRight, containing the colspan-attribute for both created table-cells. Note that a page including this must also include query_script//0 at a place later in the page where a script is allowed.
  161store_recall(Type, SL-SR) -->
  162	{ next_query_id(Id), !
  163	},
  164	html(tr([ td([ class(qstore),
  165		       colspan(SL)
  166		     ],
  167		     [ b('Remember as: '),
  168		       input([ id(qid),
  169			       name(storeAs),
  170			       size(30),
  171			       value(Id)
  172			     ])
  173		     ]),
  174		  td([ class(qrecall),
  175		       colspan(SR),
  176		       align(right)
  177		     ],
  178		     \recall(Type))
  179		])).
  180store_recall(_, SL-SR) -->
  181	{ Span is SL+SR },
  182	html(tr([ td([ class(qnostore),
  183		       colspan(Span)
  184		     ],
  185		     [ 'Login to enable save/restore of queries'
  186		     ])
  187		])).
  188
  189
  190recall(Type) -->
  191	{ http_in_session(_),
  192	  findall(Name-Query, stored_query(Name, Type, Query), Pairs),
  193	  Pairs \== []
  194	}, !,
  195	html([ b('Recall: '),
  196	       select(name(recall),
  197		      [ option([selected], '')
  198		      | \stored_queries(Pairs)
  199		      ])
  200	     ]).
  201recall(_) -->
  202	[].
  203
  204:- thread_local
  205	script_fragment/1.  206
  207stored_queries([]) --> !.
  208stored_queries(List) -->
  209	stored_queries(List, 1),
  210	{ assert(script_fragment('\nf1();\n')) }.
  211
  212stored_queries([], _) -->
  213	[].
  214stored_queries([Name-Query|T], I) -->
  215	{ I2 is I + 1,
  216	  atom_concat(f, I, FName),
  217	  js_quoted(Query, QuotedQuery),
  218	  format(atom(Script),
  219		 'function ~w()\n\c
  220		 { document.query.query.value=\'~w\';\n  \c
  221		   document.getElementById(\'qid\').value="~w";\n\c
  222		 }\n',
  223		 [ FName, QuotedQuery, Name ]),
  224	  assert(script_fragment(Script)),
  225	  format(atom(Call), '~w()', [FName])
  226	},
  227	html(option([onClick(Call)], Name)),
  228	stored_queries(T, I2).
 query_script//
Inserts the <script> holding JavaScript functions that restore the queries.
To be done
- This must be rewritten to use the post/receive mechanism.
  237query_script -->
  238	{ findall(S, retract(script_fragment(S)), Fragments),
  239	  Fragments \== []
  240	}, !,
  241	[ '\n<script language="JavaScript">\n'
  242	],
  243	Fragments,
  244	[ '\n</script>\n'
  245	].
  246query_script -->
  247	[].
 js_quoted(+Raw, -Quoted)
Quote text for use in JavaScript. Quoted does not include the leading and trailing quotes.
  254js_quoted(Raw, Quoted) :-
  255	atom_codes(Raw, Codes),
  256	phrase(js_quote_codes(Codes), QuotedCodes),
  257	atom_codes(Quoted, QuotedCodes).
  258
  259js_quote_codes([]) -->
  260	[].
  261js_quote_codes([0'\r,0'\n|T]) --> !,
  262	"\\n",
  263	js_quote_codes(T).
  264js_quote_codes([H|T]) -->
  265	js_quote_code(H),
  266	js_quote_codes(T).
  267
  268js_quote_code(0'') --> !,
  269	"\\'".
  270js_quote_code(0'\\) --> !,
  271	"\\\\".
  272js_quote_code(0'\n) --> !,
  273	"\\n".
  274js_quote_code(0'\r) --> !,
  275	"\\r".
  276js_quote_code(0'\t) --> !,
  277	"\\t".
  278js_quote_code(C) -->
  279	[C].
  280
  281
  282		 /*******************************
  283		 *	   SAVED QUERIES	*
  284		 *******************************/
 store_query(+Type, +Name, +Query) is det
Store the SPARQL/SeRQL Query under Name in the current session. Succeeds without doing anything if there is no session.
  291store_query(_, '', _) :- !.
  292store_query(Type, As, Query) :-
  293	http_in_session(_), !,
  294	set_high_id(As),
  295	http_session_retractall(stored_query(As, Type, _)),
  296	http_session_retractall(stored_query(_, Type, Query)),
  297	http_session_asserta(stored_query(As, Type, Query)).
  298store_query(_, _, _).
  299
  300stored_query(As, Type, Query) :-
  301	http_session_data(stored_query(As, Type, Query)).
  302
  303set_high_id(Name) :-
  304	http_in_session(_),
  305	atom_concat('Q-', Id, Name),
  306	catch(atom_number(Id, N), _, fail), !,
  307	(   http_session_data(qid(N0))
  308	->  (   N > N0
  309	    ->	http_session_retract(qid(_)),
  310		http_session_assert(qid(N))
  311	    ;	true
  312	    )
  313	;   http_session_assert(qid(N))
  314	).
  315set_high_id(_).
  316
  317
  318next_query_id(Id) :-
  319	http_in_session(_Session), !,
  320	(   http_session_data(qid(Id0))
  321	->  Next is Id0+1
  322	;   Next is 1
  323	),
  324	atomic_list_concat(['Q-',Next], Id)