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): 2007-2015, University of Amsterdam
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU Lesser General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(sparql_grammar,
   32	  [ sparql_parse/3		% +In, -Query, +Options
   33	  ]).   34:- use_module(library(pure_input)).   35:- use_module(library(semweb/rdf_db)).   36:- use_module(library(error), [must_be/2]).   37:- use_module(library(lists)).   38:- use_module(library(assoc)).   39:- use_module(library(uri)).   40:- use_module(library(option)).   41:- use_module(library(record)).   42:- use_module(jena_properties).   43:- use_module(text_properties).   44:- use_module(library(debug)).   45:- use_module(library(apply)).   46:- 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.
   67sparql_parse(Codes, Query, Options) :-
   68	is_list(Codes), !,
   69	(   phrase(sparql_query(Prolog, Query0), Codes)
   70	->  true
   71	;   syntax_error(unknown)
   72	),
   73	resolve_names(Prolog, Query0, Query, Options).
   74sparql_parse(Atomic, Query, Options) :-
   75	atomic(Atomic), !,
   76	atom_codes(Atomic, Codes),
   77	sparql_parse(Codes, Query, Options).
   78sparql_parse(Input, _, _) :-
   79	throw(error(type_error(text, Input), _)).
   80
   81
   82		 /*******************************
   83		 *	       ERRORS		*
   84		 *******************************/
   85
   86syntax_error(What) :-
   87	throw(error(syntax_error(sparql(What)), _)).
   88
   89add_error_location(error(syntax_error(What), Location),
   90		   Input) :-
   91	subsumes_term(end_of_file-CharCount, Location),
   92	end_of_file-CharCount = Location,
   93	length(After, CharCount),
   94	append(Before, After, Input),
   95	length(Before, BL),
   96	CLen = 80,
   97	atom_codes('...', Elipsis),
   98	atom_codes('\n**here**\n', Here),
   99	(   BL =< CLen
  100	->  BC = Before
  101	;   length(BC0, CLen),
  102	    append(_, BC0, Before),
  103	    append(Elipsis, BC0, BC)
  104	),
  105	length(After, AL),
  106	(   AL =< CLen
  107	->  AC = After
  108	;   length(AC0, CLen),
  109	    append(AC0, _, After),
  110	    append(AC0, Elipsis, AC)
  111	),
  112	append(Here, AC, HAC),
  113	append([0'\n|BC], HAC, ContextCodes),
  114	atom_codes(Context, ContextCodes), !,
  115	throw(error(syntax_error(sparql(What)),
  116		    context(_, Context))).
  117add_error_location(Error, _Input) :-
  118	throw(Error).
  119
  120:- multifile
  121	prolog:message//1,
  122	http:bad_request_error//2.  123
  124http:bad_request_error(syntax_error(sparql(_)), _).
  125
  126prolog:message(error(syntax_error(sparql(unknown)), _)) -->
  127	[ 'SPARQL: Unclassified syntax error in query'-[] ].
  128prolog:message(error(syntax_error(sparql(What)), context(_, Context))) -->
  129	[ 'SPARQL: syntax error: '-[] ],
  130	error_detail(What),
  131	(   { var(Context) }
  132	->  []
  133	;   { atomic_list_concat(Lines, '\n', Context) },
  134	    [ ' at', nl ],
  135	    lines(Lines)
  136	).
  137
  138error_detail(expected(What)) -->
  139	[ '"~w" expected'-[What] ].
  140error_detail(What) -->
  141	[ '~p'-[What] ].
  142
  143lines([]) --> [].
  144lines([H|T]) --> ['~w'-[H], nl], lines(T).
  145
  146
  147		 /*******************************
  148		 *	      RESOLVE		*
  149		 *******************************/
  150
  151:- record
  152	state(base_uri,
  153	      prefix_assoc,
  154	      prefixes_used=[],
  155	      var_assoc,
  156	      var_list=[],
  157	      graph=[],
  158	      filters=[],
  159	      aggregates=[]).
 resolve_names(+Prolog, +Query0, -Query, +Options)
Turn var(Name) into Prolog variables and resolve all IRIs to absolute IRIs.
  166resolve_names(Prolog, Q0, Q, Options) :-
  167	resolve_state(Prolog, State0, Options),
  168	resolve(Q0, Q, State0, _State).
  169
  170resolve(select(Proj0, DataSets0, Q0, Solutions0),
  171	select(Proj,  DataSets,  Q,  Solutions),
  172	State0, State) :-
  173	resolve_datasets(DataSets0, DataSets, State0),
  174	resolve_query(Q0, Q1, State0, State1),
  175	resolve_projection(Proj0, Proj, QExpr, State1, State2),
  176	resolve_solutions(Solutions0, Solutions, Q2, State2, State),
  177	mkconj(Q1, QExpr, Q12),
  178	mkconj(Q12, Q2, Q).
  179resolve(construct(Templ0, DataSets0, Q0, Solutions0),
  180	construct(Templ,  DataSets,  Q,  Solutions),
  181	State0, State) :-
  182	resolve_datasets(DataSets0, DataSets, State0),
  183	resolve_query(Q0, Q1, State0, State1),
  184	resolve_construct_template(Templ0, Templ, Q2, State1, State2),
  185	resolve_solutions(Solutions0, Solutions, Q3, State2, State),
  186	mkconj(Q1, Q2, Q12),
  187	mkconj(Q12, Q3, Q).
  188resolve(ask(DataSets0, Q0, Solutions0), ask(DataSets, Q, Solutions),
  189	State0, State) :-
  190	resolve_datasets(DataSets0, DataSets, State0),
  191	resolve_query(Q0, Q1, State0, State1),
  192	resolve_solutions(Solutions0, Solutions, Q2, State1, State),
  193	mkconj(Q1, Q2, Q).
  194resolve(describe(Proj0, DataSets0, Q0, Solutions0),
  195	describe(Proj,  DataSets,  Q,  Solutions),
  196	State0, State) :-
  197	resolve_datasets(DataSets0, DataSets, State0),
  198	resolve_query(Q0, Q1, State0, State1),
  199	resolve_projection(Proj0, Proj, QE, State1, State2),
  200	resolve_solutions(Solutions0, Solutions, Q2, State2, State),
  201	mkconj(Q1, QE, Q12),
  202	mkconj(Q12, Q2, Q).
  203resolve(update(Updates0), update(Updates), State0, State) :-
  204	resolve_updates(Updates0, Updates, State0, State).
 resolve_datasets(+Raw, -IRIs, +State)
TBD: what is the difference between named and non-named?
  210resolve_datasets([], [], _).
  211resolve_datasets([H0|T0], [H|T], S) :-
  212	resolve_dataset(H0, H, S),
  213	resolve_datasets(T0, T, S).
  214
  215resolve_dataset(T0, IRI, S) :-
  216	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.

  234resolve_query(List, Q, S0, S) :-
  235	is_list(List), !,
  236	list_to_conj(List, Q, S0, S).
  237resolve_query(group(G), Q, S0, S) :- !,
  238	state_filters(S0, FSave),
  239	set_filters_of_state([], S0, S1),
  240	resolve_query(G, Q0, S1, S2),
  241	state_filters(S2, Filters),
  242	set_filters_of_state(FSave, S2, S3),
  243	resolve_query(Filters, Q1, S3, S),
  244	mkconj(Q0, Q1, Q2),
  245	steadfast(Q2, Q).
  246resolve_query(service(Silent, VarOrIRI, G, QText),
  247	      sparql_service(Silent, Address, Prefixes, Vars, QText),
  248	      S0, S) :- !,
  249	resolve_graph_term(VarOrIRI, Address, true, S0, S0),
  250	assertion(Address \== '$null$'),	% Fresh variable
  251	service_state(S0, ServState0),
  252	resolve_query(G, _, ServState0, ServState),
  253	service_prefixes(ServState, Prefixes),
  254	state_var_list(ServState, Vars),
  255	resolve_service_vars(Vars, S0, S).
  256resolve_query((A0,minus(B0)), sparql_minus(A,B), S0, S) :- !,
  257	resolve_query(A0, A, S0, S1),
  258	resolve_query(B0, B, S1, S).
  259resolve_query((A0,B0), Q, S0, S) :- !,
  260	resolve_query(A0, A, S0, S1),
  261	resolve_query(B0, B, S1, S),
  262	mkconj(A, B, Q).
  263resolve_query((A0;B0), (A;B), S0, S) :- !,
  264	resolve_query(A0, A, S0, S1),
  265	resolve_query(B0, B, S1, S).
  266resolve_query(optional(true), true, S, S) :- !.
  267resolve_query(optional(Q0), (Q *-> true ; true), S0, S) :- !,
  268	resolve_query(Q0, Q, S0, S).
  269resolve_query(rdf(Subj0,P0,O0), Q, S0, S) :-
  270	resolve_iri(P0, P1, S0),
  271	atom(P1),
  272	sparql:current_functional_property(P1, P, _), !,
  273	resolve_graph_term(Subj0, Subj, Q1, S0, S1),
  274	(   nonvar(O0),
  275	    O0 = collection(ArgList0),
  276	    resolve_graph_terms(ArgList0, ArgList, Q2, S1, S)
  277	->  true
  278	;   resolve_graph_term(O0, Arg, Q2, S1, S),
  279	    ArgList = [Arg]
  280	),
  281	FP =.. [P|ArgList],
  282	length(ArgList, ArgCount),
  283	(   sparql:current_functional_property(P1, P, ArgCount)
  284	->  true
  285	;   throw(error(existence_error(functional_property, FP), _))
  286	),
  287	mkconj(Q1, Q2, Q12),
  288	FuncProp = sparql:functional_property(Subj, FP),
  289	mkconj(Q12, FuncProp, Q).
  290resolve_query(rdf(Subj,P,O), Q, S0, S) :- !,
  291	resolve_triple(Subj, P, O, Q, S0, S).
  292resolve_query(graph(G0, Q0), Q, S0, S) :- !,
  293	resolve_graph_term(G0, G, Q1, S0, S1),
  294	state_graph(S1, GL),
  295	set_graph_of_state([G|GL], S1, S2),
  296	resolve_query(Q0, Q2, S2, S3),
  297	mkconj(Q1, Q2, Q),
  298	set_graph_of_state(GL, S3, S).
  299resolve_query(Function, Q, S0, S) :-
  300	resolve_function(Function, Call, QF, S0, S), !,
  301	mkconj(QF, Call, Q).
  302resolve_query(ebv(E0), Q, S0, S) :- !,
  303	resolve_expression(E0, E, QE, S0, S),
  304	mkconj(QE, sparql_true(E), Q).
  305resolve_query(filter(E0), true, S0, S) :- !,
  306	state_filters(S0, F),
  307	set_filters_of_state([ebv(E0)|F], S0, S).
  308resolve_query(bind(Expr0, var(VarName)), Q, S0, S) :- !,
  309	resolve_var(VarName, Var, S0, S1),
  310	state_aggregates(S1, A1),
  311	resolve_expression(Expr0, Expr, QE, S1, S2),
  312	state_aggregates(S2, A2),
  313	(   var(Expr)			% BIND(?var1 as ?var2)
  314	->  Var = Expr,
  315	    Q = rdfql_cond_bind_null([Var]),
  316	    S = S2
  317	;   A1 == A2
  318	->  mkconj(sparql_eval(Expr, Var), QE, Q),
  319	    S = S2
  320	;   Q = QE,
  321	    set_aggregates_of_state([sparql_eval(Expr, Var)|A2], S2, S)
  322	).
  323resolve_query(sub_select(Proj0, Q0, Sols0),
  324	      sparql_subquery(Proj, Q, Sols),
  325	      S0, S) :- !,
  326	subquery_state(S0, S1),
  327	resolve_query(Q0, Q1, S1, S2),
  328	resolve_projection(Proj0, Proj1, QExpr, S2, S3),
  329	resolve_solutions(Sols0, Sols, Q2, S3, _SubState),
  330	mkconj(Q1, QExpr, Q12),
  331	mkconj(Q12, Q2, Q),
  332	join_subquery_projection(Proj1, Proj, S0, S).
  333resolve_query(var_in(var(Name), Values0), member(Var, Values), S0, S) :-
  334	resolve_var(Name, Var, S0, S),
  335	resolve_values(Values0, Values, S).
  336resolve_query(vars_in(Vars0, Values0), member(Vars, Values), S0, S) :-
  337	resolve_vars(Vars0, Vars, S0, S),
  338	resolve_values_full(Values0, Values, S).
  339resolve_query(Q, Q, S, S).		% TBD
  340
  341mkconj(true, Q, Q) :- !.
  342mkconj(Q, true, Q) :- !.
  343mkconj(A, B, (A,B)).
  344
  345list_to_conj([], true, S, S) :- !.
  346list_to_conj([Q0], Q, S0, S) :- !,
  347	resolve_query(Q0, Q, S0, S).
  348list_to_conj([H|T], (QH,QT), S0, S) :-
  349	resolve_query(H, QH, S0, S1),
  350	list_to_conj(T, QT, S1, S).
  351
  352mkdisj(true, _, true) :- !.
  353mkdisj(_, true, true) :- !.
  354mkdisj(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.
  364resolve_projection(*, Vars, true, State, State) :- !,
  365	state_var_list(State, Vars0),
  366	reverse(Vars0, Vars).
  367resolve_projection(projection(VarNames, Bind), Vars, Q, State0, State) :-
  368	proj_vars(VarNames, Vars, State0, State1),
  369	resolve_query(Bind, Q, State1, State).
  370
  371proj_vars([], [], State, State).
  372proj_vars([var(Name)|T0], [Name=Var|T], State0, State) :- !,
  373	resolve_var(Name, Var, State0, State1),
  374	proj_vars(T0, T, State1, State).
  375proj_vars([IRI0|T0], [IRI|T], State0, State) :-	% for DESCRIBE queries
  376	resolve_iri(IRI0, IRI, State0),
  377	proj_vars(T0, T, State0, State).
 resolve_construct_template(+Templ0, -Templ, -Q, +State)
Deal with ORDER BY clause.
  383resolve_construct_template([], [], true, S, S).
  384resolve_construct_template([H0|T0], [H|T], Q, S0, S) :-
  385	resolve_construct_triple(H0, H, Q1, S0, S1),
  386	resolve_construct_template(T0, T, Q2, S1, S),
  387	mkconj(Q1, Q2, Q).
  388
  389resolve_construct_triple(rdf(S0,P0,O0), rdf(S,P,O), Q, St0, St) :-
  390	resolve_graph_term(S0, S, Q1, St0, St1),
  391	resolve_graph_term(P0, P, Q2, St1, St2),
  392	resolve_graph_term(O0, O, Q3, St2, St),
  393	mkconj(Q1, Q2, Q12),
  394	mkconj(Q12, Q3, Q).
 resolve_solutions(+Solutions0, -Solutions, -Q, +State0, -State)
  398resolve_solutions(distinct(S0), distinct(S), Q, State0, State) :- !,
  399	resolve_solutions(S0, S, Q, State0, State).
  400resolve_solutions(reduced(S0), reduced(S), Q, State0, State) :- !,
  401	resolve_solutions(S0, S, Q, State0, State).
  402resolve_solutions(solutions(Group0, Having0,      Order0, Limit, Offset),
  403		  solutions( Group,  Having,  Agg, Order, Limit, Offset),
  404		  Q, State0, State) :-
  405	resolve_group_by(Group0, Group, Q1, State0, State1),
  406	resolve_having(Having0, Having, Q2, State1, State2),
  407	resolve_order_by(Order0, Order, Q3, State2, State),
  408	state_aggregates(State, Agg),
  409	mkconj(Q1, Q2, Q12),
  410	mkconj(Q12, Q3, Q).
 resolve_order_by(+OrderBy0, -OrderBy, -Q, +State0, -State)
  415resolve_order_by(unsorted, unsorted, true, State, State).
  416resolve_order_by(order_by(Cols0), order_by(Cols), Q, State0, State) :-
  417	resolve_order_by_cols(Cols0, Cols, Q, State0, State).
  418
  419resolve_order_by_cols([], [], true, State, State).
  420resolve_order_by_cols([H0|T0], [H|T], Q, State0, State) :-
  421	resolve_order_by_col(H0, H, Q1, State0, State1),
  422	resolve_order_by_cols(T0, T, Q2, State1, State),
  423	mkconj(Q1, Q2, Q).
  424
  425resolve_order_by_col(ascending(O0), ascending(O), Goal, State0, State) :- !,
  426	compile_expression(O0, O, Goal, State0, State).
  427resolve_order_by_col(descending(O0), descending(O), Goal, State0, State) :- !,
  428	compile_expression(O0, O, Goal, State0, State).
 resolve_group_by(+Groups0, -Groups, -Q, +State0, -State)
  432resolve_group_by([], [], true, State, State).
  433resolve_group_by([H0|T0], [H|T], Q, State0, State) :-
  434	compile_expression(H0, H, Q1, State0, State1),
  435	resolve_group_by(T0, T, Q2, State1, State),
  436	mkconj(Q1, Q2, Q).
 resolve_having(+Having0, -Having, -Q, +State0, -State)
  440resolve_having(Having0, Having, true, State0, State) :-
  441	resolve_query(Having0, Having, State0, State).
 resolve_state(+Prolog, -State, +Options)
Create initial state.
  448resolve_state(prologue(PrefixesList), State, Options) :-
  449	option(base_uri(Base), Options, 'http://default.base.org/'),
  450	resolve_state(prologue(Base, PrefixesList), State, Options).
  451resolve_state(prologue(Base, PrefixesList),
  452	      State, Options) :-
  453	sort(PrefixesList, OrdPrefixList),
  454	ord_list_to_assoc(OrdPrefixList, Prefixes),
  455	initial_vars(Vars, Options),
  456	make_state([ base_uri(Base),
  457		     prefix_assoc(Prefixes),
  458		     var_assoc(Vars)
  459		   ], State).
  460
  461initial_vars(Vars, Options) :-
  462	option(variable_names(Dict), Options), !,
  463	must_be(list, Dict),
  464	maplist(to_pair, Dict, Pairs),
  465	list_to_assoc(Pairs, Vars).
  466initial_vars(Vars, _) :-
  467	empty_assoc(Vars).
  468
  469to_pair(Name=Var, Name-(_Visible-Var)).
 resolve_graph_term(+T0, -T, -Q, +State0, -State) is det
  474resolve_graph_term(Var, Var, true, S, S) :-
  475	var(Var), !.
  476resolve_graph_term(var(Name), Var, true, S0, S) :- !,
  477	resolve_var(Name, Var, S0, S).
  478resolve_graph_term(T, IRI, true, S, S) :-
  479	resolve_iri(T, IRI, S), !.
  480resolve_graph_term(literal(type(IRI0, Value)),
  481		   literal(type(IRI, Value)), true, S, S) :- !,
  482	resolve_iri(IRI0, IRI, S).
  483resolve_graph_term(boolean(Val),
  484		   literal(type(Type, Val)), true, S, S) :- !,
  485	rdf_equal(Type, xsd:boolean).
  486resolve_graph_term(collection(Members), CollSubj, Q, S0, S) :- !,
  487	mkcollection(Members, CollSubj, Triples, []),
  488	resolve_query(Triples, Q, S0, S).
  489resolve_graph_term(T, T, true, S, S).
 resolve_graph_terms(+TList0, -TList, -Q, +State0, -State) is det
  493resolve_graph_terms([], [], true, S, S).
  494resolve_graph_terms([H0|T0], [H|T], Q, S0, S) :-
  495	resolve_graph_term(H0, H, Q1, S0, S1),
  496	resolve_graph_terms(T0, T, Q2, S1, S),
  497	mkconj(Q1, Q2, Q).
 resolve_triple(+Subj, +P, +O, -Q, +S0, -S)
  501resolve_triple(Subj0, P, O0, Q, S0, S) :-
  502	resolve_graph_term(Subj0, Subj, Q1, S0, S1),
  503	resolve_graph_term(O0, O, Q2, S1, S2),
  504	mkconj(Q1, Q2, Q12),
  505	resolve_path(P, Subj, O, Q3, S2, S),
  506	mkconj(Q12, Q3, Q).
 resolve_path(+P, +Subj, +Obj, -Q, +S0, -S) is det
Translate a property path expression into a goal.
  514resolve_path(P0, Subj, Obj, Q, S0, S) :-
  515	resolve_predicate(P0, P, S0, S), !,
  516	rdf_goal(Subj, P, Obj, Q, S).
  517resolve_path(P01/P02, Subj, Obj, Q, S0, S) :- !,
  518	resolve_path(P01, Subj, Tmp, Q1, S0, S1),
  519	resolve_path(P02, Tmp, Obj, Q2, S1, S),
  520	mkconj(Q1, Q2, Q).
  521resolve_path(^(P), Subj, Obj, Q, S0, S) :- !,
  522	resolve_path(P, Obj, Subj, Q, S0, S).
  523resolve_path(;(P01,P02), Subj, Obj, (Q1;Q2), S0, S) :- !,
  524	resolve_path(P01, Subj, Obj, Q1, S0, S),
  525	resolve_path(P02, Subj, Obj, Q2, S0, S).
  526resolve_path(!(NegSet0), Subj, Obj, Q, S, S) :- !,
  527	resolve_negated_property_set(NegSet0, NegSet, RevSet, S),
  528	rdf_goal(Subj, P, Obj, Q1, S),
  529	not_in_goal(P, NegSet, NotIn),
  530	(   RevSet == []
  531	->  Q = ( Q1, NotIn )
  532	;   rdf_goal(Obj, P2, Subj, Q2, S),
  533	    (	RevSet = [P2]
  534	    ->	RevNegate = Q2
  535	    ;	RevNegate = \+((Q2, memberchk(P2, RevSet)))
  536	    ),
  537	    (	NegSet == []
  538	    ->	Q = (Q1, RevNegate)
  539	    ;	Q = (Q1, NotIn, RevNegate)
  540	    )
  541	).
  542resolve_path(?(P), Subj, Obj, Q, S0, S) :- !,
  543	resolve_path(P, Subj, Obj, Q1, S0, S),
  544	Q = (Subj=Obj ; Q1).
  545resolve_path(*(P), Subj, Obj, Q, S0, S) :- !,
  546	resolve_path(P, From, To, Q1, S0, S),
  547	Q = sparql_find(Subj, Obj, From, To, Q1).
  548resolve_path(+(P), Subj, Obj, Q, S0, S) :- !,
  549	resolve_path(P, Subj, Tmp, Q1, S0, S),
  550	resolve_path(P, From, To, Q2, S0, S),
  551	Q = (Q1, sparql_find(Tmp, Obj, From, To, Q2)).
  552
  553
  554resolve_path(P, _, _, _, _, _) :-
  555	type_error(predicate_path, P).
 resolve_predicate(+P0, -P, +S0, -S) is det
  559resolve_predicate(P, P, S, S) :-
  560	var(P), !.
  561resolve_predicate(var(Name), Var, S0, S) :- !,
  562	resolve_var(Name, Var, S0, S).
  563resolve_predicate(T, IRI, S, S) :-
  564	resolve_iri(T, IRI, S), !.
 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.
  571resolve_negated_property_set(PSet, NegSet, RevSet, S) :-
  572	resolve_netaged_property_set(PSet, NegSet, [], RevSet, [], S).
  573
  574resolve_netaged_property_set((A0;B0), P0, P, N0, N, S) :- !,
  575	resolve_netaged_property_set(A0, P0, P1, N0, N1, S),
  576	resolve_netaged_property_set(B0, P1, P,  N1, N, S).
  577resolve_netaged_property_set(^(IRI0), P, P, [IRI|N], N, S) :-
  578	resolve_iri(IRI0, IRI, S).
  579resolve_netaged_property_set(IRI0, [IRI|P], P, N, N, S) :-
  580	resolve_iri(IRI0, IRI, S).
  581
  582not_in_goal(P, [One], P \== One) :- !.
  583not_in_goal(P, List, \+ memberchk(P, List)).
 rdf_goal(+S, +P, +O, -RDF, +State)
Optionally add graph to the rdf/3 statement.
  589rdf_goal(S, P, O0, RDF, State) :-
  590	rdf_goal_object(O0, O),
  591	(   state_graph(State, [Graph|_])
  592	->  RDF = rdf(S, P, O, Graph:_)
  593	;   RDF = rdf(S, P, O)
  594	).
 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.
  603rdf_goal_object(O, O) :-
  604	var(O), !.
  605rdf_goal_object(literal(X), O) :-
  606	atom(X), !,
  607	O = literal(plain(X), X).
  608rdf_goal_object(O, O).
 mkcollection(+Members, -CollectionSubject, -Triples)
  613mkcollection([Last], S, [ rdf(S, rdf:first, Last),
  614			  rdf(S, rdf:rest, rdf:nil)
  615			| Tail
  616			], Tail) :- !.
  617mkcollection([H|T], S, [ rdf(S, rdf:first, H),
  618			 rdf(S, rdf:rest, R)
  619		       | RDF
  620		       ], Tail) :-
  621	mkcollection(T, R, RDF, Tail).
 resolve_expression(+E0, -E, -Q, +State0, -State)
  626resolve_expression(Var, Var, true, S, S) :-
  627	var(Var), !.
  628resolve_expression(or(A0,B0), or(A,B), Q, S0, S) :- !,
  629	resolve_expression(A0, A, Q1, S0, S1),
  630	resolve_expression(B0, B, Q2, S1, S),
  631	mkdisj(Q1, Q2, Q).
  632resolve_expression(and(A0,B0), and(A,B), Q, S0, S) :- !,
  633	resolve_expression(A0, A, Q1, S0, S1),
  634	resolve_expression(B0, B, Q2, S1, S),
  635	mkconj(Q1, Q2, Q).
  636resolve_expression(E0, E, Q, S0, S) :-
  637	expression_op(E0), !,
  638	E0 =.. [Op|Args0],
  639	resolve_expressions(Args0, Args, Q, S0, S),
  640	E =.. [Op|Args].
  641resolve_expression(E0, As, Q, S0, S) :-
  642	aggregate_op(E0), !,
  643	E0 =.. [Op|Args0],
  644	resolve_expressions(Args0, Args, Q, S0, S1),
  645	E =.. [Op|Args],
  646	state_aggregates(S0, A0),
  647	set_aggregates_of_state([aggregate(E,As)|A0], S1, S).
  648resolve_expression(E0, E, Q, S0, S) :-
  649	resolve_function(E0, E, Q, S0, S), !.
  650resolve_expression(exists(Pattern), boolean(True), Q, S0, S) :- !,
  651	resolve_query(Pattern, QE, S0, S),
  652	Q = (QE -> True=true ; True=false).
  653resolve_expression(in(E0, List0), in(E, List), Q, S0, S) :- !,
  654	resolve_expression(E0, E, Q1, S0, S1),
  655	resolve_expressions(List0, List, Q2, S1, S),
  656	mkconj(Q1, Q2, Q).
  657resolve_expression(not_in(E0, List0), not_in(E, List), Q, S0, S) :- !,
  658	resolve_expression(E0, E, Q1, S0, S1),
  659	resolve_expressions(List0, List, Q2, S1, S),
  660	mkconj(Q1, Q2, Q).
  661resolve_expression(not_exists(Pattern), boolean(True), Q, S0, S) :- !,
  662	resolve_query(Pattern, QE, S0, S),
  663	Q = (QE -> True=false ; True=true).
  664resolve_expression(distinct(E0), distinct(E), Q, S0, S) :- !,
  665	resolve_expression(E0, E, Q, S0, S).
  666resolve_expression(var(Name), Var, true, S0, S) :- !,
  667	resolve_var_invisible(Name, Var, S0, S).
  668resolve_expression(T0, T, Q, S0, S) :-
  669	resolve_graph_term(T0, T, Q, S0, S).	% OK?
  670
  671expression_op(_ = _).
  672expression_op(_ \= _).			% SPARQL !=
  673expression_op(_ =< _).			% SPARQL <=
  674expression_op(_ >= _).
  675expression_op(_ < _).
  676expression_op(_ > _).
  677expression_op(_ + _).
  678expression_op(_ - _).
  679expression_op(_ * _).
  680expression_op(_ / _).
  681expression_op(not(_)).			% SPARQL !(_)
  682expression_op(+ _).
  683expression_op(- _).
  684
  685
  686resolve_expressions([], [], true, S, S).
  687resolve_expressions([H0|T0], [H|T], Q, S0, S) :-
  688	resolve_expression(H0, H, Q1, S0, S1),
  689	resolve_expressions(T0, T, Q2, S1, S),
  690	mkconj(Q1, Q2, Q).
  691
  692resolve_function(function(F0, Args0), function(Term), Q, S0, S) :- !,
  693	resolve_iri(F0, F, S0),
  694	resolve_expressions(Args0, Args, Q, S0, S),
  695	Term =.. [F|Args].
  696resolve_function(concat(List0), concat(List), Q, S0, S) :- !,
  697	resolve_expressions(List0, List, Q, S0, S).
  698resolve_function(coalesce(List0), coalesce(List), Q, S0, S) :- !,
  699	resolve_expressions(List0, List, Q, S0, S).
  700resolve_function(uri(Expr0), iri(Expr, Base), Q, S0, S) :- !, % URI() == IRI()
  701	resolve_expression(Expr0, Expr, Q, S0, S),
  702	state_base_uri(S, Base).
  703resolve_function(iri(Expr0), iri(Expr, Base), Q, S0, S) :- !,
  704	resolve_expression(Expr0, Expr, Q, S0, S),
  705	state_base_uri(S, Base).
  706resolve_function(built_in(Builtin), built_in(Term), Q, S0, S) :- !,
  707	built_in_function(Builtin), !,
  708	Builtin =.. [F|Args0],
  709	resolve_expressions(Args0, Args, Q, S0, S),
  710	Term =.. [F|Args].
  711resolve_function(Builtin, Term, Q, S0, S) :- !,
  712	built_in_function(Builtin), !,
  713	Builtin =.. [F|Args0],
  714	resolve_expressions(Args0, Args, Q, S0, S),
  715	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$'.
  722resolve_var(Name, Var, State0, State) :-
  723	assertion(atom(Name)),
  724	state_var_assoc(State0, Vars),
  725	get_assoc(Name, Vars, Visible-Var), !,
  726	(   Visible == true
  727	->  State = State0
  728	;   Visible = true,
  729	    state_var_list(State0, VL),
  730	    set_var_list_of_state([Name=Var|VL], State0, State)
  731	).
  732resolve_var(Name, Var, State0, State) :-
  733	State0 \== State, !,
  734	state_var_assoc(State0, Vars0),
  735	state_var_list(State0, VL),
  736	put_assoc(Name, Vars0, true-Var, Vars),
  737	set_var_assoc_of_state(Vars, State0, State1),
  738	set_var_list_of_state([Name=Var|VL], State1, State).
  739resolve_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 *.
  746resolve_var_invisible(Name, Var, State, State) :-
  747	assertion(atom(Name)),
  748	state_var_assoc(State, Vars),
  749	get_assoc(Name, Vars, _-Var), !.
  750resolve_var_invisible(Name, Var, State0, State) :- !,
  751	state_var_assoc(State0, Vars0),
  752	put_assoc(Name, Vars0, _-Var, Vars),
  753	set_var_assoc_of_state(Vars, State0, State).
  754resolve_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.
  762resolve_iri(P:N, IRI, State) :- !,
  763	resolve_prefix(P, Prefix, State),
  764	used_prefix(P, State),
  765	url_iri(N, LocalIRI),
  766	atom_concat(Prefix, LocalIRI, IRI).
  767resolve_iri(URL0, IRI, State) :-
  768	atom(URL0),
  769	state_base_uri(State, Base),	% TBD: What if there is no base?
  770	uri_normalized(URL0, Base, URL1),
  771	url_iri(URL1, IRI).
  772
  773resolve_prefix(P, IRI, State) :-
  774	state_prefix_assoc(State, Prefixes),
  775	(   get_assoc(P, Prefixes, IRI)
  776	->  true
  777	;   rdf_db:ns(P, IRI)		% Extension: database known
  778	->  true
  779	;   throw(error(existence_error(prefix, P), _))
  780	).
 used_prefix(+P, !State) is det
Keep track of the prefixes that are actually used to support service statements.
  787used_prefix(P, State) :-
  788	state_prefixes_used(State, Used0),
  789	(   memberchk(P, Used0)
  790	->  true
  791	;   set_prefixes_used_of_state([P|Used0], State)
  792	).
 resolve_values(+Values0, -Values, +State) is det
Resolve a list of values for the VALUES clause.
  798resolve_values([], [], _).
  799resolve_values([H0|T0], [H|T], S) :-
  800	resolve_value(H0, H, S),
  801	resolve_values(T0, T, S).
  802
  803resolve_value(V0, V, S) :-
  804	resolve_graph_term(V0, V, Q, S, S2),
  805	assertion(Q == true),
  806	assertion(S2 == S).
  807
  808resolve_values_full([], [], _).
  809resolve_values_full([H0|T0], [H|T], S) :-
  810	resolve_values(H0, H, S),
  811	resolve_values_full(T0, T, S).
  812
  813resolve_vars([], [], S, S).
  814resolve_vars([var(Name)|T0], [V|T], S0, S) :-
  815	resolve_var(Name, V, S0, S1),
  816	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.
  825resolve_bnodes(P0, P) :-
  826	empty_assoc(BN0),
  827	resolve_bnodes(P0, P, BN0, _).
  828
  829resolve_bnodes(Var, Var, BN, BN) :-
  830	var(Var), !.
  831resolve_bnodes(bnode(Name), Var, BN0, BN) :- !,
  832	(   get_assoc(Name, BN0, Var)
  833	->  BN = BN0
  834	;   put_assoc(Name, BN0, Var, BN)
  835	).
  836resolve_bnodes(Term0, Term, BN0, BN) :-
  837	compound(Term0), !,
  838	functor(Term0, F, A),
  839	functor(Term, F, A),
  840	resolve_bnodes_args(0, A, Term0, Term, BN0, BN).
  841resolve_bnodes(Term, Term, BN, BN).
  842
  843resolve_bnodes_args(A, A, _, _, BN, BN) :- !.
  844resolve_bnodes_args(I0, A, T0, T, BN0, BN) :-
  845	I is I0 + 1,
  846	arg(I, T0, A0),
  847	resolve_bnodes(A0, A1, BN0, BN1),
  848	arg(I, T, A1),
  849	resolve_bnodes_args(I, A, T0, T, BN1, BN).
 subquery_state(OuterState, SubState) is det
Create an initial state for a subquery
  856subquery_state(S0, S) :-
  857	state_base_uri(S0, Base),
  858	state_prefix_assoc(S0, Prefixes),
  859	state_graph(S0, Graph),			% is this right?
  860	empty_assoc(Vars),
  861	make_state([ base_uri(Base),
  862		     prefix_assoc(Prefixes),
  863		     var_assoc(Vars),
  864		     graph(Graph)
  865		   ], 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
  874join_subquery_projection([], [], S, S).
  875join_subquery_projection([Name=InnerVar|T0], [OuterVar=InnerVar|T], S0, S) :-
  876	resolve_var(Name, OuterVar, S0, S1),
  877	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)
  898resolve_updates([], [], State, State).
  899resolve_updates([H0|T0], [H|T], State0, State) :-
  900	resolve_update(H0, H, State0, State1),
  901	resolve_updates(T0, T, State1, State).
  902
  903
  904resolve_update(insert_data(Quads0), insert_data(Quads), State0, State) :-
  905	resolve_quads(Quads0, Quads, State0, State).
  906resolve_update(delete_data(Quads0), delete_data(Quads), State0, State) :-
  907	resolve_quads(Quads0, Quads, State0, State).
  908resolve_update(delete_where(Quads0), delete_where(Quads), State0, State) :-
  909	resolve_quads(Quads0, Quads, State0, State).
  910resolve_update(add(Silent, From0, To0), add(Silent, From, To),
  911	       State, State) :-
  912	resolve_graph_or_special(From0, From, State),
  913	resolve_graph_or_special(To0, To, State).
  914resolve_update(copy(Silent, From0, To0), copy(Silent, From, To),
  915	       State, State) :-
  916	resolve_graph_or_special(From0, From, State),
  917	resolve_graph_or_special(To0, To, State).
  918resolve_update(move(Silent, From0, To0), move(Silent, From, To),
  919	       State, State) :-
  920	resolve_graph_or_special(From0, From, State),
  921	resolve_graph_or_special(To0, To, State).
  922resolve_update(create(Silent, Graph0), create(Silent, Graph), State, State) :-
  923	resolve_iri(Graph0, Graph, State).
  924resolve_update(modify(WithIRI0, InsDel0, Using0, Pattern),
  925	       modify(WithIRI,  InsDel,  Using,  Query),
  926	       State0, State) :-
  927	resolve_with(WithIRI0, WithIRI, State0),
  928	(   InsDel0 =.. [Action,Quads0]
  929	->  InsDel  =.. [Action,Quads],
  930	    resolve_quads(Quads0, Quads, State0, State2)
  931	;   InsDel0 = replace(DelQuads0, InsQuads0),
  932	    InsDel  = replace(DelQuads,  InsQuads),
  933	    resolve_quads(DelQuads0, DelQuads, State0, State1),
  934	    resolve_quads(InsQuads0, InsQuads, State1, State2)
  935	),
  936	Using0 = Using,
  937	resolve_query(Pattern, Query, State2, State).
  938resolve_update(drop(Silent, GraphAll0),
  939	       drop(Silent, GraphAll),
  940	       State, State) :-
  941	resolve_graph_or_special(GraphAll0, GraphAll, State).
  942resolve_update(clear(Silent, GraphAll0),
  943	       clear(Silent, GraphAll),
  944	       State, State) :-
  945	resolve_graph_or_special(GraphAll0, GraphAll, State).
  946resolve_update(load(Silent, IRI0, Graph0),
  947	       load(Silent, IRI,  Graph),
  948	       State, State) :-
  949	resolve_iri(IRI0, IRI, State),
  950	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.
  959resolve_quads(Quads0, Quads, State0, State) :-
  960	resolve_query(Quads0, Query, State0, State),
  961	phrase(query_quads(Query), Quads).
  962
  963query_quads((A,B)) --> !,
  964	query_quads(A),
  965	query_quads(B).
  966query_quads(true) --> !,		% results from empty triple pattern
  967	[].
  968query_quads(A) -->
  969	{ quad(A) },
  970	[A].
  971
  972quad(rdf(_,_,_)).
  973quad(rdf(_,_,_,_)).
  974
  975resolve_graph_or_special(graph(Graph0), graph(Graph), State) :- !,
  976	resolve_iri(Graph0, Graph, State).
  977resolve_graph_or_special(Special, Special, _).
  978
  979resolve_with(without, default, _).
  980resolve_with(with(IRI0), graph(IRI), State) :-
  981	resolve_iri(IRI0, IRI, State).
  982
  983
  984		 /*******************************
  985		 *	   STEAD FASTNESS	*
  986		 *******************************/
 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.
  997steadfast(Q0, sparql_group(Q1, AT0, AT1)) :-
  998	phrase(non_steadfast(Q0), NonSteadFast),
  999	NonSteadFast \== [], !,
 1000	term_variables(Q0, AllVars),
 1001	sort(AllVars, AllSorted),
 1002	sort(NonSteadFast, NSFSorted),
 1003	ord_subtract(AllSorted, NSFSorted, SteadFast),
 1004	STF =.. [v|SteadFast],
 1005	copy_term(STF-Q0, STF1-Q1),
 1006	STF = STF1,
 1007	unifiable(Q0, Q1, Unifier),
 1008	maplist(split_assignment, Unifier, A0, A1),
 1009	AT0 =.. [v|A0],
 1010	AT1 =.. [v|A1].
 1011steadfast(Q0, sparql_group(Q0)).
 1012
 1013
 1014split_assignment(A=B, A, B).
 1015
 1016non_steadfast(Var) -->
 1017	{ var(Var) }, !.
 1018non_steadfast((A,B)) --> !,
 1019	non_steadfast(A),
 1020	non_steadfast(B).
 1021non_steadfast((A;B)) --> !,
 1022	non_steadfast(A),
 1023	non_steadfast(B).
 1024non_steadfast((A->B)) --> !,
 1025	non_steadfast(A),
 1026	non_steadfast(B).
 1027non_steadfast((A*->B)) --> !,
 1028	non_steadfast(A),
 1029	non_steadfast(B).
 1030non_steadfast(\+A) --> !,
 1031	non_steadfast(A).
 1032non_steadfast(sparql_eval(Expr, _Var)) --> !,
 1033	term_variables(Expr).
 1034non_steadfast(sparql_true(Expr)) --> !,
 1035	term_variables(Expr).
 1036non_steadfast(_) -->
 1037	[].
 1038
 1039
 1040		 /*******************************
 1041		 *	COMPILE EXPRESSIONS	*
 1042		 *******************************/
 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.
 1050compile_expression(bind(Expr,var(VarName)), Var, Goal, State0, State) :- !,
 1051	resolve_var(VarName, Var, State0, State1),
 1052	compile_expression(Expr, Var, Goal, State1, State).
 1053compile_expression(Expr0, Var, Goal, State0, State) :-
 1054	resolve_expression(Expr0, Expr, Q, State0, State),
 1055	(   primitive(Expr)
 1056	->  Var = Expr,
 1057	    Goal = Q
 1058	;   mkconj(Q, sparql_eval(Expr, Var), Goal)
 1059	).
 1060
 1061primitive(Var)  :- var(Var), !.
 1062primitive(Atom) :- atom(Atom).		% IRI, '$null$'
 1063
 1064
 1065		 /*******************************
 1066		 *	      SERVICE		*
 1067		 *******************************/
 service_state(+S0, -S)
Make a resolver state for a SERVICE. We want to know
 1076service_state(S0, S) :-
 1077	state_base_uri(S0, Base),
 1078	state_prefix_assoc(S0, PrefixAssoc),
 1079	empty_assoc(VarAssoc),
 1080	make_state([ base_uri(Base),
 1081		     prefix_assoc(PrefixAssoc),
 1082		     var_assoc(VarAssoc)
 1083		   ], S).
 service_prefixes(+State, -List:list(pair)) is det
Obtain a list of Prefix-URL pairs for the prefixes used in State.
 1091service_prefixes(State, List) :-
 1092	state_prefixes_used(State, Prefixes),
 1093	maplist(prefix_binding(State), Prefixes, List).
 1094
 1095prefix_binding(State, Prefix, Prefix-IRI) :-
 1096	resolve_prefix(Prefix, IRI, State).
 1097
 1098resolve_service_vars([], State, State).
 1099resolve_service_vars([VarName=Var|T], S0, S) :-
 1100	resolve_var(VarName, Var, S0, S1),
 1101	resolve_service_vars(T,S1, S).
 1102
 1103
 1104
 1105		 /*******************************
 1106		 *	    SPARQL DCG		*
 1107		 *******************************/
 1108
 1109:- discontiguous term_expansion/2. 1110
 1111:- if(current_predicate(string_codes/2)). 1112goal_expansion(keyword(S,L,T), keyword(Codes,L,T)) :-
 1113	string(S),
 1114	string_codes(S, Codes).
 1115goal_expansion(must_see_keyword(S,L,T), must_see_keyword(Codes,L,T)) :-
 1116	string(S),
 1117	string_codes(S, Codes).
 1118:- endif. 1119
 1120/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 1121From A.7. We keep the same naming and   order of the productions to make
 1122it as easy as possible to verify the correctness of the parser.
 1123- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 query(-Prologue, -Query)//
 1127sparql_query(Prologue, Query, In, Out) :-
 1128	catch(uquery(Prologue, Query, In, Out),
 1129	      E,
 1130	      add_error_location(E, In)).
 1131
 1132uquery(Prologue, Query, In, Out) :-
 1133	phrase(unescape_code_points(Unescaped), In, Out),
 1134	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.
 1141unescape_code_points([H|T]) -->
 1142	uchar(H), !,
 1143	unescape_code_points(T).
 1144unescape_code_points([H|T]) -->
 1145	[H], !,
 1146	unescape_code_points(T).
 1147unescape_code_points([]) -->
 1148	[].
 uchar(-Code)//
\uXXXX or \UXXXXXXXX, returning character value
 1154uchar(Code) -->
 1155	"\\u", !,
 1156	(   hex(D1), hex(D2), hex(D3), hex(D4)
 1157	->  { Code is D1<<12 + D2<<8 + D3<<4 + D4 }
 1158	;   syntax_error(illegal_uchar)
 1159	).
 1160uchar(Code) -->
 1161	"\\U", !,
 1162	(   hex(D1), hex(D2), hex(D3), hex(D4),
 1163	    hex(D5), hex(D6), hex(D7), hex(D8)
 1164	->  { Code is D1<<28 + D2<<24 + D3<<20 + D4<<16 +
 1165	              D5<<12 + D6<<8 + D7<<4 + D8 }
 1166	;   syntax_error(illegal_Uchar)
 1167	).
 1168
 1169query(Prologue, Query) -->		% [2]
 1170	skip_ws,
 1171	prologue(Prologue),
 1172	(   select_query(Query)
 1173	;   construct_query(Query)
 1174	;   describe_query(Query)
 1175	;   ask_query(Query)
 1176	;   update_query(Query)
 1177	), !.
 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.
 1185prologue(Prologue) -->	% [4]
 1186	prologue_decls(0, Base, Decls),
 1187	{   Base == 0
 1188        ->  Prologue = prologue(Decls)
 1189	;   Prologue = prologue(Base, Decls)
 1190	}.
 1191
 1192prologue_decls(_, Base, Decls) -->
 1193	base_decl(Base1), !,
 1194	prologue_decls(Base1, Base, Decls).
 1195prologue_decls(Base0, Base, [H|T]) -->
 1196	prefix_decl(H, Base0), !,
 1197	prologue_decls(Base0, Base, T).
 1198prologue_decls(Base, Base, []) -->
 1199	"".
 base_decl(-Base:uri)// is semidet
Match "base <URI>".
 1205base_decl(Base) -->			% [5]
 1206	keyword("base"),
 1207	q_iri_ref(Base).
 prefix_decl(-Prefix, +Base)// is semidet
Process "prefix <qname> <URI>" into a term Qname-IRI
 1213prefix_decl(Id-IRI, Base) -->
 1214	keyword("prefix"),
 1215	(   qname_ns(Id),
 1216	    q_iri_ref(IRI0)
 1217	->  { global_url(IRI0, Base, IRI) }
 1218	;   syntax_error(illegal_prefix_declaration)
 1219	).
 select_query(-Select)// is semidet
Process "select ..." into a term

select(Projection, DataSets, Query, Solutions)

 1227select_query(select(Projection, DataSets, Query, Solutions)) --> % [7]
 1228	select_clause(Projection, Solutions, S0),
 1229	data_set_clauses(DataSets),
 1230	where_clause(QWhere),
 1231	solution_modifier(S0),
 1232	values_clause(QValue),
 1233	{ mkconj(QWhere, QValue, Query) }.
 sub_select(-SubSelect)//
 1237sub_select(sub_select(Projection, Query, Solutions)) --> % [8]
 1238	select_clause(Projection, Solutions, S0),
 1239	where_clause(WQuery),
 1240	solution_modifier(S0),
 1241	values_clause(QValues),
 1242	{ mkconj(WQuery, QValues, Query) }.
 1243
 1244
 1245select_clause(Projection, Solutions, S0) --> % [9]
 1246	keyword("select"),
 1247	(   keyword("distinct")
 1248	->  { Solutions = distinct(S0) }
 1249	;   keyword("reduced")
 1250	->  { Solutions = reduced(S0) }
 1251	;   { Solutions = S0 }
 1252	),
 1253	select_projection(Projection).
 select_projection(-Projection)// is det
Process the projection of a select query. Projection is one of
 1265select_projection(*) --> "*", !, skip_ws.
 1266select_projection(projection([H|T], B)) -->
 1267	projection_elt(H, true, B1),
 1268	projection_elts(T, B1, B), !.
 1269select_projection(_) -->
 1270	syntax_error(projection_expected).
 1271
 1272projection_elts([H|T], B0, B) -->
 1273	projection_elt(H, B0, B1),
 1274	projection_elts(T, B1, B).
 1275projection_elts([], B, B) -->
 1276	[].
 1277
 1278projection_elt(Var, B, B) -->
 1279	var(Var), !.
 1280projection_elt(Var, B0, B) -->
 1281	"(", skip_ws,
 1282	(   expression(Expr), must_see_keyword("as"), var(Var),
 1283	    must_see_close_bracket
 1284	->  skip_ws,
 1285	    { mkconj(B0, bind(Expr, Var), B) }
 1286	;   syntax_error(illegal_projection)
 1287	).
 construct_query(-Construct)// is semidet
Processes "construct ..." into a term

construct(Template, DataSets, Query, Solutions)

 1295construct_query(construct(Template, DataSets, Query, Solutions)) --> % [10]
 1296	keyword("construct"),
 1297	(   construct_template(Template),
 1298	    data_set_clauses(DataSets),
 1299	    where_clause(QWhere),
 1300	    solution_modifier(Solutions)
 1301	;   data_set_clauses(DataSets),
 1302	    keyword("where"),
 1303	    (	"{", skip_ws,
 1304		triples_template(Template, []),
 1305		"}"
 1306	    ->	skip_ws,
 1307		{QWhere = Template}
 1308	    ;	syntax_error(triples_template_expected)
 1309	    ),
 1310	    solution_modifier(Solutions)
 1311	),
 1312	values_clause(QValue),
 1313	{ mkconj(QWhere, QValue, Query) }.
 describe_query(-Describe)// is semidet
Processes "describe ..." into a term

describe(Projection, DataSets, Query, Solutions)

 1321describe_query(describe(Projection, DataSets, Query, Solutions)) --> % [11]
 1322	keyword("describe"),
 1323	desc_projection(Projection),
 1324	data_set_clauses(DataSets),
 1325	(where_clause(QWhere) -> [] ; {QWhere = true}),
 1326	solution_modifier(Solutions),
 1327	values_clause(QValue),
 1328	{ mkconj(QWhere, QValue, Query) }.
 1329
 1330desc_projection(*) --> "*", !, skip_ws.
 1331desc_projection(projection([H|T], true)) -->
 1332	var_or_iri_ref(H), !,
 1333	var_or_iri_refs(T).
 1334desc_projection(_) -->
 1335	syntax_error(projection_expected).
 1336
 1337var_or_iri_refs([H|T]) -->
 1338	var_or_iri_ref(H), !,
 1339	var_or_iri_refs(T).
 1340var_or_iri_refs([]) -->
 1341	[].
 ask_query(Query)//
 1346ask_query(ask(DataSets, Query, Solutions)) --> % [12]
 1347	keyword("ask"),
 1348	data_set_clauses(DataSets),
 1349	where_clause(QWhere),
 1350	solution_modifier(Solutions),
 1351	values_clause(QValue),
 1352	{ mkconj(QWhere, QValue, Query) }.
 1353
 1354data_set_clauses([H|T]) -->		% [13*]
 1355	dataset_clause(H), !,
 1356	data_set_clauses(T).
 1357data_set_clauses([]) -->
 1358	[].
 dataset_clause(-Src)//
 1362dataset_clause(Src) -->			% [13]
 1363	keyword("from"),
 1364	(   default_graph_clause(Src)
 1365	->  []
 1366	;   named_graph_clause(Src)
 1367	).
 default_graph_clause(-Src)
 1371default_graph_clause(Src) -->		% [14]
 1372	source_selector(Src).
 named_graph_clause(Graph)//
 1376named_graph_clause(Src) -->		% [15]
 1377	keyword("named"),
 1378	source_selector(Src).
 source_selector(-Src)//
 1382source_selector(Src) -->		% [16]
 1383	iri_ref(Src).
 where_clause(-Pattern)//
 1387where_clause(Pattern) -->		% [17]
 1388	keyword("where"), !,
 1389	must_see_group_graph_pattern(Pattern).
 1390where_clause(Pattern) -->
 1391	group_graph_pattern(Pattern).
 1392
 1393must_see_group_graph_pattern(Pattern) -->
 1394	group_graph_pattern(Pattern), !.
 1395must_see_group_graph_pattern(_) -->
 1396	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

 1413solution_modifier(Modifier) -->		% [18]
 1414	{ Modifier = solutions(Group, Having, Order, Limit, Offset) },
 1415	( group_clause(Group)   -> [] ; { Group  = [] } ),
 1416	( having_clause(Having) -> [] ; { Having = true } ),
 1417	( order_clause(Order)   -> [] ; { Order  = unsorted } ),
 1418	limit_offset_clauses(Limit, Offset).
 1419
 1420limit_offset_clauses(Limit, Offset) -->
 1421	limit_clause(Limit), !,
 1422	( offset_clause(Offset) -> [] ; { Offset = 0 } ).
 1423limit_offset_clauses(Limit, Offset) -->
 1424	offset_clause(Offset), !,
 1425	( limit_clause(Limit)   -> [] ; { Limit  = inf } ).
 1426limit_offset_clauses(inf, 0) --> [].
 group_clause(-Group)// is semidet
 1430group_clause([G0|Groups]) -->
 1431	keyword("group"),
 1432	must_see_keyword("by"),
 1433	must_see_group_condition(G0),
 1434	group_conditions(Groups).
 1435
 1436group_conditions([Group|T]) -->
 1437	group_condition(Group), !,
 1438	group_conditions(T).
 1439group_conditions([]) -->
 1440	"".
 1441
 1442must_see_group_condition(G) -->
 1443	group_condition(G), !.
 1444must_see_group_condition(_) -->
 1445	syntax_error(group_condition_expected).
 1446
 1447group_condition(Exp) -->
 1448	built_in_call(Exp), !.
 1449group_condition(Exp) -->
 1450	function_call(Exp), !.
 1451group_condition(Exp) -->
 1452	as_expression(Exp), !.
 1453group_condition(Exp) -->
 1454	var(Exp), !.
 as_expression(-Exp)// is det
Processes '(' Expression ( 'AS' Var )? ')' into one of
 1463as_expression(Exp) -->
 1464	"(", skip_ws, must_see_expression(E),
 1465	(   keyword("as")
 1466	->  must_see_var(Var),
 1467	    {Exp = bind(E, Var)}
 1468	;   {Exp = E}
 1469	), ")", skip_ws.
 having_clause(-Having)// is semidet
 1474having_clause(ebv(C)) -->
 1475	keyword("having"),
 1476	must_see_having_condition(C0),
 1477	having_conditions(C1),
 1478	{ mkand(C0, C1, C) }.
 1479
 1480having_conditions(C) -->
 1481	having_condition(C0), !,
 1482	having_conditions(C1),
 1483	{ mkand(C0, C1, C) }.
 1484having_conditions(true) -->
 1485	"".
 1486
 1487mkand(true, X, X).
 1488mkand(X, true, X).
 1489mkand(X, Y, and(X,Y)).
 1490
 1491
 1492must_see_having_condition(C) -->
 1493	having_condition(C), !.
 1494must_see_having_condition(_) -->
 1495	syntax_error(having_condition_expected).
 1496
 1497having_condition(C) -->
 1498	constraint(C).
 order_clause(-Order)//
 1503order_clause(order_by([H|T])) -->
 1504	keyword("order"), must_see_keyword("by"),
 1505	must_be_order_condition(H),
 1506	order_conditions(T).
 1507
 1508order_conditions([H|T]) -->
 1509	order_condition(H), !,
 1510	order_conditions(T).
 1511order_conditions([]) -->
 1512	[].
 1513
 1514must_be_order_condition(Cond) -->
 1515	order_condition(Cond), !.
 1516must_be_order_condition(_) -->
 1517	syntax_error(order_condition_expected).
 order_condition(-Order)//
 1521order_condition(ascending(Expr)) -->
 1522	keyword("asc"), !,
 1523	bracketted_expression(Expr).
 1524order_condition(descending(Expr)) -->
 1525	keyword("desc"), !,
 1526	bracketted_expression(Expr).
 1527order_condition(ascending(Value)) -->
 1528	(   constraint(Value)
 1529	;   var(Value)
 1530	), !.
 limit_clause(-Limit)//
 1535limit_clause(Limit) -->
 1536	keyword("limit"),
 1537	integer(Limit).
 offset_clause(Offset)//
 1542offset_clause(Offset) -->
 1543	keyword("offset"),
 1544	integer(Offset).
 values_clause(-Query)// is det
Query is one of
 1555values_clause(Q) -->			% [28]
 1556	keyword("values"), !,
 1557	data_block(Q).
 1558values_clause(true) -->
 1559	"".
 update_query(-UpdatedInfo)// is semidet
True when input is a valid SPARQL update request.
 1565update_query(update(Updates)) -->
 1566	update(Updates).
 1567
 1568update(Updates) -->
 1569	(   update1(U1)
 1570	->  { Updates = [U1|Update] },
 1571	    (  ";"
 1572	    ->	skip_ws,
 1573		must_see_update(Update)
 1574	    ;	{ Update = [] }
 1575	    )
 1576	;   { Updates = [] }
 1577	).
 1578
 1579must_see_update(Update) -->
 1580	update(Update), !.
 1581must_see_update(_) -->
 1582	syntax_error(update_expected).
 1583
 1584update1(Update) -->
 1585	get_keyword(Action),
 1586	update1(Action, Update), !.
 1587update1(Update) -->
 1588	modify(Update).
 update1(+Keyword, -UpdatedAction)// is semidet
 1592update1(load, load(Verbose, IRI, Graph)) -->
 1593	silent(Verbose),
 1594	iri_ref(IRI),
 1595	(   keyword("into")
 1596	->  graph_ref(GraphIRI),
 1597	    {Graph = graph(GraphIRI)}
 1598	;   {Graph = default}
 1599	).
 1600update1(clear, clear(Verbose, GraphRefAll)) -->
 1601	silent(Verbose),
 1602	graph_ref_all(GraphRefAll).
 1603update1(drop, drop(Verbose, GraphRefAll)) -->
 1604	silent(Verbose),
 1605	graph_ref_all(GraphRefAll).
 1606update1(create, create(Verbose, GraphRef)) -->
 1607	silent(Verbose),
 1608	graph_ref(GraphRef).
 1609update1(add, add(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1610	silent(Verbose),
 1611	graph_or_default(GraphOrDefaultFrom),
 1612	must_see_keyword("to"),
 1613	graph_or_default(GraphOrDefaultTo).
 1614update1(move, move(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1615	silent(Verbose),
 1616	graph_or_default(GraphOrDefaultFrom),
 1617	must_see_keyword("to"),
 1618	graph_or_default(GraphOrDefaultTo).
 1619update1(copy, copy(Verbose, GraphOrDefaultFrom, GraphOrDefaultTo)) -->
 1620	silent(Verbose),
 1621	graph_or_default(GraphOrDefaultFrom),
 1622	must_see_keyword("to"),
 1623	graph_or_default(GraphOrDefaultTo).
 1624update1(insert, insert_data(Quads)) -->
 1625	keyword("data"), !,
 1626	quad_data(Quads).
 1627update1(delete, delete_data(Quads)) -->
 1628	keyword("data"), !,
 1629	quad_data(Quads).
 1630update1(delete, delete_where(Quads)) -->
 1631	keyword("where"), !,
 1632	quad_pattern(Quads).
 modify(-Updated)//
 1636modify(modify(WithIRI, InsDel, Using, Pattern)) --> % [41]
 1637	optional_with(WithIRI),
 1638	(   delete_clause(Del),
 1639	    (	insert_clause(Ins)
 1640	    ->	{ InsDel = replace(Del,Ins) }
 1641	    ;	{ InsDel = delete(Del) }
 1642	    )
 1643	->  ""
 1644	;   insert_clause(Ins),
 1645	    { InsDel = insert(Ins) }
 1646	),
 1647	using_clauses(Using),
 1648	must_see_keyword("where"),
 1649	must_see_group_graph_pattern(Pattern).
 1650
 1651optional_with(with(IRI)) -->
 1652	keyword("with"), !,
 1653	must_see_iri(IRI).
 1654optional_with(without) -->
 1655	"".
 1656
 1657delete_clause(Quads) -->
 1658	keyword("delete"),
 1659	quad_pattern(Quads).
 1660insert_clause(Quads) -->
 1661	keyword("insert"),
 1662	quad_pattern(Quads).
 1663
 1664silent(silent) -->
 1665	keyword("silent"), !.
 1666silent(error) -->
 1667	"".
 1668
 1669using_clauses([U0|T]) -->
 1670	keyword("using"), !,
 1671	(   keyword("named"),
 1672	    must_see_iri(IRI)
 1673	->  { U0 = named(IRI) }
 1674	;   must_see_iri(U0)
 1675	),
 1676	using_clauses(T).
 1677using_clauses([]) -->
 1678	"".
 1679
 1680graph_ref(Graph) -->
 1681	keyword("graph"),
 1682	must_see_iri(Graph).
 1683
 1684graph_ref_all(graph(Graph)) -->
 1685	graph_ref(Graph), !.
 1686graph_ref_all(default) -->
 1687	keyword("default").
 1688graph_ref_all(named) -->
 1689	keyword("named").
 1690graph_ref_all(all) -->
 1691	keyword("all").
 1692
 1693graph_or_default(default) -->
 1694	keyword("default"), !.
 1695graph_or_default(graph(Graph)) -->
 1696	(   keyword("graph")
 1697	->  ""
 1698	;   ""
 1699	),
 1700	must_see_iri(Graph).
 1701
 1702quad_pattern(Quads) -->				% [48]
 1703	quad_data(Quads).
 1704
 1705quad_data(Quads) -->
 1706	"{", skip_ws,
 1707	(   quads(Quads),
 1708	    "}"
 1709	->  skip_ws
 1710	;   syntax_error(quads_expected)
 1711	).
 quads(-Quads)//
Quads is a list of triples and graph(Graph,Triples)
 1717quads(Quads) -->
 1718	triples_template(Quads, Tail), !,
 1719	quads_conts(Tail, []).
 1720quads(Quads) -->
 1721	quads_conts(Quads, []).
 1722
 1723quads_conts(Quads, Tail) -->
 1724	quads_cont(Quads, Tail2), !,
 1725	quads_conts(Tail2, Tail).
 1726quads_conts(Quads, Quads) -->
 1727	"".
 1728
 1729quads_cont([Graph|Tail0], Tail) -->
 1730	quads_not_triples(Graph),
 1731	optional_dot,
 1732	(   triples_template(Tail0, Tail)
 1733	->  ""
 1734	;   {Tail0=Tail}
 1735	).
 1736
 1737quads_not_triples(graph(IRI, Triples)) -->
 1738	keyword("graph"),
 1739	must_see_var_or_iri_ref(IRI),
 1740	must_see_open_brace,
 1741	(   triples_template(Triples, [])
 1742	->  ""
 1743	;   {Triples=[]}
 1744	),
 1745	must_see_close_brace.
 data_block(-DataBlock)// is det
DataBlock is one of
 1755data_block(Values) -->
 1756	inline_data_one_var(Values), !.
 1757data_block(Values) -->
 1758	inline_data_full(Values).
 1759
 1760inline_data_one_var(var_in(Var, Values)) -->
 1761	var(Var),
 1762	inline_values(Values).
 1763
 1764inline_values(Values) -->
 1765	(   datablock_body(Values)
 1766	->  ""
 1767	;   datablock_body_full(ListValues)
 1768	->  { maplist(single_body, ListValues, Values) }
 1769	;   syntax_error(datablock_values_expected)
 1770	).
 1771
 1772single_body([Var], Var).
 1773
 1774datablock_body(Values) -->
 1775	"{", skip_ws, datablock_values(Values), "}", skip_ws.
 1776
 1777datablock_values([V0|T]) -->
 1778	datablock_value(V0), !,
 1779	datablock_values(T).
 1780datablock_values([]) -->
 1781	"".
 1782
 1783datablock_value(V) -->
 1784	iri_ref(V), !.
 1785datablock_value(V) -->
 1786	rdf_literal(V), !.
 1787datablock_value(V) -->
 1788	numeric_literal(V), !.
 1789datablock_value(B) -->
 1790	boolean_literal(B), !.
 1791datablock_value(_) -->			% UNDEF acts as a variable
 1792	keyword("undef").
 1793
 1794inline_data_full(InlineData) -->
 1795	"(", skip_ws, vars(Vars),
 1796	(   ")"
 1797	->  skip_ws
 1798	;   syntax_error(expected(')'))
 1799	),
 1800	(   { Vars = [Var] }
 1801	->  inline_values(Values),
 1802	    { InlineData = var_in(Var, Values) }
 1803	;   datablock_body_full(Values)
 1804	->  { InlineData = vars_in(Vars, Values) }
 1805	;   syntax_error(datablock_values_expected)
 1806	), !.
 1807
 1808datablock_body_full(Values) -->
 1809	"{", skip_ws,
 1810	(   datablock_values_full(Values), "}"
 1811	->  skip_ws
 1812	;   syntax_error(datablock_values_expected)
 1813	).
 1814
 1815datablock_values_full([V0|T]) -->
 1816	datablock_value_full(V0), !,
 1817	datablock_values_full(T).
 1818datablock_values_full([]) -->
 1819	"".
 1820
 1821datablock_value_full(List) -->
 1822	"(", skip_ws,
 1823	datablock_values(List),
 1824	must_see_close_bracket.
 1825
 1826vars([H|T]) -->
 1827	var(H), !,
 1828	vars(T).
 1829vars([]) --> "".
 minus_graph_pattern(-Pattern) is det
 1834minus_graph_pattern(minus(Pattern)) -->
 1835	keyword("minus"),
 1836	must_see_group_graph_pattern(Pattern).
 triples_template(-Triples, Tail)//
 1840triples_template(Triples, Tail) -->	% [52]
 1841	triples_same_subject(Triples, Tail0),
 1842	(   "."
 1843	->  skip_ws,
 1844	    (	triples_template(Tail0, Tail)
 1845	    ->	""
 1846	    ;	{Tail = Tail0}
 1847	    )
 1848	;   {Tail = Tail0}
 1849	).
 group_graph_pattern(P)//
 1855group_graph_pattern(group(P)) -->		% [53]
 1856	skip_ws, "{", skip_ws,
 1857	(   sub_select(P0)
 1858	;   group_graph_pattern_sub(P0)
 1859	;   syntax_error(expected(graph_pattern))
 1860	), !,
 1861	(   "}"
 1862	->  skip_ws,
 1863	    { resolve_bnodes(P0, P) }
 1864	;   syntax_error(expected('}'))
 1865	).
 group_graph_pattern_sub(P)//
 1870group_graph_pattern_sub(P) -->		% [54]
 1871	triples_block(P0, []), !,
 1872	group_graph_pattern_sub_cont(P0, P).
 1873group_graph_pattern_sub(P) -->
 1874	group_graph_pattern_sub_cont(true, P).
 group_graph_pattern_sub_cont(+PLeft, P)//
Matches ( GraphPatternNotTriples '.'? TriplesBlock? )*
 1880group_graph_pattern_sub_cont(PLeft, P) -->
 1881	group_graph_pattern_sub_cont_1(PLeft, P0), !,
 1882	group_graph_pattern_sub_cont(P0, P).
 1883group_graph_pattern_sub_cont(PLeft, PLeft) --> "".
 1884
 1885group_graph_pattern_sub_cont_1(PLeft, P) -->
 1886	graph_pattern_not_triples(P0),
 1887	(   "."
 1888	->  skip_ws
 1889	;   ""
 1890	),
 1891	(   triples_block(P1, [])
 1892	->  { mkconj(P0, P1, P2),
 1893	      mkconj(PLeft, P2, P)
 1894	    }
 1895	;   { mkconj(PLeft, P0, P) }
 1896	).
 triples_block(-Triples, ?Tail)//
 1901triples_block(Triples, Tail) -->	% [55]
 1902	triples_same_subject_path(Triples, Tail0),
 1903	(   "."
 1904	->  skip_ws,
 1905	    (	triples_block(Tail0, Tail)
 1906	    ->	""
 1907	    ;	{ Tail = Tail0 }
 1908	    )
 1909	;   { Tail = Tail0 }
 1910	).
 1911
 1912
 1913one_dot -->
 1914	".", !, skip_ws,
 1915	(   "."
 1916	->  syntax_error(double_dot)
 1917	;   ""
 1918	).
 1919
 1920optional_dot --> ".", skip_ws.
 1921optional_dot --> "".
 graph_pattern_not_triples(-Pattern)//
 1926graph_pattern_not_triples(P) --> group_or_union_graph_pattern(P), !.
 1927graph_pattern_not_triples(P) --> optional_graph_pattern(P), !.
 1928graph_pattern_not_triples(P) --> minus_graph_pattern(P), !.
 1929graph_pattern_not_triples(P) --> graph_graph_pattern(P), !.
 1930graph_pattern_not_triples(P) --> service_graph_pattern(P), !.
 1931graph_pattern_not_triples(P) --> filter(P).
 1932graph_pattern_not_triples(P) --> bind(P).
 1933graph_pattern_not_triples(P) --> inline_data(P).
 optional_graph_pattern(Pattern)//
 1937optional_graph_pattern(Pattern) -->	% [57]
 1938	keyword("optional"),
 1939	must_see_group_graph_pattern(P0),
 1940	{ Pattern = optional(P0) }.
 graph_graph_pattern(-Graph)// is semidet
Processes a "graph ..." clause into

graph(Graph, Pattern)

 1948graph_graph_pattern(graph(Graph, Pattern)) --> % [58]
 1949	keyword("graph"), !,
 1950	must_see_var_or_iri_ref(Graph),
 1951	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>
}
 1973					% [59]
 1974service_graph_pattern(service(Silent, VarOrIRI, GroupGraphPattern, Query)) -->
 1975	keyword("service"), !,
 1976	silent(Silent),
 1977	must_see_var_or_iri_ref(VarOrIRI),
 1978	mark(Here),
 1979	must_see_group_graph_pattern(group(GroupGraphPattern)),
 1980	string_from_mark(Here, Query).
 1981
 1982mark(Here, Here, Here).
 1983
 1984string_from_mark(Start, String) -->
 1985	mark(End),
 1986	{ codes_between(Start, End, Codes),
 1987	  string_codes(String, Codes)
 1988	}.
 1989
 1990codes_between(Start, End, Codes) :-
 1991	same_term(Start, End), !,
 1992	Codes = [].
 1993codes_between([H|T], End, [H|C]) :-
 1994	codes_between(T, End, C).
 bind(P)
 1999bind(bind(Expr, Var)) -->		% [60]
 2000	keyword("bind"), !,
 2001	must_see_open_bracket,
 2002	must_see_expression(Expr),
 2003	must_see_keyword("as"),
 2004	must_see_var(Var),
 2005	must_see_close_bracket.
 inline_data(Data)
 2009inline_data(Values) -->
 2010	keyword("values"),
 2011	data_block(Values).
 group_or_union_graph_pattern(-Pattern)//
 2016group_or_union_graph_pattern(Pattern) --> % [67]
 2017	group_graph_pattern(P0),
 2018	add_union(P0, Pattern).
 2019
 2020add_union(P0, (P0;P)) -->
 2021	keyword("union"), !,
 2022	must_see_group_graph_pattern(P1),
 2023	add_union(P1, P).
 2024add_union(P, P) -->
 2025	[].
 filter(-Filter)//
 2030filter(filter(Exp)) -->
 2031	keyword("filter"),
 2032	(   constraint(Exp)
 2033	->  ""
 2034	;   syntax_error(filter_expected)
 2035	).
 constraint(-Filter)//
 2039constraint(Exp) -->
 2040	(   bracketted_expression(Exp)
 2041	->  []
 2042	;   built_in_call(Exp)
 2043	->  ""
 2044	;   function_call(Exp)
 2045	).
 function_call(-Function)// is semidet
Processes <URI>(Arg ...) into function(IRI, Args)
 2051function_call(function(F, Args)) -->
 2052	iri_ref(F),
 2053	arg_list(Args).
 arg_list(-List)//
 2058arg_list(ArgList) -->			% [71]
 2059	"(", skip_ws,
 2060	optional_distinct(ArgList, List),
 2061	(   expression(A0)
 2062	->  arg_list_cont(As),
 2063	    {List = [A0|As]}
 2064	;   {List = []}
 2065	),
 2066	(   ")"
 2067	->  []
 2068	;   syntax_error(expression_expected)
 2069	),
 2070	skip_ws.
 optional_distinct(-WrappedValue, -RealValue)//
Wrap argument in distinct(PlainArg) if there is a distinct keyword.
 2077optional_distinct(E, E1) -->
 2078	keyword("distinct"), !,
 2079	{ E = distinct(E1) }.
 2080optional_distinct(E, E) --> "".
 2081
 2082
 2083arg_list_cont([H|T]) -->
 2084	",", !, skip_ws,
 2085	must_see_expression(H),
 2086	arg_list_cont(T).
 2087arg_list_cont([]) -->
 2088	[].
 expression_list(-Expressions)//
 2092expression_list(ExprList) -->
 2093	"(", skip_ws,
 2094	(   expression(A0)
 2095	->  arg_list_cont(As),
 2096	    {ExprList = [A0|As]}
 2097	;   {ExprList = []}
 2098	),
 2099	(   ")"
 2100	->  []
 2101	;   syntax_error(expression_expected)
 2102	),
 2103	skip_ws.
 construct_template(Triples)// is semidet
 2107construct_template(Triples) -->
 2108	"{", skip_ws,
 2109	(   construct_triples(Triples), "}"
 2110	->  skip_ws
 2111	;   syntax_error(construct_template_expected)
 2112	).
 construct_triples(-List)//
 2116construct_triples(List) -->
 2117	construct_triples(List, []).
 2118
 2119construct_triples(List, T) -->
 2120	triples_same_subject(List, T0), !,
 2121	(   one_dot
 2122	->  (   peek(0'})
 2123	    ->  { T = T0 }
 2124	    ;   construct_triples(T0, T)
 2125	    )
 2126	;   { T = T0 }
 2127	).
 2128construct_triples(T, T) -->
 2129	"".
 triples_same_subject(-List, ?Tail)//
Return list of rdf(S,P,O) from triple spec.
 2135triples_same_subject(List, Tail) -->
 2136	var_or_term(S), !,
 2137	property_list_not_empty(L, List, T0),
 2138	{ make_triples_same_subject(L, S, T0, Tail) }.
 2139triples_same_subject(List, Tail) -->
 2140	triples_node(S, List, T0),
 2141	property_list(L, T0, T1),
 2142	{ make_triples_same_subject(L, S, T1, Tail) }.
 2143
 2144make_triples_same_subject([], _, T, T).
 2145make_triples_same_subject([property(P,O)|TP], S, [rdf(S,P,O)|T0], T) :-
 2146	make_triples_same_subject(TP, S, T0, T).
 property_list(-Properties, -Triples, ?TriplesTail)//
 2150property_list(L, Triples, Tail) -->
 2151	property_list_not_empty(L, Triples, Tail), !.
 2152property_list([], Tail, Tail) --> [].
 property_list_not_empty(-Properties, -Triples, ?TriplesTail)//
 2157property_list_not_empty(E, Triples, Tail) -->
 2158	verb(P),
 2159	must_see_object_list(OL, Triples, T0),
 2160	{ mk_proplist(OL, P, E, T) },
 2161	(   ";", skip_ws
 2162	->  property_list(T, T0, Tail)
 2163	;   { T = [],
 2164	      Tail = T0
 2165	    }
 2166	).
 2167
 2168mk_proplist([], _, T, T).
 2169mk_proplist([O|OT], P, [property(P,O)|T0], T) :-
 2170	mk_proplist(OT, P, T0, T).
 object_list(-L, -Triples, ?TriplesTail)//
 2174object_list(List, Triples, Tail) -->	% [79]
 2175	object(H, Triples, T0),
 2176	(   ",", skip_ws
 2177	->  { List = [H|T] },
 2178	    object_list(T, T0, Tail)
 2179	;   { List = [H],
 2180	      Tail = T0
 2181	    }
 2182	).
 2183
 2184must_see_object_list(List, Triples, Tail) -->
 2185	object_list(List, Triples, Tail), !.
 2186must_see_object_list(_,_,_) -->
 2187	syntax_error(object_list_expected).
 2188
 2189object(Obj, Triples, Tail) -->		% [80]
 2190	graph_node(Obj, Triples, Tail).
 verb(-E)//
 2194verb(E) --> var_or_iri_ref(E), !.	% [78]
 2195verb(E) --> "a", skip_ws, { rdf_equal(E, rdf:type) }.
 2196
 2197
 2198		 /*******************************
 2199		 *	      PATHS		*
 2200		 *******************************/
 2201
 2202/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 2203A property path basically describes a   complex relation from a resource
 2204to another resource. We represent a path   as rdf(S,P,O), where P is one
 2205of
 2206
 2207
 2208
 2209See http://www.w3.org/TR/sparql11-query/#propertypaths
 2210- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 triples_same_subject_path(-Triples, ?Tail)//
Similar to triples_same_subject//2, but the resulting property of each triple can be a path expression.
 2218triples_same_subject_path(Triples, Tail) -->
 2219	var_or_term(Subject), !,
 2220	property_list_path_not_empty(Props, Triples, Tail0),
 2221	{ make_triples_same_subject(Props, Subject, Tail0, Tail) }.
 2222triples_same_subject_path(Triples, Tail) -->
 2223	triples_node_path(Subject, Triples, Tail0),
 2224	property_list_path(Props, Tail0, Tail1),
 2225	{ make_triples_same_subject(Props, Subject, Tail1, Tail) }.
 2226
 2227property_list_path(Props, Triples, Tail) -->
 2228	property_list_path_not_empty(Props, Triples, Tail), !.
 2229property_list_path([], Triples, Triples) -->
 2230	"".
 2231
 2232property_list_path_not_empty(Props, Triples, Tail) --> % [83]
 2233	verb_path_or_simple(Path),
 2234	must_see_object_list_path(OL, Triples, Tail0),
 2235	{ mk_proplist(OL, Path, Props, T) },
 2236	(   ";", skip_ws
 2237	->  verb_object_lists(T, Tail0, Tail)
 2238	;   { T = [],
 2239	      Tail = Tail0
 2240	    }
 2241	).
 verb_object_lists(-Properties, -Triples, ?Tail)// is det
Parses ( ';' ( ( VerbPath | VerbSimple ) ObjectList )? )*
 2247verb_object_lists(Props, Triples, Tail) -->
 2248	verb_path_or_simple(Path), !,
 2249	must_see_object_list(OL, Triples, Tail0),
 2250	{ mk_proplist(OL, Path, Props, T) },
 2251	(   ";", skip_ws
 2252	->  verb_object_lists(T, Tail0, Tail)
 2253	;   { T = [],
 2254	      Tail = Tail0
 2255	    }
 2256	).
 2257verb_object_lists([], Triples, Triples) --> "".
 2258
 2259
 2260verb_path_or_simple(Path) -->
 2261	verb_path(Path), !.
 2262verb_path_or_simple(Path) -->
 2263	verb_simple(Path).
 2264
 2265verb_path(Path) -->			% [84]
 2266	path(Path).
 2267
 2268verb_simple(Var) -->
 2269	var(Var).
 2270
 2271must_see_object_list_path(Objects, Triples, Tail) -->
 2272	object_list_path(Objects, Triples, Tail), !.
 2273must_see_object_list_path(_,_,_) -->
 2274	syntax_error(object_list_path_expected).
 2275
 2276object_list_path(Objects, Triples, Tail) -->
 2277	object_path(H, Triples, Tail0),
 2278	(   ",", skip_ws
 2279	->  { Objects = [H|T] },
 2280	    object_list_path(T, Tail0, Tail)
 2281	;   { Objects = [H],
 2282	      Tail = Tail0
 2283	    }
 2284	).
 2285
 2286object_path(Object, Triples, Tail) -->
 2287	graph_node_path(Object, Triples, Tail).
 2288
 2289path(Path) -->
 2290	path_alternative(Path).
 2291
 2292path_alternative(PathAlt) -->
 2293	path_sequence(S0),
 2294	(   "|"
 2295	->  skip_ws,
 2296	    {PathAlt = (S0;S1)},
 2297	    path_alternative(S1)
 2298	;   {PathAlt = S0}
 2299	).
 2300
 2301path_sequence(PSeq) -->
 2302	path_elt_or_inverse(S0),
 2303	(   "/"
 2304	->  skip_ws,
 2305	    {PSeq = S0/PSeq2},
 2306	    path_sequence(PSeq2)
 2307	;   {PSeq = S0}
 2308	).
 2309
 2310path_elt_or_inverse(^(PathElt)) -->
 2311	"^", !, skip_ws,
 2312	path_elt(PathElt).
 2313path_elt_or_inverse(PathElt) -->
 2314	path_elt(PathElt).
 path_elt(PathElt)
One of [?*+=](PathPrimary)
 2320path_elt(PathElt) -->
 2321	path_primary(PP),
 2322	path_mod(PP, PathElt).
 2323
 2324path_mod(PP, ?(PP)) --> "?", \+ varname(_), !, skip_ws.
 2325path_mod(PP, *(PP)) --> "*", !, skip_ws.
 2326path_mod(PP, +(PP)) --> "+", !, skip_ws.
 2327path_mod(PP, PP) --> "".
 path_primary(-PathPrimary)//
 2332path_primary(IRI) -->			% [94]
 2333	iri_ref_or_a(IRI), !.
 2334path_primary(!(PathNegatedPropertySet)) -->
 2335	"!", !, skip_ws,
 2336	path_negated_property_set(PathNegatedPropertySet).
 2337path_primary(Path) -->
 2338	"(", !, skip_ws,
 2339	(   path(Path), ")"
 2340	->  skip_ws
 2341	;   syntax_error(path_expected)
 2342	).
 2343path_primary(distinct(Path)) -->
 2344	keyword("distinct"), !,
 2345	(   "(", skip_ws, path(Path), ")"
 2346	->  skip_ws
 2347	;   syntax_error(path_expected)
 2348	).
 2349
 2350path_negated_property_set(PathNegatedPropertySet) -->
 2351	"(", !, skip_ws,
 2352	(   paths_in_property_set(PathNegatedPropertySet),
 2353	    ")"
 2354	->  skip_ws
 2355	;   syntax_error(path_one_in_property_set_expected)
 2356	).
 2357path_negated_property_set(PathNegatedPropertySet) -->
 2358	path_one_in_property_set(PathNegatedPropertySet), !.
 2359
 2360paths_in_property_set(P) -->
 2361	path_one_in_property_set(P1),
 2362	(   "|"
 2363	->  skip_ws,
 2364	    paths_in_property_set(P2),
 2365	    { P=(P1;P2) }
 2366	;   { P=P1 }
 2367	).
 2368
 2369path_one_in_property_set(^(IRI)) -->
 2370	"^", !, skip_ws,
 2371	iri_ref_or_a(IRI).
 2372path_one_in_property_set(IRI) -->
 2373	iri_ref_or_a(IRI).
 2374
 2375iri_ref_or_a(IRI) -->
 2376	iri_ref(IRI).
 2377iri_ref_or_a(RdfType) -->
 2378	"a", !, skip_ws,
 2379	{ rdf_equal(RdfType, rdf:type) }.
 triples_node(-Subj, -Triples, ?TriplesTail)//
 2384triples_node(Subj, Triples, Tail) -->
 2385	collection(Subj, Triples, Tail), !.
 2386triples_node(Subj, Triples, Tail) -->
 2387	blank_node_property_list(Subj, Triples, Tail).
 blank_node_property_list(-Subj, -Triples, ?TriplesTail)//
 2391blank_node_property_list(Subj, Triples, Tail) -->
 2392	"[", skip_ws,
 2393	property_list_not_empty(List, Triples, T0),
 2394	"]", skip_ws,
 2395	{ make_triples_same_subject(List, Subj, T0, Tail) }.
 triples_node_path(-Subj, -Triples, ?Tail)//
 2399triples_node_path(Subj, Triples, Tail) -->
 2400	collection_path(Subj, Triples, Tail), !.
 2401triples_node_path(Subj, Triples, Tail) -->
 2402	blank_node_property_list_path(Subj, Triples, Tail).
 blank_node_property_list_path(-Subj, -Triples, ?TriplesTail)//
 2406blank_node_property_list_path(Subj, Triples, Tail) -->
 2407	"[", skip_ws,
 2408	property_list_path_not_empty(List, Triples, T0),
 2409	"]", skip_ws,
 2410	{ make_triples_same_subject(List, Subj, T0, Tail) }.
 collection(-Subj, -Triples, ?Tail)//
 2414collection(collection([H|T]), Triples, Tail) -->
 2415	"(", skip_ws,
 2416	graph_node(H, Triples, T0),
 2417	graph_nodes(T, T0, Tail),
 2418	")", skip_ws.
 collection_path(-Subj, -Triples, ?Tail)//
 2422collection_path(collection([H|T]), Triples, Tail) -->
 2423	"(", skip_ws,
 2424	(   graph_node_path(H, Triples, Tail0),
 2425	    graph_nodes_path(T, Tail0, Tail),
 2426	    ")"
 2427	->  skip_ws
 2428	;   syntax_error(graph_node_path_expected)
 2429	).
 2430
 2431
 2432graph_nodes([H|T], Triples, Tail) -->
 2433	graph_node(H, Triples, T0), !,
 2434	graph_nodes(T, T0, Tail).
 2435graph_nodes([], T, T) --> [].
 2436
 2437graph_nodes_path([H|T], Triples, Tail) -->
 2438	graph_node_path(H, Triples, T0), !,
 2439	graph_nodes_path(T, T0, Tail).
 2440graph_nodes_path([], T, T) --> [].
 graph_node(E, -Triples, ?TriplesTail)//
 2444graph_node(E, T, T)       --> var_or_term(E), !.
 2445graph_node(E, Triples, T) --> triples_node(E, Triples, T).
 graph_node_path(Node, Triples, Tail)//
 2449graph_node_path(E, T, T)          --> var_or_term(E), !.
 2450graph_node_path(E, Triples, Tail) --> triples_node_path(E, Triples, Tail).
 var_or_term(-E)//
 2454var_or_term(E) --> var(E), !.
 2455var_or_term(E) --> graph_term(E).
 var_or_iri_ref(-E)//
 2459var_or_iri_ref(E) --> var(E), !.
 2460var_or_iri_ref(E) --> iri_ref(E), !.
 var(-Var)//
 2464var(var(Name)) -->
 2465	(   var1(Name)
 2466	->  []
 2467	;   var2(Name)
 2468	).
 2469
 2470must_see_var(Var) -->
 2471	var(Var), !.
 2472must_see_var(_) -->
 2473	syntax_error(var_expected).
 2474
 2475must_see_var_or_iri_ref(Var) -->
 2476	var_or_iri_ref(Var), !.
 2477must_see_var_or_iri_ref(_) -->
 2478	syntax_error(var_or_iri_ref_expected).
 graph_term(-T)//
 2482graph_term(T)    --> iri_ref(T), !.
 2483graph_term(T)    --> rdf_literal(T), !.
 2484graph_term(T)    --> numeric_literal(T), !.
 2485graph_term(T)    --> boolean_literal(T), !.
 2486graph_term(T)	 --> blank_node(T).
 2487graph_term(T)	 --> nil(T).
 expression(-E)//
 2492expression(E) -->
 2493	conditional_or_expression(E),
 2494	skip_ws.
 2495
 2496must_see_expression(E) -->
 2497	expression(E), !.
 2498must_see_expression(_) -->
 2499	syntax_error(expression_expected).
 conditional_or_expression(-E)//
 2503conditional_or_expression(E) -->
 2504	conditional_and_expression(E0),
 2505	or_args(E0, E).
 2506
 2507or_args(E0, or(E0,E)) --> "||", !, skip_ws, value_logical(E1), or_args(E1, E).
 2508or_args(E, E) --> [].
 conditional_and_expression(-E)//
 2512conditional_and_expression(E) -->
 2513	value_logical(E0),
 2514	and_args(E0, E).
 2515
 2516and_args(E0, and(E0,E)) --> "&&", !, skip_ws, value_logical(E1), and_args(E1, E).
 2517and_args(E, E) --> [].
 value_logical(-E)//
 2522value_logical(E) --> relational_expression(E).
 relational_expression(E)//
 2526relational_expression(E) -->
 2527	numeric_expression(E0),
 2528	(   relational_op(Op)
 2529	->  skip_ws,
 2530	    numeric_expression(E1),
 2531	    { E =.. [Op,E0,E1] }
 2532	;   keyword("in")
 2533	->  expression_list(List),
 2534	    { E = in(E0, List) }
 2535	;   keyword("not"), keyword("in")
 2536	->  expression_list(List),
 2537	    { E = not_in(E0, List) }
 2538	;   { E = E0 }
 2539	).
 2540
 2541relational_op(=) --> "=".
 2542relational_op(\=) --> "!=".
 2543relational_op(>=) --> ">=".
 2544relational_op(>) --> ">".
 2545relational_op(Op) -->
 2546	"<", \+ (iri_codes(_), ">"),
 2547	(   "="
 2548	->  { Op = (=<) }
 2549	;   { Op = (<) }
 2550	).
 numeric_expression(-E)//
 2554numeric_expression(E) -->
 2555	additive_expression(E).
 additive_expression(-E)//
 2559additive_expression(E) -->
 2560	multiplicative_expression(E0),
 2561	add_args(E0, E).
 2562
 2563add_args(E0, E0+E) --> "+", !, skip_ws,
 2564	multiplicative_expression(E1), add_args(E1, E).
 2565add_args(E0, E0-E) --> "-", !, skip_ws,
 2566	multiplicative_expression(E1), add_args(E1, E).
 2567add_args(E, E) --> [].
 multiplicative_expression(-E)//
 2573multiplicative_expression(E) -->
 2574	unary_expression(E0),
 2575	mult_args(E0, E).
 2576
 2577mult_args(E0, E0*E) --> "*", !, skip_ws,
 2578	unary_expression(E1), mult_args(E1, E).
 2579mult_args(E0, E0/E) --> "/", !, skip_ws,
 2580	unary_expression(E1), mult_args(E1, E).
 2581mult_args(E, E) --> [].
 unary_expression(-E)//
 2586unary_expression(not(E)) --> "!", skip_ws, primary_expression(E).
 2587unary_expression(+(E))   --> "+", skip_ws, primary_expression(E).
 2588unary_expression(-(E))   --> "-", skip_ws, primary_expression(E).
 2589unary_expression(E)      -->		 primary_expression(E).
 primary_expression(-E)//
 2594primary_expression(E) --> bracketted_expression(E), !.
 2595primary_expression(E) --> built_in_call(E), !.
 2596primary_expression(E) --> iri_ref_or_function(E), !.
 2597primary_expression(E) --> rdf_literal(E), !.
 2598primary_expression(E) --> numeric_literal(E), !.
 2599primary_expression(E) --> boolean_literal(E), !.
 2600primary_expression(E) --> var(E), !.
 bracketted_expression(-E)//
 2605bracketted_expression(E) -->
 2606	"(", skip_ws, must_see_expression(E), ")", skip_ws.
 built_in_call(-Call)//
 2610built_in_call(F) -->			% [121]
 2611	get_keyword(KWD),
 2612	built_in_call(KWD, F).
 2613
 2614built_in_call(KWD, F) -->
 2615	{ built_in_function(KWD, Types) },
 2616	must_see_open_bracket,
 2617	arg_list(Types, Args),
 2618	must_see_close_bracket, !,
 2619	{   Args == []
 2620	->  F = built_in(KWD)
 2621	;   F =.. [KWD|Args]
 2622	}.
 2623built_in_call(KWD, F) -->
 2624	aggregate_call(KWD, F), !.
 2625built_in_call(coalesce, coalesce(List)) --> !,
 2626	expression_list(List).
 2627built_in_call(concat, concat(List)) --> !,
 2628	expression_list(List).
 2629built_in_call(substr, Substr) --> !,
 2630	substring_expression(Substr).
 2631built_in_call(replace, Replace) --> !,
 2632	str_replace_expression(Replace).
 2633built_in_call(regex, Regex) --> !,
 2634	regex_expression(Regex).
 2635built_in_call(exists, F) --> !,
 2636	exists_func(F).
 2637built_in_call(not, F) -->
 2638	not_exists_func(F).
 2639
 2640built_in_function(str,		  [expression]).
 2641built_in_function(lang,		  [expression]).
 2642built_in_function(langmatches,	  [expression, expression]).
 2643built_in_function(datatype,	  [expression]).
 2644built_in_function(bound,	  [var]).
 2645built_in_function(iri,		  [expression]).
 2646built_in_function(uri,		  [expression]).
 2647built_in_function(bnode,	  [expression]).
 2648built_in_function(bnode,	  []).
 2649built_in_function(rand,		  []).
 2650built_in_function(abs,		  [expression]).
 2651built_in_function(ceil,		  [expression]).
 2652built_in_function(floor,	  [expression]).
 2653built_in_function(round,	  [expression]).
 2654built_in_function(strlen,	  [expression]).
 2655built_in_function(ucase,	  [expression]).
 2656built_in_function(lcase,	  [expression]).
 2657built_in_function(encode_for_uri, [expression]).
 2658built_in_function(contains,	  [expression, expression]).
 2659built_in_function(strstarts,	  [expression, expression]).
 2660built_in_function(strends,	  [expression, expression]).
 2661built_in_function(strbefore,	  [expression, expression]).
 2662built_in_function(strafter,	  [expression, expression]).
 2663built_in_function(year,		  [expression]).
 2664built_in_function(month,	  [expression]).
 2665built_in_function(day,		  [expression]).
 2666built_in_function(hours,	  [expression]).
 2667built_in_function(minutes,	  [expression]).
 2668built_in_function(seconds,	  [expression]).
 2669built_in_function(timezone,	  [expression]).
 2670built_in_function(tz,		  [expression]).
 2671built_in_function(now,		  []).
 2672built_in_function(uuid,		  []).
 2673built_in_function(struuid,	  []).
 2674built_in_function(md5,		  [expression]).
 2675built_in_function(sha1,		  [expression]).
 2676built_in_function(sha256,	  [expression]).
 2677built_in_function(sha384,	  [expression]).
 2678built_in_function(sha512,	  [expression]).
 2679built_in_function(coalesce,	  [expression_list]).
 2680built_in_function(if,		  [expression, expression, expression]).
 2681built_in_function(strlang,	  [expression, expression]).
 2682built_in_function(strdt,	  [expression, expression]).
 2683built_in_function(sameterm,	  [expression, expression]).
 2684built_in_function(isiri,	  [expression]).
 2685built_in_function(isuri,	  [expression]).
 2686built_in_function(isblank,	  [expression]).
 2687built_in_function(isliteral,	  [expression]).
 2688built_in_function(isnumeric,	  [expression]).
 2689
 2690term_expansion(built_in_function(f), Clauses) :-
 2691	findall(built_in_function(F),
 2692		( built_in_function(Name, Args),
 2693		  length(Args, Argc),
 2694		  functor(F, Name, Argc)
 2695		),
 2696		Clauses).
 built_in_function(?Term) is nondet
Fact that describes defined builtin functions. Used by resolve_expression/4.
 2703built_in_function(regex(_,_,_)).
 2704built_in_function(replace(_,_,_,_)).
 2705built_in_function(substr(_,_,_)).
 2706built_in_function(substr(_,_)).
 2707built_in_function(f).
 2708
 2709
 2710arg_list([], []) --> "".
 2711arg_list([HT|TT], [HA|TA]) -->
 2712	arg(HT, HA),
 2713	arg_list_cont(TT, TA).
 2714
 2715arg_list_cont([], []) -->
 2716	[].
 2717arg_list_cont([H|T], [A|AT]) -->
 2718	",", skip_ws,
 2719	arg(H, A),
 2720	arg_list_cont(T, AT).
 2721
 2722arg(expression, A) --> expression(A).
 2723arg(var,        A) --> var(A).
 regex_expression(-Regex)//
 2727regex_expression(regex(Target, Pattern, Flags)) -->
 2728	must_see_open_bracket,
 2729	must_see_expression(Target),
 2730	must_see_comma,
 2731	must_see_expression(Pattern),
 2732	(   ",", skip_ws, must_see_expression(Flags)
 2733	->  []
 2734	;   {Flags = literal('')}
 2735	),
 2736	must_see_close_bracket.
 substring_expression(Expr)//
 2740substring_expression(Expr) --> % [123]
 2741	must_see_open_bracket,
 2742	must_see_expression(Source),
 2743	must_see_comma,
 2744	must_see_expression(StartingLoc),
 2745	(   ","
 2746	->  skip_ws,
 2747	    must_see_expression(Length),
 2748	    { Expr = substr(Source, StartingLoc, Length) }
 2749	;   { Expr = substr(Source, StartingLoc) }
 2750	),
 2751	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.
 2761must_see_comma         --> must_see_punct(0',).
 2762must_see_open_bracket  --> must_see_punct(0'().
 2763must_see_close_bracket --> must_see_punct(0')).
 2764must_see_open_brace    --> must_see_punct(0'{).
 2765must_see_close_brace   --> must_see_punct(0'}).
 2766
 2767must_see_punct(C) -->
 2768	[C], !, skip_ws.
 2769must_see_punct(C) -->
 2770	{ char_code(Char, C) },
 2771	syntax_error(expected(Char)).
 str_replace_expression(Expr)//
 2776str_replace_expression(replace(Arg, Pattern, Replacement, Flags)) --> % [124]
 2777	must_see_open_bracket,
 2778	must_see_expression(Arg),
 2779	must_see_comma,
 2780	must_see_expression(Pattern),
 2781	must_see_comma,
 2782	must_see_expression(Replacement),
 2783	(   ",", skip_ws, must_see_expression(Flags)
 2784	    ->  []
 2785	    ;   {Flags = literal('')}
 2786	),
 2787	must_see_close_bracket.
 exists_func(F)//
 2791exists_func(exists(Pattern)) -->	% [125]
 2792	must_see_group_graph_pattern(Pattern).
 2793
 2794not_exists_func(not_exists(Pattern)) --> % [126]
 2795	keyword("exists"),
 2796	must_see_group_graph_pattern(Pattern).
 aggregate_call(+Keyword, -Aggregate)//
Renamed from aggregate to avoid confusion with popular predicate.
 2802aggregate_call(count, Aggregate) -->		% [127]
 2803	aggregate_count(Aggregate), !.
 2804aggregate_call(Agg, Aggregate) -->
 2805	{ aggregate_keyword(Agg) }, !,
 2806	must_see_open_bracket,
 2807	{ Aggregate =.. [Agg,AggArg] },
 2808	optional_distinct(AggArg, AggExpr),
 2809	expression(AggExpr),
 2810	must_see_close_bracket.
 2811aggregate_call(group_concat, Aggregate) -->
 2812	aggregate_group_concat(Aggregate).
 2813
 2814aggregate_keyword(sum).
 2815aggregate_keyword(min).
 2816aggregate_keyword(max).
 2817aggregate_keyword(avg).
 2818aggregate_keyword(sample).
 2819
 2820aggregate_count(count(Count)) -->
 2821	must_see_open_bracket,
 2822	optional_distinct(Count, C1),
 2823	(   "*"
 2824	    ->  skip_ws,
 2825	    { C1 = (*) }
 2826	    ;   expression(C1)
 2827	),
 2828	must_see_close_bracket.
 2829
 2830
 2831aggregate_group_concat(group_concat(Expr, literal(Sep))) -->
 2832	must_see_open_bracket,
 2833	optional_distinct(Expr, Expr2),
 2834	expression(Expr2),
 2835	(   ";"
 2836	->  skip_ws,
 2837	    must_see_keyword("separator"),
 2838	    must_see_punct(0'=),
 2839	    string(Sep)
 2840	;   {Sep = ' '}			% default sep is a single space
 2841	),
 2842	must_see_close_bracket.
 aggregate_op(?Op) is nondet
Declaration to support resolving aggregates
 2848aggregate_op(count(_)).
 2849aggregate_op(sum(_)).
 2850aggregate_op(min(_)).
 2851aggregate_op(max(_)).
 2852aggregate_op(avg(_)).
 2853aggregate_op(sample(_)).
 2854aggregate_op(group_concat(_,_)).
 iri_ref_or_function(-Term)//
 2858iri_ref_or_function(Term) -->
 2859	iri_ref(IRI),
 2860	(   arg_list(Args)
 2861	->  { Term = function(IRI, Args) }
 2862	;   { Term = IRI }
 2863	).
 rdf_literal(-Literal)//
 2867rdf_literal(literal(Value)) -->
 2868	string(String),
 2869	(   langtag(Lang)
 2870	->  { Value = lang(Lang, String) }
 2871	;   "^^", iri_ref(IRI)
 2872	->  { Value = type(IRI, String) }
 2873	;   { Value = String }
 2874	),
 2875	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.

 2888numeric_literal(literal(type(Type, Value))) -->
 2889	optional_pm(Codes, CV),
 2890	(   double_string(CV)
 2891	->  { rdf_equal(xsd:double, Type) }
 2892	;   decimal_string(CV)
 2893	->  { rdf_equal(xsd:decimal, Type) }
 2894	;   integer_string(CV)
 2895	->  { rdf_equal(xsd:integer, Type) }
 2896	), !,
 2897	{ atom_codes(Value, Codes)
 2898	},
 2899	skip_ws.
 boolean_literal(-TrueOrFalse)//
 2903boolean_literal(Lit) -->
 2904	(   keyword("true")
 2905	->  { Lit = boolean(true) }
 2906	;   keyword("false")
 2907	->  { Lit = boolean(false) }
 2908	).
 string(-Atom)//
 2912string(Atom) --> string_literal_long1(Atom), !.
 2913string(Atom) --> string_literal_long2(Atom), !.
 2914string(Atom) --> string_literal1(Atom), !.
 2915string(Atom) --> string_literal2(Atom).
 iri_ref(IRI)//
 2919iri_ref(IRI) -->
 2920	q_iri_ref(IRI).
 2921iri_ref(IRI) -->
 2922	qname(IRI).			% TBD: qname_ns also returns atom!?
 2923
 2924must_see_iri(IRI) -->
 2925	iri_ref(IRI), !.
 2926must_see_iri(_) -->
 2927	syntax_error(iri_expected).
 qname(-Term)//
TBD: Looks like this is ambiguous!?
 2933qname(Term) -->
 2934	'QNAME'(Term), !, skip_ws.
 2935qname(Q:'') -->
 2936	qname_ns(Q).
 blank_node(-Id)//
Blank node. Anonymous blank nodes are returned with unbound Id
 2942blank_node(Id) -->
 2943	blank_node_label(Id), !.
 2944blank_node(Id) -->
 2945	anon(Id).
 2946
 2947		 /*******************************
 2948		 *	       BASICS		*
 2949		 *******************************/
 q_iri_ref(-Atom)//
 2953q_iri_ref(Atom) -->
 2954	"<",
 2955	(    q_iri_ref_codes(Codes), ">"
 2956	->   skip_ws,
 2957	     { atom_codes(Atom, Codes) }
 2958	;    syntax_error(illegal_qualified_iri)
 2959	).
 2960
 2961q_iri_ref_codes([]) -->
 2962	[].
 2963q_iri_ref_codes([H|T]) -->
 2964	iri_code(H), !,
 2965	q_iri_ref_codes(T).
 2966q_iri_ref_codes(_) -->
 2967	syntax_error(illegal_code_in_iri).
 2968
 2969iri_codes([H|T]) -->
 2970	iri_code(H), !,
 2971	iri_codes(T).
 2972iri_codes([]) -->
 2973	[].
 2974
 2975iri_code(Code) -->
 2976	[Code],
 2977	{ \+ not_iri_code(Code) }, !.
 2978
 2979not_iri_code(0'<).
 2980not_iri_code(0'>).
 2981not_iri_code(0'').
 2982not_iri_code(0'{).
 2983not_iri_code(0'}).
 2984not_iri_code(0'|).
 2985not_iri_code(0'\\).			% not sure!?
 2986not_iri_code(0'`).
 2987not_iri_code(Code) :- between(0x00, 0x20, Code).
 qname_ns(Q)//
 2992qname_ns(Q) -->
 2993	ncname_prefix(Q), ":", !, skip_ws.
 2994qname_ns('') -->
 2995	":", skip_ws.
 2996
 2997%	'QNAME'(-Term)//
 2998%
 2999%	Qualified name.  Term is one of Q:N or '':N
 3000
 3001'QNAME'(Q:N) -->
 3002	ncname_prefix(Q), ":", !, pn_local(N).
 3003'QNAME'('':N) -->
 3004	":", pn_local(N).
 blank_node_label(-Bnode)// is semidet
Processes "_:..." into a bnode(Name) term.
 3011blank_node_label(bnode(Name)) -->
 3012	"_:", pn_local(Name), skip_ws.
 var1(-Atom)// is semidet
 var2(-Atom)// is semidet
 3018var1(Name) --> "?", varname(Name).
 3019var2(Name) --> "$", varname(Name).
 langtag(-Tag)//
Return language tag (without leading @)
 3026langtag(Atom) -->
 3027	"@",
 3028	one_or_more_ascii_letters(Codes, T0),
 3029	sub_lang_ids(T0, []),
 3030	skip_ws,
 3031	{ atom_codes(Atom, Codes) }.
 3032
 3033sub_lang_ids([0'-|Codes], Tail) -->
 3034	"-", !,
 3035	one_or_more_ascii_letter_or_digits(Codes, T0),
 3036	sub_lang_ids(T0, Tail).
 3037sub_lang_ids(T, T) -->
 3038	[].
 integer(-Integer)// is semidet
Match an integer and return its value.
 3045integer(Integer) -->
 3046	integer_string(Codes),
 3047	{ number_codes(Integer, Codes)
 3048	},
 3049	skip_ws.
 integer_string(-Codes)// is semidet
Extract integer value.
 3056integer_string(Codes) -->
 3057	one_or_more_digits(Codes, []), !.
 decimal_string(-Codes)//
Extract float without exponent and return the matched text as a list of codes.
 3064decimal_string(Codes) -->
 3065	one_or_more_digits(Codes, T0), !,
 3066	dot(T0, T1),
 3067	digits(T1, []).
 3068decimal_string(Codes) -->
 3069	dot(Codes, T1),
 3070	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.
 3078double_string(Codes) -->
 3079	one_or_more_digits(Codes, T0), !,
 3080	dot(T0, T1),
 3081	digits(T1, T2),
 3082	exponent(T2, []).
 3083double_string(Codes) -->
 3084	dot(Codes, T1),
 3085	one_or_more_digits(T1, T2), !,
 3086	exponent(T2, []).
 3087double_string(Codes) -->
 3088	one_or_more_digits(Codes, T2), !,
 3089	exponent(T2, []).
 3090
 3091dot([0'.|T], T) --> ".".		% 0'
 exponent(-Codes, ?Tail)//
Float exponent. Returned as difference-list
 3098exponent(Codes, T) -->
 3099	optional_e(Codes, T0),
 3100	optional_pm(T0, T1),
 3101	one_or_more_digits(T1, T).
 3102
 3103optional_e([0'e|T], T) -->
 3104	(   "e"
 3105	;   "E"
 3106	), !.
 3107optional_e(T, T) -->
 3108	"".
 3109
 3110optional_pm([C|T], T) -->
 3111	[C],
 3112	{ C == 0'+ ; C == 0'- }, !.
 3113optional_pm(T, T) -->
 3114	"".
 string_literal1(-Atom)//
 3118string_literal1(Atom) -->
 3119	"'", !,
 3120	string_literal_codes(Codes),
 3121	"'", !,
 3122	{ atom_codes(Atom, Codes) }.
 string_literal2(-Atom)//
 3126string_literal2(Atom) -->
 3127	"\"", !,
 3128	string_literal_codes(Codes),
 3129	"\"", !,
 3130	{ atom_codes(Atom, Codes) }.
 3131
 3132string_literal_codes([]) -->
 3133	"".
 3134string_literal_codes([H|T]) -->
 3135	(   echar(H)
 3136	;   [H], { \+ not_in_string_literal(H) }
 3137	),
 3138	string_literal_codes(T).
 3139
 3140not_in_string_literal(0x5C).
 3141not_in_string_literal(0x0A).
 3142not_in_string_literal(0x0D).
 string_literal_long1(-Atom)//
 3146string_literal_long1(Atom) -->
 3147	"'''", !,
 3148	string_literal_codes_long(Codes),
 3149	"'''", !,
 3150	{ atom_codes(Atom, Codes) }.
 string_literal_long2(-Atom)//
 3154string_literal_long2(Atom) -->
 3155	"\"\"\"", !,
 3156	string_literal_codes_long(Codes),
 3157	"\"\"\"", !,
 3158	{ atom_codes(Atom, Codes) }.
 3159
 3160string_literal_codes_long([]) -->
 3161	"".
 3162string_literal_codes_long([H|T]) -->
 3163	(   echar(H)
 3164	;   [H], { H \== 0'\\ }
 3165	),
 3166	string_literal_codes_long(T).
 echar(-Code)//
Escaped character
 3173echar(Code) -->
 3174	"\\", echar2(Code).
 3175
 3176echar2(0'\t) --> "t".
 3177echar2(0'\b) --> "b".
 3178echar2(0'\n) --> "n".
 3179echar2(0'\r) --> "r".
 3180echar2(0'\f) --> "f".
 3181echar2(0'\\) --> "\\".
 3182echar2(0'")  --> "\"".
 3183echar2(0'')  --> "'".
 hex(-Weigth)//
HEX digit (returning numeric value)
 3189hex(Weigth) -->
 3190	[C],
 3191	{ code_type(C, xdigit(Weigth)) }.
 nil(-NIL)//
End-of-collection (rdf:nil)
 3198nil(NIL) --> "(", ws_star, ")", skip_ws, { rdf_equal(NIL, rdf:nil) }.
 3199
 3200%	ws//
 3201%
 3202%	white space characters.
 3203
 3204ws --> [0x20].
 3205ws --> [0x09].
 3206ws --> [0x0D].
 3207ws --> [0x0A].
 3208
 3209%	ws_star//
 3210
 3211ws_star --> ws, !, ws_star.
 3212ws_star --> "".
 3213
 3214%	anon//
 3215%
 3216%	Anonymous resource
 3217
 3218anon(bnode(_)) --> "[", ws_star, "]", skip_ws.
 pn_chars_base(-Code)//
Basic identifier characters
 3225pn_chars_base(Code) -->
 3226	esc_code(Code),
 3227	{ pn_chars_base(Code) }, !.
 3228
 3229pn_chars_base(Code) :- between(0'A, 0'Z, Code).
 3230pn_chars_base(Code) :- between(0'a, 0'z, Code).
 3231pn_chars_base(Code) :- between(0x00C0, 0x00D6, Code).
 3232pn_chars_base(Code) :- between(0x00D8, 0x00F6, Code).
 3233pn_chars_base(Code) :- between(0x00F8, 0x02FF, Code).
 3234pn_chars_base(Code) :- between(0x0370, 0x037D, Code).
 3235pn_chars_base(Code) :- between(0x037F, 0x1FFF, Code).
 3236pn_chars_base(Code) :- between(0x200C, 0x200D, Code).
 3237pn_chars_base(Code) :- between(0x2070, 0x218F, Code).
 3238pn_chars_base(Code) :- between(0x2C00, 0x2FEF, Code).
 3239pn_chars_base(Code) :- between(0x3001, 0xD7FF, Code).
 3240pn_chars_base(Code) :- between(0xF900, 0xFDCF, Code).
 3241pn_chars_base(Code) :- between(0xFDF0, 0xFFFD, Code).
 3242pn_chars_base(Code) :- between(0x10000, 0xEFFFF, Code).
 3243
 3244esc_code(Code) -->
 3245	[ Code ].
 pn_chars_u(?Code)
Allows for _
 3251pn_chars_u(Code) :-
 3252	pn_chars_base(Code).
 3253pn_chars_u(0'_).
 varname(-Atom)//
Name of a variable (after the ? or $)
 3260varname(Atom) -->
 3261	varchar1(C0),
 3262	varchars(Cs),
 3263	{ atom_codes(Atom, [C0|Cs]) },
 3264	skip_ws.
 3265
 3266varchar1(Code) -->
 3267	esc_code(Code),
 3268	{ varchar1(Code) }.
 3269
 3270varchar1(Code) :-
 3271	pn_chars_u(Code), !.
 3272varchar1(Code) :-
 3273	between(0'0, 0'9, Code), !.
 3274
 3275varchars([H|T]) -->
 3276	varchar(H), !,
 3277	varchars(T).
 3278varchars([]) -->
 3279	[].
 3280
 3281varchar(Code) -->
 3282	esc_code(Code),
 3283	{ varchar(Code) }.
 3284
 3285varchar(Code) :-
 3286	varchar1(Code), !.
 3287varchar(Code) :-
 3288	varchar_extra(Code), !.
 3289
 3290varchar_extra(0x00B7).
 3291varchar_extra(Code) :- between(0x0300, 0x036F, Code).
 3292varchar_extra(Code) :- between(0x203F, 0x2040, Code).
 3293
 3294ncchar(Code) :-
 3295	varchar(Code), !.
 3296ncchar(0'-).
 ncname_prefix(-Atom)//
 3300ncname_prefix(Atom) -->
 3301	pn_chars_base(C0),
 3302	(   ncname_prefix_suffix(Cs)
 3303	->  { atom_codes(Atom, [C0|Cs]) }
 3304        ;   { char_code(Atom, C0) }
 3305	).
 3306
 3307ncname_prefix_suffix(Codes) -->
 3308	ncchar_or_dots(Codes, []),
 3309	{ \+ last(Codes, 0'.) }, !.
 3310
 3311ncchar_or_dots([H|T0], T) -->
 3312	ncchar_or_dot(H),
 3313	ncchar_or_dots(T0, T).
 3314ncchar_or_dots(T, T) -->
 3315	[].
 3316
 3317ncchar_or_dot(Code) -->
 3318	esc_code(Code),
 3319	{ ncchar_or_dot(Code) }.
 3320
 3321ncchar_or_dot(Code) :-
 3322	ncchar(Code), !.
 3323ncchar_or_dot(0'.).
 pn_local(-Atom)//
 3327pn_local(Atom) -->			% [169]
 3328	localchar1(Codes, Tail),
 3329	pn_local_suffix(Tail),
 3330	{ atom_codes(Atom, Codes) }.
 3331
 3332pn_local_suffix(Codes) -->
 3333	pnchars(Codes, Tail),
 3334	pnchar_last(Tail, []), !.
 3335pn_local_suffix([]) -->
 3336	"".
 3337
 3338pnchars(List, Tail) -->
 3339	pnchar(List, Tail0),
 3340	pnchars(Tail0, Tail).
 3341pnchars(T, T) --> "".
 3342
 3343pnchar([C|T], T) -->
 3344	[C],
 3345	{ pnchar(C) }, !.
 3346pnchar(Codes, Tail) -->
 3347	plx(Codes, Tail).
 3348
 3349pnchar(C) :- varchar(C).
 3350pnchar(0'-).
 3351pnchar(0'.).
 3352pnchar(0':).
 3353
 3354pnchar_last([C|T], T) -->
 3355	[C],
 3356	{ pnchar_last(C) }, !.
 3357pnchar_last(Codes, Tail) -->
 3358	plx(Codes, Tail).
 3359
 3360pnchar_last(C) :- varchar(C).
 3361pnchar_last(0':).
 3362
 3363
 3364localchar1([Code|Tail], Tail) -->
 3365	esc_code(Code),
 3366	{ localchar1(Code) }, !.
 3367localchar1(Codes, Tail) -->
 3368	plx(Codes, Tail).
 3369
 3370plx(Codes, Tail) -->
 3371	percent(Codes, Tail).
 3372plx(Codes, Tail) -->
 3373	pn_local_esc(Codes, Tail).
 3374
 3375percent(Codes, Tail) -->		% [171]
 3376	"%", [H1,H2],
 3377	{ code_type(H1, xdigit(_)),
 3378	  code_type(H2, xdigit(_)),
 3379	  Codes = [0'%,H1,H2|Tail]
 3380	}.
 3381
 3382localchar1(Code) :-
 3383	pn_chars_u(Code), !.
 3384localchar1(Code) :-
 3385	between(0'0, 0'9, Code), !.
 3386localchar1(0':).
 3387
 3388pn_local_esc(List, T) -->		% [173]
 3389	"\\",
 3390	[C],
 3391	{ pn_local_esc(C),
 3392	  List = [C|T]
 3393	}.
 3394
 3395pnle('_~.-!$&\'()*+,;=/?#@%').
 3396
 3397term_expansion(pn_local_esc(esc), Clauses) :-
 3398	pnle(Atom),
 3399	findall(pn_local_esc(C),
 3400		( sub_atom(Atom, _, 1, _, Char),
 3401		  char_code(Char, C)
 3402		), Clauses).
 3403
 3404pn_local_esc(esc).
 3405
 3406
 3407
 3408		 /*******************************
 3409		 *	      EXTRAS		*
 3410		 *******************************/
 3411
 3412digit(Code) -->
 3413	[Code],
 3414	{ between(0'0, 0'9, Code) }.
 3415
 3416ascii_letter(Code) -->
 3417	[Code],
 3418	{ between(0'a, 0'z, Code)
 3419	; between(0'A, 0'Z, Code)
 3420	}, !.
 3421
 3422ascii_letter_or_digit(Code) -->
 3423	[Code],
 3424	{ between(0'a, 0'z, Code)
 3425	; between(0'A, 0'Z, Code)
 3426	; between(0'0, 0'9, Code)
 3427	}, !.
 3428
 3429digits([H|T0], T) -->
 3430	digit(H), !,
 3431	digits(T0, T).
 3432digits(T, T) -->
 3433	[].
 3434
 3435ascii_letters([H|T0], T) -->
 3436	ascii_letter(H), !,
 3437	ascii_letters(T0, T).
 3438ascii_letters(T, T) -->
 3439	[].
 3440
 3441ascii_letter_or_digits([H|T0], T) -->
 3442	ascii_letter_or_digit(H), !,
 3443	ascii_letter_or_digits(T0, T).
 3444ascii_letter_or_digits(T, T) -->
 3445	[].
 3446
 3447one_or_more_digits([C0|CT], Tail) -->
 3448	digit(C0),
 3449	digits(CT, Tail).
 3450
 3451one_or_more_ascii_letters([C0|CT], Tail) -->
 3452	ascii_letter(C0),
 3453	ascii_letters(CT, Tail).
 3454
 3455one_or_more_ascii_letter_or_digits([C0|CT], Tail) -->
 3456	ascii_letter_or_digit(C0),
 3457	ascii_letter_or_digits(CT, Tail).
 keyword(+Codes)
Case-insensitive match for a keyword.
 3463keyword([]) -->
 3464	(  ascii_letter(_)
 3465	-> !, {fail}
 3466	;  skip_ws
 3467	).
 3468keyword([H|T]) -->
 3469	[C],
 3470	{ code_type(H, to_lower(C)) },
 3471	keyword(T).
 must_see_keyword(+Codes)
 3475must_see_keyword(Codes) -->
 3476	keyword(Codes), !.
 3477must_see_keyword(Codes) -->
 3478	{ atom_codes(Atom, Codes),
 3479	  upcase_atom(Atom, Keyword)
 3480	},
 3481	syntax_error(expected(Keyword)).
 get_keyword(-Atom)
Get next identifier as lowercase
 3488get_keyword(Atom) -->
 3489	one_or_more_keyword_chars(Letters),
 3490	{ atom_codes(Raw, Letters),
 3491	  downcase_atom(Raw, Atom)
 3492	},
 3493	skip_ws.
 3494
 3495one_or_more_keyword_chars([H|T]) -->
 3496	keyword_char(H),
 3497	keyword_chars(T).
 3498
 3499keyword_chars([H|T]) -->
 3500	keyword_char(H), !,
 3501	keyword_chars(T).
 3502keyword_chars([]) --> "".
 3503
 3504keyword_char(C)   --> ascii_letter(C), !.
 3505keyword_char(C)   --> digit(C), !.
 3506keyword_char(0'_) --> "_".
 3507
 3508
 3509
 3510%	skip_ws//
 3511
 3512skip_ws -->
 3513	ws, !,
 3514	skip_ws.
 3515skip_ws -->
 3516	"#", !,
 3517	skip_comment,
 3518	skip_ws.
 3519skip_ws -->
 3520	[].
 3521
 3522skip_comment --> "\n", !.
 3523skip_comment --> "\r", !.
 3524skip_comment --> eos, !.
 3525skip_comment --> [_], skip_comment.
 3526
 3527eos([], []).
 3528
 3529peek(C, L, L) :-
 3530	L = [C|_]