1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker and Wouter Beek 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2015-2018, VU University Amsterdam 7 CWI, Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36 37:- module(rdf11, 38 [ rdf/3, % ?S, ?P, ?O 39 rdf/4, % ?S, ?P, ?O, ?G 40 rdf_has/3, % ?S, ?P, ?O 41 rdf_has/4, % ?S, ?P, ?O, -RealP 42 rdf_update/4, % +S, +P, +O, +Action 43 rdf_update/5, % +S, +P, +O, +G, +Action 44 rdf_reachable/3, % ?S, ?P, ?O 45 rdf_reachable/5, % ?S, ?P, ?O, +MaxD, -D 46 47 rdf_assert/3, % +S, +P, +O 48 rdf_assert/4, % +S, +P, +O, ?G 49 rdf_retractall/3, % ?S, ?P, ?O 50 rdf_retractall/4, % ?S, ?P, ?O, ?G 51 52 {}/1, % +Where 53 rdf_where/1, % +Where 54 rdf_compare/3, % -Diff, +Left, +Right 55 56 rdf_term/1, % ?Term 57 rdf_literal/1, % ?Term 58 rdf_bnode/1, % ?Term 59 rdf_iri/1, % ?Term 60 rdf_name/1, % ?Term 61 62 rdf_is_iri/1, % @Term 63 rdf_is_bnode/1, % @Term 64 rdf_is_literal/1, % @Term 65 rdf_is_name/1, % @Term 66 rdf_is_object/1, % @Term 67 rdf_is_predicate/1, % @Term 68 rdf_is_subject/1, % @Term 69 rdf_is_term/1, % @Term 70 71 rdf_subject/1, % ?Term 72 rdf_predicate/1, % ?Term 73 rdf_object/1, % ?Term 74 rdf_node/1, % ?Term 75 76 rdf_create_bnode/1, % ?Term 77 78 rdf_canonical_literal/2, % +In, -Canonical 79 rdf_lexical_form/2, % +Literal, -Lexical 80 81 rdf_default_graph/1, % -Graph 82 rdf_default_graph/2, % -Old, +New 83 84 rdf_estimate_complexity/4, % ?S, ?P, ?O, -Estimate 85 rdf_assert_list/2, % +PrologList, ?RDFList 86 rdf_assert_list/3, % +PrologList, ?RDFList, +G 87 rdf_last/2, % +RDFList, ?Last 88 rdf_list/1, % ?RDFList 89 rdf_list/2, % +RDFList, -PrologList 90 rdf_length/2, % ?RDFList, ?Length 91 rdf_member/2, % ?Member, +RDFList 92 rdf_nextto/2, % ?X, ?Y 93 rdf_nextto/3, % ?X, ?Y, ?RdfList 94 rdf_nth0/3, % ?Index, +RDFList, ?X 95 rdf_nth1/3, % ?Index, +RDFList, ?X 96 rdf_retract_list/1, % +RDFList 97 98 op(110, xfx, @), % must be above . 99 op(650, xfx, ^^), % must be above : 100 op(1150, fx, rdf_meta) 101 ]). 102:- use_module(library(semweb/rdf_prefixes), 103 [ (rdf_meta)/1, op(_,_,rdf_meta) 104 ]). 105:- use_module(library(semweb/rdf_db), 106 [ rdf_transaction/2, 107 rdf_match_label/3, 108 rdf_equal/2, 109 rdf_is_bnode/1, 110 rdf_transaction/1 111 ]). 112 113:- autoload(library(apply),[partition/4]). 114:- autoload(library(c14n2),[xml_write_canonical/3]). 115:- use_module(library(debug),[assertion/1,debug/3]). 116:- autoload(library(error), 117 [ must_be/2, 118 domain_error/2, 119 instantiation_error/1, 120 existence_error/2, 121 type_error/2, 122 is_of_type/2, 123 uninstantiation_error/1 124 ]). 125:- autoload(library(lists),[select/3,append/3]). 126:- autoload(library(memfile), 127 [new_memory_file/1,open_memory_file/3,free_memory_file/1]). 128:- autoload(library(sgml), 129 [ xsd_number_string/2, 130 xsd_time_string/3, 131 xml_is_dom/1, 132 load_xml/3, 133 load_html/3 134 ]). 135:- autoload(library(sgml_write),[html_write/3,xml_write/2]). 136:- autoload(library(solution_sequences),[distinct/2]). 137 138:- reexport(library(semweb/rdf_db), 139 except([ rdf/3, 140 rdf/4, 141 rdf_assert/3, 142 rdf_assert/4, 143 rdf_current_literal/1, 144 rdf_current_predicate/1, 145 rdf_has/3, 146 rdf_has/4, 147 rdf_update/4, 148 rdf_update/5, 149 rdf_reachable/3, 150 rdf_reachable/5, 151 rdf_retractall/3, 152 rdf_retractall/4, 153 rdf_node/1, 154 rdf_bnode/1, 155 rdf_is_literal/1, 156 rdf_is_resource/1, 157 rdf_literal_value/2, 158 rdf_compare/3, 159 rdf_estimate_complexity/4 160 ]) 161 ).
201:- multifile 202 in_ground_type_hook/3, % +Type, +Input, -Lexical:atom 203 out_type_hook/3, % +Type, -Output, +Lexical:atom 204 invalid_lexical_form_hook/3. % +Type, +Lexical, -Prolog 205 206:- meta_predicate 207 parse_partial_xml( , , ). 208 209:- rdf_meta 210 rdf(r,r,o), 211 rdf(r,r,o,r), 212 rdf_assert(r,r,o), 213 rdf_assert(r,r,o,r), 214 rdf_has(r,r,o), 215 rdf_has(r,r,o,-), 216 rdf_update(r,r,o,t), 217 rdf_update(r,r,o,r,t), 218 rdf_reachable(r,r,o), 219 rdf_reachable(r,r,o,+,-), 220 rdf_retractall(r,r,o), 221 rdf_retractall(r,r,o,r), 222 {}(t), 223 rdf_where(t), 224 rdf_canonical_literal(o,-), 225 rdf_lexical_form(o,-), 226 rdf_compare(-,o,o), 227 rdf_iri(r), 228 rdf_is_iri(r), 229 rdf_is_literal(o), 230 rdf_is_name(o), 231 rdf_is_object(o), 232 rdf_is_predicate(r), 233 rdf_is_subject(r), 234 rdf_is_term(o), 235 rdf_term(o), 236 rdf_literal(o), 237 rdf_name(o), 238 rdf_object(o), 239 rdf_estimate_complexity(r,r,o,-), 240 rdf_assert_list(t,r), 241 rdf_assert_list(t,r,r), 242 rdf_last(r,o), 243 rdf_list(r), 244 rdf_list(r,-), 245 rdf_length(r,-), 246 rdf_member(o,r), 247 rdf_nextto(o,o), 248 rdf_nth0(?,r,o), 249 rdf_nth1(?,r,o), 250 rdf_retract_list(r).
Triples consist of the following three terms:
Alias:Local
, where Alias and
Local are atoms. Each abbreviated IRI is expanded by the
system to a full IRI.Datatype IRI | Prolog term |
---|---|
xsd:float | float |
xsd:double | float |
xsd:decimal | float (1) |
xsd:integer | integer |
XSD integer sub-types | integer |
xsd:boolean | true or false |
xsd:date | date(Y,M,D) |
xsd:dateTime | date_time(Y,M,D,HH,MM,SS) (2,3) |
xsd:gDay | integer |
xsd:gMonth | integer |
xsd:gMonthDay | month_day(M,D) |
xsd:gYear | integer |
xsd:gYearMonth | year_month(Y,M) |
xsd:time | time(HH,MM,SS) (2) |
Notes:
(1) The current implementation of xsd:decimal
values
as floats is formally incorrect. Future versions
of SWI-Prolog may introduce decimal as a subtype
of rational.
(2) SS fields denote the number of seconds. This can either be an integer or a float.
(3) The date_time
structure can have a 7th field that
denotes the timezone offset in seconds as an
integer.
In addition, a ground object value is translated into a properly typed RDF literal using rdf_canonical_literal/2.
There is a fine distinction in how duplicate statements are handled in rdf/[3,4]: backtracking over rdf/3 will never return duplicate triples that appear in multiple graphs. rdf/4 will return such duplicate triples, because their graph term differs.
333rdf(S,P,O) :- 334 pre_object(O,O0,S,P), 335 rdf_db:rdf(S,P,O0), 336 post_object(O,O0). 337 338rdf(S,P,O,G) :- 339 pre_object(O,O0,S,P), 340 pre_graph(G,G0), 341 rdf_db:rdf(S,P,O0,G0), 342 post_graph(G, G0), 343 post_object(O,O0).
inverse_of
and
symmetric
. See rdf_set_predicate/2.353rdf_has(S,P,O) :- 354 pre_object(O,O0,S,P), 355 rdf_db:rdf_has(S,P,O0), 356 post_object(O,O0). 357 358rdf_has(S,P,O,RealP) :- 359 pre_object(O,O0,S,P), 360 rdf_db:rdf_has(S,P,O0,RealP), 361 post_object(O,O0).
literal(Value)
.
The argument matching Action must be ground. If this argument is
equivalent to the current value, no action is performed. Otherwise,
the requested action is performed on all matching triples. For
example, all resources typed rdfs:Class
can be changed to
owl:Class
using
?- rdf_update(_, rdf:type, rdfs:'Class', object(owl:'Class')).
398rdf_update(S, P, O, Action) :- 399 rdf_update(S, P, O, _, Action). 400rdf_update(S, P, O, G, Action) :- 401 must_be(ground, Action), 402 ( update_column(Action, S,P,O,G, On) 403 -> must_be(ground, On), 404 arg(1, Action, Old), 405 ( On == Old 406 -> true 407 ; rdf_transaction(rdf_update_(S, P, O, G, Action), update) 408 ) 409 ; domain_error(rdf_update_action, Action) 410 ). 411 412update_column(subject(_), S,_,_,_, S). 413update_column(predicate(_), _,P,_,_, P). 414update_column(object(_), _,_,O,_, O). 415update_column(graph(_), _,_,_,G, G). 416 417rdf_update_(S1, P, O, G, subject(S2)) :- 418 !, 419 forall(rdf(S1, P, O, G), 420 ( rdf_retractall(S1, P, O, G), 421 rdf_assert(S2, P, O, G) 422 )). 423rdf_update_(S, P1, O, G, predicate(P2)) :- 424 !, 425 forall(rdf(S, P1, O, G), 426 ( rdf_retractall(S, P1, O, G), 427 rdf_assert(S, P2, O, G) 428 )). 429rdf_update_(S, P, O1, G, object(O2)) :- 430 !, 431 forall(rdf(S, P, O1, G), 432 ( rdf_retractall(S, P, O1, G), 433 rdf_assert(S, P, O2, G) 434 )). 435rdf_update_(S, P, O, G1, graph(G2)) :- 436 !, 437 forall(rdf(S, P, O, G1), 438 ( rdf_retractall(S, P, O, G1), 439 rdf_assert(S, P, O, G2) 440 )).
inverse_of
and
symmetric
predicate properties. The version rdf_reachable/5
maximizes the steps considered and returns the number of steps
taken.
If both S and O are given, these predicates are semidet
. The
number of steps D is minimal because the implementation uses
breadth first search.
457rdf_reachable(S,P,O) :- 458 pre_object(O,O0,S,P), 459 rdf_db:rdf_reachable(S,P,O0), 460 post_object(O,O0). 461 462rdf_reachable(S,P,O,MaxD,D) :- 463 pre_object(O,O0,S,P), 464 rdf_db:rdf_reachable(S,P,O0,MaxD,D), 465 post_object(O,O0).
If a type is provided using Value^^Type syntax, additional conversions are performed. All types accept either an atom or Prolog string holding a valid RDF lexical value for the type and xsd:float and xsd:double accept a Prolog integer.
480rdf_assert(S,P,O) :- 481 rdf_default_graph(G), 482 rdf_assert(S,P,O,G). 483 484rdf_assert(S,P,O,G) :- 485 must_be(ground, O), 486 pre_ground_object(O,O0), 487 rdf_db:rdf_assert(S,P,O0,G).
496rdf_retractall(S,P,O) :- 497 pre_object(O,O0,S,P), 498 rdf_db:rdf_retractall(S,P,O0). 499 500rdf_retractall(S,P,O,G) :- 501 pre_object(O,O0,S,P), 502 pre_graph(G,G0), 503 rdf_db:rdf_retractall(S,P,O0,G0).
Note that this ordering is a complete ordering of RDF terms that is consistent with the partial ordering defined by SPARQL.
524rdf_compare(Diff, Left, Right) :-
525 pre_ground_object(Left, Left0),
526 pre_ground_object(Right, Right0),
527 rdf_db:rdf_compare(Diff, Left0, Right0).
{ Date >= "2000-01-01"^^xsd:date }, rdf(S, P, Date)
The following constraints are currently defined:
The predicates rdf_where/1 and {}/1 are identical. The
rdf_where/1 variant is provided to avoid ambiguity in
applications where {}/1 is used for other purposes. Note that it
is also possible to write rdf11:{...}
.
570{}(Where) :- 571 rdf_where(Where). 572 573rdf_where(Var) :- 574 var(Var), 575 !, 576 instantiation_error(Var). 577rdf_where((A,B)) :- 578 !, 579 rdf_where(A), 580 rdf_where(B). 581rdf_where(Constraint) :- 582 rdf_constraint(Constraint, Goal), 583 !, 584 call(Goal). 585rdf_where(Constraint) :- 586 existence_error(rdf_constraint, Constraint). 587 588% Comparison operators 589rdf_constraint(Term >= Value, 590 add_value_constraint(Term, >=, Value)). 591rdf_constraint(Term > Value, 592 add_value_constraint(Term, >, Value)). 593rdf_constraint(Term == Value, 594 add_value_constraint(Term, ==, Value)). 595rdf_constraint(Term < Value, 596 add_value_constraint(Term, <, Value)). 597rdf_constraint(Term =< Value, 598 add_value_constraint(Term, =<, Value)). 599% String selection 600rdf_constraint(prefix(Term, Pattern), 601 add_text_constraint(Term, prefix(PatternA))) :- 602 atom_string(PatternA, Pattern). 603rdf_constraint(substring(Term, Pattern), 604 add_text_constraint(Term, substring(PatternA))) :- 605 atom_string(PatternA, Pattern). 606rdf_constraint(word(Term, Pattern), 607 add_text_constraint(Term, word(PatternA))) :- 608 atom_string(PatternA, Pattern). 609rdf_constraint(like(Term, Pattern), 610 add_text_constraint(Term, like(PatternA))) :- 611 atom_string(PatternA, Pattern). 612rdf_constraint(icase(Term, Pattern), 613 add_text_constraint(Term, icase(PatternA))) :- 614 atom_string(PatternA, Pattern). 615% Lang selection 616rdf_constraint(lang_matches(Term, Pattern), 617 add_lang_constraint(Term, lang_matches(Pattern))). 618 619add_text_constraint(Var, Cond) :- 620 var(Var), 621 !, 622 ( get_attr(Var, rdf11, Cond0) 623 -> put_attr(Var, rdf11, [Cond|Cond0]) 624 ; put_attr(Var, rdf11, [Cond]) 625 ). 626add_text_constraint(Text^^_Type, Cond) :- 627 !, 628 add_text_constraint(Text, Cond). 629add_text_constraint(Text@_Lang, Cond) :- 630 !, 631 add_text_constraint(Text, Cond). 632add_text_constraint(Var, Cond) :- 633 eval_condition(Cond, Var).
639add_lang_constraint(Var, Constraint) :- 640 var(Var), 641 !, 642 ( get_attr(Var, rdf11, Cond0) 643 -> put_attr(Var, rdf11, [Constraint|Cond0]) 644 ; put_attr(Var, rdf11, [Constraint]) 645 ). 646add_lang_constraint(_Text@Lang, Constraint) :- 647 !, 648 add_lang_constraint(Lang, Constraint). 649add_lang_constraint(_Text^^_Type, _Constraint) :- 650 !, 651 fail. 652add_lang_constraint(Term, Constraint) :- 653 eval_condition(Constraint, Term).
659add_value_constraint(Term, Constraint, ValueIn) :- 660 constraint_literal_value(ValueIn, Value), 661 add_value_constraint_cann(Value, Constraint, Term). 662 663constraint_literal_value(Value, Value^^_Type) :- 664 number(Value), 665 !. 666constraint_literal_value(Value, Literal) :- 667 rdf_canonical_literal(Value, Literal). 668 669add_value_constraint_cann(RefVal^^Type, Constraint, Term) :- 670 var(Term), var(Type), 671 !, 672 add_text_constraint(Term, value(Constraint, RefVal, Type)). 673add_value_constraint_cann(RefVal^^Type, Constraint, Val^^Type2) :- 674 !, 675 Type = Type2, 676 add_text_constraint(Val, value(Constraint, RefVal, Type)). 677add_value_constraint_cann(RefVal@Lang, Constraint, Val@Lang) :- 678 !, 679 add_text_constraint(Val, value(Constraint, RefVal, lang(Lang))). 680add_value_constraint_cann(RefVal^^Type, Constraint, Val) :- 681 !, 682 ground(Val), 683 Val \= _@_, 684 eval_condition(value(Constraint, RefVal, Type), Val). 685 686put_cond(Var, []) :- 687 !, 688 del_attr(Var, rdf11). 689put_cond(Var, List) :- 690 put_attr(Var, rdf11, List). 691 692eval_condition(Cond, Literal) :- 693 text_condition(Cond), 694 !, 695 text_of(Literal, Text), 696 text_condition(Cond, Text). 697eval_condition(Cond, Literal) :- 698 lang_condition(Cond), 699 !, 700 lang_of(Literal, Lang), 701 lang_condition(Cond, Lang). 702eval_condition(value(Comp, Ref, _Type), Value) :- 703 ( number(Ref) 704 -> number(Value), 705 compare_numeric(Comp, Ref, Value) 706 ; compare_std(Comp, Ref, Value) 707 ). 708 709compare_numeric(<, Ref, Value) :- Value < Ref. 710compare_numeric(=<, Ref, Value) :- Value =< Ref. 711compare_numeric(==, Ref, Value) :- Value =:= Ref. 712compare_numeric(>=, Ref, Value) :- Value >= Ref. 713compare_numeric( >, Ref, Value) :- Value > Ref. 714 715compare_std(<, Ref, Value) :- Value @< Ref. 716compare_std(=<, Ref, Value) :- Value @=< Ref. 717compare_std(==, Ref, Value) :- Value == Ref. 718compare_std(>=, Ref, Value) :- Value @>= Ref. 719compare_std( >, Ref, Value) :- Value @> Ref. 720 721text_condition(prefix(_)). 722text_condition(substring(_)). 723text_condition(word(_)). 724text_condition(like(_)). 725text_condition(icase(_)). 726 727text_of(Literal, Text) :- 728 atomic(Literal), 729 !, 730 Text = Literal. 731text_of(Text@_Lang, Text). 732text_of(Text^^_Type, Text). 733 734text_condition(prefix(Pattern), Text) :- 735 rdf_match_label(prefix, Pattern, Text). 736text_condition(substring(Pattern), Text) :- 737 rdf_match_label(substring, Pattern, Text). 738text_condition(word(Pattern), Text) :- 739 rdf_match_label(word, Pattern, Text). 740text_condition(like(Pattern), Text) :- 741 rdf_match_label(like, Pattern, Text). 742text_condition(icase(Pattern), Text) :- 743 rdf_match_label(icase, Pattern, Text). 744 745lang_condition(lang_matches(_)). 746 747lang_of(_Text@Lang0, Lang) :- 748 !, 749 Lang = Lang0. 750lang_of(Lang, Lang) :- 751 atom(Lang). 752 753lang_condition(lang_matches(Pattern), Lang) :- 754 rdf_db:lang_matches(Lang, Pattern).
literal(Cond, _Value)
.
Translated constraints are removed from object.
762literal_condition(Object, Cond) :-
763 get_attr(Object, rdf11, Cond0),
764 best_literal_cond(Cond0, Cond, Rest),
765 put_cond(Object, Rest).
literal(Search, Value)
.
774best_literal_cond(Conditions, Best, Rest) :- 775 sort(Conditions, Unique), 776 best_literal_cond2(Unique, Best, Rest). 777 778best_literal_cond2(Conds, Best, Rest) :- 779 select(Cond, Conds, Rest0), 780 rdf10_cond(Cond, Best, Rest0, Rest), 781 !. 782 783rdf10_cond(value(=<, URef, UType), Cond, Rest0, Rest) :- 784 ( select(value(>=, LRef, LType), Rest0, Rest) 785 -> true 786 ; memberchk(value(>, LRef, LType), Rest0) 787 -> Rest = Rest0 788 ), 789 !, 790 in_constaint_type(LType, SLType, LRef, LRef0), 791 in_constaint_type(UType, SUType, URef, URef0), 792 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 793rdf10_cond(value(<, URef, UType), Cond, Rest0, Rest) :- 794 ( select(value(>=, LRef, LType), Rest0, Rest1) 795 -> true 796 ; memberchk(value(>, LRef, LType), Rest0) 797 -> Rest1 = Rest0 798 ), 799 !, 800 Rest = [value(<, URef, UType)|Rest1], 801 in_constaint_type(LType, SLType, LRef, LRef0), 802 in_constaint_type(UType, SUType, URef, URef0), 803 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 804rdf10_cond(value(Cmp, Ref, Type), Pattern, Rest, Rest) :- 805 !, 806 rdf10_compare(Cmp, Ref, Type, Pattern). 807rdf10_cond(lang_matches(_), _, _, _) :- !, fail. 808rdf10_cond(Cond, Cond, Rest, Rest). 809 810rdf10_compare(Cmp, Ref, Type, Pattern) :- 811 nonvar(Type), Type = lang(Lang), 812 !, 813 atom_string(Ref0, Ref), 814 rdf10_lang_cond(Cmp, Ref0, Lang, Pattern). 815rdf10_compare(Cmp, Ref, Type, Pattern) :- 816 in_constaint_type(Type, SType, Ref, Ref0), 817 rdf10_type_cond(Cmp, Ref0, SType, Pattern). 818 819rdf10_lang_cond( <, Ref, Lang, lt(lang(Lang,Ref))). 820rdf10_lang_cond(=<, Ref, Lang, le(lang(Lang,Ref))). 821rdf10_lang_cond(==, Ref, Lang, eq(lang(Lang,Ref))). 822rdf10_lang_cond(>=, Ref, Lang, ge(lang(Lang,Ref))). 823rdf10_lang_cond(>, Ref, Lang, gt(lang(Lang,Ref))). 824 825rdf10_type_cond( <, Ref, Type, lt(type(Type,Ref))). 826rdf10_type_cond(=<, Ref, Type, le(type(Type,Ref))). 827rdf10_type_cond(==, Ref, Type, eq(type(Type,Ref))). 828rdf10_type_cond(>=, Ref, Type, ge(type(Type,Ref))). 829rdf10_type_cond( >, Ref, Type, gt(type(Type,Ref))).
834in_constaint_type(Type, SType, Val, Val0) :- 835 nonvar(Type), ground(Val), 836 !, 837 SType = Type, 838 in_ground_type(Type, Val, Val0). 839in_constaint_type(Type, SType, Val, Val0) :- 840 var(Type), number(Val), 841 !, 842 ( integer(Val) 843 -> rdf_equal(SType, xsd:integer), 844 in_ground_type(xsd:integer, Val, Val0) 845 ; float(Val) 846 -> rdf_equal(SType, xsd:double), 847 in_ground_type(xsd:double, Val, Val0) 848 ; assertion(fail) 849 ).
857literal_class(Term, Class) :-
858 get_attr(Term, rdf11, Conds),
859 select(Cond, Conds, Rest),
860 lang_condition(Cond),
861 !,
862 Term = Text@Lang,
863 put_attr(Lang, rdf11, [Cond]),
864 put_cond(Text, Rest),
865 ( var(Text)
866 -> true
867 ; atom_string(Text2, Text)
868 ),
869 Class = lang(Lang, Text2).
873attr_unify_hook(Cond, Value) :- 874 get_attr(Value, rdf11, Cond2), 875 !, 876 append(Cond, Cond2, CondJ), 877 sort(CondJ, Unique), 878 put_cond(Value, Unique). 879attr_unify_hook(Cond, Text^^_Type) :- 880 var(Text), 881 !, 882 put_cond(Text, Cond). 883attr_unify_hook(Cond, Text@Lang) :- 884 var(Text), var(Lang), 885 !, 886 partition(lang_condition, Cond, LangCond, TextCond), 887 put_cond(Text, TextCond), 888 put_cond(Lang, LangCond). 889attr_unify_hook(Cond, Value) :- 890 sort(Cond, Unique), 891 propagate_conditions(Unique, Value). 892 893propagate_conditions([], _). 894propagate_conditions([H|T], Val) :- 895 propagate_condition(H, Val), 896 propagate_conditions(T, Val). 897 898propagate_condition(value(Comp, Ref, Type), Value) :- 899 !, 900 ( Value = Plain^^VType 901 -> VType = Type 902 ; Plain = Value 903 ), 904 cond_compare(Comp, Ref, Plain). 905propagate_condition(lang_matches(Pattern), Value) :- 906 !, 907 ( Value = _@Lang 908 -> true 909 ; Lang = Value 910 ), 911 rdf_db:lang_matches(Lang, Pattern). 912propagate_condition(Cond, Value) :- 913 Cond =.. [Name|Args], 914 Constraint =.. [Name,Value|Args], 915 rdf_constraint(Constraint, Continuation), 916 call(Continuation). 917 918cond_compare(>, Ref, Value) :- Value @> Ref. 919cond_compare(>=, Ref, Value) :- Value @>= Ref. 920cond_compare(==, Ref, Value) :- Value == Ref. 921cond_compare(=<, Ref, Value) :- Value @=< Ref. 922cond_compare( <, Ref, Value) :- Value @< Ref.
932:- create_prolog_flag(rdf_default_graph, default, 933 [ type(atom), 934 keep(true) 935 ]). 936 937rdf_default_graph(Graph) :- 938 current_prolog_flag(rdf_default_graph, Graph). 939rdf_default_graph(Old, New) :- 940 current_prolog_flag(rdf_default_graph, Old), 941 ( New == Old 942 -> true 943 ; set_prolog_flag(rdf_default_graph, New) 944 ). 945 946 947pre_graph(G, _G0) :- 948 var(G), 949 !. 950pre_graph(G, G) :- 951 atom(G), 952 !. 953pre_graph(G, _) :- 954 type_error(rdf_graph, G). 955 956post_graph(G, G0:_) :- 957 !, 958 G = G0. 959post_graph(G, G). 960 961 962% left for code calling this directly 963 964pre_object(Atom, URI) :- 965 pre_object(Atom, URI, _, _).
969pre_object(Atom, URI, _, _) :- 970 atom(Atom), 971 \+ boolean(Atom), 972 !, 973 URI = Atom. 974pre_object(Var, Var1, Subj, Pred) :- 975 var(Var), 976 !, 977 ( literal_condition(Var, Cond) 978 -> Var1 = literal(Cond, _) 979 ; literal_class(Var, Value) 980 -> Var1 = literal(Value) 981 ; ( Var == Subj 982 -> Var1 = Subj 983 ; true 984 ), 985 ( Var == Pred 986 -> Var1 = Pred 987 ; true 988 ) 989 ). 990pre_object(Val@Lang, Var1, _, _) :- 991 !, 992 ( literal_condition(Val, Cond) 993 -> Var1 = literal(Cond, lang(Lang, _)) 994 ; literal_class(Val@Lang, Class) 995 -> Var1 = literal(Class) 996 ; in_lang_string(Val, Val0), 997 Var1 = literal(lang(Lang, Val0)) 998 ). 999pre_object(Val^^Type, Var1, _, _) :- 1000 !, 1001 ( literal_condition(Val, Cond) 1002 -> Var1 = literal(Cond, type(Type, _)) 1003 ; in_type(Type, Val, Type0, Val0), 1004 ( var(Type0), var(Val0) 1005 -> Var1 = literal(_) 1006 ; Var1 = literal(type(Type0, Val0)) 1007 ) 1008 ). 1009pre_object(Obj, Val0, _, _) :- 1010 ground(Obj), 1011 !, 1012 pre_ground_object(Obj, Val0). 1013pre_object(Obj, _, _, _) :- 1014 type_error(rdf_object, Obj).
date(Y,M,D)
Converted to date(Y,M,D)
^^xsd:datedate_time(Y,M,D,HH,MM,SS)
Converted to date_time(Y,M,D,HH,MM,SS)
^^xsd:dateTimedate_time(Y,M,D,HH,MM,SS,TZ)
Converted to date_time(Y,M,D,HH,MM,SS,TZ)
^^xsd:dateTimemonth_day(M,D)
Converted to month_day(M,D)
^^xsd:gMonthDayyear_month(Y,M)
Converted to year_month(Y,M)
^^xsd:gYearMonthtime(HH,MM,SS)
Converted to time(HH,MM,SS)
^^xsd:timetrue
and false
are considered
URIs.1057:- rdf_meta 1058 pre_ground_object(+, o). 1059 1060pre_ground_object(Val@Lang, literal(lang(Lang0, Val0))) :- 1061 !, 1062 downcase_atom(Lang, Lang0), 1063 in_lang_string(Val, Val0). 1064pre_ground_object(Val^^Type, literal(type(Type0, Val0))) :- 1065 !, 1066 in_type(Type, Val, Type0, Val0). 1067pre_ground_object(literal(Lit0), literal(Lit)) :- 1068 old_literal(Lit0, Lit), 1069 !. 1070% Interpret `false' and `true' as the Boolean values. 1071pre_ground_object(false, literal(type(xsd:boolean, false))) :- !. 1072pre_ground_object(true, literal(type(xsd:boolean, true))) :- !. 1073pre_ground_object(Atom, URI) :- 1074 atom(Atom), 1075 !, 1076 URI = Atom. 1077% Interpret Prolog integer as xsd:integer. 1078pre_ground_object(Int, Object) :- 1079 integer(Int), 1080 !, 1081 rdf_equal(Object, literal(type(xsd:integer, Atom))), 1082 atom_number(Atom, Int). 1083% Interpret Prolog floating-point value as xsd:double. 1084pre_ground_object(Float, Object) :- 1085 float(Float), 1086 !, 1087 rdf_equal(Object, literal(type(xsd:double, Atom))), 1088 xsd_number_string(Float, String), 1089 atom_string(Atom, String). 1090% Interpret SWI string as xsd:string. 1091pre_ground_object(String, Object) :- 1092 string(String), 1093 !, 1094 rdf_equal(Object, literal(type(xsd:string, Atom))), 1095 atom_string(Atom, String). 1096% Interpret date(Y,M,D) as xsd:date, 1097% date_time(Y,M,D,HH,MM,SS) as xsd:dateTime, 1098% date_time(Y,M,D,HH,MM,SS,TZ) as xsd:dateTime, 1099% month_day(M,D) as xsd:gMonthDay, 1100% year_month(Y,M) as xsd:gYearMonth, and 1101% time(HH,MM,SS) as xsd:time. 1102pre_ground_object(Term, literal(type(Type, Atom))) :- 1103 xsd_date_time_term(Term), 1104 !, 1105 xsd_time_string(Term, Type, String), 1106 atom_string(Atom, String). 1107pre_ground_object(Value, _) :- 1108 type_error(rdf_object, Value). 1109 1110xsd_date_time_term(date(_,_,_)). 1111xsd_date_time_term(date_time(_,_,_,_,_,_)). 1112xsd_date_time_term(date_time(_,_,_,_,_,_,_)). 1113xsd_date_time_term(month_day(_,_)). 1114xsd_date_time_term(year_month(_,_)). 1115xsd_date_time_term(time(_,_,_)). 1116 1117old_literal(Lit0, Lit) :- 1118 old_literal(Lit0), 1119 !, 1120 Lit = Lit0. 1121old_literal(Atom, Lit) :- 1122 atom(Atom), 1123 rdf_equal(xsd:string, XSDString), 1124 Lit = type(XSDString, Atom). 1125 1126old_literal(type(Type, Value)) :- 1127 atom(Type), atom(Value). 1128old_literal(lang(Lang, Value)) :- 1129 atom(Lang), atom(Value). 1130 1131in_lang_string(Val, Val0) :- 1132 atomic(Val), 1133 !, 1134 atom_string(Val0, Val). 1135in_lang_string(_, _). 1136 1137in_type(Type, Val, Type, Val0) :- 1138 nonvar(Type), ground(Val), 1139 !, 1140 in_ground_type(Type, Val, Val0). 1141in_type(VarType, Val, VarType, Val0) :- 1142 ground(Val), 1143 \+ catch(xsd_number_string(_, Val), _, fail), 1144 !, 1145 atom_string(Val0, Val). 1146in_type(_, _, _, _). 1147 1148:- rdf_meta 1149 in_ground_type(r,?,?), 1150 in_date_component(r, +, +, -).
1158in_ground_type(Type, Input, Lex) :- 1159 \+ string(Input), 1160 in_ground_type_hook(Type, Input, Lex), 1161 !. 1162in_ground_type(IntType, Val, Val0) :- 1163 xsd_numerical(IntType, Domain, PrologType), 1164 !, 1165 in_number(PrologType, Domain, IntType, Val, Val0). 1166in_ground_type(xsd:boolean, Val, Val0) :- 1167 !, 1168 ( in_boolean(Val, Val0) 1169 -> true 1170 ; type_error(rdf_boolean, Val) 1171 ). 1172in_ground_type(rdf:langString, _Val0, _) :- 1173 !, 1174 domain_error(rdf_data_type, rdf:langString). 1175in_ground_type(DateTimeType, Val, Val0) :- 1176 xsd_date_time_type(DateTimeType), 1177 !, 1178 in_date_time(DateTimeType, Val, Val0). 1179in_ground_type(rdf:'XMLLiteral', Val, Val0) :- 1180 !, 1181 in_xml_literal(xml, Val, Val0). 1182in_ground_type(rdf:'HTML', Val, Val0) :- 1183 !, 1184 in_xml_literal(html, Val, Val0). 1185in_ground_type(_Unknown, Val, Val0) :- 1186 atom_string(Val0, Val).
1193:- rdf_meta 1194 in_date_time(r,+,-). 1195 1196in_date_time(Type, Text, Text0) :- 1197 atom(Text), 1198 !, 1199 xsd_time_string(_, Type, Text), 1200 Text0 = Text. 1201in_date_time(Type, Text, Text0) :- 1202 string(Text), 1203 !, 1204 xsd_time_string(_, Type, Text), 1205 atom_string(Text0, Text). 1206in_date_time(xsd:dateTime, Stamp, Text0) :- 1207 number(Stamp), 1208 !, 1209 format_time(atom(Text0), '%FT%T%:z', Stamp). 1210in_date_time(Type, Term, Text0) :- 1211 !, 1212 xsd_time_string(Term, Type, String), 1213 atom_string(Text0, String).
1220in_boolean(true, true). 1221in_boolean(false, false). 1222in_boolean("true", true). 1223in_boolean("false", false). 1224in_boolean(1, true). 1225in_boolean(0, false). 1226 1227boolean(false). 1228boolean(true).
1237in_number(integer, Domain, XSDType, Val, Val0) :- 1238 integer(Val), 1239 !, 1240 check_integer_domain(Domain, XSDType, Val), 1241 atom_number(Val0, Val). 1242in_number(integer, Domain, XSDType, Val, Val0) :- 1243 atomic(Val), 1244 atom_number(Val, Num), 1245 integer(Num), 1246 !, 1247 check_integer_domain(Domain, XSDType, Num), 1248 atom_number(Val0, Num). 1249in_number(double, _Domain, _, Val, Val0) :- 1250 number(Val), 1251 !, 1252 ValF is float(Val), 1253 xsd_number_string(ValF, ValS), 1254 atom_string(Val0, ValS). 1255in_number(double, _Domain, _, Val, Val0) :- 1256 atomic(Val), 1257 xsd_number_string(Num, Val), 1258 ValF is float(Num), 1259 !, 1260 xsd_number_string(ValF, ValS), 1261 atom_string(Val0, ValS). 1262in_number(decimal, _Domain, _, Val, Val0) :- 1263 number(Val), 1264 !, 1265 ValF is float(Val), 1266 atom_number(Val0, ValF). 1267in_number(decimal, _Domain, _, Val, Val0) :- 1268 atomic(Val), 1269 xsd_number_string(Num, Val), 1270 ValF is float(Num), 1271 !, 1272 atom_number(Val0, ValF). 1273in_number(PrologType, _, _, Val, _) :- 1274 type_error(PrologType, Val). 1275 1276check_integer_domain(PLType, _, Val) :- 1277 is_of_type(PLType, Val), 1278 !. 1279check_integer_domain(_, XSDType, Val) :- 1280 domain_error(XSDType, Val). 1281 1282errorhas_type(nonpos, T):- 1283 integer(T), 1284 T =< 0. 1285 1286%check_integer_domain(between(Low, High), XSDType, Val) :- 1287% ( between(Low, High, Val) 1288% -> true 1289% ; domain_error(XSDType, Val) 1290% ). 1291%check_integer_domain(integer, _, _).
1295:- rdf_meta 1296 xsd_numerical(r, ?, ?). 1297 1298xsd_numerical(xsd:byte, between(-128,127), integer). 1299xsd_numerical(xsd:double, float, double). 1300xsd_numerical(xsd:decimal, float, decimal). 1301xsd_numerical(xsd:float, float, double). 1302xsd_numerical(xsd:int, between(-2147483648,2147483647), integer). 1303xsd_numerical(xsd:integer, integer, integer). 1304xsd_numerical(xsd:long, between(-9223372036854775808, 1305 9223372036854775807), integer). 1306xsd_numerical(xsd:negativeInteger, negative_integer, integer). 1307xsd_numerical(xsd:nonNegativeInteger, nonneg, integer). 1308xsd_numerical(xsd:nonPositiveInteger, nonpos, integer). 1309xsd_numerical(xsd:positiveInteger, positive_integer, integer). 1310xsd_numerical(xsd:short, between(-32768,32767), integer). 1311xsd_numerical(xsd:unsignedByte, between(0,255), integer). 1312xsd_numerical(xsd:unsignedInt, between(0,4294967295), integer). 1313xsd_numerical(xsd:unsignedLong, between(0,18446744073709551615), integer). 1314xsd_numerical(xsd:unsignedShort, between(0,65535), integer).
1320:- rdf_meta 1321 xsd_date_time_type(r). 1322 1323xsd_date_time_type(xsd:date). 1324xsd_date_time_type(xsd:dateTime). 1325xsd_date_time_type(xsd:gDay). 1326xsd_date_time_type(xsd:gMonth). 1327xsd_date_time_type(xsd:gMonthDay). 1328xsd_date_time_type(xsd:gYear). 1329xsd_date_time_type(xsd:gYearMonth). 1330xsd_date_time_type(xsd:time).
1340in_xml_literal(Type, Val, Val0) :- 1341 xml_is_dom(Val), 1342 !, 1343 write_xml_literal(Type, Val, Val0). 1344in_xml_literal(xml, Val, Val0) :- 1345 parse_partial_xml(load_xml, Val, DOM), 1346 write_xml_literal(xml, DOM, Val0). 1347in_xml_literal(html, Val, Val0) :- 1348 parse_partial_xml(load_html, Val, DOM), 1349 write_xml_literal(html, DOM, Val0). 1350 1351parse_partial_xml(Parser, Val, DOM) :- 1352 setup_call_cleanup( 1353 new_memory_file(MF), 1354 ( setup_call_cleanup( 1355 open_memory_file(MF, write, Out), 1356 format(Out, "<xml>~w</xml>", [Val]), 1357 close(Out)), 1358 setup_call_cleanup( 1359 open_memory_file(MF, read, In), 1360 call(Parser, stream(In), [element(xml, _, DOM)], []), 1361 close(In)) 1362 ), 1363 free_memory_file(MF)). 1364 1365 1366write_xml_literal(xml, DOM, Text) :- 1367 with_output_to(atom(Text), 1368 xml_write_canonical(current_output, DOM, [])). 1369write_xml_literal(html, DOM, Text) :- 1370 with_output_to(atom(Text), 1371 html_write(current_output, DOM, 1372 [ header(false), 1373 layout(false) 1374 ])).
Prolog Term | Datatype IRI |
---|---|
float | xsd:double |
integer | xsd:integer |
string | xsd:string |
true or false | xsd:boolean |
date(Y,M,D) | xsd:date |
date_time(Y,M,D,HH,MM,SS) | xsd:dateTime |
date_time(Y,M,D,HH,MM,SS,TZ) | xsd:dateTime |
month_day(M,D) | xsd:gMonthDay |
year_month(Y,M) | xsd:gYearMonth |
time(HH,MM,SS) | xsd:time |
For example:
?- rdf_canonical_literal(42, X). X = 42^^'http://www.w3.org/2001/XMLSchema#integer'.
1402rdf_canonical_literal(In, Literal) :- 1403 ground(In), 1404 !, 1405 pre_ground_object(In, DBTerm), 1406 post_object(Literal, DBTerm). 1407rdf_canonical_literal(In, _) :- 1408 must_be(ground, In).
1421% For example, 1422% 1423% == 1424% ?- rdf_lexical_form(2.3^^xsd:double, L). 1425% L = "2.3E0"^^'http://www.w3.org/2001/XMLSchema#double'. 1426% == 1427 1428rdf_lexical_form(Literal, Lexical) :- 1429 pre_ground_object(Literal, literal(Lit0)), 1430 !, 1431 text_of0(Lit0, Lexical). 1432rdf_lexical_form(Literal, _) :- 1433 type_error(rdf_literal, Literal). 1434 1435text_of0(type(TypeA, LexicalA), LexicalS^^TypeA) :- 1436 atom_string(LexicalA, LexicalS). 1437text_of0(lang(LangA, LexicalA), LexicalS@LangA) :- 1438 atom_string(LexicalA, LexicalS). 1439 1440 1441 /******************************* 1442 * POST PROCESSING * 1443 *******************************/ 1444 1445:- rdf_meta 1446 post_object(o,o), 1447 out_type(r,-,+). 1448 1449post_object(Val, _) :- 1450 ground(Val), 1451 !. % already specified and matched 1452post_object(URI, URI0) :- 1453 atom(URI0), 1454 !, 1455 URI = URI0. 1456post_object(Val@Lang, literal(lang(Lang, Val0))) :- 1457 nonvar(Lang), % lang(Lang,Text) returns var(Lang) if no lang 1458 !, 1459 atom_string(Val0, Val). 1460post_object(Val^^Type, literal(type(Type, Val0))) :- 1461 !, 1462 out_type(Type, Val, Val0). 1463post_object(Val^^xsd:string, literal(Plain)) :- 1464 !, 1465 atomic(Plain), 1466 atom_string(Plain, Val). 1467post_object(Val@Lang, literal(_, lang(Lang, Val0))) :- 1468 nonvar(Lang), 1469 !, 1470 atom_string(Val0, Val). 1471post_object(Val^^Type, literal(_, type(Type, Val0))) :- 1472 !, 1473 out_type(Type, Val, Val0). 1474post_object(Val^^xsd:string, literal(_, Plain)) :- 1475 atomic(Plain), 1476 atom_string(Plain, Val). 1477 1478out_type(xsd:string, Val, Val0) :- % catches unbound type too 1479 !, 1480 atom_string(Val0, Val). 1481out_type(Type, Val, Val0) :- 1482 out_type_hook(Type, Val, Val0), 1483 !. 1484out_type(IntType, Val, Val0) :- 1485 xsd_numerical(IntType, _Domain, _BasicType), 1486 !, 1487 xsd_number_string(Val, Val0). 1488out_type(DateTimeType, Val, Val0) :- 1489 xsd_date_time_type(DateTimeType), 1490 !, 1491 out_date_time(DateTimeType, Val, Val0). 1492out_type(xsd:boolean, Val, Val0) :- 1493 !, 1494 Val = Val0. 1495out_type(rdf:'XMLLiteral', XML, DOM) :- 1496 xml_is_dom(DOM), 1497 !, 1498 with_output_to(string(XML), 1499 xml_write(DOM, [header(false)])). 1500out_type(_Unknown, Val, Val0) :- 1501 atom_string(Val0, Val).
1509out_date_time(Type, Prolog, Lexical) :-
1510 catch(xsd_time_string(Prolog, Type, Lexical),
1511 error(_,_),
1512 invalid_lexical_form_hook(Type, Lexical, Prolog)).
1522 /******************************* 1523 * ENUMERATION * 1524 *******************************/
1533rdf_term(N) :- 1534 ground(N), 1535 !, 1536 pre_object(N, N0, _, _), 1537 visible_term(N0). 1538rdf_term(N) :- 1539 gen_term(N). 1540 1541gen_term(N) :- 1542 resource(N), 1543 visible_term(N). 1544gen_term(O) :- % performs double conversion! 1545 rdf_literal(O), 1546 (rdf(_,_,O) -> true).
1554rdf_literal(Term) :- 1555 ground(Term), 1556 !, 1557 ( boolean(Term) 1558 ; \+ atom(Term) 1559 ), 1560 !, 1561 pre_ground_object(Term, Object), 1562 (rdf_db:rdf(_,_,Object)->true). 1563rdf_literal(Term) :- 1564 pre_object(Term,literal(Lit0), _, _), 1565 rdf_db:rdf_current_literal(Lit0), 1566 (rdf_db:rdf(_,_,literal(Lit0))->true), 1567 post_object(Term, literal(Lit0)).
1574rdf_bnode(BNode) :- 1575 atom(BNode), 1576 !, 1577 current_bnode(BNode). 1578rdf_bnode(BNode) :- 1579 rdf_db:rdf_resource(BNode), 1580 current_bnode(BNode). 1581 1582current_bnode(BNode) :- 1583 rdf_is_bnode(BNode), 1584 visible_node(BNode). % Assumes BNodes cannot be predicates
1591rdf_iri(IRI) :- 1592 atom(IRI), 1593 !, 1594 \+ rdf_is_bnode(IRI), 1595 visible_term(IRI). 1596rdf_iri(IRI) :- 1597 resource(IRI), 1598 \+ rdf_is_bnode(IRI), 1599 visible_term(IRI).
1606rdf_name(Name) :- 1607 atom(Name), \+ boolean(Name), 1608 !, 1609 \+ rdf_is_bnode(Name), 1610 visible_term(Name). 1611rdf_name(Name) :- 1612 ground(Name), 1613 !, 1614 pre_ground_object(Name, Name0), 1615 (rdf_db:rdf(_,_,Name0)->true). 1616rdf_name(Name) :- 1617 rdf_iri(Name). 1618rdf_name(Name) :- 1619 rdf_literal(Name).
1634rdf_predicate(P) :- 1635 atom(P), 1636 !, 1637 (rdf(_,P,_) -> true). 1638rdf_predicate(P) :- 1639 rdf_db:rdf_current_predicate(P), 1640 (rdf(_,P,_) -> true).
1649rdf_object(O) :- 1650 ground(O), 1651 !, 1652 ( atom(O), \+ boolean(O) 1653 -> (rdf_db:rdf(_,_,O) -> true) 1654 ; rdf_literal(O) 1655 ). 1656rdf_object(O) :- 1657 rdf_db:rdf_resource(O), 1658 (rdf_db:rdf(_,_,O) -> true). 1659rdf_object(O) :- 1660 rdf_literal(O).
1667rdf_node(N) :- 1668 var(N), 1669 !, 1670 gen_node(N). 1671rdf_node(N) :- 1672 pre_ground_object(N, N0), 1673 visible_node(N0). 1674 1675gen_node(N) :- 1676 rdf_db:rdf_resource(N), 1677 visible_node(N). 1678gen_node(O) :- % performs double conversion! 1679 rdf_literal(O), 1680 (rdf(_,_,O) -> true).
1688resource(R) :- 1689 var(R), 1690 !, 1691 gen_resource(R). 1692resource(R) :- 1693 rdf_db:rdf_resource(R), 1694 !. 1695resource(R) :- 1696 rdf_db:rdf_current_predicate(R), 1697 !. 1698 1699gen_resource(R) :- 1700 rdf_db:rdf_resource(R). 1701gen_resource(R) :- 1702 rdf_db:rdf_current_predicate(R), 1703 \+ rdf_db:rdf_resource(R). 1704 1705visible_node(Term) :- 1706 atom(Term), 1707 !, 1708 ( rdf_db:rdf(Term,_,_) 1709 ; rdf_db:rdf(_,_,Term) 1710 ), 1711 !. 1712visible_node(Term) :- 1713 rdf_db:rdf(_,_,Term). 1714 1715visible_term(Term) :- 1716 atom(Term), 1717 !, 1718 ( rdf_db:rdf(Term,_,_) 1719 ; rdf_db:rdf(_,Term,_) 1720 ; rdf_db:rdf(_,_,Term) 1721 ), 1722 !. 1723visible_term(Term) :- 1724 rdf_db:rdf(_,_,Term).
_:
. Blank nodes generated by this predicate are of the form
_:genid
followed by a unique integer.1732rdf_create_bnode(BNode) :- 1733 var(BNode), 1734 !, 1735 rdf_db:rdf_bnode(BNode). 1736rdf_create_bnode(BNode) :- 1737 uninstantiation_error(BNode). 1738 1739 1740 /******************************* 1741 * TYPE CHECKING * 1742 *******************************/
For performance reasons, this does not check for compliance to the syntax defined in RFC 3987. This checks whether the term is (1) an atom and (2) not a blank node identifier.
Success of this goal does not imply that the IRI is present in the database (see rdf_iri/1 for that).
1757rdf_is_iri(IRI) :-
1758 atom(IRI),
1759 \+ rdf_is_bnode(IRI).
A blank node is represented by an atom that starts with
_:
.
Success of this goal does not imply that the blank node is present in the database (see rdf_bnode/1 for that).
For backwards compatibility, atoms that are represented with
an atom that starts with __
are also considered to be a
blank node.
An RDF literal term is of the form `String@LanguageTag or
Value^^Datatype`.
Success of this goal does not imply that the literal is well-formed or that it is present in the database (see rdf_literal/1 for that).
1787rdf_is_literal(Literal) :- 1788 literal_form(Literal), 1789 !, 1790 ground(Literal). 1791 1792literal_form(_@_). 1793literal_form(_^^_).
Success of this goal does not imply that the name is well-formed or that it is present in the database (see rdf_name/1 for that).
1804rdf_is_name(T) :- rdf_is_iri(T), !. 1805rdf_is_name(T) :- rdf_is_literal(T).
Success of this goal does not imply that the object term in well-formed or that it is present in the database (see rdf_object/1 for that).
Since any RDF term can appear in the object position, this is equaivalent to rdf_is_term/1.
1819rdf_is_object(T) :- rdf_is_subject(T), !. 1820rdf_is_object(T) :- rdf_is_literal(T).
Success of this goal does not imply that the predicate term is present in the database (see rdf_predicate/1 for that).
Since only IRIs can appear in the predicate position, this is equivalent to rdf_is_iri/1.
1833rdf_is_predicate(T) :- rdf_is_iri(T).
Only blank nodes and IRIs can appear in the subject position.
Success of this goal does not imply that the subject term is present in the database (see rdf_subject/1 for that).
Since blank nodes are represented by atoms that start with
`_:` and an IRIs are atoms as well, this is equivalent to
atom(Term)
.
1849rdf_is_subject(T) :- atom(T).
Success of this goal does not imply that the RDF term is present in the database (see rdf_term/1 for that).
1859rdf_is_term(N) :- rdf_is_subject(N), !. 1860rdf_is_term(N) :- rdf_is_literal(N). 1861 1862 1863 /******************************* 1864 * COLLECTIONS * 1865 *******************************/
rdf:first
and rdf:rest
property and
the list ends in rdf:nil
.
If RDFTerm is unbound, RDFTerm is bound to each maximal RDF
list. An RDF list is maximal if there is no triple rdf(_,
rdf:rest, RDFList)
.
1877rdf_list(L) :- 1878 var(L), 1879 !, 1880 rdf_has(L, rdf:first, _), 1881 \+ rdf_has(_, rdf:rest, L), 1882 rdf_list_g(L). 1883rdf_list(L) :- 1884 rdf_list_g(L), 1885 !. 1886 1887:- rdf_meta 1888 rdf_list_g(r). 1889 1890rdf_list_g(rdf:nil) :- !. 1891rdf_list_g(L) :- 1892 once(rdf_has(L, rdf:first, _)), 1893 rdf_has(L, rdf:rest, Rest), 1894 ( rdf_equal(rdf:nil, Rest) 1895 -> true 1896 ; rdf_list_g(Rest) 1897 ).
1906rdf_list(RDFList, Prolog) :- 1907 rdf_is_subject(RDFList), 1908 !, 1909 rdf_list_to_prolog(RDFList, Prolog). 1910rdf_list(RDFList, _Prolog) :- 1911 type_error(rdf_subject, RDFList). 1912 1913:- rdf_meta 1914 rdf_list_to_prolog(r,-). 1915 1916rdf_list_to_prolog(rdf:nil, Prolog) :- 1917 !, 1918 Prolog = []. 1919rdf_list_to_prolog(RDF, [H|T2]) :- 1920 ( rdf_has(RDF, rdf:first, H0), 1921 rdf_has(RDF, rdf:rest, T1) 1922 *-> H = H0, 1923 rdf_list_to_prolog(T1, T2) 1924 ; type_error(rdf_list, RDF) 1925 ).
1936rdf_length(RDFList, Len) :- 1937 rdf_is_subject(RDFList), 1938 !, 1939 rdf_length(RDFList, 0, Len). 1940 1941:- rdf_meta 1942 rdf_length(r,+,-). 1943 1944rdf_length(rdf:nil, Len, Len) :- !. 1945rdf_length(RDF, Len0, Len) :- 1946 ( rdf_has(RDF, rdf:rest, T) 1947 *-> Len1 is Len0+1, 1948 rdf_length(T, Len1, Len) 1949 ; type_error(rdf_list, RDF) 1950 ).
1957rdf_member(M, L) :- 1958 ground(M), 1959 !, 1960 ( rdf_member2(M, L) 1961 -> true 1962 ). 1963rdf_member(M, L) :- 1964 rdf_member2(M, L). 1965 1966rdf_member2(M, L) :- 1967 rdf_has(L, rdf:first, M). 1968rdf_member2(M, L) :- 1969 rdf_has(L, rdf:rest, L1), 1970 rdf_member2(M, L1).
1978rdf_nextto(X, Y) :- 1979 distinct(X-Y, rdf_nextto(X, Y, _)). 1980 1981 1982rdf_nextto(X, Y, L) :- 1983 var(X), ground(Y), 1984 !, 1985 rdf_nextto(Y, X, L). 1986rdf_nextto(X, Y, L) :- 1987 rdf_has(L, rdf:first, X), 1988 rdf_has(L, rdf:rest, T), 1989 rdf_has(T, rdf:first, Y).
1999rdf_nth0(I, L, X) :- 2000 rdf_nth(0, I, L, X). 2001 2002rdf_nth1(I, L, X) :- 2003 rdf_nth(1, I, L, X). 2004 2005rdf_nth(Offset, I, L, X) :- 2006 rdf_is_subject(L), 2007 !, 2008 ( var(I) 2009 -> true 2010 ; must_be(nonneg, I) 2011 ), 2012 rdf_nth_(I, Offset, L, X). 2013rdf_nth(_, _, L, _) :- 2014 type_error(rdf_subject, L). 2015 2016rdf_nth_(I, I0, L, X) :- 2017 ( I0 == I 2018 -> ! 2019 ; I0 = I 2020 ), 2021 rdf_has(L, rdf:first, X). 2022rdf_nth_(I, I0, L, X) :- 2023 rdf_has(L, rdf:rest, T), 2024 I1 is I0+1, 2025rdf_nth_(I, I1, T, X).
2034rdf_last(L, Last) :- 2035 rdf_is_subject(L), 2036 !, 2037 rdf_has(L, rdf:rest, T), 2038 ( rdf_equal(T, rdf:nil) 2039 -> rdf_has(L, rdf:first, Last) 2040 ; rdf_last(T, Last) 2041 ). 2042rdf_last(L, _) :- 2043 type_error(rdf_subject, L).
2048rdf_estimate_complexity(S, P, O, Estimate) :-
2049 pre_object(O,O0,S,P),
2050 rdf_db:rdf_estimate_complexity(S,P,O0,Estimate).
2062rdf_assert_list(Prolog, RDF) :- 2063 rdf_default_graph(G), 2064 rdf_assert_list(Prolog, RDF, G). 2065 2066rdf_assert_list(Prolog, RDF, G) :- 2067 must_be(list, Prolog), 2068 rdf_transaction(rdf_assert_list_(Prolog, RDF, G)). 2069 2070rdf_assert_list_([], Nil, _) :- 2071 rdf_equal(rdf:nil, Nil). 2072rdf_assert_list_([H|T], L2, G) :- 2073 (var(L2) -> rdf_create_bnode(L2) ; true), 2074 rdf_assert(L2, rdf:type, rdf:'List', G), 2075 rdf_assert(L2, rdf:first, H, G), 2076 ( T == [] 2077 -> rdf_assert(L2, rdf:rest, rdf:nil, G) 2078 ; rdf_create_bnode(T2), 2079 rdf_assert(L2, rdf:rest, T2, G), 2080 rdf_assert_list_(T, T2, G) 2081 ).
2090rdf_retract_list(L) :- 2091 rdf_is_subject(L), 2092 !, 2093 rdf_transaction(rdf_retract_list_(L)). 2094rdf_retract_list(L) :- 2095 type_error(rdf_subject, L). 2096 2097:- rdf_meta 2098 rdf_retract_list_(r). 2099 2100rdf_retract_list_(rdf:nil) :- !. 2101rdf_retract_list_(L) :- 2102 rdf_retractall(L, rdf:first, _), 2103 forall(rdf_has(L, rdf:rest, L1), 2104 rdf_retract_list_(L1)), 2105 rdf_retractall(L, rdf:rest, _), 2106 rdf_retractall(L, rdf:type, rdf:'List')
RDF 1.1 API
This library provides a new API on top of library(semweb/rdf_db). The new API follows the RDF 1.1 terminology and notation as much as possible. It runs on top of the old API, which implies that applications can use the new API in one file and the other in another one. Once the new API is considered stable and robust the old API will be deprecated.
In a nutshell, the following issues are addressed:
literal(+Search,-Value)
construct used by library(semweb/rdf_db). For example, the following query returns literals with prefix "ams", exploiting the RDF literal index.