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@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2018, University of Amsterdam,
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(rdfql_queries,
   37          [ query_form//1,              % +Options
   38            store_recall//2,            % +Type, +ColsStore-CollsRecall
   39            query_script//0,            %
   40            store_query/3               % +Type, +Id, +Query
   41          ]).   42:- use_module(library(http/http_session)).   43:- use_module(library(http/html_write)).   44:- use_module(library(http/html_head)).   45:- 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.
   63query_form(Options) -->
   64    html([ form([ class(query),
   65                  name(query),
   66                  action(location_by_id(evaluate_query)),
   67                  method('GET')
   68                ],
   69                [ \hidden(repository, default),
   70                  \hidden(serialization, rdfxml),
   71                  h3([ 'Interactive ',
   72                       \query_language(Options, Hidden),
   73                       ' query'
   74                     ]),
   75                  Hidden,
   76                  table([ class(query)
   77                        ],
   78                        [ \store_recall(_, 3-2),
   79                          tr([ td(colspan(5),
   80                                  textarea(name(query), ''))
   81                             ]),
   82                          tr([ td([ span(class(label), 'Result format: '),
   83                                    \result_format
   84                                  ]),
   85                               td([ span(class(label), 'Resource: '),
   86                                    \resource_menu
   87                                  ]),
   88                               td([ span(class(label), 'Entailment: '),
   89                                    \entailment
   90                                  ]),
   91                               td(align(right),
   92                                  [ input([ type(reset),
   93                                            value('Clear')
   94                                          ]),
   95                                    input([ type(submit),
   96                                            value('Go!')
   97                                          ])
   98                                  ])
   99                             ])
  100                        ])
  101                ]),
  102           \query_script
  103         ]).
  104
  105
  106result_format -->
  107    html(select(name(resultFormat),
  108                [ option([], xml),
  109                  option([selected], html),
  110                  option([], json),
  111                  option([], csv)
  112                ])).
  113
  114query_language(Options, Hidden) -->
  115    { option(query_languages(LangList), Options, ['SPARQL', 'SeRQL'])
  116    },
  117    (   { LangList = [Lang] }
  118    ->  html([Lang]),
  119        { Hidden = \hidden(queryLanguage, Lang) }
  120    ;   { LangList = [DefLang|More] },
  121        html(select(name(queryLanguage),
  122                    [ option([selected], DefLang)
  123                    | \options(More)
  124                    ])),
  125        { Hidden = '' }
  126    ).
  127
  128options([]) --> [].
  129options([Value|T]) -->
  130    html(option([], Value)),
  131    options(T).
  132
  133
  134resource_menu -->
  135    html(select(name(resourceFormat),
  136                [ option([value(plain)],            plain),
  137                  option([value(ns), selected],     'ns:local'),
  138                  option([value(nslabel)],          'ns:label')
  139                ])).
  140
  141entailment -->
  142    { findall(E, cliopatria:entailment(E, _), Es)
  143    },
  144    html(select(name(entailment),
  145                \entailments(Es))).
  146
  147entailments([]) -->
  148    [].
  149entailments([E|T]) -->
  150    (   { setting(cliopatria:default_entailment, E)
  151        }
  152    ->  html(option([selected], E))
  153    ;   html(option([], E))
  154    ),
  155    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.
  166store_recall(Type, SL-SR) -->
  167    { next_query_id(Id), !
  168    },
  169    html(tr([ td([ class(qstore),
  170                   colspan(SL)
  171                 ],
  172                 [ b('Remember as: '),
  173                   input([ id(qid),
  174                           name(storeAs),
  175                           size(30),
  176                           value(Id)
  177                         ])
  178                 ]),
  179              td([ class(qrecall),
  180                   colspan(SR),
  181                   align(right)
  182                 ],
  183                 \recall(Type))
  184            ])).
  185store_recall(_, SL-SR) -->
  186    { Span is SL+SR },
  187    html(tr([ td([ class(qnostore),
  188                   colspan(Span)
  189                 ],
  190                 [ 'Login to enable save/restore of queries'
  191                 ])
  192            ])).
  193
  194
  195recall(Type) -->
  196    { http_in_session(_),
  197      findall(Name-Query, stored_query(Name, Type, Query), Pairs),
  198      Pairs \== []
  199    },
  200    !,
  201    html([ b('Recall: '),
  202           select(name(recall),
  203                  [ option([selected], '')
  204                  | \stored_queries(Pairs)
  205                  ])
  206         ]).
  207recall(_) -->
  208    [].
  209
  210:- thread_local
  211    script_fragment/1.  212
  213stored_queries([]) --> !.
  214stored_queries(List) -->
  215    stored_queries(List, 1),
  216    { assert(script_fragment('\nf1();\n')) }.
  217
  218stored_queries([], _) -->
  219    [].
  220stored_queries([Name-Query|T], I) -->
  221    { I2 is I + 1,
  222      atom_concat(f, I, FName),
  223      js_quoted(Query, QuotedQuery),
  224      format(atom(Script),
  225             'function ~w()\n\c
  226                 { document.query.query.value=\'~w\';\n  \c
  227                   document.getElementById(\'qid\').value="~w";\n\c
  228                 }\n',
  229             [ FName, QuotedQuery, Name ]),
  230      assert(script_fragment(Script)),
  231      format(atom(Call), '~w()', [FName])
  232    },
  233    html(option([onClick(Call)], Name)),
  234    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.
  243query_script -->
  244    { findall(S, retract(script_fragment(S)), Fragments),
  245      Fragments \== []
  246    },
  247    !,
  248    [ '\n<script language="JavaScript">\n'
  249    ],
  250    Fragments,
  251    [ '\n</script>\n'
  252    ].
  253query_script -->
  254    [].
 js_quoted(+Raw, -Quoted)
Quote text for use in JavaScript. Quoted does not include the leading and trailing quotes.
  261js_quoted(Raw, Quoted) :-
  262    atom_codes(Raw, Codes),
  263    phrase(js_quote_codes(Codes), QuotedCodes),
  264    atom_codes(Quoted, QuotedCodes).
  265
  266js_quote_codes([]) -->
  267    [].
  268js_quote_codes([0'\r,0'\n|T]) -->
  269    !,
  270    "\\n",
  271    js_quote_codes(T).
  272js_quote_codes([H|T]) -->
  273    js_quote_code(H),
  274    js_quote_codes(T).
  275
  276js_quote_code(0'') -->
  277    !,
  278    "\\'".
  279js_quote_code(0'\\) -->
  280    !,
  281    "\\\\".
  282js_quote_code(0'\n) -->
  283    !,
  284    "\\n".
  285js_quote_code(0'\r) -->
  286    !,
  287    "\\r".
  288js_quote_code(0'\t) -->
  289    !,
  290    "\\t".
  291js_quote_code(C) -->
  292    [C].
  293
  294
  295                 /*******************************
  296                 *         SAVED QUERIES        *
  297                 *******************************/
 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.
  304store_query(_, '', _) :- !.
  305store_query(Type, As, Query) :-
  306    http_in_session(_),
  307    !,
  308    set_high_id(As),
  309    http_session_retractall(stored_query(As, Type, _)),
  310    http_session_retractall(stored_query(_, Type, Query)),
  311    http_session_asserta(stored_query(As, Type, Query)).
  312store_query(_, _, _).
  313
  314stored_query(As, Type, Query) :-
  315    http_session_data(stored_query(As, Type, Query)).
  316
  317set_high_id(Name) :-
  318    http_in_session(_),
  319    atom_concat('Q-', Id, Name),
  320    catch(atom_number(Id, N), _, fail),
  321    !,
  322    (   http_session_data(qid(N0))
  323    ->  (   N > N0
  324        ->  http_session_retract(qid(_)),
  325            http_session_assert(qid(N))
  326        ;   true
  327        )
  328    ;   http_session_assert(qid(N))
  329    ).
  330set_high_id(_).
  331
  332
  333next_query_id(Id) :-
  334    http_in_session(_Session),
  335    !,
  336    (   http_session_data(qid(Id0))
  337    ->  Next is Id0+1
  338    ;   Next is 1
  339    ),
  340    atomic_list_concat(['Q-',Next], Id)