View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    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(sparql_grammar,
   37          [ sparql_parse/3              % +In, -Query, +Options
   38          ]).   39:- use_module(library(pure_input)).   40:- use_module(library(semweb/rdf_db)).   41:- use_module(library(error), [must_be/2]).   42:- use_module(library(lists)).   43:- use_module(library(assoc)).   44:- use_module(library(uri)).   45:- use_module(library(option)).   46:- use_module(library(record)).   47:- use_module(jena_properties).   48:- use_module(text_properties).   49:- use_module(library(debug)).   50:- use_module(library(apply)).   51:- use_module(library(ordsets)).

SPARQL Parser

See also
- SPARQL 1.1 specification
- SPARQL test cases at http://www.w3.org/2009/sparql/docs/tests/ */
 sparql_parse(+SPARQL, -Query, +Options)
Parse the SPARQL statement Input into a Prolog representation. Based on "SPARQL Query Language for RDF", April 6, 2006. Options supported:
base_uri(+Base)
Base used if there is no BASE clause in the query.
variable_names(+VarDict)
Prolog Name=Var list to use as initial binding list. This option is used to support SPARQL Quasi Quotations.
   72sparql_parse(Codes, Query, Options) :-
   73    is_list(Codes),
   74    !,
   75    (   phrase(sparql_query(Prolog, Query0), Codes)
   76    ->  true
   77    ;   syntax_error(unknown)
   78    ),
   79    resolve_names(Prolog, Query0, Query, Options).
   80sparql_parse(Atomic, Query, Options) :-
   81    atomic(Atomic),
   82    !,
   83    atom_codes(Atomic, Codes),
   84    sparql_parse(Codes, Query, Options).
   85sparql_parse(Input, _, _) :-
   86    throw(error(type_error(text, Input), _)).
   87
   88
   89                 /*******************************
   90                 *             ERRORS           *
   91                 *******************************/
   92
   93syntax_error(What) :-
   94    throw(error(syntax_error(sparql(What)), _)).
   95
   96add_error_location(error(syntax_error(What), Location),
   97                   Input) :-
   98    subsumes_term(end_of_file-CharCount, Location),
   99    end_of_file-CharCount = Location,
  100    length(After, CharCount),
  101    append(Before, After, Input),
  102    length(Before, BL),
  103    CLen = 80,
  104    atom_codes('...', Elipsis),
  105    atom_codes('\n**here**\n', Here),
  106    (   BL =< CLen
  107    ->  BC = Before
  108    ;   length(BC0, CLen),
  109        append(_, BC0, Before),
  110        append(Elipsis, BC0, BC)
  111    ),
  112    length(After, AL),
  113    (   AL =< CLen
  114    ->  AC = After
  115    ;   length(AC0, CLen),
  116        append(AC0, _, After),
  117        append(AC0, Elipsis, AC)
  118    ),
  119    append(Here, AC, HAC),
  120    append([0'\n|BC], HAC, ContextCodes),
  121    atom_codes(Context, ContextCodes),
  122    !,
  123    throw(error(syntax_error(sparql(What)),
  124                context(_, Context))).
  125add_error_location(Error, _Input) :-
  126    throw(Error).
  127
  128:- multifile
  129    prolog:message//1,
  130    http:bad_request_error//2.  131
  132http:bad_request_error(syntax_error(sparql(_)), _).
  133
  134prolog:message(error(syntax_error(sparql(unknown)), _)) -->
  135    [ 'SPARQL: Unclassified syntax error in query'-[] ].
  136prolog:message(error(syntax_error(sparql(What)), context(_, Context))) -->
  137    [ 'SPARQL: syntax error: '-[] ],
  138    error_detail(What),
  139    (   { var(Context) }
  140    ->  []
  141    ;   { atomic_list_concat(Lines, '\n', Context) },
  142        [ ' at', nl ],
  143        lines(Lines)
  144    ).
  145
  146error_detail(expected(What)) -->
  147    [ '"~w" expected'-[What] ].
  148error_detail(What) -->
  149    [ '~p'-[What] ].
  150
  151lines([]) --> [].
  152lines([H|T]) --> ['~w'-[H], nl], lines(T).
  153
  154
  155                 /*******************************
  156                 *            RESOLVE           *
  157                 *******************************/
  158
  159:- record
  160    state(base_uri,
  161          prefix_assoc,
  162          prefixes_used=[],
  163          var_assoc,
  164          var_list=[],
  165          graph=[],
  166          filters=[],
  167          aggregates=[]).
 resolve_names(+Prolog, +Query0, -Query, +Options)
Turn var(Name) into Prolog variables and resolve all IRIs to absolute IRIs.
  174resolve_names(Prolog, Q0, Q, Options) :-
  175    resolve_state(Prolog, State0, Options),
  176    resolve(Q0, Q, State0, _State).
  177
  178resolve(select(Proj0, DataSets0, Q0, Solutions0),
  179        select(Proj,  DataSets,  Q,  Solutions),
  180        State0, State) :-
  181    resolve_datasets(DataSets0, DataSets, State0),
  182    resolve_query(Q0, Q1, State0, State1),
  183    resolve_projection(Proj0, Proj, QExpr, State1, State2),
  184    resolve_solutions(Solutions0, Solutions, Q2, State2, State),
  185    mkconj(Q1, QExpr, Q12),
  186    mkconj(Q12, Q2, Q).
  187resolve(construct(Templ0, DataSets0, Q0, Solutions0),
  188        construct(Templ,  DataSets,  Q,  Solutions),
  189        State0, State) :-
  190    resolve_datasets(DataSets0, DataSets, State0),
  191    resolve_query(Q0, Q1, State0, State1),
  192    resolve_construct_template(Templ0, Templ, Q2, State1, State2),
  193    resolve_solutions(Solutions0, Solutions, Q3, State2, State),
  194    mkconj(Q1, Q2, Q12),
  195    mkconj(Q12, Q3, Q).
  196resolve(ask(DataSets0, Q0, Solutions0), ask(DataSets, Q, Solutions),
  197        State0, State) :-
  198    resolve_datasets(DataSets0, DataSets, State0),
  199    resolve_query(Q0, Q1, State0, State1),
  200    resolve_solutions(Solutions0, Solutions, Q2, State1, State),
  201    mkconj(Q1, Q2, Q).
  202resolve(describe(Proj0, DataSets0, Q0, Solutions0),
  203        describe(Proj,  DataSets,  Q,  Solutions),
  204        State0, State) :-
  205    resolve_datasets(DataSets0, DataSets, State0),
  206    resolve_query(Q0, Q1, State0, State1),
  207    resolve_projection(Proj0, Proj, QE, State1, State2),
  208    resolve_solutions(Solutions0, Solutions, Q2, State2, State),
  209    mkconj(Q1, QE, Q12),
  210    mkconj(Q12, Q2, Q).
  211resolve(update(Updates0), update(Updates), State0, State) :-
  212    resolve_updates(Updates0, Updates, State0, State).
 resolve_datasets(+Raw, -IRIs, +State)
TBD: what is the difference between named and non-named?
  218resolve_datasets([], [], _).
  219resolve_datasets([H0|T0], [H|T], S) :-
  220    resolve_dataset(H0, H, S),
  221    resolve_datasets(T0, T, S).
  222
  223resolve_dataset(T0, IRI, S) :-
  224    resolve_iri(T0, IRI, S).
 resolve_query(+Q0, -Q, +State0, -State)
Create the initial translation from the output of the parser to a Prolog query. Constructs in the output are:

Note that an rdf/3 object can be literal(plain(X), X) to demand an unqualified literal.

  242resolve_query(List, Q, S0, S) :-
  243    is_list(List),
  244    !,
  245    list_to_conj(List, Q, S0, S).
  246resolve_query(group(G), Q, S0, S) :-
  247    !,
  248    state_filters(S0, FSave),
  249    set_filters_of_state([], S0, S1),
  250    resolve_query(G, Q0, S1, S2),
  251    state_filters(S2, Filters),
  252    set_filters_of_state(FSave, S2, S3),
  253    resolve_query(Filters, Q1, S3, S),
  254    mkconj(Q0, Q1, Q2),
  255    steadfast(Q2, Q).
  256resolve_query(service(Silent, VarOrIRI, G, QText),
  257              sparql_service(Silent, Address, Prefixes, Vars, QText),
  258              S0, S) :-
  259    !,
  260    resolve_graph_term(VarOrIRI, Address, true, S0, S0),
  261    assertion(Address \== '$null$'),        % Fresh variable
  262    service_state(S0, ServState0),
  263    resolve_query(G, _, ServState0, ServState),
  264    service_prefixes(ServState, Prefixes),
  265    state_var_list(ServState, Vars),
  266    resolve_service_vars(Vars, S0, S).
  267resolve_query((A0,minus(B0)), sparql_minus(A,B), S0, S) :-
  268    !,
  269    resolve_query(A0, A, S0, S1),
  270    resolve_query(B0, B, S1, S).
  271resolve_query((A0,B0), Q, S0, S) :-
  272    !,
  273    resolve_query(A0, A, S0, S1),
  274    resolve_query(B0, B, S1, S),
  275    mkconj(A, B, Q).
  276resolve_query((A0;B0), (A;B), S0, S) :-
  277    !,
  278    resolve_query(A0, A, S0, S1),
  279    resolve_query(B0, B, S1, S).
  280resolve_query(optional(true), true, S, S) :- !.
  281resolve_query(optional(Q0), (Q *-> true ; true), S0, S) :-
  282    !,
  283    resolve_query(Q0, Q, S0, S).
  284resolve_query(rdf(Subj0,P0,O0), Q, S0, S) :-
  285    resolve_iri(P0, P1, S0),
  286    atom(P1),
  287    sparql:current_functional_property(P1, P, _),
  288    !,
  289    resolve_graph_term(Subj0, Subj, Q1, S0, S1),
  290    (   nonvar(O0),
  291        O0 = collection(ArgList0),
  292        resolve_graph_terms(ArgList0, ArgList, Q2, S1, S)
  293    ->  true
  294    ;   resolve_graph_term(O0, Arg, Q2, S1, S),
  295        ArgList = [Arg]
  296    ),
  297    FP =.. [P|ArgList],
  298    length(ArgList, ArgCount),
  299    (   sparql:current_functional_property(P1, P, ArgCount)
  300    ->  true
  301    ;   throw(error(existence_error(functional_property, FP), _))
  302    ),
  303    mkconj(Q1, Q2, Q12),
  304    FuncProp = sparql:functional_property(Subj, FP),
  305    mkconj(Q12, FuncProp, Q).
  306resolve_query(rdf(Subj,P,O), Q, S0, S) :-
  307    !,
  308    resolve_triple(Subj, P, O, Q, S0, S).
  309resolve_query(graph(G0, Q0), Q, S0, S) :-
  310    !,
  311    resolve_graph_term(G0, G, Q1, S0, S1),
  312    state_graph(S1, GL),
  313    set_graph_of_state([G|GL], S1, S2),
  314    resolve_query(Q0, Q2, S2, S3),
  315    mkconj(Q1, Q2, Q),
  316    set_graph_of_state(GL, S3, S).
  317resolve_query(Function, Q, S0, S) :-
  318    resolve_function(Function, Call, QF, S0, S),
  319    !,
  320    mkconj(QF, Call, Q).
  321resolve_query(ebv(E0), Q, S0, S) :-
  322    !,
  323    resolve_expression(E0, E, QE, S0, S),
  324    mkconj(QE, sparql_true(E), Q).
  325resolve_query(filter(E0), true, S0, S) :-
  326    !,
  327    state_filters(S0, F),
  328    set_filters_of_state([ebv(E0)|F], S0, S).
  329resolve_query(bind(Expr0, var(VarName)), Q, S0, S) :-
  330    !,
  331    resolve_var(VarName, Var, S0, S1),
  332    state_aggregates(S1, A1),
  333    resolve_expression(Expr0, Expr, QE, S1, S2),
  334    state_aggregates(S2, A2),
  335    (   var(Expr)                   % BIND(?var1 as ?var2)
  336    ->  Var = Expr,
  337        Q = rdfql_cond_bind_null([Var]),
  338        S = S2
  339    ;   A1 == A2
  340    ->  mkconj(sparql_eval(Expr, Var), QE, Q),
  341        S = S2
  342    ;   Q = QE,
  343        set_aggregates_of_state([sparql_eval(Expr, Var)|A2], S2, S)
  344    ).
  345resolve_query(sub_select(Proj0, Q0, Sols0),
  346              sparql_subquery(Proj, Q, Sols),
  347              S0, S) :-
  348    !,
  349    subquery_state(S0, S1),
  350    resolve_query(Q0, Q1, S1, S2),
  351    resolve_projection(Proj0, Proj1, QExpr, S2, S3),
  352    resolve_solutions(Sols0, Sols, Q2, S3, _SubState),
  353    mkconj(Q1, QExpr, Q12),
  354    mkconj(Q12, Q2, Q),
  355    join_subquery_projection(Proj1, Proj, S0, S).
  356resolve_query(var_in(var(Name), Values0), member(Var, Values), S0, S) :-
  357    resolve_var(Name, Var, S0, S),
  358    resolve_values(Values0, Values, S).
  359resolve_query(vars_in(Vars0, Values0), member(Vars, Values), S0, S) :-
  360    resolve_vars(Vars0, Vars, S0, S),
  361    resolve_values_full(Values0, Values, S).
  362resolve_query(Q, Q, S, S).              % TBD
  363
  364mkconj(true, Q, Q) :- !.
  365mkconj(Q, true, Q) :- !.
  366mkconj(A, B, (A,B)).
  367
  368list_to_conj([], true, S, S) :- !.
  369list_to_conj([Q0], Q, S0, S) :-
  370    !,
  371    resolve_query(Q0, Q, S0, S).
  372list_to_conj([H|T], (QH,QT), S0, S) :-
  373    resolve_query(H, QH, S0, S1),
  374    list_to_conj(T, QT, S1, S).
  375
  376mkdisj(true, _, true) :- !.
  377mkdisj(_, true, true) :- !.
  378mkdisj(A, B, (A;B)).
 resolve_projection(+Proj0, -VarList, -ExprQuery, +State0, State)
Return actual projection as a list of Name=Var
Arguments:
ExprQuery- is the query to resolve expressions that appear in the projection.
  388resolve_projection(*, Vars, true, State, State) :-
  389    !,
  390    state_var_list(State, Vars0),
  391    reverse(Vars0, Vars).
  392resolve_projection(projection(VarNames, Bind), Vars, Q, State0, State) :-
  393    proj_vars(VarNames, Vars, State0, State1),
  394    resolve_query(Bind, Q, State1, State).
  395
  396proj_vars([], [], State, State).
  397proj_vars([var(Name)|T0], [Name=Var|T], State0, State) :-
  398    !,
  399    resolve_var(Name, Var, State0, State1),
  400    proj_vars(T0, T, State1, State).
  401proj_vars([IRI0|T0], [IRI|T], State0, State) :- % for DESCRIBE queries
  402    resolve_iri(IRI0, IRI, State0),
  403    proj_vars(T0, T, State0, State).
 resolve_construct_template(+Templ0, -Templ, -Q, +State)
Deal with ORDER BY clause.
  409resolve_construct_template([], [], true, S, S).
  410resolve_construct_template([H0|T0], [H|T], Q, S0, S) :-
  411    resolve_construct_triple(H0, H, Q1, S0, S1),
  412    resolve_construct_template(T0, T, Q2, S1, S),
  413    mkconj(Q1, Q2, Q).
  414
  415resolve_construct_triple(rdf(S0,P0,O0), rdf(S,P,O), Q, St0, St) :-
  416    resolve_graph_term(S0, S, Q1, St0, St1),
  417    resolve_graph_term(P0, P, Q2, St1, St2),
  418    resolve_graph_term(O0, O, Q3, St2, St),
  419    mkconj(Q1, Q2, Q12),
  420    mkconj(Q12, Q3, Q).
 resolve_solutions(+Solutions0, -Solutions, -Q, +State0, -State)
  424resolve_solutions(distinct(S0), distinct(S), Q, State0, State) :-
  425    !,
  426    resolve_solutions(S0, S, Q, State0, State).
  427resolve_solutions(reduced(S0), reduced(S), Q, State0, State) :-
  428    !,
  429    resolve_solutions(S0, S, Q, State0, State).
  430resolve_solutions(solutions(Group0, Having0,      Order0, Limit, Offset),
  431                  solutions( Group,  Having,  Agg, Order, Limit, Offset),
  432                  Q, State0, State) :-
  433    resolve_group_by(Group0, Group, Q1, State0, State1),
  434    resolve_having(Having0, Having, Q2, State1, State2),
  435    resolve_order_by(Order0, Order, Q3, State2, State),
  436    state_aggregates(State, Agg),
  437    mkconj(Q1, Q2, Q12),
  438    mkconj(Q12, Q3, Q).
 resolve_order_by(+OrderBy0, -OrderBy, -Q, +State0, -State)
  443resolve_order_by(unsorted, unsorted, true, State, State).
  444resolve_order_by(order_by(Cols0), order_by(Cols), Q, State0, State) :-
  445    resolve_order_by_cols(Cols0, Cols, Q, State0, State).
  446
  447resolve_order_by_cols([], [], true, State, State).
  448resolve_order_by_cols([H0|T0], [H|T], Q, State0, State) :-
  449    resolve_order_by_col(H0, H, Q1, State0, State1),
  450    resolve_order_by_cols(T0, T, Q2, State1, State),
  451    mkconj(Q1, Q2, Q).
  452
  453resolve_order_by_col(ascending(O0), ascending(O), Goal, State0, State) :-
  454    !,
  455    compile_expression(O0, O, Goal, State0, State).
  456resolve_order_by_col(descending(O0), descending(O), Goal, State0, State) :-
  457    !,
  458    compile_expression(O0, O, Goal, State0, State).
 resolve_group_by(+Groups0, -Groups, -Q, +State0, -State)
  462resolve_group_by([], [], true, State, State).
  463resolve_group_by([H0|T0], [H|T], Q, State0, State) :-
  464    compile_expression(H0, H, Q1, State0, State1),
  465    resolve_group_by(T0, T, Q2, State1, State),
  466    mkconj(Q1, Q2, Q).
 resolve_having(+Having0, -Having, -Q, +State0, -State)
  470resolve_having(Having0, Having, true, State0, State) :-
  471    resolve_query(Having0, Having, State0, State).
 resolve_state(+Prolog, -State, +Options)
Create initial state.
  478resolve_state(prologue(PrefixesList), State, Options) :-
  479    option(base_uri(Base), Options, 'http://default.base.org/'),
  480    resolve_state(prologue(Base, PrefixesList), State, Options).
  481resolve_state(prologue(Base, PrefixesList),
  482              State, Options) :-
  483    sort(PrefixesList, OrdPrefixList),
  484    ord_list_to_assoc(OrdPrefixList, Prefixes),
  485    initial_vars(Vars, Options),
  486    make_state([ base_uri(Base),
  487                 prefix_assoc(Prefixes),
  488                 var_assoc(Vars)
  489               ], State).
  490
  491initial_vars(Vars, Options) :-
  492    option(variable_names(Dict), Options),
  493    !,
  494    must_be(list, Dict),
  495    maplist(to_pair, Dict, Pairs),
  496    list_to_assoc(Pairs, Vars).
  497initial_vars(Vars, _) :-
  498    empty_assoc(Vars).
  499
  500to_pair(Name=Var, Name-(_Visible-Var)).
 resolve_graph_term(+T0, -T, -Q, +State0, -State) is det
  505resolve_graph_term(Var, Var, true, S, S) :-
  506    var(Var),
  507    !.
  508resolve_graph_term(var(Name), Var, true, S0, S) :-
  509    !,
  510    resolve_var(Name, Var, S0, S).
  511resolve_graph_term(T, IRI, true, S, S) :-
  512    resolve_iri(T, IRI, S),
  513    !.
  514resolve_graph_term(literal(type(IRI0, Value)),
  515                   literal(type(IRI, Value)), true, S, S) :-
  516    !,
  517    resolve_iri(IRI0, IRI, S).
  518resolve_graph_term(boolean(Val),
  519                   literal(type(Type, Val)), true, S, S) :-
  520    !,
  521    rdf_equal(Type, xsd:boolean).
  522resolve_graph_term(collection(Members), CollSubj, Q, S0, S) :-
  523    !,
  524    mkcollection(Members, CollSubj, Triples, []),
  525    resolve_query(Triples, Q, S0, S).
  526resolve_graph_term(T, T, true, S, S).
 resolve_graph_terms(+TList0, -TList, -Q, +State0, -State) is det
  530resolve_graph_terms([], [], true, S, S).
  531resolve_graph_terms([H0|T0], [H|T], Q, S0, S) :-
  532    resolve_graph_term(H0, H, Q1, S0, S1),
  533    resolve_graph_terms(T0, T, Q2, S1, S),
  534    mkconj(Q1, Q2, Q).
 resolve_triple(+Subj, +P, +O, -Q, +S0, -S)
  538resolve_triple(Subj0, P, O0, Q, S0, S) :-
  539    resolve_graph_term(Subj0, Subj, Q1, S0, S1),
  540    resolve_graph_term(O0, O, Q2, S1, S2),
  541    mkconj(Q1, Q2, Q12),
  542    resolve_path(P, Subj, O, Q3, S2, S),
  543    mkconj(Q12, Q3, Q).
 resolve_path(+P, +Subj, +Obj, -Q, +S0, -S) is det
Translate a property path expression into a goal.
  551resolve_path(P0, Subj, Obj, Q, S0, S) :-
  552    resolve_predicate(P0, P, S0, S),
  553    !,
  554    rdf_goal(Subj, P, Obj, Q, S).
  555resolve_path(P01/P02, Subj, Obj, Q, S0, S) :-
  556    !,
  557    resolve_path(P01, Subj, Tmp, Q1, S0, S1),
  558    resolve_path(P02, Tmp, Obj, Q2, S1, S),
  559    mkconj(Q1, Q2, Q).
  560resolve_path(^(P), Subj, Obj, Q, S0, S) :-
  561    !,
  562    resolve_path(P, Obj, Subj, Q, S0, S).
  563resolve_path(;(P01,P02), Subj, Obj, (Q1;Q2), S0, S) :-
  564    !,
  565    resolve_path(P01, Subj, Obj, Q1, S0, S),
  566    resolve_path(P02, Subj, Obj, Q2, S0, S).
  567resolve_path(!(NegSet0), Subj, Obj, Q, S, S) :-
  568    !,
  569    resolve_negated_property_set(NegSet0, NegSet, RevSet, S),
  570    rdf_goal(Subj, P, Obj, Q1, S),
  571    not_in_goal(P, NegSet, NotIn),
  572    (   RevSet == []
  573    ->  Q = ( Q1, NotIn )
  574    ;   rdf_goal(Obj, P2, Subj, Q2, S),
  575        (   RevSet = [P2]
  576        ->  RevNegate = Q2
  577        ;   RevNegate = \+((Q2, memberchk(P2, RevSet)))
  578        ),
  579        (   NegSet == []
  580        ->  Q = (Q1, RevNegate)
  581        ;   Q = (Q1, NotIn, RevNegate)
  582        )
  583    ).
  584resolve_path(?(P), Subj, Obj, Q, S0, S) :-
  585    !,
  586    resolve_path(P, Subj, Obj, Q1, S0, S),
  587    Q = (Subj=Obj ; Q1).
  588resolve_path(*(P), Subj, Obj, Q, S0, S) :-
  589    !,
  590    resolve_path(P, From, To, Q1, S0, S),
  591    Q = sparql_find(Subj, Obj, From, To, Q1).
  592resolve_path(+(P), Subj, Obj, Q, S0, S) :-
  593    !,
  594    resolve_path(P, Subj, Tmp, Q1, S0, S),
  595    resolve_path(P, From, To, Q2, S0, S),
  596    Q = (Q1, sparql_find(Tmp, Obj, From, To, Q2)).
  597
  598
  599resolve_path(P, _, _, _, _, _) :-
  600    type_error(predicate_path, P).
 resolve_predicate(+P0, -P, +S0, -S) is det
  604resolve_predicate(P, P, S, S) :-
  605    var(P),
  606    !.
  607resolve_predicate(var(Name), Var, S0, S) :-
  608    !,
  609    resolve_var(Name, Var, S0, S).
  610resolve_predicate(T, IRI, S, S) :-
  611    resolve_iri(T, IRI, S),
  612    !.
 resolve_negated_property_set(+PSet, -NegSet, -RevSet, +S) is det
True when NegSet is the set of forward negated properties in PSet and RevSet is the set of backward negated properties.
  619resolve_negated_property_set(PSet, NegSet, RevSet, S) :-
  620    resolve_netaged_property_set(PSet, NegSet, [], RevSet, [], S).
  621
  622resolve_netaged_property_set((A0;B0), P0, P, N0, N, S) :-
  623    !,
  624    resolve_netaged_property_set(A0, P0, P1, N0, N1, S),
  625    resolve_netaged_property_set(B0, P1, P,  N1, N, S).
  626resolve_netaged_property_set(^(IRI0), P, P, [IRI|N], N, S) :-
  627    resolve_iri(IRI0, IRI, S).
  628resolve_netaged_property_set(IRI0, [IRI|P], P, N, N, S) :-
  629    resolve_iri(IRI0, IRI, S).
  630
  631not_in_goal(P, [One], P \== One) :- !.
  632not_in_goal(P, List, \+ memberchk(P, List)).
 rdf_goal(+S, +P, +O, -RDF, +State)
Optionally add graph to the rdf/3 statement.
  638rdf_goal(S, P, O0, RDF, State) :-
  639    rdf_goal_object(O0, O),
  640    (   state_graph(State, [Graph|_])
  641    ->  RDF = rdf(S, P, O, Graph:_)
  642    ;   RDF = rdf(S, P, O)
  643    ).
 rdf_goal_object(+ObjIn, -ObjGoal) is det
Note that in SPARQL plain literals (e.g., "hello") only match literals that have neither a language nor a type-qualifier. The SemWeb library introduced rdf(S,P,literal(plain(X), X)) for this purpose.
  652rdf_goal_object(O, O) :-
  653    var(O),
  654    !.
  655rdf_goal_object(literal(X), O) :-
  656    atom(X),
  657    !,
  658    O = literal(plain(X), X).
  659rdf_goal_object(O, O).
 mkcollection(+Members, -CollectionSubject, -Triples)
  664mkcollection([Last], S, [ rdf(S, rdf:first, Last),
  665                          rdf(S, rdf:rest, rdf:nil)
  666                        | Tail
  667                        ], Tail) :- !.
  668mkcollection([H|T], S, [ rdf(S, rdf:first, H),
  669                         rdf(S, rdf:rest, R)
  670                       | RDF
  671                       ], Tail) :-
  672    mkcollection(T, R, RDF, Tail).
 resolve_expression(+E0, -E, -Q, +State0, -State)
  677resolve_expression(Var, Var, true, S, S) :-
  678    var(Var),
  679    !.
  680resolve_expression(or(A0,B0), or(A,B), Q, S0, S) :-
  681    !,
  682    resolve_expression(A0, A, Q1, S0, S1),
  683    resolve_expression(B0, B, Q2, S1, S),
  684    mkdisj(Q1, Q2, Q).
  685resolve_expression(and(A0,B0), and(A,B), Q, S0, S) :-
  686    !,
  687    resolve_expression(A0, A, Q1, S0, S1),
  688    resolve_expression(B0, B, Q2, S1, S),
  689    mkconj(Q1, Q2, Q).
  690resolve_expression(E0, E, Q, S0, S) :-
  691    expression_op(E0),
  692    !,
  693    E0 =.. [Op|Args0],
  694    resolve_expressions(Args0, Args, Q, S0, S),
  695    E =.. [Op|Args].
  696resolve_expression(E0, As, Q, S0, S) :-
  697    aggregate_op(E0),
  698    !,
  699    E0 =.. [Op|Args0],
  700    resolve_expressions(Args0, Args, Q, S0, S1),
  701    E =.. [Op|Args],
  702    state_aggregates(S0, A0),
  703    set_aggregates_of_state([aggregate(E,As)|A0], S1, S).
  704resolve_expression(E0, E, Q, S0, S) :-
  705    resolve_function(E0, E, Q, S0, S),
  706    !.
  707resolve_expression(exists(Pattern), boolean(True), Q, S0, S) :-
  708    !,
  709    resolve_query(Pattern, QE, S0, S),
  710    Q = (QE -> True=true ; True=false).
  711resolve_expression(in(E0, List0), in(E, List), Q, S0, S) :-
  712    !,
  713    resolve_expression(E0, E, Q1, S0, S1),
  714    resolve_expressions(List0, List, Q2, S1, S),
  715    mkconj(Q1, Q2, Q).
  716resolve_expression(not_in(E0, List0), not_in(E, List), Q, S0, S) :-
  717    !,
  718    resolve_expression(E0, E, Q1, S0, S1),
  719    resolve_expressions(List0, List, Q2, S1, S),
  720    mkconj(Q1, Q2, Q).
  721resolve_expression(not_exists(Pattern), boolean(True), Q, S0, S) :-
  722    !,
  723    resolve_query(Pattern, QE, S0, S),
  724    Q = (QE -> True=false ; True=true).
  725resolve_expression(distinct(E0), distinct(E), Q, S0, S) :-
  726    !,
  727    resolve_expression(E0, E, Q, S0, S).
  728resolve_expression(var(Name), Var, true, S0, S) :-
  729    !,
  730    resolve_var_invisible(Name, Var, S0, S).
  731resolve_expression(T0, T, Q, S0, S) :-
  732    resolve_graph_term(T0, T, Q, S0, S).    % OK?
  733
  734expression_op(_ = _).
  735expression_op(_ \= _).                  % SPARQL !=
  736expression_op(_ =< _).                  % SPARQL <=
  737expression_op(_ >= _).
  738expression_op(_ < _).
  739expression_op(_ > _).
  740expression_op(_ + _).
  741expression_op(_ - _).
  742expression_op(_ * _).
  743expression_op(_ / _).
  744expression_op(not(_)).                  % SPARQL !(_)
  745expression_op(+ _).
  746expression_op(- _).
  747
  748
  749resolve_expressions([], [], true, S, S).
  750resolve_expressions([H0|T0], [H|T], Q, S0, S) :-
  751    resolve_expression(H0, H, Q1, S0, S1),
  752    resolve_expressions(T0, T, Q2, S1, S),
  753    mkconj(Q1, Q2, Q).
  754
  755resolve_function(function(F0, Args0), function(Term), Q, S0, S) :-
  756    !,
  757    resolve_iri(F0, F, S0),
  758    resolve_expressions(Args0, Args, Q, S0, S),
  759    Term =.. [F|Args].
  760resolve_function(concat(List0), concat(List), Q, S0, S) :-
  761    !,
  762    resolve_expressions(List0, List, Q, S0, S).
  763resolve_function(coalesce(List0), coalesce(List), Q, S0, S) :-
  764    !,
  765    resolve_expressions(List0, List, Q, S0, S).
  766resolve_function(uri(Expr0), iri(Expr, Base), Q, S0, S) :-   % URI() == IRI()
  767    !,
  768    resolve_expression(Expr0, Expr, Q, S0, S),
  769    state_base_uri(S, Base).
  770resolve_function(iri(Expr0), iri(Expr, Base), Q, S0, S) :-
  771    !,
  772    resolve_expression(Expr0, Expr, Q, S0, S),
  773    state_base_uri(S, Base).
  774resolve_function(built_in(Builtin), built_in(Term), Q, S0, S) :-
  775    !,
  776    built_in_function(Builtin),
  777    !,
  778    Builtin =.. [F|Args0],
  779    resolve_expressions(Args0, Args, Q, S0, S),
  780    Term =.. [F|Args].
  781resolve_function(Builtin, Term, Q, S0, S) :-
  782    !,
  783    built_in_function(Builtin),
  784    !,
  785    Builtin =.. [F|Args0],
  786    resolve_expressions(Args0, Args, Q, S0, S),
  787    Term =.. [F|Args].
 resolve_var(+Name, -Var, +State0, ?State)
Resolve a variable. If State0 == State and it concerns a new variable the variable is bound to '$null$'.
  794resolve_var(Name, Var, State0, State) :-
  795    assertion(atom(Name)),
  796    state_var_assoc(State0, Vars),
  797    get_assoc(Name, Vars, Visible-Var),
  798    !,
  799    (   Visible == true
  800    ->  State = State0
  801    ;   Visible = true,
  802        state_var_list(State0, VL),
  803        set_var_list_of_state([Name=Var|VL], State0, State)
  804    ).
  805resolve_var(Name, Var, State0, State) :-
  806    State0 \== State,
  807    !,
  808    state_var_assoc(State0, Vars0),
  809    state_var_list(State0, VL),
  810    put_assoc(Name, Vars0, true-Var, Vars),
  811    set_var_assoc_of_state(Vars, State0, State1),
  812    set_var_list_of_state([Name=Var|VL], State1, State).
  813resolve_var(_, '$null$', State, State).
 resolve_var_invisible(Name, -Var, +State0, ?State)
Similar to resolve_var/4, but does not add the variable to the set of variables visible in the projection if this is *.
  820resolve_var_invisible(Name, Var, State, State) :-
  821    assertion(atom(Name)),
  822    state_var_assoc(State, Vars),
  823    get_assoc(Name, Vars, _-Var),
  824    !.
  825resolve_var_invisible(Name, Var, State0, State) :-
  826    !,
  827    state_var_assoc(State0, Vars0),
  828    put_assoc(Name, Vars0, _-Var, Vars),
  829    set_var_assoc_of_state(Vars, State0, State).
  830resolve_var_invisible(_, '$null$', State, State).
 resolve_iri(+Spec, -IRI:atom, +State) is det
Translate Spec into a fully expanded IRI as used in RDF-DB. Note that we must expand %xx sequences here.
  838resolve_iri(P:N, IRI, State) :-
  839    !,
  840    resolve_prefix(P, Prefix, State),
  841    used_prefix(P, State),
  842    url_iri(N, LocalIRI),
  843    atom_concat(Prefix, LocalIRI, IRI).
  844resolve_iri(URL0, IRI, State) :-
  845    atom(URL0),
  846    state_base_uri(State, Base),    % TBD: What if there is no base?
  847    uri_normalized(URL0, Base, URL1),
  848    url_iri(URL1, IRI).
  849
  850resolve_prefix(P, IRI, State) :-
  851    state_prefix_assoc(State, Prefixes),
  852    (   get_assoc(P, Prefixes, IRI)
  853    ->  true
  854    ;   rdf_db:ns(P, IRI)           % Extension: database known
  855    ->  true
  856    ;   throw(error(existence_error(prefix, P), _))
  857    ).
 used_prefix(+P, !State) is det
Keep track of the prefixes that are actually used to support service statements.
  864used_prefix(P, State) :-
  865    state_prefixes_used(State, Used0),
  866    (   memberchk(P, Used0)
  867    ->  true
  868    ;   set_prefixes_used_of_state([P|Used0], State)
  869    ).
 resolve_values(+Values0, -Values, +State) is det
Resolve a list of values for the VALUES clause.
  875resolve_values([], [], _).
  876resolve_values([H0|T0], [H|T], S) :-
  877    resolve_value(H0, H, S),
  878    resolve_values(T0, T, S).
  879
  880resolve_value(V0, V, S) :-
  881    resolve_graph_term(V0, V, Q, S, S2),
  882    assertion(Q == true),
  883    assertion(S2 == S).
  884
  885resolve_values_full([], [], _).
  886resolve_values_full([H0|T0], [H|T], S) :-
  887    resolve_values(H0, H, S),
  888    resolve_values_full(T0, T, S).
  889
  890resolve_vars([], [], S, S).
  891resolve_vars([var(Name)|T0], [V|T], S0, S) :-
  892    resolve_var(Name, V, S0, S1),
  893    resolve_vars(T0, T, S1, S).
 resolve_bnodes(+Pattern0, -Pattern)
Blank nodes are scoped into a basic graph pattern (i.e. within {...}). The code below does a substitution of bnode(X) to variables in an arbitrary term.
  902resolve_bnodes(P0, P) :-
  903    empty_assoc(BN0),
  904    resolve_bnodes(P0, P, BN0, _).
  905
  906resolve_bnodes(Var, Var, BN, BN) :-
  907    var(Var),
  908    !.
  909resolve_bnodes(bnode(Name), Var, BN0, BN) :-
  910    !,
  911    (   get_assoc(Name, BN0, Var)
  912    ->  BN = BN0
  913    ;   put_assoc(Name, BN0, Var, BN)
  914    ).
  915resolve_bnodes(Term0, Term, BN0, BN) :-
  916    compound(Term0),
  917    !,
  918    functor(Term0, F, A),
  919    functor(Term, F, A),
  920    resolve_bnodes_args(0, A, Term0, Term, BN0, BN).
  921resolve_bnodes(Term, Term, BN, BN).
  922
  923resolve_bnodes_args(A, A, _, _, BN, BN) :- !.
  924resolve_bnodes_args(I0, A, T0, T, BN0, BN) :-
  925    I is I0 + 1,
  926    arg(I, T0, A0),
  927    resolve_bnodes(A0, A1, BN0, BN1),
  928    arg(I, T, A1),
  929    resolve_bnodes_args(I, A, T0, T, BN1, BN).
 subquery_state(OuterState, SubState) is det
Create an initial state for a subquery
  936subquery_state(S0, S) :-
  937    state_base_uri(S0, Base),
  938    state_prefix_assoc(S0, Prefixes),
  939    state_graph(S0, Graph),                 % is this right?
  940    empty_assoc(Vars),
  941    make_state([ base_uri(Base),
  942                 prefix_assoc(Prefixes),
  943                 var_assoc(Vars),
  944                 graph(Graph)
  945               ], S).
 join_subquery_projection(+Proj0, -Proj, +S0, -S) is det
Link the projection variables of the inner query to the outer query.
Arguments:
Proj- is a list OuterVar=InnerVar
  954join_subquery_projection([], [], S, S).
  955join_subquery_projection([Name=InnerVar|T0], [OuterVar=InnerVar|T], S0, S) :-
  956    resolve_var(Name, OuterVar, S0, S1),
  957    join_subquery_projection(T0, T, S1, S).
 resolve_updates(+UpdatesIn, -UpdatesOut, +StateIn, -StateOut)
Resolve update requests. Each update is expressed by one of the following terms:
insert_data(+Quads)
Insert Quads. Quads is a list of rdf/3 or rdf/4 terms.
delete_data(+Quads)
Delete Quads. Quads is a list of rdf/3 or rdf/4 terms.
delete_where(+Quads)
Delete Quads. Quads is a list of rdf/3 or rdf/4 terms.
add(+Silent, +FromGraph, +ToGraph)
Copy all triples from FromGraph to ToGraph
create(+Silent, +Graph)
Create an empty graph
modify(WithIRI, +InsDel, +Using, -Query)
load(+Silent, +IRI, +Graph)
  978resolve_updates([], [], State, State).
  979resolve_updates([H0|T0], [H|T], State0, State) :-
  980    resolve_update(H0, H, State0, State1),
  981    resolve_updates(T0, T, State1, State).
  982
  983
  984resolve_update(insert_data(Quads0), insert_data(Quads), State0, State) :-
  985    resolve_quads(Quads0, Quads, State0, State).
  986resolve_update(delete_data(Quads0), delete_data(Quads), State0, State) :-
  987    resolve_quads(Quads0, Quads, State0, State).
  988resolve_update(delete_where(Quads0), delete_where(Quads), State0, State) :-
  989    resolve_quads(Quads0, Quads, State0, State).
  990resolve_update(add(Silent, From0, To0), add(Silent, From, To),
  991               State, State) :-
  992    resolve_graph_or_special(From0, From, State),
  993    resolve_graph_or_special(To0, To, State).
  994resolve_update(copy(Silent, From0, To0), copy(Silent, From, To),
  995               State, State) :-
  996    resolve_graph_or_special(From0, From, State),
  997    resolve_graph_or_special(To0, To, State).
  998resolve_update(move(Silent, From0, To0), move(Silent, From, To),
  999               State, State) :-
 1000    resolve_graph_or_special(From0, From, State),
 1001    resolve_graph_or_special(To0, To, State).
 1002resolve_update(create(Silent, Graph0), create(Silent, Graph), State, State) :-
 1003    resolve_iri(Graph0, Graph, State).
 1004resolve_update(modify(WithIRI0, InsDel0, Using0, Pattern),
 1005               modify(WithIRI,  InsDel,  Using,  Query),
 1006               State0, State) :-
 1007    resolve_with(WithIRI0, WithIRI, State0),
 1008    (   InsDel0 =.. [Action,Quads0]
 1009    ->  InsDel  =.. [Action,Quads],
 1010        resolve_quads(Quads0, Quads, State0, State2)
 1011    ;   InsDel0 = replace(DelQuads0, InsQuads0),
 1012        InsDel  = replace(DelQuads,  InsQuads),
 1013        resolve_quads(DelQuads0, DelQuads, State0, State1),
 1014        resolve_quads(InsQuads0, InsQuads, State1, State2)
 1015    ),
 1016    Using0 = Using,
 1017    resolve_query(Pattern, Query, State2, State).
 1018resolve_update(drop(Silent, GraphAll0),
 1019               drop(Silent, GraphAll),
 1020               State, State) :-
 1021    resolve_graph_or_special(GraphAll0, GraphAll, State).
 1022resolve_update(clear(Silent, GraphAll0),
 1023               clear(Silent, GraphAll),
 1024               State, State) :-
 1025    resolve_graph_or_special(GraphAll0, GraphAll, State).
 1026resolve_update(load(Silent, IRI0, Graph0),
 1027               load(Silent, IRI,  Graph),
 1028               State, State) :-
 1029    resolve_iri(IRI0, IRI, State),
 1030    resolve_graph_or_special(Graph0, Graph, State).
 resolve_quads(+Quads, -Query, +State0, -State) is det
This seems to be the same as resolve_query/4. It does a bit more, but that should not harm us. The output is a conjunction, which we do not want, so we convert it back into a list.
 1039resolve_quads(Quads0, Quads, State0, State) :-
 1040    resolve_query(Quads0, Query, State0, State),
 1041    phrase(query_quads(Query), Quads).
 1042
 1043query_quads((A,B)) -->
 1044    !,
 1045    query_quads(A),
 1046    query_quads(B).
 1047query_quads(true) -->                  % results from empty triple pattern
 1048    !,
 1049    [].
 1050query_quads(A) -->
 1051    { quad(A) },
 1052    [A].
 1053
 1054quad(rdf(_,_,_)).
 1055quad(rdf(_,_,_,_)).
 1056
 1057resolve_graph_or_special(graph(Graph0), graph(Graph), State) :-
 1058    !,
 1059    resolve_iri(Graph0, Graph, State).
 1060resolve_graph_or_special(Special, Special, _).
 1061
 1062resolve_with(without, default, _).
 1063resolve_with(with(IRI0), graph(IRI), State) :-
 1064    resolve_iri(IRI0, IRI, State).
 1065
 1066
 1067                 /*******************************
 1068                 *         STEAD FASTNESS       *
 1069                 *******************************/
 steadfast(Q0, Q) is det
Make Q0 steadfast. The problem is that the SPARQL semantics assume bottom-up evaluation. Top-down evaluation yields the same result as long as the code is steadfast. Unfortunately, some queries are not. This applies notably to expression evaluation in BIND. We fix this by rewriting copying non-stead-fast parts of the query and a post-execution unification.
 1080steadfast(Q0, sparql_group(Q1, AT0, AT1)) :-
 1081    phrase(non_steadfast(Q0), NonSteadFast),
 1082    NonSteadFast \== [],
 1083    !,
 1084    term_variables(Q0, AllVars),
 1085    sort(AllVars, AllSorted),
 1086    sort(NonSteadFast, NSFSorted),
 1087    ord_subtract(AllSorted, NSFSorted, SteadFast),
 1088    STF =.. [v|SteadFast],
 1089    copy_term(STF-Q0, STF1-Q1),
 1090    STF = STF1,
 1091    unifiable(Q0, Q1, Unifier),
 1092    maplist(split_assignment, Unifier, A0, A1),
 1093    AT0 =.. [v|A0],
 1094    AT1 =.. [v|A1].
 1095steadfast(Q0, sparql_group(Q0)).
 1096
 1097
 1098split_assignment(A=B, A, B).
 1099
 1100non_steadfast(Var) -->
 1101    { var(Var) },
 1102    !.
 1103non_steadfast((A,B)) -->
 1104    !,
 1105    non_steadfast(A),
 1106    non_steadfast(B).
 1107non_steadfast((A;B)) -->
 1108    !,
 1109    non_steadfast(A),
 1110    non_steadfast(B).
 1111non_steadfast((A->B)) -->
 1112    !,
 1113    non_steadfast(A),
 1114    non_steadfast(B).
 1115non_steadfast((A*->B)) -->
 1116    !,
 1117    non_steadfast(A),
 1118    non_steadfast(B).
 1119non_steadfast(\+A) -->
 1120    !,
 1121    non_steadfast(A).
 1122non_steadfast(sparql_eval(Expr, _Var)) -->
 1123    !,
 1124    term_variables(Expr).
 1125non_steadfast(sparql_true(Expr)) -->
 1126    !,
 1127    term_variables(Expr).
 1128non_steadfast(_) -->
 1129    [].
 1130
 1131
 1132                 /*******************************
 1133                 *      COMPILE EXPRESSIONS     *
 1134                 *******************************/
 compile_expression(+Expression, -Var, -Goal, +State0, -State)
Compile an expression into a (compound) goal that evaluates to the variable var. This version is not realy compiling. Its just the entry point for a future compiler.
 1142compile_expression(bind(Expr,var(VarName)), Var, Goal, State0, State) :-
 1143    !,
 1144    resolve_var(VarName, Var, State0, State1),
 1145    compile_expression(Expr, Var, Goal, State1, State).
 1146compile_expression(Expr0, Var, Goal, State0, State) :-
 1147    resolve_expression(Expr0, Expr, Q, State0, State),
 1148    (   primitive(Expr)
 1149    ->  Var = Expr,
 1150        Goal = Q
 1151    ;   mkconj(Q, sparql_eval(Expr, Var), Goal)
 1152    ).
 1153
 1154primitive(Var)  :- var(Var), !.
 1155primitive(Atom) :- atom(Atom).          % IRI, '$null$'
 1156
 1157
 1158                 /*******************************
 1159                 *            SERVICE           *
 1160                 *******************************/
 service_state(+S0, -S)
Make a resolver state for a SERVICE. We want to know
 1169service_state(S0, S) :-
 1170    state_base_uri(S0, Base),
 1171    state_prefix_assoc(S0, PrefixAssoc),
 1172    empty_assoc(VarAssoc),
 1173    make_state([ base_uri(Base),
 1174                 prefix_assoc(PrefixAssoc),
 1175                 var_assoc(VarAssoc)
 1176               ], S).
 service_prefixes(+State, -List:list(pair)) is det
Obtain a list of Prefix-URL pairs for the prefixes used in State.
 1184service_prefixes(State, List) :-
 1185    state_prefixes_used(State, Prefixes),
 1186    maplist(prefix_binding(State), Prefixes, List).
 1187
 1188prefix_binding(State, Prefix, Prefix-IRI) :-
 1189    resolve_prefix(Prefix, IRI, State).
 1190
 1191resolve_service_vars([], State, State).
 1192resolve_service_vars([VarName=Var|T], S0, S) :-
 1193    resolve_var(VarName, Var, S0, S1),
 1194    resolve_service_vars(T,S1, S).
 1195
 1196
 1197
 1198                 /*******************************
 1199                 *          SPARQL DCG          *
 1200                 *******************************/
 1201
 1202:- discontiguous term_expansion/2. 1203
 1204:- if(current_predicate(string_codes/2)). 1205goal_expansion(keyword(S,L,T), keyword(Codes,L,T)) :-
 1206    string(S),
 1207    string_codes(S, Codes).
 1208goal_expansion(must_see_keyword(S,L,T), must_see_keyword(Codes,L,T)) :-
 1209    string(S),
 1210    string_codes(S, Codes).
 1211:- endif. 1212
 1213/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 1214From A.7. We keep the same naming and   order of the productions to make
 1215it as easy as possible to verify the correctness of the parser.
 1216- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 query(-Prologue, -Query)//
 1220sparql_query(Prologue, Query, In, Out) :-
 1221    catch(uquery(Prologue, Query, In, Out),
 1222          E,
 1223          add_error_location(E, In)).
 1224
 1225uquery(Prologue, Query, In, Out) :-
 1226    phrase(unescape_code_points(Unescaped), In, Out),
 1227    phrase(query(Prologue, Query), Unescaped).
 unescape_code_points(-Unescaped)//
According to the SPARQL grammar, any code point may be escaped using \uXXXX or \UXXXXXXXX anywhere and must be decoded first.
 1234unescape_code_points([H|T]) -->
 1235    uchar(H),
 1236    !,
 1237    unescape_code_points(T).
 1238unescape_code_points([H|T]) -->
 1239    [H],
 1240    !,
 1241    unescape_code_points(T).
 1242unescape_code_points([]) -->
 1243    [].
 uchar(-Code)//
\uXXXX or \UXXXXXXXX, returning character value
 1249uchar(Code) -->
 1250    "\\u",
 1251    !,
 1252    (   hex(D1), hex(D2), hex(D3), hex(D4)
 1253    ->  { Code is D1<<12 + D2<<8 + D3<<4 + D4 }
 1254    ;   syntax_error(illegal_uchar)
 1255    ).
 1256uchar(Code) -->
 1257    "\\U",
 1258    !,
 1259    (   hex(D1), hex(D2), hex(D3), hex(D4),
 1260        hex(D5), hex(D6), hex(D7), hex(D8)
 1261    ->  { Code is D1<<28 + D2<<24 + D3<<20 + D4<<16 +
 1262                  D5<<12 + D6<<8 + D7<<4 + D8 }
 1263    ;   syntax_error(illegal_Uchar)
 1264    ).
 1265
 1266query(Prologue, Query) -->              % [2]
 1267    skip_ws,
 1268    prologue(Prologue),
 1269    (   select_query(Query)
 1270    ;   construct_query(Query)
 1271    ;   describe_query(Query)
 1272    ;   ask_query(Query)
 1273    ;   update_query(Query)
 1274    ),
 1275    !.
 prologue(-Decls)//
The Prologue consists of zero or more BASE and PREFIX declarations. The result is the last BASE declaration and each PREFIX is resolved against the last preceeding BASE declaration.
 1283prologue(Prologue) -->  % [4]
 1284    prologue_decls(0, Base, Decls),
 1285    {   Base == 0
 1286    ->  Prologue = prologue(Decls)
 1287    ;   Prologue = prologue(Base, Decls)
 1288    }.
 1289
 1290prologue_decls(_, Base, Decls) -->
 1291    base_decl(Base1),
 1292    !,
 1293    prologue_decls(Base1, Base, Decls).
 1294prologue_decls(Base0, Base, [H|T]) -->
 1295    prefix_decl(H, Base0),
 1296    !,
 1297    prologue_decls(Base0, Base, T).
 1298prologue_decls(Base, Base, []) -->
 1299    "".
 base_decl(-Base:uri)// is semidet
Match "base <URI>".
 1305base_decl(Base) -->                     % [5]
 1306    keyword("base"),
 1307    q_iri_ref(Base).
 prefix_decl(-Prefix, +Base)// is semidet
Process "prefix <qname> <URI>" into a term Qname-IRI
 1313prefix_decl(Id-IRI, Base) -->
 1314    keyword("prefix"),
 1315    (   qname_ns(Id),
 1316        q_iri_ref(IRI0)
 1317    ->  { global_url(IRI0, Base, IRI) }
 1318    ;   syntax_error(illegal_prefix_declaration)
 1319    ).
 select_query(-Select)// is semidet
Process "select ..." into a term

select(Projection, DataSets, Query, Solutions)

 1327select_query(select(Projection, DataSets, Query, Solutions)) --> % [7]
 1328    select_clause(Projection, Solutions, S0),
 1329    data_set_clauses(DataSets),
 1330    where_clause(QWhere),
 1331    solution_modifier(S0),
 1332    values_clause(QValue),
 1333    { mkconj(QWhere, QValue, Query) }.
 sub_select(-SubSelect)//
 1337sub_select(sub_select(Projection, Query, Solutions)) --> % [8]
 1338    select_clause(Projection, Solutions, S0),
 1339    where_clause(WQuery),
 1340    solution_modifier(S0),
 1341    values_clause(QValues),
 1342    { mkconj(WQuery, QValues, Query) }.
 1343
 1344
 1345select_clause(Projection, Solutions, S0) --> % [9]
 1346    keyword("select"),
 1347    (   keyword("distinct")
 1348    ->  { Solutions = distinct(S0) }
 1349    ;   keyword("reduced")
 1350    ->  { Solutions = reduced(S0) }
 1351    ;   { Solutions = S0 }
 1352    ),
 1353    select_projection(Projection).
 select_projection(-Projection)// is det
Process the projection of a select query. Projection is one of
 1365select_projection(*) --> "*", !, skip_ws.
 1366select_projection(projection([H|T], B)) -->
 1367    projection_elt(H, true, B1),
 1368    projection_elts(T, B1, B),
 1369    !.
 1370select_projection(_) -->
 1371    syntax_error(projection_expected).
 1372
 1373projection_elts([H|T], B0, B) -->
 1374    projection_elt(H, B0, B1),
 1375    projection_elts(T, B1, B).
 1376projection_elts([], B, B) -->
 1377    [].
 1378
 1379projection_elt(Var, B, B) -->
 1380    var(Var),
 1381    !.
 1382projection_elt(Var, B0, B) -->
 1383    "(", skip_ws,
 1384    (   expression(Expr), must_see_keyword("as"), var(Var),
 1385        must_see_close_bracket
 1386    ->  skip_ws,
 1387        { mkconj(B0, bind(Expr, Var), B) }
 1388    ;   syntax_error(illegal_projection)
 1389    ).
 construct_query(-Construct)// is semidet
Processes "construct ..." into a term

construct(Template, DataSets, Query, Solutions)

 1397construct_query(construct(Template, DataSets, Query, Solutions)) --> % [10]
 1398    keyword("construct"),
 1399    (   construct_template(Template),
 1400        data_set_clauses(DataSets),
 1401        where_clause(QWhere),
 1402        solution_modifier(Solutions)
 1403    ;   data_set_clauses(DataSets),
 1404        keyword("where"),
 1405        (   "{", skip_ws,
 1406            triples_template(Template, []),
 1407            "}"
 1408        ->  skip_ws,
 1409            {QWhere = Template}
 1410        ;   syntax_error(triples_template_expected)
 1411        ),
 1412        solution_modifier(Solutions)
 1413    ),
 1414    values_clause(QValue),
 1415    { mkconj(QWhere, QValue, Query) }.
 describe_query(-Describe)// is semidet
Processes "describe ..." into a term

describe(Projection, DataSets, Query, Solutions)

 1423describe_query(describe(Projection, DataSets, Query, Solutions)) --> % [11]
 1424    keyword("describe"),
 1425    desc_projection(Projection),
 1426    data_set_clauses(DataSets),
 1427    (where_clause(QWhere) -> [] ; {QWhere = true}),
 1428    solution_modifier(Solutions),
 1429    values_clause(QValue),
 1430    { mkconj(QWhere, QValue, Query) }.
 1431
 1432desc_projection(*) --> "*", !, skip_ws.
 1433desc_projection(projection([H|T], true)) -->
 1434    var_or_iri_ref(H),
 1435    !,
 1436    var_or_iri_refs(T).
 1437desc_projection(_) -->
 1438    syntax_error(projection_expected).
 1439
 1440var_or_iri_refs([H|T]) -->
 1441    var_or_iri_ref(H),
 1442    !,
 1443    var_or_iri_refs(T).
 1444var_or_iri_refs([]) -->
 1445    [].
 ask_query(Query)//
 1450ask_query(ask(DataSets, Query, Solutions)) --> % [12]
 1451    keyword("ask"),
 1452    data_set_clauses(DataSets),
 1453    where_clause(QWhere),
 1454    solution_modifier(Solutions),
 1455    values_clause(QValue),
 1456    { mkconj(QWhere, QValue, Query) }.
 1457
 1458data_set_clauses([H|T]) -->             % [13*]
 1459    dataset_clause(H),
 1460    !,
 1461    data_set_clauses(T).
 1462data_set_clauses([]) -->
 1463    [].
 dataset_clause(-Src)//
 1467dataset_clause(Src) -->                 % [13]
 1468    keyword("from"),
 1469    (   default_graph_clause(Src)
 1470    ->  []
 1471    ;   named_graph_clause(Src)
 1472    ).
 default_graph_clause(-Src)
 1476default_graph_clause(Src) -->           % [14]
 1477    source_selector(Src).
 named_graph_clause(Graph)//
 1481named_graph_clause(Src) -->             % [15]
 1482    keyword("named"),
 1483    source_selector(Src).
 source_selector(-Src)//
 1487source_selector(Src) -->                % [16]
 1488    iri_ref(Src).
 where_clause(-Pattern)//
 1492where_clause(Pattern) -->               % [17]
 1493    keyword("where"),
 1494    !,
 1495    must_see_group_graph_pattern(Pattern).
 1496where_clause(Pattern) -->
 1497    group_graph_pattern(Pattern).
 1498
 1499must_see_group_graph_pattern(Pattern) -->
 1500    group_graph_pattern(Pattern),
 1501    !.
 1502must_see_group_graph_pattern(_) -->
 1503    syntax_error(expected(group_graph_pattern)).
 solution_modifier(-Solutions)// is det
Processes order by, limit and offet clauses into a term
solutions(Group, Having, Order, Limit, Offset)

Where

 1520solution_modifier(Modifier) -->         % [18]
 1521    { Modifier = solutions(Group, Having, Order, Limit, Offset) },
 1522    ( group_clause(Group)   -> [] ; { Group  = [] } ),
 1523    ( having_clause(Having) -> [] ; { Having = true } ),
 1524    ( order_clause(Order)   -> [] ; { Order  = unsorted } ),
 1525    limit_offset_clauses(Limit, Offset).
 1526
 1527limit_offset_clauses(Limit, Offset) -->
 1528    limit_clause(Limit),
 1529    !,
 1530    ( offset_clause(Offset) -> [] ; { Offset = 0 } ).
 1531limit_offset_clauses(Limit, Offset) -->
 1532    offset_clause(Offset),
 1533    !,
 1534    ( limit_clause(Limit)   -> [] ; { Limit  = inf } ).
 1535limit_offset_clauses(inf, 0) --> [].
 group_clause(-Group)// is semidet
 1539group_clause([G0|Groups]) -->
 1540    keyword("group"),
 1541    must_see_keyword("by"),
 1542    must_see_group_condition(G0),
 1543    group_conditions(Groups).
 1544
 1545group_conditions([Group|T]) -->
 1546    group_condition(Group),
 1547    !,
 1548    group_conditions(T).
 1549group_conditions([]) -->
 1550    "".
 1551
 1552must_see_group_condition(G) -->
 1553    group_condition(G),
 1554    !.
 1555must_see_group_condition(_) -->
 1556    syntax_error(group_condition_expected).
 1557
 1558group_condition(Exp) -->
 1559    built_in_call(Exp),
 1560    !.
 1561group_condition(Exp) -->
 1562    function_call(Exp),
 1563    !.
 1564group_condition(Exp) -->
 1565    as_expression(Exp),
 1566    !.
 1567group_condition(Exp) -->
 1568    var(Exp),
 1569    !.
 as_expression(-Exp)// is det
Processes '(' Expression ( 'AS' Var )? ')' into one of
 1578as_expression(Exp) -->
 1579    "(", skip_ws, must_see_expression(E),
 1580    (   keyword("as")
 1581    ->  must_see_var(Var),
 1582        {Exp = bind(E, Var)}
 1583    ;   {Exp = E}
 1584    ), ")", skip_ws.
 having_clause(-Having)// is semidet
 1589having_clause(ebv(C)) -->
 1590    keyword("having"),
 1591    must_see_having_condition(C0),
 1592    having_conditions(C1),
 1593    { mkand(C0, C1, C) }.
 1594
 1595having_conditions(C) -->
 1596    having_condition(C0),
 1597    !,
 1598    having_conditions(C1),
 1599    { mkand(C0, C1, C) }.
 1600having_conditions(true) -->
 1601    "".
 1602
 1603mkand(true, X, X).
 1604mkand(X, true, X).
 1605mkand(X, Y, and(X,Y)).
 1606
 1607
 1608must_see_having_condition(C) -->
 1609    having_condition(C),
 1610    !.
 1611must_see_having_condition(_) -->
 1612    syntax_error(having_condition_expected).
 1613
 1614having_condition(C) -->
 1615    constraint(C).
 order_clause(-Order)//
 1620order_clause(order_by([H|T])) -->
 1621    keyword("order"), must_see_keyword("by"),
 1622    must_be_order_condition(H),
 1623    order_conditions(T).
 1624
 1625order_conditions([H|T]) -->
 1626    order_condition(H),
 1627    !,
 1628    order_conditions(T).
 1629order_conditions([]) -->
 1630    [].
 1631
 1632must_be_order_condition(Cond) -->
 1633    order_condition(Cond),
 1634    !.
 1635must_be_order_condition(_) -->
 1636    syntax_error(order_condition_expected).
 order_condition(-Order)//
 1640order_condition(ascending(Expr)) -->
 1641    keyword("asc"),
 1642    !,
 1643    bracketted_expression(Expr).
 1644order_condition(descending(Expr)) -->
 1645    keyword("desc"),
 1646    !,
 1647    bracketted_expression(Expr).
 1648order_condition(ascending(Value)) -->
 1649    (   constraint(Value)
 1650    ;   var(Value)
 1651    ),
 1652    !.
 limit_clause(-Limit)//
 1657limit_clause(Limit) -->
 1658    keyword("limit"),
 1659    integer(Limit).
 offset_clause(Offset)//
 1664offset_clause(Offset) -->
 1665    keyword("offset"),
 1666    integer(Offset).
 values_clause(-Query)// is det
Query is one of
 1677values_clause(Q) -->                    % [28]
 1678    keyword("values"),
 1679    !,
 1680    data_block(Q).
 1681values_clause(true) -->
 1682    "".
 update_query(-UpdatedInfo)// is semidet
True when input is a valid SPARQL update request.
 1688update_query(update(Updates)) -->
 1689    update(Updates).
 1690
 1691update(Updates) -->
 1692    (   update1(U1)
 1693    ->  { Updates = [U1|Update] },
 1694        (  ";"
 1695        ->  skip_ws,
 1696            must_see_update(Update)
 1697        ;   { Update = [] }
 1698        )
 1699    ;   { Updates = [] }
 1700    ).
 1701
 1702must_see_update(Update) -->
 1703    update(Update),
 1704    !.
 1705must_see_update(_) -->
 1706    syntax_error(update_expected).
 1707
 1708update1(Update) -->
 1709    get_keyword(Action),
 1710    update1(Action, Update),
 1711    !.
 1712update1(Update) -->
 1713    modify(Update).
 update1(+Keyword, -UpdatedAction)// is semidet
 1717update1(load, load(Verbose, IRI, Graph)) -->
 1718    silent(Verbose),
 1719    iri_ref(IRI),
 1720    (   keyword("into")
 1721    ->  graph_ref(GraphIRI),
 1722        {Graph = graph(GraphIRI)}
 1723    ;   {Graph = default}
 1724    ).
 1725update1(clear, clear(Verbose, GraphRefAll)) -->
 1726    silent(Verbose),
 1727    graph_ref_all(GraphRefAll).
 1728update1(drop, drop(Verbose, GraphRefAll)) -->
 1729    silent(Verbose),
 1730    graph_ref_all(GraphRefAll).
 1731update1(create, create(Verbose, GraphRef)) -->
 1732    silent(Verbose),
 1733    graph_ref(GraphRef).
 1734update1(add, add(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1735    silent(Verbose),
 1736    graph_or_default(GraphOrDefaultFrom),
 1737    must_see_keyword("to"),
 1738    graph_or_default(GraphOrDefaultTo).
 1739update1(move, move(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1740    silent(Verbose),
 1741    graph_or_default(GraphOrDefaultFrom),
 1742    must_see_keyword("to"),
 1743    graph_or_default(GraphOrDefaultTo).
 1744update1(copy, copy(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1745    silent(Verbose),
 1746    graph_or_default(GraphOrDefaultFrom),
 1747    must_see_keyword("to"),
 1748    graph_or_default(GraphOrDefaultTo).
 1749update1(insert, insert_data(Quads)) -->
 1750    keyword("data"),
 1751    !,
 1752    quad_data(Quads).
 1753update1(delete, delete_data(Quads)) -->
 1754    keyword("data"),
 1755    !,
 1756    quad_data(Quads).
 1757update1(delete, delete_where(Quads)) -->
 1758    keyword("where"),
 1759    !,
 1760    quad_pattern(Quads).
 modify(-Updated)//
 1764modify(modify(WithIRI, InsDel, Using, Pattern)) --> % [41]
 1765    optional_with(WithIRI),
 1766    (   delete_clause(Del),
 1767        (   insert_clause(Ins)
 1768        ->  { InsDel = replace(Del,Ins) }
 1769        ;   { InsDel = delete(Del) }
 1770        )
 1771    ->  ""
 1772    ;   insert_clause(Ins),
 1773        { InsDel = insert(Ins) }
 1774    ),
 1775    using_clauses(Using),
 1776    must_see_keyword("where"),
 1777    must_see_group_graph_pattern(Pattern).
 1778
 1779optional_with(with(IRI)) -->
 1780    keyword("with"),
 1781    !,
 1782    must_see_iri(IRI).
 1783optional_with(without) -->
 1784    "".
 1785
 1786delete_clause(Quads) -->
 1787    keyword("delete"),
 1788    quad_pattern(Quads).
 1789insert_clause(Quads) -->
 1790    keyword("insert"),
 1791    quad_pattern(Quads).
 1792
 1793silent(silent) -->
 1794    keyword("silent"),
 1795    !.
 1796silent(error) -->
 1797    "".
 1798
 1799using_clauses([U0|T]) -->
 1800    keyword("using"),
 1801    !,
 1802    (   keyword("named"),
 1803        must_see_iri(IRI)
 1804    ->  { U0 = named(IRI) }
 1805    ;   must_see_iri(U0)
 1806    ),
 1807    using_clauses(T).
 1808using_clauses([]) -->
 1809    "".
 1810
 1811graph_ref(Graph) -->
 1812    keyword("graph"),
 1813    must_see_iri(Graph).
 1814
 1815graph_ref_all(graph(Graph)) -->
 1816    graph_ref(Graph),
 1817    !.
 1818graph_ref_all(default) -->
 1819    keyword("default").
 1820graph_ref_all(named) -->
 1821    keyword("named").
 1822graph_ref_all(all) -->
 1823    keyword("all").
 1824
 1825graph_or_default(default) -->
 1826    keyword("default"),
 1827    !.
 1828graph_or_default(graph(Graph)) -->
 1829    (   keyword("graph")
 1830    ->  ""
 1831    ;   ""
 1832    ),
 1833    must_see_iri(Graph).
 1834
 1835quad_pattern(Quads) -->                         % [48]
 1836    quad_data(Quads).
 1837
 1838quad_data(Quads) -->
 1839    "{", skip_ws,
 1840    (   quads(Quads),
 1841        "}"
 1842    ->  skip_ws
 1843    ;   syntax_error(quads_expected)
 1844    ).
 quads(-Quads)//
Quads is a list of triples and graph(Graph,Triples)
 1850quads(Quads) -->
 1851    triples_template(Quads, Tail),
 1852    !,
 1853    quads_conts(Tail, []).
 1854quads(Quads) -->
 1855    quads_conts(Quads, []).
 1856
 1857quads_conts(Quads, Tail) -->
 1858    quads_cont(Quads, Tail2),
 1859    !,
 1860    quads_conts(Tail2, Tail).
 1861quads_conts(Quads, Quads) -->
 1862    "".
 1863
 1864quads_cont([Graph|Tail0], Tail) -->
 1865    quads_not_triples(Graph),
 1866    optional_dot,
 1867    (   triples_template(Tail0, Tail)
 1868    ->  ""
 1869    ;   {Tail0=Tail}
 1870    ).
 1871
 1872quads_not_triples(graph(IRI, Triples)) -->
 1873    keyword("graph"),
 1874    must_see_var_or_iri_ref(IRI),
 1875    must_see_open_brace,
 1876    (   triples_template(Triples, [])
 1877    ->  ""
 1878    ;   {Triples=[]}
 1879    ),
 1880    must_see_close_brace.
 data_block(-DataBlock)// is det
DataBlock is one of
 1890data_block(Values) -->
 1891    inline_data_one_var(Values),
 1892    !.
 1893data_block(Values) -->
 1894    inline_data_full(Values).
 1895
 1896inline_data_one_var(var_in(Var, Values)) -->
 1897    var(Var),
 1898    inline_values(Values).
 1899
 1900inline_values(Values) -->
 1901    (   datablock_body(Values)
 1902    ->  ""
 1903    ;   datablock_body_full(ListValues)
 1904    ->  { maplist(single_body, ListValues, Values) }
 1905    ;   syntax_error(datablock_values_expected)
 1906    ).
 1907
 1908single_body([Var], Var).
 1909
 1910datablock_body(Values) -->
 1911    "{", skip_ws, datablock_values(Values), "}", skip_ws.
 1912
 1913datablock_values([V0|T]) -->
 1914    datablock_value(V0),
 1915    !,
 1916    datablock_values(T).
 1917datablock_values([]) -->
 1918    "".
 1919
 1920datablock_value(V) -->
 1921    iri_ref(V),
 1922    !.
 1923datablock_value(V) -->
 1924    rdf_literal(V),
 1925    !.
 1926datablock_value(V) -->
 1927    numeric_literal(V),
 1928    !.
 1929datablock_value(B) -->
 1930    boolean_literal(B),
 1931    !.
 1932datablock_value(_) -->                  % UNDEF acts as a variable
 1933    keyword("undef").
 1934
 1935inline_data_full(InlineData) -->
 1936    "(", skip_ws, vars(Vars),
 1937    (   ")"
 1938    ->  skip_ws
 1939    ;   syntax_error(expected(')'))
 1940    ),
 1941    (   { Vars = [Var] }
 1942    ->  inline_values(Values),
 1943        { InlineData = var_in(Var, Values) }
 1944    ;   datablock_body_full(Values)
 1945    ->  { InlineData = vars_in(Vars, Values) }
 1946    ;   syntax_error(datablock_values_expected)
 1947    ),
 1948    !.
 1949
 1950datablock_body_full(Values) -->
 1951    "{", skip_ws,
 1952    (   datablock_values_full(Values), "}"
 1953    ->  skip_ws
 1954    ;   syntax_error(datablock_values_expected)
 1955    ).
 1956
 1957datablock_values_full([V0|T]) -->
 1958    datablock_value_full(V0),
 1959    !,
 1960    datablock_values_full(T).
 1961datablock_values_full([]) -->
 1962    "".
 1963
 1964datablock_value_full(List) -->
 1965    "(", skip_ws,
 1966    datablock_values(List),
 1967    must_see_close_bracket.
 1968
 1969vars([H|T]) -->
 1970    var(H),
 1971    !,
 1972    vars(T).
 1973vars([]) --> "".
 minus_graph_pattern(-Pattern) is det
 1978minus_graph_pattern(minus(Pattern)) -->
 1979    keyword("minus"),
 1980    must_see_group_graph_pattern(Pattern).
 triples_template(-Triples, Tail)//
 1984triples_template(Triples, Tail) -->     % [52]
 1985    triples_same_subject(Triples, Tail0),
 1986    (   "."
 1987    ->  skip_ws,
 1988        (   triples_template(Tail0, Tail)
 1989        ->  ""
 1990        ;   {Tail = Tail0}
 1991        )
 1992    ;   {Tail = Tail0}
 1993    ).
 group_graph_pattern(P)//
 1999group_graph_pattern(group(P)) -->               % [53]
 2000    skip_ws, "{", skip_ws,
 2001    (   sub_select(P0)
 2002    ;   group_graph_pattern_sub(P0)
 2003    ;   syntax_error(expected(graph_pattern))
 2004    ),
 2005    !,
 2006    (   "}"
 2007    ->  skip_ws,
 2008        { resolve_bnodes(P0, P) }
 2009    ;   syntax_error(expected('}'))
 2010    ).
 group_graph_pattern_sub(P)//
 2015group_graph_pattern_sub(P) -->          % [54]
 2016    triples_block(P0, []),
 2017    !,
 2018    group_graph_pattern_sub_cont(P0, P).
 2019group_graph_pattern_sub(P) -->
 2020    group_graph_pattern_sub_cont(true, P).
 group_graph_pattern_sub_cont(+PLeft, P)//
Matches ( GraphPatternNotTriples '.'? TriplesBlock? )*
 2026group_graph_pattern_sub_cont(PLeft, P) -->
 2027    group_graph_pattern_sub_cont_1(PLeft, P0),
 2028    !,
 2029    group_graph_pattern_sub_cont(P0, P).
 2030group_graph_pattern_sub_cont(PLeft, PLeft) --> "".
 2031
 2032group_graph_pattern_sub_cont_1(PLeft, P) -->
 2033    graph_pattern_not_triples(P0),
 2034    (   "."
 2035    ->  skip_ws
 2036    ;   ""
 2037    ),
 2038    (   triples_block(P1, [])
 2039    ->  { mkconj(P0, P1, P2),
 2040          mkconj(PLeft, P2, P)
 2041        }
 2042    ;   { mkconj(PLeft, P0, P) }
 2043    ).
 triples_block(-Triples, ?Tail)//
 2048triples_block(Triples, Tail) -->        % [55]
 2049    triples_same_subject_path(Triples, Tail0),
 2050    (   "."
 2051    ->  skip_ws,
 2052        (   triples_block(Tail0, Tail)
 2053        ->  ""
 2054        ;   { Tail = Tail0 }
 2055        )
 2056    ;   { Tail = Tail0 }
 2057    ).
 2058
 2059
 2060one_dot -->
 2061    ".", !, skip_ws,
 2062    (   "."
 2063    ->  syntax_error(double_dot)
 2064    ;   ""
 2065    ).
 2066
 2067optional_dot --> ".", skip_ws.
 2068optional_dot --> "".
 graph_pattern_not_triples(-Pattern)//
 2073graph_pattern_not_triples(P) --> group_or_union_graph_pattern(P), !.
 2074graph_pattern_not_triples(P) --> optional_graph_pattern(P), !.
 2075graph_pattern_not_triples(P) --> minus_graph_pattern(P), !.
 2076graph_pattern_not_triples(P) --> graph_graph_pattern(P), !.
 2077graph_pattern_not_triples(P) --> service_graph_pattern(P), !.
 2078graph_pattern_not_triples(P) --> filter(P).
 2079graph_pattern_not_triples(P) --> bind(P).
 2080graph_pattern_not_triples(P) --> inline_data(P).
 optional_graph_pattern(Pattern)//
 2084optional_graph_pattern(Pattern) -->     % [57]
 2085    keyword("optional"),
 2086    must_see_group_graph_pattern(P0),
 2087    { Pattern = optional(P0) }.
 graph_graph_pattern(-Graph)// is semidet
Processes a "graph ..." clause into

graph(Graph, Pattern)

 2095graph_graph_pattern(graph(Graph, Pattern)) --> % [58]
 2096    keyword("graph"),
 2097    !,
 2098    must_see_var_or_iri_ref(Graph),
 2099    must_see_group_graph_pattern(Pattern).
 service_graph_pattern(-P)//
Process a federated query. We need to find three things

We issue the following query on the remote service:

PREFIX ...
SELECT ?out1,?out2,... WHERE {
  BIND(in1 as ?v1)
  BIND(in2 as ?v2)
  ...
  <Original query>
}
 2121                                        % [59]
 2122service_graph_pattern(service(Silent, VarOrIRI, GroupGraphPattern, Query)) -->
 2123    keyword("service"),
 2124    !,
 2125    silent(Silent),
 2126    must_see_var_or_iri_ref(VarOrIRI),
 2127    mark(Here),
 2128    must_see_group_graph_pattern(group(GroupGraphPattern)),
 2129    string_from_mark(Here, Query).
 2130
 2131mark(Here, Here, Here).
 2132
 2133string_from_mark(Start, String) -->
 2134    mark(End),
 2135    { codes_between(Start, End, Codes),
 2136      string_codes(String, Codes)
 2137    }.
 2138
 2139codes_between(Start, End, Codes) :-
 2140    same_term(Start, End),
 2141    !,
 2142    Codes = [].
 2143codes_between([H|T], End, [H|C]) :-
 2144    codes_between(T, End, C).
 bind(P)
 2149bind(bind(Expr, Var)) -->               % [60]
 2150    keyword("bind"),
 2151    !,
 2152    must_see_open_bracket,
 2153    must_see_expression(Expr),
 2154    must_see_keyword("as"),
 2155    must_see_var(Var),
 2156    must_see_close_bracket.
 inline_data(Data)
 2160inline_data(Values) -->
 2161    keyword("values"),
 2162    data_block(Values).
 group_or_union_graph_pattern(-Pattern)//
 2167group_or_union_graph_pattern(Pattern) --> % [67]
 2168    group_graph_pattern(P0),
 2169    add_union(P0, Pattern).
 2170
 2171add_union(P0, (P0;P)) -->
 2172    keyword("union"),
 2173    !,
 2174    must_see_group_graph_pattern(P1),
 2175    add_union(P1, P).
 2176add_union(P, P) -->
 2177    [].
 filter(-Filter)//
 2182filter(filter(Exp)) -->
 2183    keyword("filter"),
 2184    (   constraint(Exp)
 2185    ->  ""
 2186    ;   syntax_error(filter_expected)
 2187    ).
 constraint(-Filter)//
 2191constraint(Exp) -->
 2192    (   bracketted_expression(Exp)
 2193    ->  []
 2194    ;   built_in_call(Exp)
 2195    ->  ""
 2196    ;   function_call(Exp)
 2197    ).
 function_call(-Function)// is semidet
Processes <URI>(Arg ...) into function(IRI, Args)
 2203function_call(function(F, Args)) -->
 2204    iri_ref(F),
 2205    arg_list(Args).
 arg_list(-List)//
 2210arg_list(ArgList) -->                   % [71]
 2211    "(", skip_ws,
 2212    optional_distinct(ArgList, List),
 2213    (   expression(A0)
 2214    ->  arg_list_cont(As),
 2215        {List = [A0|As]}
 2216    ;   {List = []}
 2217    ),
 2218    (   ")"
 2219    ->  []
 2220    ;   syntax_error(expression_expected)
 2221    ),
 2222    skip_ws.
 optional_distinct(-WrappedValue, -RealValue)//
Wrap argument in distinct(PlainArg) if there is a distinct keyword.
 2229optional_distinct(E, E1) -->
 2230    keyword("distinct"),
 2231    !,
 2232    { E = distinct(E1) }.
 2233optional_distinct(E, E) --> "".
 2234
 2235
 2236arg_list_cont([H|T]) -->
 2237    ",", !, skip_ws,
 2238    must_see_expression(H),
 2239    arg_list_cont(T).
 2240arg_list_cont([]) -->
 2241    [].
 expression_list(-Expressions)//
 2245expression_list(ExprList) -->
 2246    "(", skip_ws,
 2247    (   expression(A0)
 2248    ->  arg_list_cont(As),
 2249        {ExprList = [A0|As]}
 2250    ;   {ExprList = []}
 2251    ),
 2252    (   ")"
 2253    ->  []
 2254    ;   syntax_error(expression_expected)
 2255    ),
 2256    skip_ws.
 construct_template(Triples)// is semidet
 2260construct_template(Triples) -->
 2261    "{", skip_ws,
 2262    (   construct_triples(Triples), "}"
 2263    ->  skip_ws
 2264    ;   syntax_error(construct_template_expected)
 2265    ).
 construct_triples(-List)//
 2269construct_triples(List) -->
 2270    construct_triples(List, []).
 2271
 2272construct_triples(List, T) -->
 2273    triples_same_subject(List, T0),
 2274    !,
 2275    (   one_dot
 2276    ->  (   peek(0'})
 2277        ->  { T = T0 }
 2278        ;   construct_triples(T0, T)
 2279        )
 2280    ;   { T = T0 }
 2281    ).
 2282construct_triples(T, T) -->
 2283    "".
 triples_same_subject(-List, ?Tail)//
Return list of rdf(S,P,O) from triple spec.
 2289triples_same_subject(List, Tail) -->
 2290    var_or_term(S),
 2291    !,
 2292    property_list_not_empty(L, List, T0),
 2293    { make_triples_same_subject(L, S, T0, Tail) }.
 2294triples_same_subject(List, Tail) -->
 2295    triples_node(S, List, T0),
 2296    property_list(L, T0, T1),
 2297    { make_triples_same_subject(L, S, T1, Tail) }.
 2298
 2299make_triples_same_subject([], _, T, T).
 2300make_triples_same_subject([property(P,O)|TP], S, [rdf(S,P,O)|T0], T) :-
 2301    make_triples_same_subject(TP, S, T0, T).
 property_list(-Properties, -Triples, ?TriplesTail)//
 2305property_list(L, Triples, Tail) -->
 2306    property_list_not_empty(L, Triples, Tail),
 2307    !.
 2308property_list([], Tail, Tail) --> [].
 property_list_not_empty(-Properties, -Triples, ?TriplesTail)//
 2313property_list_not_empty(E, Triples, Tail) -->
 2314    verb(P),
 2315    must_see_object_list(OL, Triples, T0),
 2316    { mk_proplist(OL, P, E, T) },
 2317    (   ";", skip_ws
 2318    ->  property_list(T, T0, Tail)
 2319    ;   { T = [],
 2320          Tail = T0
 2321        }
 2322    ).
 2323
 2324mk_proplist([], _, T, T).
 2325mk_proplist([O|OT], P, [property(P,O)|T0], T) :-
 2326    mk_proplist(OT, P, T0, T).
 object_list(-L, -Triples, ?TriplesTail)//
 2330object_list(List, Triples, Tail) -->    % [79]
 2331    object(H, Triples, T0),
 2332    (   ",", skip_ws
 2333    ->  { List = [H|T] },
 2334        object_list(T, T0, Tail)
 2335    ;   { List = [H],
 2336          Tail = T0
 2337        }
 2338    ).
 2339
 2340must_see_object_list(List, Triples, Tail) -->
 2341    object_list(List, Triples, Tail),
 2342    !.
 2343must_see_object_list(_,_,_) -->
 2344    syntax_error(object_list_expected).
 2345
 2346object(Obj, Triples, Tail) -->          % [80]
 2347    graph_node(Obj, Triples, Tail).
 verb(-E)//
 2351verb(E) --> var_or_iri_ref(E), !.       % [78]
 2352verb(E) --> "a", skip_ws, { rdf_equal(E, rdf:type) }.
 2353
 2354
 2355                 /*******************************
 2356                 *            PATHS             *
 2357                 *******************************/
 2358
 2359/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 2360A property path basically describes a   complex relation from a resource
 2361to another resource. We represent a path   as rdf(S,P,O), where P is one
 2362of
 2363
 2364
 2365
 2366See http://www.w3.org/TR/sparql11-query/#propertypaths
 2367- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 triples_same_subject_path(-Triples, ?Tail)//
Similar to triples_same_subject//2, but the resulting property of each triple can be a path expression.
 2375triples_same_subject_path(Triples, Tail) -->
 2376    var_or_term(Subject),
 2377    !,
 2378    property_list_path_not_empty(Props, Triples, Tail0),
 2379    { make_triples_same_subject(Props, Subject, Tail0, Tail) }.
 2380triples_same_subject_path(Triples, Tail) -->
 2381    triples_node_path(Subject, Triples, Tail0),
 2382    property_list_path(Props, Tail0, Tail1),
 2383    { make_triples_same_subject(Props, Subject, Tail1, Tail) }.
 2384
 2385property_list_path(Props, Triples, Tail) -->
 2386    property_list_path_not_empty(Props, Triples, Tail),
 2387    !.
 2388property_list_path([], Triples, Triples) -->
 2389    "".
 2390
 2391property_list_path_not_empty(Props, Triples, Tail) --> % [83]
 2392    verb_path_or_simple(Path),
 2393    must_see_object_list_path(OL, Triples, Tail0),
 2394    { mk_proplist(OL, Path, Props, T) },
 2395    (   ";", skip_ws
 2396    ->  verb_object_lists(T, Tail0, Tail)
 2397    ;   { T = [],
 2398          Tail = Tail0
 2399        }
 2400    ).
 verb_object_lists(-Properties, -Triples, ?Tail)// is det
Parses ( ';' ( ( VerbPath | VerbSimple ) ObjectList )? )*
 2406verb_object_lists(Props, Triples, Tail) -->
 2407    verb_path_or_simple(Path),
 2408    !,
 2409    must_see_object_list(OL, Triples, Tail0),
 2410    { mk_proplist(OL, Path, Props, T) },
 2411    (   ";", skip_ws
 2412    ->  verb_object_lists(T, Tail0, Tail)
 2413    ;   { T = [],
 2414          Tail = Tail0
 2415        }
 2416    ).
 2417verb_object_lists([], Triples, Triples) --> "".
 2418
 2419
 2420verb_path_or_simple(Path) -->
 2421    verb_path(Path),
 2422    !.
 2423verb_path_or_simple(Path) -->
 2424    verb_simple(Path).
 2425
 2426verb_path(Path) -->                     % [84]
 2427    path(Path).
 2428
 2429verb_simple(Var) -->
 2430    var(Var).
 2431
 2432must_see_object_list_path(Objects, Triples, Tail) -->
 2433    object_list_path(Objects, Triples, Tail),
 2434    !.
 2435must_see_object_list_path(_,_,_) -->
 2436    syntax_error(object_list_path_expected).
 2437
 2438object_list_path(Objects, Triples, Tail) -->
 2439    object_path(H, Triples, Tail0),
 2440    (   ",", skip_ws
 2441    ->  { Objects = [H|T] },
 2442        object_list_path(T, Tail0, Tail)
 2443    ;   { Objects = [H],
 2444          Tail = Tail0
 2445        }
 2446    ).
 2447
 2448object_path(Object, Triples, Tail) -->
 2449    graph_node_path(Object, Triples, Tail).
 2450
 2451path(Path) -->
 2452    path_alternative(Path).
 2453
 2454path_alternative(PathAlt) -->
 2455    path_sequence(S0),
 2456    (   "|"
 2457    ->  skip_ws,
 2458        {PathAlt = (S0;S1)},
 2459        path_alternative(S1)
 2460    ;   {PathAlt = S0}
 2461    ).
 2462
 2463path_sequence(PSeq) -->
 2464    path_elt_or_inverse(S0),
 2465    (   "/"
 2466    ->  skip_ws,
 2467        {PSeq = S0/PSeq2},
 2468        path_sequence(PSeq2)
 2469    ;   {PSeq = S0}
 2470    ).
 2471
 2472path_elt_or_inverse(^(PathElt)) -->
 2473    "^", !, skip_ws,
 2474    path_elt(PathElt).
 2475path_elt_or_inverse(PathElt) -->
 2476    path_elt(PathElt).
 path_elt(PathElt)
One of [?*+=](PathPrimary)
 2482path_elt(PathElt) -->
 2483    path_primary(PP),
 2484    path_mod(PP, PathElt).
 2485
 2486path_mod(PP, ?(PP)) --> "?", \+ varname(_), !, skip_ws.
 2487path_mod(PP, *(PP)) --> "*", !, skip_ws.
 2488path_mod(PP, +(PP)) --> "+", !, skip_ws.
 2489path_mod(PP, PP) --> "".
 path_primary(-PathPrimary)//
 2494path_primary(IRI) -->                   % [94]
 2495    iri_ref_or_a(IRI),
 2496    !.
 2497path_primary(!(PathNegatedPropertySet)) -->
 2498    "!", !, skip_ws,
 2499    path_negated_property_set(PathNegatedPropertySet).
 2500path_primary(Path) -->
 2501    "(", !, skip_ws,
 2502    (   path(Path), ")"
 2503    ->  skip_ws
 2504    ;   syntax_error(path_expected)
 2505    ).
 2506path_primary(distinct(Path)) -->
 2507    keyword("distinct"),
 2508    !,
 2509    (   "(", skip_ws, path(Path), ")"
 2510    ->  skip_ws
 2511    ;   syntax_error(path_expected)
 2512    ).
 2513
 2514path_negated_property_set(PathNegatedPropertySet) -->
 2515    "(", !, skip_ws,
 2516    (   paths_in_property_set(PathNegatedPropertySet),
 2517        ")"
 2518    ->  skip_ws
 2519    ;   syntax_error(path_one_in_property_set_expected)
 2520    ).
 2521path_negated_property_set(PathNegatedPropertySet) -->
 2522    path_one_in_property_set(PathNegatedPropertySet),
 2523    !.
 2524
 2525paths_in_property_set(P) -->
 2526    path_one_in_property_set(P1),
 2527    (   "|"
 2528    ->  skip_ws,
 2529        paths_in_property_set(P2),
 2530        { P=(P1;P2) }
 2531    ;   { P=P1 }
 2532    ).
 2533
 2534path_one_in_property_set(^(IRI)) -->
 2535    "^", !, skip_ws,
 2536    iri_ref_or_a(IRI).
 2537path_one_in_property_set(IRI) -->
 2538    iri_ref_or_a(IRI).
 2539
 2540iri_ref_or_a(IRI) -->
 2541    iri_ref(IRI).
 2542iri_ref_or_a(RdfType) -->
 2543    "a", !, skip_ws,
 2544    { rdf_equal(RdfType, rdf:type) }.
 triples_node(-Subj, -Triples, ?TriplesTail)//
 2549triples_node(Subj, Triples, Tail) -->
 2550    collection(Subj, Triples, Tail),
 2551    !.
 2552triples_node(Subj, Triples, Tail) -->
 2553    blank_node_property_list(Subj, Triples, Tail).
 blank_node_property_list(-Subj, -Triples, ?TriplesTail)//
 2557blank_node_property_list(Subj, Triples, Tail) -->
 2558    "[", skip_ws,
 2559    property_list_not_empty(List, Triples, T0),
 2560    "]", skip_ws,
 2561    { make_triples_same_subject(List, Subj, T0, Tail) }.
 triples_node_path(-Subj, -Triples, ?Tail)//
 2565triples_node_path(Subj, Triples, Tail) -->
 2566    collection_path(Subj, Triples, Tail),
 2567    !.
 2568triples_node_path(Subj, Triples, Tail) -->
 2569    blank_node_property_list_path(Subj, Triples, Tail).
 blank_node_property_list_path(-Subj, -Triples, ?TriplesTail)//
 2573blank_node_property_list_path(Subj, Triples, Tail) -->
 2574    "[", skip_ws,
 2575    property_list_path_not_empty(List, Triples, T0),
 2576    "]", skip_ws,
 2577    { make_triples_same_subject(List, Subj, T0, Tail) }.
 collection(-Subj, -Triples, ?Tail)//
 2581collection(collection([H|T]), Triples, Tail) -->
 2582    "(", skip_ws,
 2583    graph_node(H, Triples, T0),
 2584    graph_nodes(T, T0, Tail),
 2585    ")", skip_ws.
 collection_path(-Subj, -Triples, ?Tail)//
 2589collection_path(collection([H|T]), Triples, Tail) -->
 2590    "(", skip_ws,
 2591    (   graph_node_path(H, Triples, Tail0),
 2592        graph_nodes_path(T, Tail0, Tail),
 2593        ")"
 2594    ->  skip_ws
 2595    ;   syntax_error(graph_node_path_expected)
 2596    ).
 2597
 2598
 2599graph_nodes([H|T], Triples, Tail) -->
 2600    graph_node(H, Triples, T0),
 2601    !,
 2602    graph_nodes(T, T0, Tail).
 2603graph_nodes([], T, T) --> [].
 2604
 2605graph_nodes_path([H|T], Triples, Tail) -->
 2606    graph_node_path(H, Triples, T0),
 2607    !,
 2608    graph_nodes_path(T, T0, Tail).
 2609graph_nodes_path([], T, T) --> [].
 graph_node(E, -Triples, ?TriplesTail)//
 2613graph_node(E, T, T)       --> var_or_term(E), !.
 2614graph_node(E, Triples, T) --> triples_node(E, Triples, T).
 graph_node_path(Node, Triples, Tail)//
 2618graph_node_path(E, T, T)          --> var_or_term(E), !.
 2619graph_node_path(E, Triples, Tail) --> triples_node_path(E, Triples, Tail).
 var_or_term(-E)//
 2623var_or_term(E) --> var(E), !.
 2624var_or_term(E) --> graph_term(E).
 var_or_iri_ref(-E)//
 2628var_or_iri_ref(E) --> var(E), !.
 2629var_or_iri_ref(E) --> iri_ref(E), !.
 var(-Var)//
 2633var(var(Name)) -->
 2634    (   var1(Name)
 2635    ->  []
 2636    ;   var2(Name)
 2637    ).
 2638
 2639must_see_var(Var) -->
 2640    var(Var),
 2641    !.
 2642must_see_var(_) -->
 2643    syntax_error(var_expected).
 2644
 2645must_see_var_or_iri_ref(Var) -->
 2646    var_or_iri_ref(Var),
 2647    !.
 2648must_see_var_or_iri_ref(_) -->
 2649    syntax_error(var_or_iri_ref_expected).
 graph_term(-T)//
 2653graph_term(T)    --> iri_ref(T), !.
 2654graph_term(T)    --> rdf_literal(T), !.
 2655graph_term(T)    --> numeric_literal(T), !.
 2656graph_term(T)    --> boolean_literal(T), !.
 2657graph_term(T)    --> blank_node(T).
 2658graph_term(T)    --> nil(T).
 expression(-E)//
 2663expression(E) -->
 2664    conditional_or_expression(E),
 2665    skip_ws.
 2666
 2667must_see_expression(E) -->
 2668    expression(E),
 2669    !.
 2670must_see_expression(_) -->
 2671    syntax_error(expression_expected).
 conditional_or_expression(-E)//
 2675conditional_or_expression(E) -->
 2676    conditional_and_expression(E0),
 2677    or_args(E0, E).
 2678
 2679or_args(E0, or(E0,E)) --> "||", !, skip_ws, value_logical(E1), or_args(E1, E).
 2680or_args(E, E) --> [].
 conditional_and_expression(-E)//
 2684conditional_and_expression(E) -->
 2685    value_logical(E0),
 2686    and_args(E0, E).
 2687
 2688and_args(E0, and(E0,E)) --> "&&", !, skip_ws, value_logical(E1), and_args(E1, E).
 2689and_args(E, E) --> [].
 value_logical(-E)//
 2694value_logical(E) --> relational_expression(E).
 relational_expression(E)//
 2698relational_expression(E) -->
 2699    numeric_expression(E0),
 2700    (   relational_op(Op)
 2701    ->  skip_ws,
 2702        numeric_expression(E1),
 2703        { E =.. [Op,E0,E1] }
 2704    ;   keyword("in")
 2705    ->  expression_list(List),
 2706        { E = in(E0, List) }
 2707    ;   keyword("not"), keyword("in")
 2708    ->  expression_list(List),
 2709        { E = not_in(E0, List) }
 2710    ;   { E = E0 }
 2711    ).
 2712
 2713relational_op(=) --> "=".
 2714relational_op(\=) --> "!=".
 2715relational_op(>=) --> ">=".
 2716relational_op(>) --> ">".
 2717relational_op(Op) -->
 2718    "<", \+ (iri_codes(_), ">"),
 2719    (   "="
 2720    ->  { Op = (=<) }
 2721    ;   { Op = (<) }
 2722    ).
 numeric_expression(-E)//
 2726numeric_expression(E) -->
 2727    additive_expression(E).
 additive_expression(-E)//
 2731additive_expression(E) -->
 2732    multiplicative_expression(E0),
 2733    add_args(E0, E).
 2734
 2735add_args(E0, E0+E) --> "+", !, skip_ws,
 2736    multiplicative_expression(E1), add_args(E1, E).
 2737add_args(E0, E0-E) --> "-", !, skip_ws,
 2738    multiplicative_expression(E1), add_args(E1, E).
 2739add_args(E, E) --> [].
 multiplicative_expression(-E)//
 2745multiplicative_expression(E) -->
 2746    unary_expression(E0),
 2747    mult_args(E0, E).
 2748
 2749mult_args(E0, E0*E) --> "*", !, skip_ws,
 2750    unary_expression(E1), mult_args(E1, E).
 2751mult_args(E0, E0/E) --> "/", !, skip_ws,
 2752    unary_expression(E1), mult_args(E1, E).
 2753mult_args(E, E) --> [].
 unary_expression(-E)//
 2758unary_expression(not(E)) --> "!", skip_ws, primary_expression(E).
 2759unary_expression(+(E))   --> "+", skip_ws, primary_expression(E).
 2760unary_expression(-(E))   --> "-", skip_ws, primary_expression(E).
 2761unary_expression(E)      -->             primary_expression(E).
 primary_expression(-E)//
 2766primary_expression(E) --> bracketted_expression(E), !.
 2767primary_expression(E) --> built_in_call(E), !.
 2768primary_expression(E) --> iri_ref_or_function(E), !.
 2769primary_expression(E) --> rdf_literal(E), !.
 2770primary_expression(E) --> numeric_literal(E), !.
 2771primary_expression(E) --> boolean_literal(E), !.
 2772primary_expression(E) --> var(E), !.
 bracketted_expression(-E)//
 2777bracketted_expression(E) -->
 2778    "(", skip_ws, must_see_expression(E), ")", skip_ws.
 built_in_call(-Call)//
 2782built_in_call(F) -->                    % [121]
 2783    get_keyword(KWD),
 2784    built_in_call(KWD, F).
 2785
 2786built_in_call(KWD, F) -->
 2787    { built_in_function(KWD, Types) },
 2788    must_see_open_bracket,
 2789    arg_list(Types, Args),
 2790    must_see_close_bracket,
 2791    !,
 2792    {   Args == []
 2793    ->  F = built_in(KWD)
 2794    ;   F =.. [KWD|Args]
 2795    }.
 2796built_in_call(KWD, F) -->
 2797    aggregate_call(KWD, F),
 2798    !.
 2799built_in_call(coalesce, coalesce(List)) -->
 2800    !,
 2801    expression_list(List).
 2802built_in_call(concat, concat(List)) -->
 2803    !,
 2804    expression_list(List).
 2805built_in_call(substr, Substr) -->
 2806    !,
 2807    substring_expression(Substr).
 2808built_in_call(replace, Replace) -->
 2809    !,
 2810    str_replace_expression(Replace).
 2811built_in_call(regex, Regex) -->
 2812    !,
 2813    regex_expression(Regex).
 2814built_in_call(exists, F) -->
 2815    !,
 2816    exists_func(F).
 2817built_in_call(not, F) -->
 2818    not_exists_func(F).
 2819
 2820built_in_function(str,            [expression]).
 2821built_in_function(lang,           [expression]).
 2822built_in_function(langmatches,    [expression, expression]).
 2823built_in_function(datatype,       [expression]).
 2824built_in_function(bound,          [var]).
 2825built_in_function(iri,            [expression]).
 2826built_in_function(uri,            [expression]).
 2827built_in_function(bnode,          [expression]).
 2828built_in_function(bnode,          []).
 2829built_in_function(rand,           []).
 2830built_in_function(abs,            [expression]).
 2831built_in_function(ceil,           [expression]).
 2832built_in_function(floor,          [expression]).
 2833built_in_function(round,          [expression]).
 2834built_in_function(strlen,         [expression]).
 2835built_in_function(ucase,          [expression]).
 2836built_in_function(lcase,          [expression]).
 2837built_in_function(encode_for_uri, [expression]).
 2838built_in_function(contains,       [expression, expression]).
 2839built_in_function(strstarts,      [expression, expression]).
 2840built_in_function(strends,        [expression, expression]).
 2841built_in_function(strbefore,      [expression, expression]).
 2842built_in_function(strafter,       [expression, expression]).
 2843built_in_function(year,           [expression]).
 2844built_in_function(month,          [expression]).
 2845built_in_function(day,            [expression]).
 2846built_in_function(hours,          [expression]).
 2847built_in_function(minutes,        [expression]).
 2848built_in_function(seconds,        [expression]).
 2849built_in_function(timezone,       [expression]).
 2850built_in_function(tz,             [expression]).
 2851built_in_function(now,            []).
 2852built_in_function(uuid,           []).
 2853built_in_function(struuid,        []).
 2854built_in_function(md5,            [expression]).
 2855built_in_function(sha1,           [expression]).
 2856built_in_function(sha256,         [expression]).
 2857built_in_function(sha384,         [expression]).
 2858built_in_function(sha512,         [expression]).
 2859built_in_function(coalesce,       [expression_list]).
 2860built_in_function(if,             [expression, expression, expression]).
 2861built_in_function(strlang,        [expression, expression]).
 2862built_in_function(strdt,          [expression, expression]).
 2863built_in_function(sameterm,       [expression, expression]).
 2864built_in_function(isiri,          [expression]).
 2865built_in_function(isuri,          [expression]).
 2866built_in_function(isblank,        [expression]).
 2867built_in_function(isliteral,      [expression]).
 2868built_in_function(isnumeric,      [expression]).
 2869
 2870term_expansion(built_in_function(f), Clauses) :-
 2871    findall(built_in_function(F),
 2872            ( built_in_function(Name, Args),
 2873              length(Args, Argc),
 2874              functor(F, Name, Argc)
 2875            ),
 2876            Clauses).
 built_in_function(?Term) is nondet
Fact that describes defined builtin functions. Used by resolve_expression/4.
 2883built_in_function(regex(_,_,_)).
 2884built_in_function(replace(_,_,_,_)).
 2885built_in_function(substr(_,_,_)).
 2886built_in_function(substr(_,_)).
 2887built_in_function(f).
 2888
 2889
 2890arg_list([], []) --> "".
 2891arg_list([HT|TT], [HA|TA]) -->
 2892    arg(HT, HA),
 2893    arg_list_cont(TT, TA).
 2894
 2895arg_list_cont([], []) -->
 2896    [].
 2897arg_list_cont([H|T], [A|AT]) -->
 2898    ",", skip_ws,
 2899    arg(H, A),
 2900    arg_list_cont(T, AT).
 2901
 2902arg(expression, A) --> expression(A).
 2903arg(var,        A) --> var(A).
 regex_expression(-Regex)//
 2907regex_expression(regex(Target, Pattern, Flags)) -->
 2908    must_see_open_bracket,
 2909    must_see_expression(Target),
 2910    must_see_comma,
 2911    must_see_expression(Pattern),
 2912    (   ",", skip_ws, must_see_expression(Flags)
 2913    ->  []
 2914    ;   {Flags = literal('')}
 2915    ),
 2916    must_see_close_bracket.
 substring_expression(Expr)//
 2920substring_expression(Expr) --> % [123]
 2921    must_see_open_bracket,
 2922    must_see_expression(Source),
 2923    must_see_comma,
 2924    must_see_expression(StartingLoc),
 2925    (   ","
 2926    ->  skip_ws,
 2927        must_see_expression(Length),
 2928        { Expr = substr(Source, StartingLoc, Length) }
 2929    ;   { Expr = substr(Source, StartingLoc) }
 2930    ),
 2931    must_see_close_bracket.
 must_see_comma// is det
 must_see_open_bracket// is det
 must_see_close_bracket// is det
 must_see_punct(+C)// is det
Demand punctuation. Throw a syntax error if the demanded punctiation is not present.
 2941must_see_comma         --> must_see_punct(0',).
 2942must_see_open_bracket  --> must_see_punct(0'().
 2943must_see_close_bracket --> must_see_punct(0')).
 2944must_see_open_brace    --> must_see_punct(0'{).
 2945must_see_close_brace   --> must_see_punct(0'}).
 2946
 2947must_see_punct(C) -->
 2948    [C], !, skip_ws.
 2949must_see_punct(C) -->
 2950    { char_code(Char, C) },
 2951    syntax_error(expected(Char)).
 str_replace_expression(Expr)//
 2956str_replace_expression(replace(Arg, Pattern, Replacement, Flags)) --> % [124]
 2957    must_see_open_bracket,
 2958    must_see_expression(Arg),
 2959    must_see_comma,
 2960    must_see_expression(Pattern),
 2961    must_see_comma,
 2962    must_see_expression(Replacement),
 2963    (   ",", skip_ws, must_see_expression(Flags)
 2964        ->  []
 2965        ;   {Flags = literal('')}
 2966    ),
 2967    must_see_close_bracket.
 exists_func(F)//
 2971exists_func(exists(Pattern)) -->        % [125]
 2972    must_see_group_graph_pattern(Pattern).
 2973
 2974not_exists_func(not_exists(Pattern)) --> % [126]
 2975    keyword("exists"),
 2976    must_see_group_graph_pattern(Pattern).
 aggregate_call(+Keyword, -Aggregate)//
Renamed from aggregate to avoid confusion with popular predicate.
 2982aggregate_call(count, Aggregate) -->            % [127]
 2983    aggregate_count(Aggregate),
 2984    !.
 2985aggregate_call(Agg, Aggregate) -->
 2986    { aggregate_keyword(Agg) },
 2987    !,
 2988    must_see_open_bracket,
 2989    { Aggregate =.. [Agg,AggArg] },
 2990    optional_distinct(AggArg, AggExpr),
 2991    expression(AggExpr),
 2992    must_see_close_bracket.
 2993aggregate_call(group_concat, Aggregate) -->
 2994    aggregate_group_concat(Aggregate).
 2995
 2996aggregate_keyword(sum).
 2997aggregate_keyword(min).
 2998aggregate_keyword(max).
 2999aggregate_keyword(avg).
 3000aggregate_keyword(sample).
 3001
 3002aggregate_count(count(Count)) -->
 3003    must_see_open_bracket,
 3004    optional_distinct(Count, C1),
 3005    (   "*"
 3006        ->  skip_ws,
 3007        { C1 = (*) }
 3008        ;   expression(C1)
 3009    ),
 3010    must_see_close_bracket.
 3011
 3012
 3013aggregate_group_concat(group_concat(Expr, literal(Sep))) -->
 3014    must_see_open_bracket,
 3015    optional_distinct(Expr, Expr2),
 3016    expression(Expr2),
 3017    (   ";"
 3018    ->  skip_ws,
 3019        must_see_keyword("separator"),
 3020        must_see_punct(0'=),
 3021        string(Sep)
 3022    ;   {Sep = ' '}                 % default sep is a single space
 3023    ),
 3024    must_see_close_bracket.
 aggregate_op(?Op) is nondet
Declaration to support resolving aggregates
 3030aggregate_op(count(_)).
 3031aggregate_op(sum(_)).
 3032aggregate_op(min(_)).
 3033aggregate_op(max(_)).
 3034aggregate_op(avg(_)).
 3035aggregate_op(sample(_)).
 3036aggregate_op(group_concat(_,_)).
 iri_ref_or_function(-Term)//
 3040iri_ref_or_function(Term) -->
 3041    iri_ref(IRI),
 3042    (   arg_list(Args)
 3043    ->  { Term = function(IRI, Args) }
 3044    ;   { Term = IRI }
 3045    ).
 rdf_literal(-Literal)//
 3049rdf_literal(literal(Value)) -->
 3050    string(String),
 3051    (   langtag(Lang)
 3052    ->  { Value = lang(Lang, String) }
 3053    ;   "^^", iri_ref(IRI)
 3054    ->  { Value = type(IRI, String) }
 3055    ;   { Value = String }
 3056    ),
 3057    skip_ws.
 numeric_literal(-Number)//
Match a literal value and return it as a term
literal(type(Type, Atom))

Where Type is one of xsd:double, xsd:decimal or xsd:integer and Atom is the matched text. The value cannot always be obtained using atom_number/2 because floats and decimals can start or end with a '.', something which is not allowed in Prolog.

 3070numeric_literal(literal(type(Type, Value))) -->
 3071    optional_pm(Codes, CV),
 3072    (   double_string(CV)
 3073    ->  { rdf_equal(xsd:double, Type) }
 3074    ;   decimal_string(CV)
 3075    ->  { rdf_equal(xsd:decimal, Type) }
 3076    ;   integer_string(CV)
 3077    ->  { rdf_equal(xsd:integer, Type) }
 3078    ),
 3079    !,
 3080    { atom_codes(Value, Codes)
 3081    },
 3082    skip_ws.
 boolean_literal(-TrueOrFalse)//
 3086boolean_literal(Lit) -->
 3087    (   keyword("true")
 3088    ->  { Lit = boolean(true) }
 3089    ;   keyword("false")
 3090    ->  { Lit = boolean(false) }
 3091    ).
 string(-Atom)//
 3095string(Atom) --> string_literal_long1(Atom), !.
 3096string(Atom) --> string_literal_long2(Atom), !.
 3097string(Atom) --> string_literal1(Atom), !.
 3098string(Atom) --> string_literal2(Atom).
 iri_ref(IRI)//
 3102iri_ref(IRI) -->
 3103    q_iri_ref(IRI).
 3104iri_ref(IRI) -->
 3105    qname(IRI).                     % TBD: qname_ns also returns atom!?
 3106
 3107must_see_iri(IRI) -->
 3108    iri_ref(IRI),
 3109    !.
 3110must_see_iri(_) -->
 3111    syntax_error(iri_expected).
 qname(-Term)//
TBD: Looks like this is ambiguous!?
 3117qname(Term) -->
 3118    'QNAME'(Term), !, skip_ws.
 3119qname(Q:'') -->
 3120    qname_ns(Q).
 blank_node(-Id)//
Blank node. Anonymous blank nodes are returned with unbound Id
 3126blank_node(Id) -->
 3127    blank_node_label(Id),
 3128    !.
 3129blank_node(Id) -->
 3130    anon(Id).
 3131
 3132                 /*******************************
 3133                 *             BASICS           *
 3134                 *******************************/
 q_iri_ref(-Atom)//
 3138q_iri_ref(Atom) -->
 3139    "<",
 3140    (    q_iri_ref_codes(Codes), ">"
 3141    ->   skip_ws,
 3142         { atom_codes(Atom, Codes) }
 3143    ;    syntax_error(illegal_qualified_iri)
 3144    ).
 3145
 3146q_iri_ref_codes([]) -->
 3147    [].
 3148q_iri_ref_codes([H|T]) -->
 3149    iri_code(H),
 3150    !,
 3151    q_iri_ref_codes(T).
 3152q_iri_ref_codes(_) -->
 3153    syntax_error(illegal_code_in_iri).
 3154
 3155iri_codes([H|T]) -->
 3156    iri_code(H),
 3157    !,
 3158    iri_codes(T).
 3159iri_codes([]) -->
 3160    [].
 3161
 3162iri_code(Code) -->
 3163    [Code],
 3164    { \+ not_iri_code(Code) },
 3165    !.
 3166
 3167not_iri_code(0'<).
 3168not_iri_code(0'>).
 3169not_iri_code(0'').
 3170not_iri_code(0'{).
 3171not_iri_code(0'}).
 3172not_iri_code(0'|).
 3173not_iri_code(0'\\).                     % not sure!?
 3174not_iri_code(0'`).
 3175not_iri_code(Code) :- between(0x00, 0x20, Code).
 qname_ns(Q)//
 3180qname_ns(Q) -->
 3181    ncname_prefix(Q), ":", !, skip_ws.
 3182qname_ns('') -->
 3183    ":", skip_ws.
 3184
 3185%       'QNAME'(-Term)//
 3186%
 3187%       Qualified name.  Term is one of Q:N or '':N
 3188
 3189'QNAME'(Q:N) -->
 3190    ncname_prefix(Q), ":", !, pn_local(N).
 3191'QNAME'('':N) -->
 3192    ":", pn_local(N).
 blank_node_label(-Bnode)// is semidet
Processes "_:..." into a bnode(Name) term.
 3199blank_node_label(bnode(Name)) -->
 3200    "_:", pn_local(Name), skip_ws.
 var1(-Atom)// is semidet
 var2(-Atom)// is semidet
 3206var1(Name) --> "?", varname(Name).
 3207var2(Name) --> "$", varname(Name).
 langtag(-Tag)//
Return language tag (without leading @)
 3214langtag(Atom) -->
 3215    "@",
 3216    one_or_more_ascii_letters(Codes, T0),
 3217    sub_lang_ids(T0, []),
 3218    skip_ws,
 3219    { atom_codes(Atom, Codes) }.
 3220
 3221sub_lang_ids([0'-|Codes], Tail) -->
 3222    "-",
 3223    !,
 3224    one_or_more_ascii_letter_or_digits(Codes, T0),
 3225    sub_lang_ids(T0, Tail).
 3226sub_lang_ids(T, T) -->
 3227    [].
 integer(-Integer)// is semidet
Match an integer and return its value.
 3234integer(Integer) -->
 3235    integer_string(Codes),
 3236    { number_codes(Integer, Codes)
 3237    },
 3238    skip_ws.
 integer_string(-Codes)// is semidet
Extract integer value.
 3245integer_string(Codes) -->
 3246    one_or_more_digits(Codes, []),
 3247    !.
 decimal_string(-Codes)//
Extract float without exponent and return the matched text as a list of codes.
 3254decimal_string(Codes) -->
 3255    one_or_more_digits(Codes, T0),
 3256    !,
 3257    dot(T0, T1),
 3258    digits(T1, []).
 3259decimal_string(Codes) -->
 3260    dot(Codes, T1),
 3261    one_or_more_digits(T1, []).
 double_string(-Codes)// is semidet
Extract a float number with exponent and return the result as a list of codes.
 3269double_string(Codes) -->
 3270    one_or_more_digits(Codes, T0),
 3271    !,
 3272    dot(T0, T1),
 3273    digits(T1, T2),
 3274    exponent(T2, []).
 3275double_string(Codes) -->
 3276    dot(Codes, T1),
 3277    one_or_more_digits(T1, T2),
 3278    !,
 3279    exponent(T2, []).
 3280double_string(Codes) -->
 3281    one_or_more_digits(Codes, T2),
 3282    !,
 3283    exponent(T2, []).
 3284
 3285dot([0'.|T], T) --> ".".                % 0'
 exponent(-Codes, ?Tail)//
Float exponent. Returned as difference-list
 3292exponent(Codes, T) -->
 3293    optional_e(Codes, T0),
 3294    optional_pm(T0, T1),
 3295    one_or_more_digits(T1, T).
 3296
 3297optional_e([0'e|T], T) -->
 3298    (   "e"
 3299    ;   "E"
 3300    ),
 3301    !.
 3302optional_e(T, T) -->
 3303    "".
 3304
 3305optional_pm([C|T], T) -->
 3306    [C],
 3307    { C == 0'+ ; C == 0'- },
 3308    !.
 3309optional_pm(T, T) -->
 3310    "".
 string_literal1(-Atom)//
 3314string_literal1(Atom) -->
 3315    "'",
 3316    !,
 3317    string_literal_codes(Codes),
 3318    "'",
 3319    !,
 3320    { atom_codes(Atom, Codes) }.
 string_literal2(-Atom)//
 3324string_literal2(Atom) -->
 3325    "\"",
 3326    !,
 3327    string_literal_codes(Codes),
 3328    "\"",
 3329    !,
 3330    { atom_codes(Atom, Codes) }.
 3331
 3332string_literal_codes([]) -->
 3333    "".
 3334string_literal_codes([H|T]) -->
 3335    (   echar(H)
 3336    ;   [H], { \+ not_in_string_literal(H) }
 3337    ),
 3338    string_literal_codes(T).
 3339
 3340not_in_string_literal(0x5C).
 3341not_in_string_literal(0x0A).
 3342not_in_string_literal(0x0D).
 string_literal_long1(-Atom)//
 3346string_literal_long1(Atom) -->
 3347    "'''",
 3348    !,
 3349    string_literal_codes_long(Codes),
 3350    "'''",
 3351    !,
 3352    { atom_codes(Atom, Codes) }.
 string_literal_long2(-Atom)//
 3356string_literal_long2(Atom) -->
 3357    "\"\"\"",
 3358    !,
 3359    string_literal_codes_long(Codes),
 3360    "\"\"\"",
 3361    !,
 3362    { atom_codes(Atom, Codes) }.
 3363
 3364string_literal_codes_long([]) -->
 3365    "".
 3366string_literal_codes_long([H|T]) -->
 3367    (   echar(H)
 3368    ;   [H], { H \== 0'\\ }
 3369    ),
 3370    string_literal_codes_long(T).
 echar(-Code)//
Escaped character
 3377echar(Code) -->
 3378    "\\", echar2(Code).
 3379
 3380echar2(0'\t) --> "t".
 3381echar2(0'\b) --> "b".
 3382echar2(0'\n) --> "n".
 3383echar2(0'\r) --> "r".
 3384echar2(0'\f) --> "f".
 3385echar2(0'\\) --> "\\".
 3386echar2(0'")  --> "\"".
 3387echar2(0'')  --> "'".
 hex(-Weigth)//
HEX digit (returning numeric value)
 3393hex(Weigth) -->
 3394    [C],
 3395    { code_type(C, xdigit(Weigth)) }.
 nil(-NIL)//
End-of-collection (rdf:nil)
 3402nil(NIL) --> "(", ws_star, ")", skip_ws, { rdf_equal(NIL, rdf:nil) }.
 3403
 3404%       ws//
 3405%
 3406%       white space characters.
 3407
 3408ws --> [0x20].
 3409ws --> [0x09].
 3410ws --> [0x0D].
 3411ws --> [0x0A].
 3412
 3413%       ws_star//
 3414
 3415ws_star --> ws, !, ws_star.
 3416ws_star --> "".
 3417
 3418%       anon//
 3419%
 3420%       Anonymous resource
 3421
 3422anon(bnode(_)) --> "[", ws_star, "]", skip_ws.
 pn_chars_base(-Code)//
Basic identifier characters
 3429pn_chars_base(Code) -->
 3430    esc_code(Code),
 3431    { pn_chars_base(Code) },
 3432    !.
 3433
 3434pn_chars_base(Code) :- between(0'A, 0'Z, Code).
 3435pn_chars_base(Code) :- between(0'a, 0'z, Code).
 3436pn_chars_base(Code) :- between(0x00C0, 0x00D6, Code).
 3437pn_chars_base(Code) :- between(0x00D8, 0x00F6, Code).
 3438pn_chars_base(Code) :- between(0x00F8, 0x02FF, Code).
 3439pn_chars_base(Code) :- between(0x0370, 0x037D, Code).
 3440pn_chars_base(Code) :- between(0x037F, 0x1FFF, Code).
 3441pn_chars_base(Code) :- between(0x200C, 0x200D, Code).
 3442pn_chars_base(Code) :- between(0x2070, 0x218F, Code).
 3443pn_chars_base(Code) :- between(0x2C00, 0x2FEF, Code).
 3444pn_chars_base(Code) :- between(0x3001, 0xD7FF, Code).
 3445pn_chars_base(Code) :- between(0xF900, 0xFDCF, Code).
 3446pn_chars_base(Code) :- between(0xFDF0, 0xFFFD, Code).
 3447pn_chars_base(Code) :- between(0x10000, 0xEFFFF, Code).
 3448
 3449esc_code(Code) -->
 3450    [ Code ].
 pn_chars_u(?Code)
Allows for _
 3456pn_chars_u(Code) :-
 3457    pn_chars_base(Code).
 3458pn_chars_u(0'_).
 varname(-Atom)//
Name of a variable (after the ? or $)
 3465varname(Atom) -->
 3466    varchar1(C0),
 3467    varchars(Cs),
 3468    { atom_codes(Atom, [C0|Cs]) },
 3469    skip_ws.
 3470
 3471varchar1(Code) -->
 3472    esc_code(Code),
 3473    { varchar1(Code) }.
 3474
 3475varchar1(Code) :-
 3476    pn_chars_u(Code),
 3477    !.
 3478varchar1(Code) :-
 3479    between(0'0, 0'9, Code),
 3480    !.
 3481
 3482varchars([H|T]) -->
 3483    varchar(H),
 3484    !,
 3485    varchars(T).
 3486varchars([]) -->
 3487    [].
 3488
 3489varchar(Code) -->
 3490    esc_code(Code),
 3491    { varchar(Code) }.
 3492
 3493varchar(Code) :-
 3494    varchar1(Code),
 3495    !.
 3496varchar(Code) :-
 3497    varchar_extra(Code),
 3498    !.
 3499
 3500varchar_extra(0x00B7).
 3501varchar_extra(Code) :- between(0x0300, 0x036F, Code).
 3502varchar_extra(Code) :- between(0x203F, 0x2040, Code).
 3503
 3504ncchar(Code) :-
 3505    varchar(Code),
 3506    !.
 3507ncchar(0'-).
 ncname_prefix(-Atom)//
 3511ncname_prefix(Atom) -->
 3512    pn_chars_base(C0),
 3513    (   ncname_prefix_suffix(Cs)
 3514    ->  { atom_codes(Atom, [C0|Cs]) }
 3515    ;   { char_code(Atom, C0) }
 3516    ).
 3517
 3518ncname_prefix_suffix(Codes) -->
 3519    ncchar_or_dots(Codes, []),
 3520    { \+ last(Codes, 0'.) },
 3521    !.
 3522
 3523ncchar_or_dots([H|T0], T) -->
 3524    ncchar_or_dot(H),
 3525    ncchar_or_dots(T0, T).
 3526ncchar_or_dots(T, T) -->
 3527    [].
 3528
 3529ncchar_or_dot(Code) -->
 3530    esc_code(Code),
 3531    { ncchar_or_dot(Code) }.
 3532
 3533ncchar_or_dot(Code) :-
 3534    ncchar(Code),
 3535    !.
 3536ncchar_or_dot(0'.).
 pn_local(-Atom)//
 3540pn_local(Atom) -->                      % [169]
 3541    localchar1(Codes, Tail),
 3542    pn_local_suffix(Tail),
 3543    { atom_codes(Atom, Codes) }.
 3544
 3545pn_local_suffix(Codes) -->
 3546    pnchars(Codes, Tail),
 3547    pnchar_last(Tail, []),
 3548    !.
 3549pn_local_suffix([]) -->
 3550    "".
 3551
 3552pnchars(List, Tail) -->
 3553    pnchar(List, Tail0),
 3554    pnchars(Tail0, Tail).
 3555pnchars(T, T) --> "".
 3556
 3557pnchar([C|T], T) -->
 3558    [C],
 3559    { pnchar(C) },
 3560    !.
 3561pnchar(Codes, Tail) -->
 3562    plx(Codes, Tail).
 3563
 3564pnchar(C) :- varchar(C).
 3565pnchar(0'-).
 3566pnchar(0'.).
 3567pnchar(0':).
 3568
 3569pnchar_last([C|T], T) -->
 3570    [C],
 3571    { pnchar_last(C) },
 3572    !.
 3573pnchar_last(Codes, Tail) -->
 3574    plx(Codes, Tail).
 3575
 3576pnchar_last(C) :- varchar(C).
 3577pnchar_last(0':).
 3578
 3579
 3580localchar1([Code|Tail], Tail) -->
 3581    esc_code(Code),
 3582    { localchar1(Code) },
 3583    !.
 3584localchar1(Codes, Tail) -->
 3585    plx(Codes, Tail).
 3586
 3587plx(Codes, Tail) -->
 3588    percent(Codes, Tail).
 3589plx(Codes, Tail) -->
 3590    pn_local_esc(Codes, Tail).
 3591
 3592percent(Codes, Tail) -->                % [171]
 3593    "%", [H1,H2],
 3594    { code_type(H1, xdigit(_)),
 3595      code_type(H2, xdigit(_)),
 3596      Codes = [0'%,H1,H2|Tail]
 3597    }.
 3598
 3599localchar1(Code) :-
 3600    pn_chars_u(Code),
 3601    !.
 3602localchar1(Code) :-
 3603    between(0'0, 0'9, Code),
 3604    !.
 3605localchar1(0':).
 3606
 3607pn_local_esc(List, T) -->               % [173]
 3608    "\\",
 3609    [C],
 3610    { pn_local_esc(C),
 3611      List = [C|T]
 3612    }.
 3613
 3614pnle('_~.-!$&\'()*+,;=/?#@%').
 3615
 3616term_expansion(pn_local_esc(esc), Clauses) :-
 3617    pnle(Atom),
 3618    findall(pn_local_esc(C),
 3619            ( sub_atom(Atom, _, 1, _, Char),
 3620              char_code(Char, C)
 3621            ), Clauses).
 3622
 3623pn_local_esc(esc).
 3624
 3625
 3626
 3627                 /*******************************
 3628                 *            EXTRAS            *
 3629                 *******************************/
 3630
 3631digit(Code) -->
 3632    [Code],
 3633    { between(0'0, 0'9, Code) }.
 3634
 3635ascii_letter(Code) -->
 3636    [Code],
 3637    { between(0'a, 0'z, Code)
 3638    ; between(0'A, 0'Z, Code)
 3639    },
 3640    !.
 3641
 3642ascii_letter_or_digit(Code) -->
 3643    [Code],
 3644    { between(0'a, 0'z, Code)
 3645    ; between(0'A, 0'Z, Code)
 3646    ; between(0'0, 0'9, Code)
 3647    },
 3648    !.
 3649
 3650digits([H|T0], T) -->
 3651    digit(H),
 3652    !,
 3653    digits(T0, T).
 3654digits(T, T) -->
 3655    [].
 3656
 3657ascii_letters([H|T0], T) -->
 3658    ascii_letter(H),
 3659    !,
 3660    ascii_letters(T0, T).
 3661ascii_letters(T, T) -->
 3662    [].
 3663
 3664ascii_letter_or_digits([H|T0], T) -->
 3665    ascii_letter_or_digit(H),
 3666    !,
 3667    ascii_letter_or_digits(T0, T).
 3668ascii_letter_or_digits(T, T) -->
 3669    [].
 3670
 3671one_or_more_digits([C0|CT], Tail) -->
 3672    digit(C0),
 3673    digits(CT, Tail).
 3674
 3675one_or_more_ascii_letters([C0|CT], Tail) -->
 3676    ascii_letter(C0),
 3677    ascii_letters(CT, Tail).
 3678
 3679one_or_more_ascii_letter_or_digits([C0|CT], Tail) -->
 3680    ascii_letter_or_digit(C0),
 3681    ascii_letter_or_digits(CT, Tail).
 keyword(+Codes)
Case-insensitive match for a keyword.
 3687keyword([]) -->
 3688    (  ascii_letter(_)
 3689    -> !, {fail}
 3690    ;  skip_ws
 3691    ).
 3692keyword([H|T]) -->
 3693    [C],
 3694    { code_type(H, to_lower(C)) },
 3695    keyword(T).
 must_see_keyword(+Codes)
 3699must_see_keyword(Codes) -->
 3700    keyword(Codes),
 3701    !.
 3702must_see_keyword(Codes) -->
 3703    { atom_codes(Atom, Codes),
 3704      upcase_atom(Atom, Keyword)
 3705    },
 3706    syntax_error(expected(Keyword)).
 get_keyword(-Atom)
Get next identifier as lowercase
 3713get_keyword(Atom) -->
 3714    one_or_more_keyword_chars(Letters),
 3715    { atom_codes(Raw, Letters),
 3716      downcase_atom(Raw, Atom)
 3717    },
 3718    skip_ws.
 3719
 3720one_or_more_keyword_chars([H|T]) -->
 3721    keyword_char(H),
 3722    keyword_chars(T).
 3723
 3724keyword_chars([H|T]) -->
 3725    keyword_char(H),
 3726    !,
 3727    keyword_chars(T).
 3728keyword_chars([]) --> "".
 3729
 3730keyword_char(C)   --> ascii_letter(C), !.
 3731keyword_char(C)   --> digit(C), !.
 3732keyword_char(0'_) --> "_".
 3733
 3734
 3735
 3736%       skip_ws//
 3737
 3738skip_ws -->
 3739    ws,
 3740    !,
 3741    skip_ws.
 3742skip_ws -->
 3743    "#",
 3744    !,
 3745    skip_comment,
 3746    skip_ws.
 3747skip_ws -->
 3748    [].
 3749
 3750skip_comment --> "\n", !.
 3751skip_comment --> "\r", !.
 3752skip_comment --> eos, !.
 3753skip_comment --> [_], skip_comment.
 3754
 3755eos([], []).
 3756
 3757peek(C, L, L) :-
 3758    L = [C|_]