View source with formatted 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): 2004-2017, 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_runtime,
   32	  [ sparql_true/1,		% +Expression
   33	    sparql_eval/2,		% +Expression, -Value
   34	    sparql_eval_raw/2,		% +Expression, -Value
   35	    sparql_simplify/2,		% :Goal, -SimpleGoal
   36	    sparql_subquery/3,		% +Proj, +Query, +Sols
   37	    sparql_update/1,		% +UpdateRequest
   38	    sparql_find/5,		% ?From, ?To, ?F, ?T, :Q
   39	    sparql_minus/2,		% :Pattern1, :Pattern2
   40	    sparql_group/1,		% :Query
   41	    sparql_group/3,		% :Query, +OuterVars, +InnerVars
   42	    sparql_service/5,		% +Silent, +URL, +Prefixes, +Vars, +QText
   43	    sparql_reset_bnodes/0
   44	  ]).   45:- use_module(library(semweb/rdf_db)).   46:- use_module(library(semweb/rdf11), [rdf_lexical_form/2]).   47:- use_module(library(xsdp_types)).   48:- use_module(library(lists)).   49:- use_module(library(apply)).   50:- use_module(library(assoc)).   51:- use_module(library(ordsets)).   52:- use_module(library(uri)).   53:- use_module(library(dcg/basics)).   54:- use_module(library(semweb/sparql_client)).   55:- use_module(library(debug)).   56:- use_module(library(error)).   57:- if(exists_source(library(uuid))).   58:- use_module(library(uuid)).   59:- endif.   60
   61:- discontiguous
   62	term_expansion/2.   63
   64:- meta_predicate
   65	sparql_find(?, ?, ?, ?, 0),
   66	sparql_minus(0, 0),
   67	sparql_group(0),
   68	sparql_group(0, +, +),
   69	sparql_subquery(+, 0, +),
   70	sparql_update(:).   71
   72/** <module> SPARQL runtime support
   73
   74@see	rdfql_runtime.pl merges this module with generic predicates as well
   75	as runtime libraries for other query languages.
   76@see	These routines are part of the _entailment_ modules.  See
   77	../entailment/README.txt
   78*/
   79
   80:- thread_local
   81	bnode_store/2.   82
   83%%	sparql_true(+Term)
   84%
   85%	Generated from FILTER Term, where Term must be converted to a
   86%	boolean as 'Effective Boolean Value'.
   87
   88sparql_true(Term) :-
   89	typed_eval(boolean, Term, Result), !,
   90	true(Result).
   91
   92true(boolean(true)).
   93
   94%%	eval(+Term, -Result)
   95
   96eval(Var, unbound(Var)) :-
   97	var(Var), !.
   98eval(literal(Literal), Result) :- !,
   99	eval_literal(Literal, Result).
  100eval(Atom, iri(Atom)) :-
  101	atom(Atom), !.
  102eval(built_in(Term), Result) :- !,
  103	op(Term, Result).
  104eval(Term, Result) :-
  105	sparql_op(Term), !,
  106	op(Term, Result).
  107eval(function(Term), Result) :- !,
  108	(   xsd_cast(Term, Type, Value0)
  109	->  eval(Value0, Value),
  110	    eval_cast(Type, Value, Result)
  111	;   eval_function(Term, Result)
  112	).
  113eval(Term, Term).			% Result of sub-eval
  114
  115%%	eval(+Type, +Term, -Result) is semidet.
  116%
  117%	Evaluate Term, converting the resulting argument to Type.
  118
  119typed_eval(no_eval, Term, Term).
  120typed_eval(any, Term, Result) :-
  121	eval(Term, Result).
  122typed_eval(simple_literal, Term, Result) :-
  123	eval(Term, Result).
  124typed_eval(boolean, Term, Result) :-
  125	eval(Term, Result0),
  126	effective_boolean_value(Result0, Result).
  127typed_eval(numeric, Term, Result) :-
  128	eval(Term, Result),
  129	Result = numeric(_,_).
  130
  131
  132eval_literal(type(Type, Atom), Value) :- !,
  133	eval_typed_literal(Type, Atom, Value).
  134eval_literal(lang(Lang, Atom), lang(Lang, Atom)) :- !.
  135eval_literal(Atom, simple_literal(Atom)) :-
  136	atom(Atom), !.
  137
  138eval_typed_literal(Type, Atom, numeric(Type, Value)) :-
  139	xsdp_numeric_uri(Type, Generic), !,
  140	numeric_literal_value(Generic, Atom, Value).
  141eval_typed_literal(Type, Atom, Value) :-
  142	eval_known_typed_literal(Type, Atom, Value0), !,
  143	Value = Value0.
  144eval_typed_literal(Type, Atom, type(Type, Atom)).
  145
  146%%	eval_known_typed_literal(+Type, +Plain, -Typed) is semidet.
  147%
  148%	Map known datatypes to a value   that is suitable for comparison
  149%	using Prolog standard order of terms.  Note that the mapped time
  150%	representations can all be compared.
  151
  152:- rdf_meta eval_known_typed_literal(r, +, t).  153
  154eval_known_typed_literal(xsd:boolean,	 Atom, boolean(Atom)).
  155eval_known_typed_literal(xsd:string,	 Atom, string(Atom)).
  156eval_known_typed_literal(xsd:gYear,	 Atom, time(xsd:gYear, Atom)).
  157eval_known_typed_literal(xsd:gYearMonth, Atom, time(xsd:gYearMonth, Atom)).
  158eval_known_typed_literal(xsd:date,	 Atom, time(xsd:date, Atom)).
  159eval_known_typed_literal(xsd:dateTime,	 Atom, time(xsd:dateTime, Atom)).
  160
  161%%	numeric_literal_value(+Literal, -Value) is semidet.
  162%
  163%	Convert a SPARQL numeric literal into  its value for the purpose
  164%	of comparison-by-value.
  165%
  166%	@tbd	Move this into the rdf_db library.  There we can achieve
  167%		better performance and we can do more efficient
  168%		matching.
  169
  170numeric_literal_value(Type, Text, Value) :-
  171	rdf_equal(Type, xsd:integer), !,
  172	atom(Text),
  173	atom_number(Text, Value),
  174	integer(Value).
  175numeric_literal_value(Type, Text, Value) :-
  176	rdf_equal(Type, xsd:decimal), !,
  177	atom(Text),
  178	atom_number(Text, Value).
  179numeric_literal_value(_, Text, Value) :-
  180	atom(Text),
  181	atom_number(Text, Value), !.
  182numeric_literal_value(_, Text, Value) :-
  183	catch(rdf_text_to_float(Text, Value), _, fail).
  184
  185rdf_text_to_float(Text, Value) :-
  186	atom_codes(Text, Codes),
  187	optional_sign(Codes, Rest, Sign),
  188	(   Rest = [0'.|_]
  189	->  number_codes(NonnegValue, [0'0|Rest])
  190	;   last(Rest, 0'.)
  191	->  append(Rest, [0'0], NonnegCodes),
  192	    number_codes(NonnegCodes, NonnegValue)
  193        ),
  194	Value is NonnegValue*Sign.
  195
  196optional_sign([0'+|Rest], Rest, 1) :- !.
  197optional_sign([0'-|Rest], Rest, -1) :- !.
  198optional_sign(Rest, Rest, 1).
  199
  200
  201%	Evaluation of function arguments
  202
  203eval_any(Term, Value) :-
  204	eval(Term, Value), !.
  205eval_any(_, boolean(error)).
  206
  207eval_boolean(Term, Bool) :-
  208	eval(Term, Value),
  209	effective_boolean_value(Value, Bool), !.
  210eval_boolean(_, boolean(error)).
  211
  212eval_numeric(Term, Numeric) :-
  213	eval(Term, Numeric),
  214	Numeric = numeric(_,_), !.
  215eval_numeric(_, boolean(error)).
  216
  217%%	sparql_op(+ListOfDelcs)
  218
  219term_expansion((:- sparql_op(Decls)), Clauses) :-
  220	maplist(decl_op, Decls, Clauses).
  221
  222decl_op(Term, op_decl(Gen, Args)) :-
  223	functor(Term, Name, Arity),
  224	functor(Gen,  Name, Arity),
  225	Term =.. [Name|Args].
  226
  227
  228%%	expand_op(+In, -Clause) is det.
  229%
  230%	Expand SPARQL operators into a nice clause.
  231
  232expand_op((op(Op,Result) :- Body),
  233	  [(op(Op1,Result) :- Body1), sparql_op(Op1)]) :-
  234	rdf_global_term(Op, Op0),
  235	functor(Op0, Name, Arity),
  236	functor(Op1, Name, Arity),
  237	(   op_decl(Op1, Types)
  238	->  true
  239	;   Op0 =.. [Name|Args],
  240	    maplist(op_arg_type, Args, Types)
  241	),
  242	Op0 =.. [Name|Args0],
  243	Op1 =.. [Name|Args1],
  244	maplist(convert_goal, Types, Args1, Args0, ConvertList),
  245	list_to_conj(ConvertList, Convert),
  246	mkconj(Convert, Body, Body1).
  247
  248op_arg_type(Var,               any) :- var(Var), !.
  249op_arg_type(boolean(_),	       boolean) :- !.
  250op_arg_type(numeric(_,_),      numeric) :- !.
  251op_arg_type(simple_literal(_), simple_literal) :- !.
  252op_arg_type(_,		       any).
  253
  254list_to_conj([], true).
  255list_to_conj([G], G) :- !.
  256list_to_conj([H|T], G) :-
  257	list_to_conj(T, G1),
  258	mkconj(H, G1, G).
  259
  260mkconj(true, G, G) :- !.
  261mkconj(G, true, G) :- !.
  262mkconj(G1,G2,(G1,G2)).
  263
  264convert_goal(no_eval, Arg, Arg, true).
  265convert_goal(any, Arg0, Arg1, eval_any(Arg0, Arg1)).
  266convert_goal(simple_literal, Arg0, Arg1, eval_any(Arg0, Arg1)).
  267convert_goal(boolean, Arg0, Arg1, eval_boolean(Arg0, Arg1)).
  268convert_goal(numeric, Arg0, Arg1, eval_numeric(Arg0, Arg1)).
  269
  270term_expansion((op(Op,Result) :- Body), Clauses) :-
  271	expand_op((op(Op,Result) :- Body), Clauses).
  272term_expansion((op(Op,Result)), Clauses) :-
  273	expand_op((op(Op,Result) :- true), Clauses).
  274
  275%%	op(+Operator, -Result) is semidet.
  276%
  277%	@param Operator	Term of the format Op(Arg...) where each Arg
  278%			is embedded in its type.
  279%	@param Result	Result-value, embedded in its type.
  280
  281:- rdf_meta op(t,t).  282:- discontiguous op/2, op_decl/2, sparql_op/1.  283
  284:- sparql_op([ bound(no_eval)
  285	     ]).  286
  287% SPARQL Unary operators
  288op(not(boolean(X)), boolean(Result)) :-
  289	not(X, Result).
  290op(+(numeric(Type, X)), numeric(Type, X)).
  291op(-(numeric(Type, X)), numeric(Type, Result)) :-
  292	Result is -X.
  293
  294% SPARQL Tests, defined in section 11.4
  295op(bound(X), boolean(Result)) :-
  296	(bound(X) -> Result = true ; Result = false).
  297op(isiri(X), boolean(Result)) :-
  298	(isiri(X) -> Result = true ; Result = false).
  299op(isuri(X), boolean(Result)) :-
  300	(isiri(X) -> Result = true ; Result = false).
  301op(isblank(X), boolean(Result)) :-
  302	(isblank(X) -> Result = true ; Result = false).
  303op(isliteral(X), boolean(Result)) :-
  304	(isliteral(X) -> Result = true ; Result = false).
  305
  306:- sparql_op([ iri(any, no_eval),
  307	       str(no_eval)
  308	     ]).  309
  310% SPARQL Accessors
  311op(str(X), simple_literal(Str)) :-
  312	str(X, Str).
  313op(lang(X), simple_literal(Lang)) :-
  314	lang(X, Lang).
  315op(datatype(X), Type) :-
  316	datatype(X, Type).
  317op(strdt(simple_literal(Lex), iri(Type)), type(Type, Lex)).
  318op(strlang(simple_literal(Lex), simple_literal(Lang)), lang(Lang, Lex)).
  319:- if(current_predicate(uuid/1)).  320op(uuid, iri(URNUUID)) :-
  321	uuid(UUID),
  322	atom_concat('urn:uuid:', UUID, URNUUID).
  323op(struuid, simple_literal(UUID)) :-
  324	uuid(UUID).
  325:- endif.  326op(bnode, iri(Id)) :-
  327	rdf_bnode(Id).
  328op(bnode(simple_literal(Id)), iri(BNode)) :-
  329	id_to_bnode(Id, BNode).
  330op(iri(Spec, Base), iri(URI)) :-
  331	iri(Spec, Base, URI).
  332
  333% SPARQL Binary operators
  334% Logical connectives, defined in section 11.4
  335op(and(boolean(A), boolean(B)), boolean(Result)) :-
  336	sparql_and(A, B, Result).
  337op(or(boolean(A), boolean(B)), boolean(Result)) :-
  338	sparql_or(A, B, Result).
  339
  340:- sparql_op([ coalesce(no_eval)
  341	     ]).  342
  343% SPARQL functional forms
  344op(if(Test, V1, V2), Result) :-
  345	typed_eval(boolean, Test, TestResult),
  346	(   TestResult == boolean(true)
  347	->  eval(V1, Result)
  348	;   TestResult == boolean(false)
  349	->  eval(V2, Result)
  350	).
  351op(coalesce(List), Result) :-
  352	member(Expr, List),
  353	ground(Expr),
  354	eval(Expr, Result),
  355	\+ invalid(Result), !.
  356
  357invalid('$null$').
  358invalid(boolean(error)).
  359
  360% XPath Tests
  361op(X = Y, boolean(Result)) :-
  362	(   equal(X, Y)
  363	->  Result = true
  364	;   Result = false
  365	).
  366op(X \= Y, boolean(Result)) :-
  367	(   equal(X, Y)
  368	->  Result = false
  369	;   Result = true
  370	).
  371
  372equal(X, X) :- !.
  373equal(numeric(_, X), numeric(_, Y)) :- X =:= Y.
  374equal(boolean(A), boolean(B)) :-
  375	eq_bool(A, B, true).
  376
  377op(X < Y, boolean(Result)) :-
  378	(   lt(X,Y)
  379	->  Result = true
  380	;   functor(X, Name, Arity),
  381	    functor(Y, Name, Arity)
  382	->  Result = false
  383	).
  384op(X > Y, boolean(Result)) :-
  385	(   gt(X,Y)
  386	->  Result = true
  387	;   functor(X, Name, Arity),
  388	    functor(Y, Name, Arity)
  389	->  Result = false
  390	).
  391op(X =< Y, boolean(Result)) :-
  392	(   leq(X,Y)
  393	->  Result = true
  394	;   functor(X, Name, Arity),
  395	    functor(Y, Name, Arity)
  396	->  Result = false
  397	).
  398op(X >= Y, boolean(Result)) :-
  399	(   geq(X,Y)
  400	->  Result = true
  401	;   functor(X, Name, Arity),
  402	    functor(Y, Name, Arity)
  403	->  Result = false
  404	).
  405
  406lt(numeric(_, X), numeric(_, Y)) :- X < Y.
  407lt(simple_literal(X), simple_literal(Y)) :- X @< Y.
  408lt(string(X), string(Y)) :- X @< Y.
  409lt(time(T, X), time(T, Y)) :- X @< Y.
  410lt(type(T, X), type(T, Y)) :- X @< Y.
  411
  412gt(numeric(_, X), numeric(_, Y)) :- X > Y.
  413gt(simple_literal(X), simple_literal(Y)) :- X @> Y.
  414gt(string(X), string(Y)) :- X @> Y.
  415gt(time(T, X), time(T, Y)) :- X @> Y.
  416gt(type(T, X), type(T, Y)) :- X @> Y.
  417
  418leq(numeric(_, X), numeric(_, Y)) :- X =< Y.
  419leq(simple_literal(X), simple_literal(Y)) :- X @=< Y.
  420leq(string(X), string(Y)) :- X @=< Y.
  421leq(time(T, X), time(T, Y)) :- X @=< Y.
  422leq(type(T, X), type(T, Y)) :- X @=< Y.
  423
  424geq(numeric(_, X), numeric(_, Y)) :- X >= Y.
  425geq(simple_literal(X), simple_literal(Y)) :- X @>= Y.
  426geq(string(X), string(Y)) :- X @>= Y.
  427geq(time(T, X), time(T, Y)) :- X @>= Y.
  428geq(type(T, X), type(T, Y)) :- X @>= Y.
  429
  430% arithmetic
  431op(numeric(TX, X) * numeric(TY, Y), numeric(Type, Result)) :-
  432	Result is X * Y,
  433	combine_types(TX, TY, Type).
  434op(numeric(TX, X) / numeric(TY, Y), numeric(Type, Result)) :-
  435	Y =\= 0,
  436	Result is X / Y,
  437	combine_types_div(TX, TY, Type).
  438op(numeric(TX, X) + numeric(TY, Y), numeric(Type, Result)) :-
  439	Result is X + Y,
  440	combine_types(TX, TY, Type).
  441op(numeric(TX, X) - numeric(TY, Y), numeric(Type, Result)) :-
  442	Result is X - Y,
  443	combine_types(TX, TY, Type).
  444% arithmetic to support aggregates
  445op(min(numeric(TX, X), numeric(TY, Y)), numeric(Type, Result)) :-
  446	(   X < Y
  447	->  Type = TX, Result = X
  448	;   X > Y
  449	->  Type = TY, Result = Y
  450	;   combine_types(TX, TY, Type),
  451	    (	Type == TX
  452	    ->	Result = X
  453	    ;	Result = Y
  454	    )
  455	).
  456op(max(numeric(TX, X), numeric(TY, Y)), numeric(Type, Result)) :-
  457	(   X > Y
  458	->  Type = TX, Result = X
  459	;   X < Y
  460	->  Type = TY, Result = Y
  461	;   combine_types(TX, TY, Type),
  462	    (	Type == TX
  463	    ->	Result = X
  464	    ;	Result = Y
  465	    )
  466	).
  467
  468% SPARQL Tests, defined in section 11.4
  469
  470op(in(Value, List), boolean(Result)) :-
  471	sparql_in(Value, List, Result).
  472op(not_in(Value, List), boolean(Result)) :-
  473	sparql_in(Value, List, R0),
  474	not(R0, Result).
  475
  476sparql_in(Value, List, Result) :-
  477	(   memberchk(Value, List)
  478	->  Result = true
  479	;   member(E, List),
  480	    eval(E, EV),
  481	    rdf_equal(Value, EV)
  482	->  Result = true
  483	;   Result = false
  484	).
  485
  486
  487% SPARQL builtin string functions (1.1)
  488
  489:- sparql_op([ strlen(any),
  490	       substr(any, numeric),
  491	       substr(any, numeric, numeric),
  492	       ucase(any),
  493	       lcase(any),
  494	       strstarts(any, any),
  495	       strends(any, any),
  496	       contains(any, any),
  497	       strbefore(any, any),
  498	       strafter(any, any),
  499	       encode_for_uri(any),
  500	       concat(no_eval)
  501	     ]).  502
  503op(strlen(A), numeric(xsd:integer, Len)) :-
  504	string_op(A, Len, strlen).
  505op(substr(A, numeric(xsd:integer, Start)), R) :-
  506	string_int_op_string(A, Start, R, substr).
  507op(substr(A, numeric(xsd:integer, Start), numeric(xsd:integer, Len)), R) :-
  508	string_int_int_op_string(A, Start, Len, R, substr).
  509op(ucase(A), U) :-
  510	string_op_string(A, U, ucase).
  511op(lcase(A), U) :-
  512	string_op_string(A, U, lcase).
  513op(strstarts(String, Starts), boolean(True)) :-
  514	argument_compatible(String, Starts, True, strstarts).
  515op(strends(String, Starts), boolean(True)) :-
  516	argument_compatible(String, Starts, True, strends).
  517op(contains(String, Starts), boolean(True)) :-
  518	argument_compatible(String, Starts, True, contains).
  519op(strbefore(A1, A2), R) :-
  520	string_string_op(A1, A2, R, strbefore).
  521op(strafter(A1, A2), R) :-
  522	string_string_op(A1, A2, R, strafter).
  523op(encode_for_uri(S), simple_literal(URI)) :-
  524	str_value(S, Text),
  525	uri_encoded(path, Text, IRI),
  526	uri_iri(URI, IRI).
  527op(concat(List), R) :-
  528	maplist(eval, List, Evaluated),
  529	maplist(str_text, Evaluated, StrList),
  530	atomic_list_concat(StrList, Lex),
  531	(   maplist(is_string, Evaluated)
  532	->  R = string(Lex)
  533	;   maplist(is_lang(L), Evaluated)
  534	->  R = lang(L, Lex)
  535	;   R = simple_literal(Lex)
  536	).
  537op(langmatches(simple_literal(Lang),
  538	       simple_literal(Pat)),
  539   boolean(Result)) :-
  540	(lang_matches(Lang, Pat) -> Result = true ; Result = false).
  541op(regex(A, simple_literal(Pat)), boolean(Result)) :-
  542	string_op(A, Result, regex(Pat, '')).
  543op(regex(A, simple_literal(Pat), simple_literal(Flags)), boolean(Result)) :-
  544	string_op(A, Result, regex(Pat, Flags)).
  545op(compiled_regex(Regex, A), boolean(Result)) :-
  546	string_op(A, Result, compiled_regex(Regex)).
  547op(replace(simple_literal(Input),
  548	   simple_literal(Pattern),
  549	   simple_literal(Replace),
  550	   simple_literal(Flags)),
  551   simple_literal(Result)) :-
  552	regex_replace(Input, Pattern, Replace, Flags, Result).
  553op(replace(string(Input),
  554	   simple_literal(Pattern),
  555	   simple_literal(Replace),
  556	   simple_literal(Flags)),
  557   string(Result)) :-
  558	regex_replace(Input, Pattern, Replace, Flags, Result).
  559op(replace(lang(Lang, Input),
  560	   simple_literal(Pattern),
  561	   simple_literal(Replace),
  562	   simple_literal(Flags)),
  563   lang(Lang, Result)) :-
  564	regex_replace(Input, Pattern, Replace, Flags, Result).
  565
  566% SPARQL builtin numeric functions (1.1, 17.4.4)
  567
  568:- sparql_op([ isnumeric(any)
  569	     ]).  570
  571op(isnumeric(A), boolean(True)) :-
  572	( A = numeric(_,_) ->  True = true ; True = false ).
  573op(abs(numeric(T, A1)), numeric(T, R)) :-
  574	R is abs(A1).
  575op(round(numeric(T, A1)), numeric(T, R)) :-
  576	R is round(A1).
  577op(ceil(numeric(T, A1)), numeric(T, R)) :-
  578	R is ceil(A1).
  579op(floor(numeric(T, A1)), numeric(T, R)) :-
  580	R is floor(A1).
  581op(rand, numeric(xsd:double, R)) :-
  582	R is random_float.
  583
  584% SPARQL builtin date and time functions (1.1, 17.4.5)
  585
  586op(now, time(xsd:dateTime, Date)) :-
  587	get_time(Now),
  588	format_time(atom(Date), '%FT%T.%3f%:z', Now).
  589op(year(time(Type, DateTime)), numeric(xsd:integer, Year)) :-
  590	time_part(year, Type, DateTime, Year).
  591op(month(time(Type, DateTime)), numeric(xsd:integer, Month)) :-
  592	time_part(month, Type, DateTime, Month).
  593op(day(time(Type, DateTime)), numeric(xsd:integer, Day)) :-
  594	time_part(day, Type, DateTime, Day).
  595op(hours(time(Type, DateTime)), numeric(xsd:integer, Hours)) :-
  596	time_part(hours, Type, DateTime, Hours).
  597op(minutes(time(Type, DateTime)), numeric(xsd:integer, Minutes)) :-
  598	time_part(minutes, Type, DateTime, Minutes).
  599op(seconds(time(Type, DateTime)), numeric(xsd:decimal, Seconds)) :-
  600	time_part(seconds, Type, DateTime, Seconds).
  601op(timezone(time(Type, DateTime)), type(xsd:dayTimeDuration, Timezone)) :-
  602	time_part(tzs, Type, DateTime, TZs),
  603	phrase(tz_offset(TZOffset), TZs),
  604	xsd_duration_seconds(Timezone, TZOffset).
  605op(tz(time(Type, DateTime)), simple_literal(TZ)) :-
  606	time_part(tz, Type, DateTime, TZ).
  607
  608% SPARQL builtin hash functions (1.1, 17.4.6)
  609
  610:- sparql_op([ md5(any),
  611	       sha1(any),
  612	       sha256(any),
  613	       sha384(any),
  614	       sha512(any)
  615	     ]).  616
  617op(md5(String), simple_literal(Hash)) :-
  618	string_hash(String, Hash, md5).
  619op(sha1(String), simple_literal(Hash)) :-
  620	string_hash(String, Hash, sha1).
  621op(sha256(String), simple_literal(Hash)) :-
  622	string_hash(String, Hash, sha256).
  623op(sha384(String), simple_literal(Hash)) :-
  624	string_hash(String, Hash, sha384).
  625op(sha512(String), simple_literal(Hash)) :-
  626	string_hash(String, Hash, sha512).
  627
  628
  629		 /*******************************
  630		 *   HASH SUPPORT FUNCTIONS	*
  631		 *******************************/
  632
  633string_hash(simple_literal(S), Hash, Algorithm) :-
  634	atom_hash(Algorithm, S, Hash).
  635string_hash(string(S), Hash, Algorithm) :-
  636	atom_hash(Algorithm, S, Hash).
  637
  638atom_hash(md5, S, Hash) :- !,
  639	rdf_atom_md5(S, 1, Hash).
  640atom_hash(SHA, S, Hash) :-
  641	sha_hash(S, HashCodes,
  642		 [ algorithm(SHA),
  643		   encoding(utf8)
  644		 ]),
  645	hash_atom(HashCodes, Hash).
  646
  647
  648		 /*******************************
  649		 *    TIME SUPPORT FUNCTIONS	*
  650		 *******************************/
  651
  652%%	time_part(+Part, +Type, +String, -Value) is semidet.
  653
  654:- if(current_predicate(sub_string/5)).  655time_part(year, _Type, String, Value) :- !,
  656	sub_string(String, 0, 4, _, Digits),
  657	number_string(Value, Digits).
  658time_part(month, _Type, String, Value) :- !,
  659	sub_string(String, 5, 2, _, Digits),
  660	number_string(Value, Digits).
  661time_part(day, _Type, String, Value) :- !,
  662	sub_string(String, 8, 2, _, Digits),
  663	number_string(Value, Digits).
  664:- endif.  665time_part(Part, _Type, DateTime, Value) :-
  666	atom_codes(DateTime, Codes),
  667	phrase(time_dcg(Part, Value), Codes, _).
  668
  669time_dcg(year,  Year)  --> digits4(Year).
  670time_dcg(month, Month) --> time_dcg(year, _),    "-", digits2(Month).
  671time_dcg(day,   Day)   --> time_dcg(month, _),   "-", digits2(Day).
  672time_dcg(hours, Hours) --> time_dcg(day, _),     "T", digits2(Hours).
  673time_dcg(minutes, Min) --> time_dcg(hours, _),   ":", digits2(Min).
  674time_dcg(seconds, Sec) --> time_dcg(minutes, _), ":", number(Sec).
  675time_dcg(tzs,     TZs) --> time_dcg(seconds, _),      string_without("", TZs).
  676time_dcg(tz,      TZ)  --> time_dcg(tzs, TZs), { atom_codes(TZ, TZs) }.
  677
  678tz_offset(TZOffset) -->
  679	"Z", !, { TZOffset = 0 }.
  680tz_offset(TZOffset) -->
  681	"+", digits2(Hours), ":", digits2(Minutes),
  682	{ TZOffset is Hours*3600+Minutes*60 }.
  683tz_offset(TZOffset) -->
  684	"-", digits2(Hours), ":", digits2(Minutes),
  685	{ TZOffset is -(Hours*3600+Minutes*60) }.
  686
  687%%	seconds_xsd_duration(+Seconds, -XSDDuration)
  688%
  689%	@see http://docs.oracle.com/cd/E13214_01/wli/docs92/xref/xqdurfunc.html#wp1183764
  690%	@tbd	Implement other direction and move this to XSD or datetime
  691%		library.
  692
  693xsd_duration_seconds(XSDDuration, Secs) :-
  694	var(XSDDuration), !,
  695	must_be(number, Secs),
  696	phrase(xsd_duration(Secs), Codes),
  697	atom_codes(XSDDuration, Codes).
  698
  699xsd_duration(Secs) -->
  700	{ Secs < 0, !, PosSecs is -Secs },
  701	"-",
  702	xsd_duration(PosSecs).
  703xsd_duration(Secs) -->
  704	{ Secs =:= 0 }, !,
  705	"PT0S".
  706xsd_duration(Secs) -->
  707	"P",
  708	xsd_duration_days(Secs, Rem),
  709	xsd_duration_time(Rem).
  710
  711xsd_duration_days(Secs, Rem) -->
  712	{ Days is Secs // (24*3600),
  713	  Days > 0, !,
  714	  Rem is Secs - Days*24*3600
  715	},
  716	integer(Days),
  717	"D".
  718xsd_duration_days(Secs, Secs) --> "".
  719
  720xsd_duration_time(Secs) -->
  721	{ Secs =:= 0 }, !.
  722xsd_duration_time(Secs) -->
  723	"T",
  724	xsd_duration_hours(Secs, S1),
  725	xsd_duration_minutes(S1, S2),
  726	xsd_duration_seconds(S2).
  727
  728xsd_duration_hours(Secs, Rem) -->
  729	{ Hours is Secs // 3600,
  730	  Hours > 0, !,
  731	  Rem is Secs - Hours*3600
  732	},
  733	integer(Hours),
  734	"H".
  735xsd_duration_hours(Secs, Secs) --> "".
  736
  737xsd_duration_minutes(Secs, Rem) -->
  738	{ Min is Secs // 60,
  739	  Min > 0, !,
  740	  Rem is Secs - Min*60
  741	},
  742	integer(Min),
  743	"M".
  744xsd_duration_minutes(Secs, Secs) --> "".
  745
  746xsd_duration_seconds(Secs) -->
  747	{ Secs =:= 0 }, !.
  748xsd_duration_seconds(Secs) -->
  749	number(Secs),
  750	"S".
  751
  752
  753digits4(Value) -->
  754	digit(D1),digit(D2),digit(D3),digit(D4),
  755	{ number_codes(Value, [D1,D2,D3,D4]) }.
  756digits2(Value) -->
  757	digit(D1),digit(D2),
  758	{ number_codes(Value, [D1,D2]) }.
  759
  760
  761		 /*******************************
  762		 *  STRING SUPPORT PRIMITIVES	*
  763		 *******************************/
  764
  765is_string(string(_)).
  766is_lang(L, lang(L,_)).
  767
  768%%	string_op1(+A1, -R, +Op)
  769
  770string_op(simple_literal(A), R, Op) :-
  771	atom_op(Op, A, R).
  772string_op(lang(_, A), R, Op) :-
  773	atom_op(Op, A, R).
  774string_op(string(A), R, Op) :-
  775	atom_op(Op, A, R).
  776
  777%%	string_op_string(+A, -R)
  778
  779string_op_string(simple_literal(A), simple_literal(R), Op) :-
  780	atom_op(Op, A, R).
  781string_op_string(lang(L,A), lang(L,R), Op) :-
  782	atom_op(Op, A, R).
  783string_op_string(string(A), string(R), Op) :-
  784	atom_op(Op, A, R).
  785
  786%%	string_int_op_string(+S0, +I, -S)
  787
  788string_int_op_string(simple_literal(S0), I, simple_literal(S), Op) :-
  789	atom_op(Op, S0, I, S).
  790string_int_op_string(lang(L, S0), I, lang(L, S), Op) :-
  791	atom_op(Op, S0, I, S).
  792string_int_op_string(string(S0), I, string(S), Op) :-
  793	atom_op(Op, S0, I, S).
  794
  795%%	string_int_int_op_string(+S0, +I, -S)
  796
  797string_int_int_op_string(simple_literal(S0), I1, I2, simple_literal(S), Op) :-
  798	atom_op(Op, S0, I1, I2, S).
  799string_int_int_op_string(lang(L, S0), I1, I2, lang(L, S), Op) :-
  800	atom_op(Op, S0, I1, I2, S).
  801string_int_int_op_string(string(S0), I1, I2, string(S), Op) :-
  802	atom_op(Op, S0, I1, I2, S).
  803
  804%%	string_op2(+A1, +A2, -R, +Op)
  805%
  806%	Define operations on strings.
  807
  808string_string_op(simple_literal(A1), simple_literal(A2), Result, Op) :-
  809	(   atom_op(Op, A1, A2, R)
  810	->  Result = simple_literal(R)
  811	;   Result = simple_literal('')
  812	).
  813string_string_op(simple_literal(A1), string(A2), Result, Op) :-
  814	(   atom_op(Op, A1, A2, R)
  815	->  Result = simple_literal(R)
  816	;   Result = simple_literal('')
  817	).
  818string_string_op(string(A1), simple_literal(A2), Result, Op) :-
  819	(   atom_op(Op, A1, A2, R)
  820	->  Result = string(R)
  821	;   Result = simple_literal('')
  822	).
  823string_string_op(string(A1), string(A2), Result, Op) :-
  824	(   atom_op(Op, A1, A2, R)
  825	->  Result = string(R)
  826	;   Result = simple_literal('')
  827	).
  828string_string_op(lang(L, A1), lang(L, A2), Result, Op) :-
  829	(   atom_op(Op, A1, A2, R)
  830	->  Result = lang(L, R)
  831	;   Result = simple_literal('')
  832	).
  833string_string_op(lang(L, A1), string(A2), Result, Op) :-
  834	(   atom_op(Op, A1, A2, R)
  835	->  Result = lang(L, R)
  836	;   Result = simple_literal('')
  837	).
  838string_string_op(lang(L, A1), simple_literal(A2), Result, Op) :-
  839	(   atom_op(Op, A1, A2, R)
  840	->  Result = lang(L, R)
  841	;   Result = simple_literal('')
  842	).
  843
  844%%	iri(+Spec, +Base, -IRI)
  845
  846iri(simple_literal(URI0), Base, URI) :- !,
  847	uri_normalized(URI0, Base, URI).
  848iri(string(URI0), Base, URI) :-
  849	uri_normalized(URI0, Base, URI).
  850iri(iri(URI), _, URI).
  851
  852%%	argument_compatible(+A1, +A2, -Bool, +Op)
  853
  854argument_compatible(simple_literal(A1), simple_literal(A2), Bool, Op) :- !,
  855	arg_compatible(Op, A1, A2, Bool).
  856argument_compatible(simple_literal(A1), string(A2), Bool, Op) :- !,
  857	arg_compatible(Op, A1, A2, Bool).
  858argument_compatible(string(A1), simple_literal(A2), Bool, Op) :- !,
  859	arg_compatible(Op, A1, A2, Bool).
  860argument_compatible(string(A1), string(A2), Bool, Op) :- !,
  861	arg_compatible(Op, A1, A2, Bool).
  862argument_compatible(lang(L,A1), lang(L,A2), Bool, Op) :- !,
  863	arg_compatible(Op, A1, A2, Bool).
  864argument_compatible(lang(_,A1), simple_literal(A2), Bool, Op) :- !,
  865	arg_compatible(Op, A1, A2, Bool).
  866argument_compatible(lang(_,A1), string(A2), Bool, Op) :- !,
  867	arg_compatible(Op, A1, A2, Bool).
  868argument_compatible(_, _, boolean(error), _).
  869
  870arg_compatible(Op, A1, A2, Bool) :-
  871	(   arg_compatible(Op, A1, A2)
  872	->  Bool = true
  873	;   Bool = false
  874	).
  875
  876arg_compatible(strstarts, A1, A2) :- sub_atom(A1, 0, _, _, A2).
  877arg_compatible(strends,   A1, A2) :- sub_atom(A1, _, _, 0, A2).
  878arg_compatible(contains,  A1, A2) :- sub_atom(A1, _, _, _, A2), !.
  879
  880
  881%%	atom_op(+Op, +Atom, -Result).
  882
  883atom_op(strlen, A, Len) :-
  884	atom_length(A, Len).
  885atom_op(ucase, A, U) :-
  886	upcase_atom(A, U).
  887atom_op(lcase, A, U) :-
  888	downcase_atom(A, U).
  889atom_op(compiled_regex(Regex), Data, Matches) :-
  890	(   compiled_regex(Regex, Data)
  891	->  Matches = true
  892	;   Matches = false
  893	).
  894atom_op(regex(Pat, Flags), Data, Matches) :-
  895	(   regex(Data, Pat, Flags)
  896	->  Matches = true
  897	;   Matches = false
  898	).
  899
  900%%	atom_op(+Op, +Atom, +Arg, -Result).
  901
  902atom_op(substr, Atom, Start, Sub) :-
  903	S is Start - 1,
  904	(   sub_atom(Atom, S, _, 0, Sub0)
  905	->  Sub = Sub0
  906	;   Sub = ''			% is this ok?
  907	).
  908atom_op(strbefore, Atom, Search, Before) :-
  909	(   Search == ''
  910	->  Before = ''
  911	;   sub_atom(Atom, BL, _, _, Search)
  912	->  sub_atom(Atom, 0, BL, _, Before)
  913	).
  914atom_op(strafter, Atom, Search, After) :-
  915	(   sub_atom(Atom, _, _, AL, Search)
  916	->  sub_atom(Atom, _, AL, 0, After)
  917	).
  918
  919%%	atom_op(+Op, +Atom, +A1, +A2, -Result).
  920
  921atom_op(substr, Atom, Start, Len, Sub) :-
  922	S is Start - 1,
  923	(   sub_atom(Atom, S, Len, _, Sub0)
  924	->  Sub = Sub0
  925	;   sub_atom(Atom, S, _, 0, Sub0)
  926	->  Sub = Sub0
  927	;   Sub = ''			% is this ok?
  928	).
  929
  930
  931%	Numeric types follows the Xpath definitions of
  932%	http://www.w3.org/TR/xpath-functions/#numeric-functions
  933%	TBD:
  934
  935%%	combine_types_div(+TypeLeft, +TypeRight, -Type)
  936
  937combine_types_div(TX, TY, T) :-
  938	rdf_equal(xsd:integer, IntType),
  939	xsdp_numeric_uri(TX, IntType),
  940	xsdp_numeric_uri(TY, IntType), !,
  941	rdf_equal(xsd:decimal, T).
  942combine_types_div(TX, TY, T) :-
  943	combine_types(TX, TY, T).
  944
  945%%	combine_types(+TypeLeft, +TypeRight, -Type)
  946
  947%combine_types(T, T, T) :- !.
  948combine_types(TL, TR, T) :-
  949	xsdp_numeric_uri(TL, STL),
  950	xsdp_numeric_uri(TR, STR),
  951	promote_types(STL, STR, T).
  952
  953promote_types(TL, TR, T) :-
  954	type_index(TL, IL),
  955	type_index(TR, IR),
  956	TI is max(IL, IR),
  957	type_index(T, TI), !.
  958
  959term_expansion(type_index(NS:Local, I), type_index(URI, I)) :-
  960	rdf_global_id(NS:Local, URI).
  961
  962type_index(xsd:integer, 1).
  963type_index(xsd:decimal, 2).
  964type_index(xsd:float,   3).
  965type_index(xsd:double,  4).
  966
  967
  968%%	rdf_equal(+RDFTerm, +RDFTerm, -Boolean)
  969%
  970%	RDF Term equivalence. Described as   lexical equivalence, except
  971%	where we have the logic to do value equivalence.
  972
  973:- rdf_meta rdf_equal(t,t,-).  974
  975rdf_equal(X, X, boolean(true)) :- !.
  976rdf_equal(boolean(A), boolean(B),  boolean(Eq)) :- !,
  977	eq_bool(A, B, Eq).
  978rdf_equal(_, _, boolean(false)).
  979
  980
  981eq_bool(X, X, true) :- !.
  982eq_bool(true, false, false) :- !.
  983eq_bool(false, true, false) :- !.
  984eq_bool(X, Y, true) :-
  985	boolean_value(X, V1),
  986	boolean_value(Y, V2),
  987	V1 == V2, !.
  988eq_bool(_, _, false).
  989
  990%%	boolean_value(+Content, -Bool)
  991%
  992%	Convert the value from literal(xsd:boolean, Content) into
  993%	either 'true' or 'false'.
  994
  995boolean_value(true,  true) :- !.
  996boolean_value(false, false) :- !.
  997boolean_value('0',   false) :- !.
  998boolean_value('',    false) :- !.
  999boolean_value(False, false) :-
 1000	downcase_atom(False, false), !.
 1001boolean_value(_,     true).
 1002
 1003
 1004		 /*******************************
 1005		 *	       CASTS		*
 1006		 *******************************/
 1007
 1008%%	xsd_cast(+Term, -Type, -Arg)
 1009%
 1010%	Deals with xsd:dateTime(?a), casting ?a to   the XML Schema type
 1011%	dateTime. Supported types are the numeric types, xsd:boolean and
 1012%	xsd:dateTime.
 1013
 1014term_expansion(xsd_cast(term,type,arg), Clauses) :-
 1015	findall(Clause, xsd_cast_clause(Clause), Clauses).
 1016
 1017xsd_cast_clause(xsd_cast(Term, Type, Arg)) :-
 1018	(   xsdp_numeric_uri(Type, _)
 1019	;   rdf_equal(xsd:dateTime, Type)
 1020	;   rdf_equal(xsd:boolean, Type)
 1021	),
 1022	Term =.. [Type,Arg].
 1023
 1024xsd_cast(term,type,arg).
 1025
 1026%%	eval_cast(+Type, +Value, -Result)
 1027%
 1028%	Cast Value to Type, resulting  in   a  typed  literal. Currently
 1029%	casts plain literals to the requested type and numeric values to
 1030%	other numeric values.
 1031
 1032eval_cast(Type, simple_literal(Value), Result) :-
 1033	atom(Value), !,
 1034	eval_typed_literal(Type, Value, Result).
 1035eval_cast(Type, numeric(_, Value0), numeric(Type, Value)) :-
 1036	xsdp_numeric_uri(Type, Generic),
 1037	(   rdf_equal(Generic, xsd:integer)
 1038	->  Value is integer(Value0)
 1039	;   (   rdf_equal(Generic, xsd:float)
 1040	    ;   rdf_equal(Generic, xsd:double)
 1041	    )
 1042	->  Value is float(Value0)
 1043	;   Value = Value0
 1044	).
 1045
 1046
 1047%%	eval_function(+Term, -Result)
 1048%
 1049%	Eval user-defined function.  User-defined functions are of the
 1050%	form sparql:function(Term, Result).
 1051
 1052:- multifile
 1053	sparql:function/2,
 1054	sparql:current_function/1. 1055
 1056eval_function(Term0, Result) :-
 1057	Term0 =.. [F|Args0],
 1058	eval_args(Args0, Args),
 1059	Term =.. [F|Args],
 1060	sparql:function(Term, Result0), !,
 1061	eval(Result0, Result).
 1062eval_function(Term, boolean(error)) :-
 1063	sparql:current_function(Term), !.
 1064eval_function(Term, _) :-
 1065	functor(Term, Name, Arity),
 1066	throw(error(existence_error(sparql_function, Name/Arity), _)).
 1067
 1068eval_args([], []).
 1069eval_args([H0|T0], [H|T]) :-
 1070	sparql_eval(H0, H),
 1071	eval_args(T0, T).
 1072
 1073
 1074		 /*******************************
 1075		 *	SUPPORT PREDICATES	*
 1076		 *******************************/
 1077
 1078%%	not(+Bool, -Negated)
 1079
 1080not(true, false).
 1081not(false, true).
 1082not(error, error).
 1083
 1084%%	bound(X)
 1085%
 1086%	Does not evaluate args.  If the argument is a function it
 1087%	is always bound.
 1088
 1089bound(X) :- nonvar(X).
 1090
 1091%%	str(+RDFTerm, -Atom)
 1092%
 1093%	Extract lexical representation from RDFTerm.
 1094
 1095str(Var, _) :-
 1096	var(Var), !, fail.
 1097str(literal(X), Str) :- !,
 1098	str_literal(X, Str).
 1099str(IRI, IRI) :-
 1100	atom(IRI), !,
 1101	\+ rdf_is_bnode(IRI).
 1102str(Expr, Str) :-
 1103	eval(Expr, Value),
 1104	str_value(Value, Str).
 1105
 1106str_value(simple_literal(X), X).
 1107str_value(lang(_, X), X).
 1108str_value(boolean(X), X).
 1109str_value(string(X), X).
 1110str_value(iri(IRI), IRI).
 1111
 1112str_literal(type(_, Str), Str) :- !.
 1113str_literal(lang(_, Str), Str) :- !.
 1114str_literal(Str, Str).
 1115
 1116str_text(simple_literal(X), X).
 1117str_text(lang(_, X), X).
 1118str_text(string(X), X).
 1119
 1120
 1121%%	lang(+RDFTerm, -Lang)
 1122%
 1123%	Extract language specification from an RDFTerm
 1124
 1125lang(lang(Lang,_), Lang) :- !.
 1126lang(string(_), '').
 1127lang(simple_literal(_), '').
 1128lang(type(_,_), '').
 1129lang(numeric(_,_), '').
 1130
 1131%%	datatype(+RDFTerm, -IRI)
 1132%
 1133%	Extract type specification from an RDFTerm
 1134
 1135:- rdf_meta
 1136	datatype(t,t). 1137
 1138datatype(0, _) :- !, fail.
 1139datatype(literal(type(Type, _)), iri(Type)) :- !.
 1140datatype(numeric(Type, _), iri(Type)) :- !.
 1141datatype(boolean(_), iri(xsd:boolean)) :- !.
 1142datatype(time(Type, _), iri(Type)) :- !.
 1143datatype(string(_), iri(xsd_string)) :- !.
 1144datatype(Expr, Type) :-
 1145	eval(Expr, Value),
 1146	Value \== Expr,
 1147	datatype(Value, Type).
 1148
 1149
 1150%%	sparql_and(+A, +B, -Result)
 1151
 1152sparql_and(true, true,  true) :- !.
 1153sparql_and(true, error, error) :- !.
 1154sparql_and(error, true, error) :- !.
 1155sparql_and(_,    _,     false).
 1156
 1157%%	sparql_or(+A, +B, -Result)
 1158
 1159sparql_or(true,	 _,	true) :- !.
 1160sparql_or(_,	 true,	true) :- !.
 1161sparql_or(false, false,	false) :- !.
 1162sparql_or(_,	 _,	error).
 1163
 1164%%	isiri(+IRI)
 1165%
 1166%	True if IRI is an IRI.  We get the argument un-evaluated.
 1167
 1168isiri(IRI) :-
 1169	atom(IRI), !,
 1170	\+ rdf_is_bnode(IRI).
 1171isiri(literal(_)) :- !, fail.
 1172isiri(Expr) :-
 1173	eval(Expr, Value),
 1174	Value = iri(IRI),
 1175	\+ rdf_is_bnode(IRI).
 1176
 1177isblank(IRI) :-
 1178	atom(IRI), !,
 1179	rdf_is_bnode(IRI).
 1180isblank(literal(_)) :- !, fail.
 1181isblank(Expr) :-
 1182	eval(Expr, Value),
 1183	Value = iri(IRI),
 1184	rdf_is_bnode(IRI).
 1185
 1186isliteral(literal(_)) :- !.
 1187isliteral(Atom) :-
 1188	atom(Atom), !, fail.
 1189isliteral(Expr) :-
 1190	eval(Expr, Value),
 1191	Value \= iri(_).
 1192
 1193
 1194		 /*******************************
 1195		 *     REGULAR EXPRESSIONS	*
 1196		 *******************************/
 1197
 1198:- if(exists_source(library(pcre))). 1199:- use_module(library(pcre)). 1200
 1201%!	regex(+Haystack, +Needle, +Flags) is semidet.
 1202
 1203regex(String, Pattern, '') :- !,
 1204	re_match(Pattern, String).
 1205regex(String, Pattern, Flags) :-
 1206	re_match(Pattern/Flags, String).
 1207
 1208%%	compiled_regex(+Compiled, +Text) is semidet.
 1209%
 1210%	Test using a regex that has been   prepared. Compiled is a regex
 1211%	blob created by regex_obj/3.
 1212
 1213compiled_regex(Regex, String) :-
 1214	re_match(Regex, String).
 1215
 1216regex_obj(Pattern, Flags, Regex) :-
 1217	flag_options(Flags, Options),
 1218	re_compile(Pattern, Regex, Options).
 1219
 1220flag_options(Flags, Options) :-
 1221	atom_chars(Flags, Chars),
 1222	maplist(re_flag_option, Chars, Options).
 1223
 1224re_flag_option(Flag, Option) :-
 1225	re_flag_option_(Flag, Option), !.
 1226re_flag_option(Flag, _) :-
 1227	existence_error(re_flag, Flag).
 1228
 1229re_flag_option_(i, caseless(true)).
 1230re_flag_option_(m, multiline(true)).
 1231re_flag_option_(x, extended(true)).
 1232re_flag_option_(s, dotall(true)).
 1233
 1234
 1235%%	regex_replace(+Input, +Pattern, +Replace, +Flags, -Result)
 1236
 1237regex_replace(Input, Pattern, Replace, Flags, Result) :-
 1238	re_replace(Pattern/Flags, Replace, Input, ResultS),
 1239	atom_string(Result, ResultS).
 1240
 1241:- else.					% XPCE based version
 1242
 1243%%	regex(+String, +Pattern, +Flags)
 1244%
 1245%	TBD:
 1246%		- Avoid XPCE
 1247%		- Complete flags
 1248
 1249:- dynamic
 1250	pattern_cache/3.		% Pattern, Flags, Regex
 1251
 1252regex(String, Pattern, Flags) :-
 1253	with_mutex(sparql_regex,
 1254		   ( regex_obj(Pattern, Flags, Regex),
 1255		     send(Regex, search, string(String)))).
 1256
 1257regex_obj(Pattern, Flags, Regex) :-
 1258	pattern_cache(Pattern, Flags, Regex), !.
 1259regex_obj(Pattern, Flags, Regex) :-
 1260	make_regex(Pattern, Flags, Regex),
 1261	asserta(pattern_cache(Pattern, Flags, Regex)).
 1262
 1263make_regex(Pattern, i, Regex) :- !,
 1264	new(Regex, regex(Pattern, @(off))).
 1265make_regex(Pattern, _, Regex) :- !,
 1266	new(Regex, regex(Pattern)).
 1267
 1268%%	compiled_regex(+Compiled, +Text) is semidet.
 1269%
 1270%	Test using a regex that has   been  prepared. Compiled takes the
 1271%	following forms:
 1272%
 1273%	  - XPCE object
 1274
 1275compiled_regex(@(Regex), String) :-
 1276	send(@(Regex), search, string(String)).
 1277
 1278%%	regex_replace(+Input, +Pattern, +Replace, +Flags, -Result)
 1279
 1280regex_replace(Input, Pattern, Replace0, Flags, Result) :-
 1281	dollar_replace(Replace0, Replace),
 1282	with_mutex(sparql_regex,
 1283		   locked_replace(Input, Pattern, Replace, Flags, Result)).
 1284
 1285dollar_replace(Replace0, Replace) :-
 1286	sub_atom(Replace0, _, _, _, $), !,
 1287	regex_replace(Replace0, '\\$([0-9])', '\\\\1', '', Replace).
 1288dollar_replace(Replace, Replace).
 1289
 1290
 1291locked_replace(Input, Pattern, Replace, Flags, Result) :-
 1292	regex_obj(Pattern, Flags, Regex),
 1293	new(S, string('%s', Input)),
 1294	send(Regex, for_all, S,
 1295	     message(@(arg1), replace, @(arg2), Replace)),
 1296	get(S, value, Result).
 1297
 1298:- endif.					% regex pcre/xpce
 1299
 1300
 1301%%	effective_boolean_value(+Expr, -Bool)
 1302%
 1303%	See SPARQL document, section 11.2.2: Effecitive Boolean Value
 1304
 1305effective_boolean_value(boolean(X), boolean(True)) :- !,
 1306	True = X.
 1307effective_boolean_value(string(X),  boolean(True)) :- !,
 1308	(X == '' -> True = false ; True = true).
 1309effective_boolean_value(simple_literal(X),  boolean(True)) :- !,
 1310	(X == '' -> True = false ; True = true).
 1311effective_boolean_value(numeric(_, X),  boolean(True)) :- !,
 1312	(X =:= 0 -> True = false ; True = true).
 1313effective_boolean_value(_,  boolean(error)).
 1314
 1315%%	sparql_eval(+Expr, -Results)
 1316%
 1317%	Evaluate a SPARQL expression.
 1318
 1319sparql_eval(Expr, Expr) :-
 1320	is_rdf(Expr), !.
 1321sparql_eval(Expr, Result) :-
 1322	eval(Expr, Result0), !,
 1323	to_rdf(Result0, Result).
 1324sparql_eval(Expr, '$null$') :-
 1325	debug(sparql(eval), '~p --> NULL', [Expr]).
 1326
 1327%%	sparql_eval_raw(+Expr, -Result)
 1328%
 1329%	Same as sparql_eval/2, but return the raw result.
 1330
 1331sparql_eval_raw(Expr, Result) :-
 1332	(   eval(Expr, Result0)
 1333	->  Result = Result0
 1334	;   Result = '$null$',
 1335	    debug(sparql(eval), '~p --> NULL', [Expr])
 1336	).
 1337
 1338:- rdf_meta
 1339	to_rdf(+,t). 1340
 1341to_rdf(numeric(Type, Value), literal(type(Type, Atom))) :- !,
 1342	atom_number(Atom, Value).
 1343to_rdf(boolean(Val), literal(type(xsd:boolean, Val))) :- !.
 1344to_rdf(type(T, Val), literal(type(T, Val))) :- !.
 1345to_rdf(lang(L, Val), literal(lang(L, Val))) :- !.
 1346to_rdf(simple_literal(L), literal(L)) :- !.
 1347to_rdf(string(L), literal(type(xsd:string, L))) :- !.
 1348to_rdf(time(Type, D), literal(type(Type, D))) :- !.
 1349to_rdf(iri(IRI), IRI) :- !.
 1350to_rdf(X, X) :- is_rdf(X).
 1351
 1352%%	is_rdf(+Term)
 1353%
 1354%	True if Term is a valid RDF term.
 1355
 1356is_rdf(IRI) :- atom(IRI).
 1357is_rdf(Var) :- var(Var), !, fail.
 1358is_rdf(literal(_)).
 1359
 1360
 1361		 /*******************************
 1362		 *     PROPERTY PATH SUPPORT	*
 1363		 *******************************/
 1364
 1365%%	sparql_find(?From, ?To, ?F, ?T, :Q) is nondet.
 1366%
 1367%	Implement *(PropertyPath). We should probably collect translated
 1368%	queries in a dynamic predicate to   avoid the copy_term. Also, Q
 1369%	will quite often  be  simple.  In  that   case  we  can  map  to
 1370%	rdf_reachable/3,  although  one  of   the    problems   is  that
 1371%	rdf_reachable/3 uses rdf_has/3, and does not deal with graphs.
 1372%
 1373%	We should be a bit  smarter   here  and  choose between forward,
 1374%	backward, two-sided breath-first, etc.  based   on  which  start
 1375%	point is given.
 1376%
 1377%	@tbd	Maybe a thing for using tor?  Planning most likely more
 1378%		important than the iteration speed.
 1379
 1380sparql_find(From, To, F, T, Q) :-
 1381	empty_assoc(Visited),
 1382	(   nonvar(From)
 1383	->  sparql_find_f(From, To, F, T, Q, Visited)
 1384	;   nonvar(To)
 1385	->  sparql_find_b(From, To, F, T, Q, Visited)
 1386	;   query_graph(Q, Graph)
 1387	->  rdf_current_node(Graph, From),
 1388	    sparql_find_f(From, To, F, T, Q, Visited)
 1389	;   rdf_current_node(From),
 1390	    sparql_find_f(From, To, F, T, Q, Visited)
 1391	).
 1392
 1393sparql_find_f(Place, Place, _, _, _, _).
 1394sparql_find_f(From, To, F, T, Q, Visited) :-
 1395	copy_term(t(F,T,Q), t(From, Tmp, Q2)),
 1396	call(Q2),
 1397	\+ get_assoc(Tmp, Visited, _),
 1398	put_assoc(Tmp, Visited, true, V2),
 1399	sparql_find_f(Tmp, To, F, T, Q, V2).
 1400
 1401
 1402sparql_find_b(Place, Place, _, _, _, _).
 1403sparql_find_b(From, To, F, T, Q, Visited) :-
 1404	copy_term(t(F,T,Q), t(Tmp, To, Q2)),
 1405	call(Q2),
 1406	\+ get_assoc(Tmp, Visited, _),
 1407	put_assoc(Tmp, Visited, true, V2),
 1408	sparql_find_b(From, Tmp, F, T, Q, V2).
 1409
 1410
 1411%%	query_graph(+Query, -Graph) is semidet.
 1412%
 1413%	True when Query is associated with graph.  Note that property
 1414%	paths are always executed in a single graph.
 1415
 1416query_graph(V, _) :-
 1417	var(V), !, fail.
 1418query_graph(_:Q, G) :-
 1419	query_graph(Q, G).
 1420query_graph((A,B), G) :-
 1421	(   query_graph(A, G)
 1422	;   query_graph(B, G)
 1423	).
 1424query_graph((A;B), G) :-
 1425	(   query_graph(A, G)
 1426	;   query_graph(B, G)
 1427	).
 1428query_graph((A->B), G) :-
 1429	(   query_graph(A, G)
 1430	;   query_graph(B, G)
 1431	).
 1432query_graph((A*->B), G) :-
 1433	(   query_graph(A, G)
 1434	;   query_graph(B, G)
 1435	).
 1436query_graph(rdf(_,_,_,G:_), G).
 1437
 1438
 1439%%	rdf_current_node(?Graph, -Resource)
 1440%
 1441%	True when Resource is a resource in Graph.  This means it is
 1442%	either a subject or an object of a triple in Graph.
 1443
 1444rdf_current_node(Graph, R) :-
 1445	rdf_graph(Graph),
 1446	setof(R,
 1447	      (	rdf(S,_,O,Graph),
 1448	        (   R = S
 1449		;   atom(O),
 1450		    R = O
 1451		)
 1452	      ),
 1453	      Rs),
 1454	member(R, Rs).
 1455
 1456
 1457%%	rdf_current_node(-Resource)
 1458%
 1459%	Generates all known resources on backtracing.   This is there to
 1460%	support {?s :p* ?o}. A highly dubious query.
 1461
 1462rdf_current_node(From) :-
 1463	rdf_subject(From).
 1464rdf_current_node(From) :-
 1465	findall(R, (rdf(_,_,R), \+ (atom(R), rdf_subject(R))), Rs),
 1466	sort(Rs, Set),
 1467	member(From, Set).
 1468
 1469
 1470%%	sparql_minus(:QLeft, :QRight)
 1471%
 1472%	Realise SPARQL =MINUS=.  This is defined to
 1473%
 1474%	    - Take the variables of QLeft
 1475%	    - Determine the result-set for these variables for
 1476%	      both QLeft and QRight
 1477%	    - Substract those from QLeft that are in QRight
 1478%
 1479%	@tbd:	Both the result set and the minus set are in standard
 1480%		order of terms, so we can do ordered subtraction.
 1481
 1482sparql_minus(QLeft, QRight) :-
 1483	term_variables(QLeft,  VarsLeft0),  sort(VarsLeft0,  VarsLeft),
 1484	term_variables(QRight, VarsRight0), sort(VarsRight0, VarsRight),
 1485	ord_intersection(VarsLeft, VarsRight, VarsCommon),
 1486	(   VarsCommon == []
 1487	->  QLeft
 1488	;   ord_subtract(VarsLeft, VarsCommon, ExtraLeft),
 1489	    VLeft =.. [v|ExtraLeft],
 1490	    VCommon =.. [v|VarsCommon],
 1491	    findall(VCommon-VLeft, (QLeft,cond_bind_null(VarsLeft)), AllSols),
 1492	    AllSols \== [],
 1493	    sort(AllSols, AllSorted),
 1494	    findall(VCommon, (QRight,cond_bind_null(VarsCommon)), MinusSols),
 1495	    sort(MinusSols, MinusSorted),
 1496	    member(VCommon-VLeft, AllSorted),
 1497	    \+ memberchk(VCommon, MinusSorted)
 1498	).
 1499
 1500cond_bind_null([]).
 1501cond_bind_null([H|T]) :-
 1502	(   var(H)
 1503	->  H = '$null$'
 1504	;   true
 1505	),
 1506	cond_bind_null(T).
 1507
 1508
 1509		 /*******************************
 1510		 *	   SPARQL GROUP		*
 1511		 *******************************/
 1512
 1513%%	sparql_group(:Goal)
 1514%
 1515%	Same as call.  Intended to keep groups together to avoid invalid
 1516%	optimizations.
 1517
 1518sparql_group(Goal) :-
 1519	call(Goal).
 1520
 1521%%	sparql_group(:Goal, +OuterVars, +InnerVars)
 1522%
 1523%	Execute a group that contains non-steadfast variables, which
 1524%	asks for delayed unification of the output arguments.
 1525
 1526sparql_group(Goal, OuterVars, InnerVars) :-
 1527	call(Goal),
 1528	OuterVars = InnerVars.
 1529
 1530
 1531		 /*******************************
 1532		 *	      SERVICE		*
 1533		 *******************************/
 1534
 1535%!	sparql_service(+Silent, +URL, +Prefixes, +Bindings, +QText)
 1536%
 1537%	Execute a remote SPARQL SERVICE request
 1538%
 1539%	@arg Silent is one of `silent` or `error`
 1540%	@arg URL is the address of the SPARQL server
 1541%	@arg Prefixes is a list `Prefix-URL`
 1542%	@arg Bindings is a list `VarName=Var`
 1543%	@arg QText is a string holding the remote query
 1544
 1545sparql_service(Silent, URL, Prefixes, Bindings, QText) :-
 1546	parse_url(URL, Options),
 1547	maplist(prefix_line, Prefixes, PrefLines),
 1548	partition(bound_binding, Bindings, In, Out),
 1549	maplist(proj, Out, Proj),
 1550	atomics_to_string(Proj, " ", Projection),
 1551	format(string(SubSel), 'SELECT ~w WHERE {', [Projection]),
 1552	maplist(binding_line, In, BindLines),
 1553	append([ PrefLines, [SubSel], BindLines, [QText], ["}"] ], Lines),
 1554	atomics_to_string(Lines, "\n", Query),
 1555	debug(sparql(service), 'SERVICE:~n~w', [Query]),
 1556	maplist(binding_var, Out, Vars),
 1557	Row =.. [row|Vars],
 1558	(   Silent == error
 1559	->  sparql_query(Query, Row, Options)
 1560	;   catch(sparql_query(Query, Row, Options), _, true)
 1561	).
 1562
 1563prefix_line(Pref-URL, Line) :-
 1564	format(string(Line), 'PREFIX ~w: <~w>', [Pref, URL]).
 1565
 1566bound_binding(_Name = Var) :-
 1567	ground(Var).
 1568
 1569proj(Name=_, Proj) :-
 1570	format(string(Proj), '?~w', [Name]).
 1571
 1572binding_line(Name=IRI, Line) :-
 1573	atom(IRI), !,
 1574	with_output_to(string(QIRI),
 1575		       turtle:turtle_write_uri(current_output, IRI)),
 1576	format(string(Line), 'BIND(~s as ?~w)', [QIRI, Name]).
 1577binding_line(Name=Literal, Line) :-
 1578	rdf_lexical_form(Literal, Lex),
 1579	(   Lex = ^^(String,Type)
 1580	->  with_output_to(
 1581		string(QString),
 1582		turtle:turtle_write_quoted_string(current_output, String)),
 1583	    with_output_to(
 1584		string(QType),
 1585		turtle:turtle_write_uri(current_output, Type)),
 1586	    format(string(Line), 'BIND(~s^^<~w> as ?~w)',
 1587		   [QString, QType, Name])
 1588	;   Lex = @(String,Lang)
 1589	->  with_output_to(
 1590		string(QString),
 1591		turtle:turtle_write_quoted_string(current_output, String)),
 1592	    format(string(Line), 'BIND(~s@~w as ?~w)',
 1593		   [QString, Lang, Name])
 1594	).
 1595
 1596binding_var(_Name=Var, Var).
 1597
 1598
 1599		 /*******************************
 1600		 *	       BNODES		*
 1601		 *******************************/
 1602
 1603%%	sparql_reset_bnodes
 1604%
 1605%	Reset the database for the BNODE(str) function
 1606
 1607sparql_reset_bnodes :-
 1608	retractall(bnode_store(_,_)).
 1609
 1610
 1611		 /*******************************
 1612		 *	      SIMPLIFY		*
 1613		 *******************************/
 1614
 1615%%	sparql_simplify(:Goal, -Simple) is det.
 1616%
 1617%	Simplify goals to the SPARQL runtime functions before they are
 1618%	handed to the general optimizer and runtime evaluation.
 1619
 1620sparql_simplify(sparql_true(E), G) :-
 1621	simplify_true(E, G), !.
 1622sparql_simplify(sparql_eval(E, V), G) :-
 1623	simplify_eval(E, V, G), !.
 1624sparql_simplify(Goal, Goal).
 1625
 1626
 1627%%	simplify_true(+Expr, -Goal) is semidet.
 1628%
 1629%	Simplify a boolean expression  resulting   from  a SPARQL FILTER
 1630%	statement. Ideally, this should be   a simple partial evaluation
 1631%	of sparql_true/1.
 1632
 1633simplify_true(Var, Var) :-		% E.g., FILTER(?a)
 1634	var(Var), !,
 1635	fail.
 1636simplify_true(or(A0,B0), (A;B)) :- !,
 1637	simplify_true(A0, A),
 1638	simplify_true(B0, B).
 1639simplify_true(and(A0,B0), (A,B)) :- !,
 1640	simplify_true(A0, A),
 1641	simplify_true(B0, B).
 1642simplify_true(A0=B0, A=B) :- !,
 1643	peval(A0, A, IsResource),
 1644	peval(B0, B, IsResource),
 1645	IsResource == true.		% at least one is a resource
 1646simplify_true(A0\=B0, A\=B) :- !,
 1647	peval(A0, A, IsResource),
 1648	peval(B0, B, IsResource),
 1649	IsResource == true.		% at least one is a resource
 1650simplify_true(Expr, sparql_true(PExpr)) :-
 1651	simplify_expression(Expr, PExpr).
 1652
 1653simplify_expression(Var, Var) :-
 1654	var(Var), !.
 1655simplify_expression(Term0, Term) :-
 1656	ground(Term0), !,
 1657	eval(Term0, Term).
 1658simplify_expression(Term0, Term) :-
 1659	list_arg(Term0), !,
 1660	Term0 =.. [Name,Args0],
 1661	maplist(simplify_expression, Args0, Args),
 1662	Term =.. [Name,Args].
 1663simplify_expression(Term0, Term) :-
 1664	compound(Term0), !,
 1665	Term0 =.. [Name|Args0],
 1666	maplist(simplify_expression, Args0, Args),
 1667	Term1 =.. [Name|Args],
 1668	simplify_test(Term1, Term).
 1669simplify_expression(Term, Term).
 1670
 1671list_arg(concat(_)).
 1672list_arg(coalesce(_)).
 1673
 1674%%	simplify_test(+Expr0, -Expr) is det.
 1675%
 1676%	Perform analysis on specific tests.   Currently  optimizes regex
 1677%	tests.
 1678
 1679simplify_test(regex(String, simple_literal(Pattern), simple_literal(Flags)),
 1680	      compiled_regex(Regex, String)) :-
 1681	atom(Pattern), atom(Flags), !,
 1682	regex_obj(Pattern, Flags, Regex).
 1683simplify_test(Expr, Expr).
 1684
 1685%%	simplify_eval(+Expr, +Value, -Goal) is semidet.
 1686
 1687simplify_eval(Expr, Var, Goal) :-
 1688	simplify_expression(Expr, Expr1),
 1689	Goal = sparql_eval(Expr1, Var).
 1690
 1691peval(Var, Var, IsResource) :-
 1692	var(Var), !,
 1693	(   get_attr(Var, annotations, Annot),
 1694	    memberchk(resource, Annot)
 1695	->  IsResource = true
 1696	;   true
 1697	).
 1698peval(Resource, Resource, true) :-
 1699	atom(Resource).
 1700
 1701
 1702		 /*******************************
 1703		 *	SUBQUERY EVALUATION	*
 1704		 *******************************/
 1705
 1706%%	sparql_subquery(+Proj, :Query, +Solutions) is nondet.
 1707%
 1708%	Execute a SPARQL subquery.
 1709%
 1710%	@param	Proj is a list of variables that are shared with the
 1711%		outer query.
 1712%	@tbd	Call the optimizer.
 1713%	@tbd	Sub queries must be evaluated before the outer query,
 1714%		so we must move them to the head of the query
 1715%		evaluation.  Not doing so causes no harm, but leads
 1716%		to repetitive execution of the subquery.
 1717
 1718sparql_subquery(Proj, Query, Solutions) :-
 1719	vars_in_bindings(Proj, Vars),
 1720	Reply =.. [row|Vars],
 1721	sparql:select_results(Solutions, Reply, Query),
 1722	debug(sparql(subquery), 'SubQuery result: ~q', [Proj]),
 1723	unify_projection(Proj).
 1724
 1725vars_in_bindings([], []).
 1726vars_in_bindings([_Outer=Var|T0], [Var|T]) :-
 1727	vars_in_bindings(T0, T).
 1728
 1729
 1730unify_projection([]).
 1731unify_projection([V=V|T]) :-
 1732	unify_projection(T).
 1733
 1734
 1735		 /*******************************
 1736		 *	      UPDATE		*
 1737		 *******************************/
 1738
 1739%%	sparql_update(:Updates) is det.
 1740%
 1741%	Handle SPARQL update requests.
 1742%
 1743%	@tbd	Realise authorization rules
 1744
 1745sparql_update(Module:Updates) :-
 1746	rdf_transaction(update(Updates, Module), 'SPARQL').
 1747
 1748update([], _).
 1749update([H|T], M) :-
 1750	update(H, M),
 1751	update(T, M).
 1752update(insert_data(Quads), _) :-
 1753	maplist(insert_triple(user), Quads).
 1754update(delete_data(Quads), _) :-
 1755	maplist(delete_triple(user), Quads).
 1756update(delete_where(Quads), _):-
 1757	maplist(delete_triples(user), Quads).
 1758update(add(_Silent, From, To), _) :-	% TBD: Error of From does not exist
 1759	db(From, FromDB),
 1760	db(To, ToDB),
 1761	forall(rdf(S,P,O,FromDB:Line),
 1762	       rdf_assert(S,P,O,ToDB:Line)).
 1763update(move(_Silent, From, To), _) :-
 1764	db(From, FromGraph),
 1765	db(To, ToGraph),
 1766	rdf_retractall(_,_,_,ToGraph),
 1767	forall(rdf(S,P,O,FromGraph:Line),
 1768	       ( rdf_retractall(S,P,O,FromGraph:Line),
 1769		 rdf_assert(S,P,O,ToGraph:Line)
 1770	       )).
 1771update(copy(_Silent, From, To), _) :-
 1772	db(From, FromGraph),
 1773	db(To, ToGraph),
 1774	rdf_retractall(_,_,_,ToGraph),
 1775	forall(rdf(S,P,O,FromGraph:Line),
 1776	       rdf_assert(S,P,O,ToGraph:Line)).
 1777update(modify(With, Modify, _Using, Query), Module) :-
 1778	db(With, Graph),
 1779	forall(Module:Query,
 1780	       modify(Modify, Graph)).
 1781update(load(_Silent, URI, Into), _) :-
 1782	(   Into = graph(Graph)
 1783	->  rdf_load(URI, [graph(Graph)])
 1784	;   rdf_load(URI)
 1785	).
 1786update(clear(_Silent, Clear), _) :-
 1787	clear_db(Clear).
 1788
 1789db(default, user).
 1790db(graph(G), G).
 1791
 1792modify(delete(Delete), Graph) :-
 1793	maplist(delete_triple(Graph), Delete).
 1794modify(insert(Insert), Graph) :-
 1795	maplist(insert_triple(Graph), Insert).
 1796modify(replace(Delete, Insert), Graph) :-
 1797	maplist(delete_triple(Graph), Delete),
 1798	maplist(insert_triple(Graph), Insert).
 1799
 1800%%	insert_triple(+Graph, +Triple) is det.
 1801
 1802insert_triple(Graph, rdf(S0,P,O0)) :- !,
 1803	modify_subject(S0, S),
 1804	modify_object(O0, O),
 1805	rdf_assert(S,P,O, Graph).
 1806insert_triple(_, rdf(S0,P,O0,G0)) :-
 1807	graph(G0, G),
 1808	modify_subject(S0, S),
 1809	modify_object(O0, O),
 1810	rdf_assert(S,P,O,G).
 1811
 1812%%	delete_triple(+Graph, +Triple) is det.
 1813%
 1814%	Delete matching triples
 1815
 1816delete_triple(Graph, rdf(S,P,O0)) :- !,
 1817	modify_object(O0, O),
 1818	rdf_retractall(S,P,O,Graph).
 1819delete_triple(_, rdf(S,P,O0,G0)) :- !,
 1820	graph(G0, G),
 1821	modify_object(O0, O),
 1822	rdf_retractall(S,P,O,G).
 1823
 1824%%	delete_triples(+Graph:atom, +SimpleTriplePattern:compound) is det.
 1825
 1826delete_triples(G0, Triple):-
 1827	(   Triple = rdf(S,P,O),
 1828	    G = G0
 1829	;   Triple = rdf(S,P,O,G)
 1830	),
 1831	forall(
 1832	    rdf(S,P,O),
 1833	    delete_triple(G, rdf(S,P,O))
 1834	).
 1835
 1836modify_subject(bnode(Id), BNode) :- !,
 1837	id_to_bnode(Id, BNode).
 1838modify_subject(S, S).
 1839
 1840modify_object(literal(_Q,V), literal(V)) :- !.
 1841modify_object(bnode(Id), BNode) :- !,
 1842	id_to_bnode(Id, BNode).
 1843modify_object(O, O).
 1844
 1845id_to_bnode(Id, BNode):-
 1846	(   bnode_store(Id, BN)
 1847	->  BN = BNode
 1848	;   rdf_bnode(BN),
 1849	    asserta(bnode_store(Id, BN))
 1850	->  BN = BNode
 1851	).
 1852
 1853%%	graph(+Spec, -Graph)
 1854
 1855graph(G:L, Graph) :-
 1856	atom(G), !,
 1857	(   integer(L)
 1858	->  Graph = (G:L)
 1859	;   Graph = G
 1860	).
 1861graph(G, G).
 1862
 1863%%	clear_db(+Clear)
 1864%
 1865%	Note that CLEAR ALL cannot use rdf_reset_db  because we are in a
 1866%	transaction.
 1867
 1868clear_db(all) :-
 1869	rdf_retractall(_,_,_).
 1870clear_db(default) :-
 1871	rdf_retractall(_,_,_,user).
 1872clear_db(named) :-
 1873	forall((rdf_graph(Graph), Graph \== user),
 1874	       rdf_retractall(_,_,_,Graph)).
 1875clear_db(graph(Graph)) :-
 1876	rdf_retractall(_,_,_,Graph)