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(c14n2)). 103:- use_module(library(debug)). 104:- use_module(library(error)). 105:- use_module(library(lists)). 106:- use_module(library(memfile)). 107:- reexport(library(semweb/rdf_db), 108 except([ rdf/3, 109 rdf/4, 110 rdf_assert/3, 111 rdf_assert/4, 112 rdf_current_literal/1, 113 rdf_current_predicate/1, 114 rdf_has/3, 115 rdf_has/4, 116 rdf_update/4, 117 rdf_update/5, 118 rdf_reachable/3, 119 rdf_reachable/5, 120 rdf_retractall/3, 121 rdf_retractall/4, 122 rdf_node/1, 123 rdf_bnode/1, 124 rdf_is_literal/1, 125 rdf_is_resource/1, 126 rdf_literal_value/2, 127 rdf_compare/3, 128 rdf_estimate_complexity/4 129 ]) 130 ). 131:- use_module(library(sgml)). 132:- use_module(library(solution_sequences)).
173:- multifile 174 in_ground_type_hook/3, % +Type, +Input, -Lexical:atom 175 out_type_hook/3, % +Type, -Output, +Lexical:atom 176 invalid_lexical_form_hook/3. % +Type, +Lexical, -Prolog 177 178:- meta_predicate 179 parse_partial_xml( , , ). 180 181:- rdf_meta 182 rdf(r,r,o), 183 rdf(r,r,o,r), 184 rdf_assert(r,r,o), 185 rdf_assert(r,r,o,r), 186 rdf_has(r,r,o), 187 rdf_has(r,r,o,-), 188 rdf_update(r,r,o,t), 189 rdf_update(r,r,o,r,t), 190 rdf_reachable(r,r,o), 191 rdf_reachable(r,r,o,+,-), 192 rdf_retractall(r,r,o), 193 rdf_retractall(r,r,o,r), 194 {}(t), 195 rdf_where(t), 196 rdf_canonical_literal(o,-), 197 rdf_lexical_form(o,-), 198 rdf_compare(-,o,o), 199 rdf_iri(r), 200 rdf_is_iri(r), 201 rdf_is_literal(o), 202 rdf_is_name(o), 203 rdf_is_object(o), 204 rdf_is_predicate(r), 205 rdf_is_subject(r), 206 rdf_is_term(o), 207 rdf_term(o), 208 rdf_literal(o), 209 rdf_name(o), 210 rdf_object(o), 211 rdf_estimate_complexity(r,r,o,-), 212 rdf_assert_list(t,r), 213 rdf_assert_list(t,r,r), 214 rdf_last(r,o), 215 rdf_list(r), 216 rdf_list(r,-), 217 rdf_length(r,-), 218 rdf_member(o,r), 219 rdf_nextto(o,o), 220 rdf_nth0(?,r,o), 221 rdf_nth1(?,r,o), 222 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.
305rdf(S,P,O) :- 306 pre_object(O,O0), 307 rdf_db:rdf(S,P,O0), 308 post_object(O,O0). 309 310rdf(S,P,O,G) :- 311 pre_object(O,O0), 312 pre_graph(G,G0), 313 rdf_db:rdf(S,P,O0,G0), 314 post_graph(G, G0), 315 post_object(O,O0).
inverse_of
and
symmetric
. See rdf_set_predicate/2.325rdf_has(S,P,O) :- 326 pre_object(O,O0), 327 rdf_db:rdf_has(S,P,O0), 328 post_object(O,O0). 329 330rdf_has(S,P,O,RealP) :- 331 pre_object(O,O0), 332 rdf_db:rdf_has(S,P,O0,RealP), 333 post_object(O,O0).
literal(Value)
.
The argument matching the 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')).
370rdf_update(S, P, O, Action) :- 371 rdf_update(S, P, O, _, Action). 372rdf_update(S, P, O, G, Action) :- 373 must_be(ground, Action), 374 ( update_column(Action, S,P,O,G, On) 375 -> must_be(ground, On), 376 arg(1, Action, Old), 377 ( On == Old 378 -> true 379 ; rdf_transaction(rdf_update_(S, P, O, G, Action), update) 380 ) 381 ; domain_error(rdf_update_action, Action) 382 ). 383 384update_column(subject(_), S,_,_,_, S). 385update_column(predicate(_), _,P,_,_, P). 386update_column(object(_), _,_,O,_, O). 387update_column(graph(_), _,_,_,G, G). 388 389rdf_update_(S1, P, O, G, subject(S2)) :- 390 !, 391 forall(rdf(S1, P, O, G), 392 ( rdf_retractall(S1, P, O, G), 393 rdf_assert(S2, P, O, G) 394 )). 395rdf_update_(S, P1, O, G, predicate(P2)) :- 396 !, 397 forall(rdf(S, P1, O, G), 398 ( rdf_retractall(S, P1, O, G), 399 rdf_assert(S, P2, O, G) 400 )). 401rdf_update_(S, P, O1, G, object(O2)) :- 402 !, 403 forall(rdf(S, P, O1, G), 404 ( rdf_retractall(S, P, O1, G), 405 rdf_assert(S, P, O2, G) 406 )). 407rdf_update_(S, P, O, G1, graph(G2)) :- 408 !, 409 forall(rdf(S, P, O, G1), 410 ( rdf_retractall(S, P, O, G1), 411 rdf_assert(S, P, O, G2) 412 )).
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
breath first search.
429rdf_reachable(S,P,O) :- 430 pre_object(O,O0), 431 rdf_db:rdf_reachable(S,P,O0), 432 post_object(O,O0). 433 434rdf_reachable(S,P,O,MaxD,D) :- 435 pre_object(O,O0), 436 rdf_db:rdf_reachable(S,P,O0,MaxD,D), 437 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.
452rdf_assert(S,P,O) :- 453 rdf_default_graph(G), 454 rdf_assert(S,P,O,G). 455 456rdf_assert(S,P,O,G) :- 457 must_be(ground, O), 458 pre_ground_object(O,O0), 459 rdf_db:rdf_assert(S,P,O0,G).
468rdf_retractall(S,P,O) :- 469 pre_object(O,O0), 470 rdf_db:rdf_retractall(S,P,O0). 471 472rdf_retractall(S,P,O,G) :- 473 pre_object(O,O0), 474 pre_graph(G,G0), 475 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.
496rdf_compare(Diff, Left, Right) :-
497 pre_ground_object(Left, Left0),
498 pre_ground_object(Right, Right0),
499 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:{...}
.
542{}(Where) :- 543 rdf_where(Where). 544 545rdf_where(Var) :- 546 var(Var), 547 !, 548 instantiation_error(Var). 549rdf_where((A,B)) :- 550 !, 551 rdf_where(A), 552 rdf_where(B). 553rdf_where(Constraint) :- 554 rdf_constraint(Constraint, Goal), 555 !, 556 call(Goal). 557rdf_where(Constraint) :- 558 existence_error(rdf_constraint, Constraint). 559 560% Comparison operators 561rdf_constraint(Term >= Value, 562 add_value_constraint(Term, >=, Value)). 563rdf_constraint(Term > Value, 564 add_value_constraint(Term, >, Value)). 565rdf_constraint(Term == Value, 566 add_value_constraint(Term, ==, Value)). 567rdf_constraint(Term < Value, 568 add_value_constraint(Term, <, Value)). 569rdf_constraint(Term =< Value, 570 add_value_constraint(Term, =<, Value)). 571% String selection 572rdf_constraint(prefix(Term, Pattern), 573 add_text_constraint(Term, prefix(PatternA))) :- 574 atom_string(PatternA, Pattern). 575rdf_constraint(substring(Term, Pattern), 576 add_text_constraint(Term, substring(PatternA))) :- 577 atom_string(PatternA, Pattern). 578rdf_constraint(word(Term, Pattern), 579 add_text_constraint(Term, word(PatternA))) :- 580 atom_string(PatternA, Pattern). 581rdf_constraint(like(Term, Pattern), 582 add_text_constraint(Term, like(PatternA))) :- 583 atom_string(PatternA, Pattern). 584rdf_constraint(icase(Term, Pattern), 585 add_text_constraint(Term, icase(PatternA))) :- 586 atom_string(PatternA, Pattern). 587% Lang selection 588rdf_constraint(lang_matches(Term, Pattern), 589 add_lang_constraint(Term, lang_matches(Pattern))). 590 591add_text_constraint(Var, Cond) :- 592 var(Var), 593 !, 594 ( get_attr(Var, rdf11, Cond0) 595 -> put_attr(Var, rdf11, [Cond|Cond0]) 596 ; put_attr(Var, rdf11, [Cond]) 597 ). 598add_text_constraint(Text^^_Type, Cond) :- 599 !, 600 add_text_constraint(Text, Cond). 601add_text_constraint(Text@_Lang, Cond) :- 602 !, 603 add_text_constraint(Text, Cond). 604add_text_constraint(Var, Cond) :- 605 eval_condition(Cond, Var).
611add_lang_constraint(Var, Constraint) :- 612 var(Var), 613 !, 614 ( get_attr(Var, rdf11, Cond0) 615 -> put_attr(Var, rdf11, [Constraint|Cond0]) 616 ; put_attr(Var, rdf11, [Constraint]) 617 ). 618add_lang_constraint(_Text@Lang, Constraint) :- 619 !, 620 add_lang_constraint(Lang, Constraint). 621add_lang_constraint(_Text^^_Type, _Constraint) :- 622 !, 623 fail. 624add_lang_constraint(Term, Constraint) :- 625 eval_condition(Constraint, Term).
631add_value_constraint(Term, Constraint, ValueIn) :- 632 constraint_literal_value(ValueIn, Value), 633 add_value_constraint_cann(Value, Constraint, Term). 634 635constraint_literal_value(Value, Value^^_Type) :- 636 number(Value), 637 !. 638constraint_literal_value(Value, Literal) :- 639 rdf_canonical_literal(Value, Literal). 640 641add_value_constraint_cann(RefVal^^Type, Constraint, Term) :- 642 var(Term), var(Type), 643 !, 644 add_text_constraint(Term, value(Constraint, RefVal, Type)). 645add_value_constraint_cann(RefVal^^Type, Constraint, Val^^Type2) :- 646 !, 647 Type = Type2, 648 add_text_constraint(Val, value(Constraint, RefVal, Type)). 649add_value_constraint_cann(RefVal@Lang, Constraint, Val@Lang) :- 650 !, 651 add_text_constraint(Val, value(Constraint, RefVal, lang(Lang))). 652add_value_constraint_cann(RefVal^^Type, Constraint, Val) :- 653 !, 654 ground(Val), 655 Val \= _@_, 656 eval_condition(value(Constraint, RefVal, Type), Val). 657 658put_cond(Var, []) :- 659 !, 660 del_attr(Var, rdf11). 661put_cond(Var, List) :- 662 put_attr(Var, rdf11, List). 663 664eval_condition(Cond, Literal) :- 665 text_condition(Cond), 666 !, 667 text_of(Literal, Text), 668 text_condition(Cond, Text). 669eval_condition(Cond, Literal) :- 670 lang_condition(Cond), 671 !, 672 lang_of(Literal, Lang), 673 lang_condition(Cond, Lang). 674eval_condition(value(Comp, Ref, _Type), Value) :- 675 ( number(Ref) 676 -> number(Value), 677 compare_numeric(Comp, Ref, Value) 678 ; compare_std(Comp, Ref, Value) 679 ). 680 681compare_numeric(<, Ref, Value) :- Value < Ref. 682compare_numeric(=<, Ref, Value) :- Value =< Ref. 683compare_numeric(==, Ref, Value) :- Value =:= Ref. 684compare_numeric(>=, Ref, Value) :- Value >= Ref. 685compare_numeric( >, Ref, Value) :- Value > Ref. 686 687compare_std(<, Ref, Value) :- Value @< Ref. 688compare_std(=<, Ref, Value) :- Value @=< Ref. 689compare_std(==, Ref, Value) :- Value == Ref. 690compare_std(>=, Ref, Value) :- Value @>= Ref. 691compare_std( >, Ref, Value) :- Value @> Ref. 692 693text_condition(prefix(_)). 694text_condition(substring(_)). 695text_condition(word(_)). 696text_condition(like(_)). 697text_condition(icase(_)). 698 699text_of(Literal, Text) :- 700 atomic(Literal), 701 !, 702 Text = Literal. 703text_of(Text@_Lang, Text). 704text_of(Text^^_Type, Text). 705 706text_condition(prefix(Pattern), Text) :- 707 rdf_match_label(prefix, Pattern, Text). 708text_condition(substring(Pattern), Text) :- 709 rdf_match_label(substring, Pattern, Text). 710text_condition(word(Pattern), Text) :- 711 rdf_match_label(word, Pattern, Text). 712text_condition(like(Pattern), Text) :- 713 rdf_match_label(like, Pattern, Text). 714text_condition(icase(Pattern), Text) :- 715 rdf_match_label(icase, Pattern, Text). 716 717lang_condition(lang_matches(_)). 718 719lang_of(_Text@Lang0, Lang) :- 720 !, 721 Lang = Lang0. 722lang_of(Lang, Lang) :- 723 atom(Lang). 724 725lang_condition(lang_matches(Pattern), Lang) :- 726 rdf_db:lang_matches(Lang, Pattern).
literal(Cond, _Value)
.
Translated constraints are removed from object.734literal_condition(Object, Cond) :- 735 var(Object), 736 !, 737 get_attr(Object, rdf11, Cond0), 738 best_literal_cond(Cond0, Cond, Rest), 739 put_cond(Object, Rest). 740literal_condition(Text@_Lang, Cond) :- 741 get_attr(Text, rdf11, Cond0), 742 !, 743 best_literal_cond(Cond0, Cond, Rest), 744 put_cond(Text, Rest). 745literal_condition(Text^^_Type, Cond) :- 746 get_attr(Text, rdf11, Cond0), 747 best_literal_cond(Cond0, Cond, Rest), 748 put_cond(Text, Rest).
literal(Search, Value)
.
757best_literal_cond(Conditions, Best, Rest) :- 758 sort(Conditions, Unique), 759 best_literal_cond2(Unique, Best, Rest). 760 761best_literal_cond2(Conds, Best, Rest) :- 762 select(Cond, Conds, Rest0), 763 rdf10_cond(Cond, Best, Rest0, Rest), 764 !. 765 766rdf10_cond(value(=<, URef, UType), Cond, Rest0, Rest) :- 767 ( select(value(>=, LRef, LType), Rest0, Rest) 768 -> true 769 ; memberchk(value(>, LRef, LType), Rest0) 770 -> Rest = Rest0 771 ), 772 !, 773 in_constaint_type(LType, SLType, LRef, LRef0), 774 in_constaint_type(UType, SUType, URef, URef0), 775 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 776rdf10_cond(value(<, URef, UType), Cond, Rest0, Rest) :- 777 ( select(value(>=, LRef, LType), Rest0, Rest1) 778 -> true 779 ; memberchk(value(>, LRef, LType), Rest0) 780 -> Rest1 = Rest0 781 ), 782 !, 783 Rest = [value(<, URef, UType)|Rest1], 784 in_constaint_type(LType, SLType, LRef, LRef0), 785 in_constaint_type(UType, SUType, URef, URef0), 786 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 787rdf10_cond(value(Cmp, Ref, Type), Pattern, Rest, Rest) :- 788 !, 789 rdf10_compare(Cmp, Ref, Type, Pattern). 790rdf10_cond(lang_matches(_), _, _, _) :- !, fail. 791rdf10_cond(Cond, Cond, Rest, Rest). 792 793rdf10_compare(Cmp, Ref, Type, Pattern) :- 794 nonvar(Type), Type = lang(Lang), 795 !, 796 atom_string(Ref0, Ref), 797 rdf10_lang_cond(Cmp, Ref0, Lang, Pattern). 798rdf10_compare(Cmp, Ref, Type, Pattern) :- 799 in_constaint_type(Type, SType, Ref, Ref0), 800 rdf10_type_cond(Cmp, Ref0, SType, Pattern). 801 802rdf10_lang_cond( <, Ref, Lang, lt(lang(Lang,Ref))). 803rdf10_lang_cond(=<, Ref, Lang, le(lang(Lang,Ref))). 804rdf10_lang_cond(==, Ref, Lang, eq(lang(Lang,Ref))). 805rdf10_lang_cond(>=, Ref, Lang, ge(lang(Lang,Ref))). 806rdf10_lang_cond(>, Ref, Lang, gt(lang(Lang,Ref))). 807 808rdf10_type_cond( <, Ref, Type, lt(type(Type,Ref))). 809rdf10_type_cond(=<, Ref, Type, le(type(Type,Ref))). 810rdf10_type_cond(==, Ref, Type, eq(type(Type,Ref))). 811rdf10_type_cond(>=, Ref, Type, ge(type(Type,Ref))). 812rdf10_type_cond( >, Ref, Type, gt(type(Type,Ref))).
817in_constaint_type(Type, SType, Val, Val0) :- 818 nonvar(Type), ground(Val), 819 !, 820 SType = Type, 821 in_ground_type(Type, Val, Val0). 822in_constaint_type(Type, SType, Val, Val0) :- 823 var(Type), number(Val), 824 !, 825 ( integer(Val) 826 -> rdf_equal(SType, xsd:integer), 827 in_ground_type(xsd:integer, Val, Val0) 828 ; float(Val) 829 -> rdf_equal(SType, xsd:double), 830 in_ground_type(xsd:double, Val, Val0) 831 ; assertion(fail) 832 ).
840literal_class(Term, Class) :-
841 get_attr(Term, rdf11, Conds),
842 select(Cond, Conds, Rest),
843 lang_condition(Cond),
844 !,
845 Term = Text@Lang,
846 put_attr(Lang, rdf11, [Cond]),
847 put_cond(Text, Rest),
848 ( var(Text)
849 -> true
850 ; atom_string(Text2, Text)
851 ),
852 Class = lang(Lang, Text2).
856attr_unify_hook(Cond, Value) :- 857 get_attr(Value, rdf11, Cond2), 858 !, 859 append(Cond, Cond2, CondJ), 860 sort(CondJ, Unique), 861 put_cond(Value, Unique). 862attr_unify_hook(Cond, Text^^_Type) :- 863 var(Text), 864 !, 865 put_cond(Text, Cond). 866attr_unify_hook(Cond, Text@Lang) :- 867 var(Text), var(Lang), 868 !, 869 partition(lang_condition, Cond, LangCond, TextCond), 870 put_cond(Text, TextCond), 871 put_cond(Lang, LangCond). 872attr_unify_hook(Cond, Value) :- 873 sort(Cond, Unique), 874 propagate_conditions(Unique, Value). 875 876propagate_conditions([], _). 877propagate_conditions([H|T], Val) :- 878 propagate_condition(H, Val), 879 propagate_conditions(T, Val). 880 881propagate_condition(value(Comp, Ref, Type), Value) :- 882 !, 883 ( Value = Plain^^VType 884 -> VType = Type 885 ; Plain = Value 886 ), 887 cond_compare(Comp, Ref, Plain). 888propagate_condition(lang_matches(Pattern), Value) :- 889 !, 890 ( Value = _@Lang 891 -> true 892 ; Lang = Value 893 ), 894 rdf_db:lang_matches(Lang, Pattern). 895propagate_condition(Cond, Value) :- 896 Cond =.. [Name|Args], 897 Constraint =.. [Name,Value|Args], 898 rdf_constraint(Constraint, Continuation), 899 call(Continuation). 900 901cond_compare(>, Ref, Value) :- Value @> Ref. 902cond_compare(>=, Ref, Value) :- Value @>= Ref. 903cond_compare(==, Ref, Value) :- Value == Ref. 904cond_compare(=<, Ref, Value) :- Value @=< Ref. 905cond_compare( <, Ref, Value) :- Value @< Ref.
915:- create_prolog_flag(rdf_default_graph, default, 916 [ type(atom), 917 keep(true) 918 ]). 919 920rdf_default_graph(Graph) :- 921 current_prolog_flag(rdf_default_graph, Graph). 922rdf_default_graph(Old, New) :- 923 current_prolog_flag(rdf_default_graph, Old), 924 ( New == Old 925 -> true 926 ; set_prolog_flag(rdf_default_graph, New) 927 ). 928 929 930pre_graph(G, _G0) :- 931 var(G), 932 !. 933pre_graph(G, G) :- 934 atom(G), 935 !. 936pre_graph(G, _) :- 937 type_error(rdf_graph, G). 938 939post_graph(G, G0:_) :- 940 !, 941 G = G0. 942post_graph(G, G). 943 944 945pre_object(Literal, literal(Cond, Value)) :- 946 literal_condition(Literal, Cond), 947 !, 948 debug(literal_index, 'Search literal using ~p', [literal(Cond, Value)]), 949 literal_value0(Literal, Value). 950pre_object(Literal, literal(Value)) :- 951 literal_class(Literal, Value), 952 !, 953 debug(literal_index, 'Search literal using ~p', [literal(Value)]). 954pre_object(Var, _Var) :- 955 var(Var), 956 !. 957pre_object(Atom, URI) :- 958 atom(Atom), 959 \+ boolean(Atom), 960 !, 961 URI = Atom. 962pre_object(Val@Lang, literal(lang(Lang, Val0))) :- 963 !, 964 in_lang_string(Val, Val0). 965pre_object(Val^^Type, literal(Literal)) :- 966 !, 967 in_type(Type, Val, Type0, Val0), 968 ( var(Type0), var(Val0) 969 -> true 970 ; Literal = type(Type0, Val0) 971 ). 972pre_object(Obj, Val0) :- 973 ground(Obj), 974 !, 975 pre_ground_object(Obj, Val0). 976pre_object(Obj, _) :- 977 type_error(rdf_object, Obj). 978 979literal_value0(Var, _) :- 980 var(Var), 981 !. 982literal_value0(_ @Lang, lang(Lang, _)). 983literal_value0(_^^Type, type(Type, _)).
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.1026:- rdf_meta 1027 pre_ground_object(+, o). 1028 1029% Interpret Prolog integer as xsd:integer. 1030pre_ground_object(Int, Object) :- 1031 integer(Int), 1032 !, 1033 rdf_equal(Object, literal(type(xsd:integer, Atom))), 1034 atom_number(Atom, Int). 1035% Interpret Prolog floating-point value as xsd:double. 1036pre_ground_object(Float, Object) :- 1037 float(Float), 1038 !, 1039 rdf_equal(Object, literal(type(xsd:double, Atom))), 1040 xsd_number_string(Float, String), 1041 atom_string(Atom, String). 1042% Interpret SWI string as xsd:string. 1043pre_ground_object(String, Object) :- 1044 string(String), 1045 !, 1046 rdf_equal(Object, literal(type(xsd:string, Atom))), 1047 atom_string(Atom, String). 1048% Interpret `false' and `true' as the Boolean values. 1049pre_ground_object(false, literal(type(xsd:boolean, false))) :- !. 1050pre_ground_object(true, literal(type(xsd:boolean, true))) :- !. 1051% Interpret date(Y,M,D) as xsd:date, 1052% date_time(Y,M,D,HH,MM,SS) as xsd:dateTime, 1053% date_time(Y,M,D,HH,MM,SS,TZ) as xsd:dateTime, 1054% month_day(M,D) as xsd:gMonthDay, 1055% year_month(Y,M) as xsd:gYearMonth, and 1056% time(HH,MM,SS) as xsd:time. 1057pre_ground_object(Term, literal(type(Type, Atom))) :- 1058 xsd_date_time_term(Term), 1059 !, 1060 xsd_time_string(Term, Type, Atom). 1061pre_ground_object(Val@Lang, literal(lang(Lang0, Val0))) :- 1062 !, 1063 downcase_atom(Lang, Lang0), 1064 in_lang_string(Val, Val0). 1065pre_ground_object(Val^^Type, literal(type(Type0, Val0))) :- 1066 !, 1067 in_type(Type, Val, Type0, Val0). 1068pre_ground_object(Atom, URI) :- 1069 atom(Atom), 1070 !, 1071 URI = Atom. 1072%pre_ground_object(NS:Local, URI) :- % still leaves S and P. 1073% atom(NS), atom(Local), !, 1074% rdf_global_id(NS:Local, URI). 1075pre_ground_object(literal(Lit0), literal(Lit)) :- 1076 old_literal(Lit0, Lit), 1077 !. 1078pre_ground_object(Value, _) :- 1079 type_error(rdf_object, Value). 1080 1081xsd_date_time_term(date(_,_,_)). 1082xsd_date_time_term(date_time(_,_,_,_,_,_)). 1083xsd_date_time_term(date_time(_,_,_,_,_,_,_)). 1084xsd_date_time_term(month_day(_,_)). 1085xsd_date_time_term(year_month(_,_)). 1086xsd_date_time_term(time(_,_,_)). 1087 1088old_literal(Lit0, Lit) :- 1089 old_literal(Lit0), 1090 !, 1091 Lit = Lit0. 1092old_literal(Atom, Lit) :- 1093 atom(Atom), 1094 rdf_equal(xsd:string, XSDString), 1095 Lit = type(XSDString, Atom). 1096 1097old_literal(type(Type, Value)) :- 1098 atom(Type), atom(Value). 1099old_literal(lang(Lang, Value)) :- 1100 atom(Lang), atom(Value). 1101 1102in_lang_string(Val, Val0) :- 1103 atomic(Val), 1104 !, 1105 atom_string(Val0, Val). 1106in_lang_string(_, _). 1107 1108in_type(Type, Val, Type, Val0) :- 1109 nonvar(Type), ground(Val), 1110 !, 1111 in_ground_type(Type, Val, Val0). 1112in_type(VarType, Val, VarType, Val0) :- 1113 ground(Val), 1114 \+ catch(xsd_number_string(_, Val), _, fail), 1115 !, 1116 atom_string(Val0, Val). 1117in_type(_, _, _, _). 1118 1119:- rdf_meta 1120 in_ground_type(r,?,?), 1121 in_date_component(r, +, +, -).
1129in_ground_type(Type, Input, Lex) :- 1130 \+ string(Input), 1131 in_ground_type_hook(Type, Input, Lex), 1132 !. 1133in_ground_type(IntType, Val, Val0) :- 1134 xsd_numerical(IntType, Domain, PrologType), 1135 !, 1136 in_number(PrologType, Domain, IntType, Val, Val0). 1137in_ground_type(xsd:boolean, Val, Val0) :- 1138 !, 1139 ( in_boolean(Val, Val0) 1140 -> true 1141 ; type_error(rdf_boolean, Val) 1142 ). 1143in_ground_type(rdf:langString, _Val0, _) :- 1144 !, 1145 domain_error(rdf_data_type, rdf:langString). 1146in_ground_type(DateTimeType, Val, Val0) :- 1147 xsd_date_time_type(DateTimeType), 1148 !, 1149 in_date_time(DateTimeType, Val, Val0). 1150in_ground_type(rdf:'XMLLiteral', Val, Val0) :- 1151 !, 1152 in_xml_literal(xml, Val, Val0). 1153in_ground_type(rdf:'HTML', Val, Val0) :- 1154 !, 1155 in_xml_literal(html, Val, Val0). 1156in_ground_type(_Unknown, Val, Val0) :- 1157 atom_string(Val0, Val).
1164:- rdf_meta 1165 in_date_time(r,+,-). 1166 1167in_date_time(Type, Text, Text0) :- 1168 atom(Text), 1169 !, 1170 xsd_time_string(_, Type, Text), 1171 Text0 = Text. 1172in_date_time(Type, Text, Text0) :- 1173 string(Text), 1174 !, 1175 xsd_time_string(_, Type, Text), 1176 atom_string(Text0, Text). 1177in_date_time(xsd:dateTime, Stamp, Text0) :- 1178 number(Stamp), 1179 !, 1180 format_time(atom(Text0), '%FT%T%:z', Stamp). 1181in_date_time(Type, Term, Text0) :- 1182 !, 1183 xsd_time_string(Term, Type, String), 1184 atom_string(Text0, String).
1191in_boolean(true, true). 1192in_boolean(false, false). 1193in_boolean("true", true). 1194in_boolean("false", false). 1195in_boolean(1, true). 1196in_boolean(0, false). 1197 1198boolean(false). 1199boolean(true).
1208in_number(integer, Domain, XSDType, Val, Val0) :- 1209 integer(Val), 1210 !, 1211 check_integer_domain(Domain, XSDType, Val), 1212 atom_number(Val0, Val). 1213in_number(integer, Domain, XSDType, Val, Val0) :- 1214 atomic(Val), 1215 atom_number(Val, Num), 1216 integer(Num), 1217 !, 1218 check_integer_domain(Domain, XSDType, Num), 1219 atom_number(Val0, Num). 1220in_number(double, _Domain, _, Val, Val0) :- 1221 number(Val), 1222 !, 1223 ValF is float(Val), 1224 xsd_number_string(ValF, ValS), 1225 atom_string(Val0, ValS). 1226in_number(double, _Domain, _, Val, Val0) :- 1227 atomic(Val), 1228 xsd_number_string(Num, Val), 1229 ValF is float(Num), 1230 !, 1231 xsd_number_string(ValF, ValS), 1232 atom_string(Val0, ValS). 1233in_number(PrologType, _, _, Val, _) :- 1234 type_error(PrologType, Val). 1235 1236check_integer_domain(PLType, _, Val) :- 1237 is_of_type(PLType, Val), 1238 !. 1239check_integer_domain(_, XSDType, Val) :- 1240 domain_error(XSDType, Val). 1241 1242errorhas_type(nonpos, T):- 1243 integer(T), 1244 T =< 0. 1245 1246%check_integer_domain(between(Low, High), XSDType, Val) :- 1247% ( between(Low, High, Val) 1248% -> true 1249% ; domain_error(XSDType, Val) 1250% ). 1251%check_integer_domain(integer, _, _).
1255:- rdf_meta 1256 xsd_numerical(r, ?, ?). 1257 1258xsd_numerical(xsd:byte, between(-128,127), integer). 1259xsd_numerical(xsd:double, float, double). 1260xsd_numerical(xsd:decimal, float, double). 1261xsd_numerical(xsd:float, float, double). 1262xsd_numerical(xsd:int, between(-2147483648,2147483647), integer). 1263xsd_numerical(xsd:integer, integer, integer). 1264xsd_numerical(xsd:long, between(-9223372036854775808, 1265 9223372036854775807), integer). 1266xsd_numerical(xsd:negativeInteger, negative_integer, integer). 1267xsd_numerical(xsd:nonNegativeInteger, nonneg, integer). 1268xsd_numerical(xsd:nonPositiveInteger, nonpos, integer). 1269xsd_numerical(xsd:positiveInteger, positive_integer, integer). 1270xsd_numerical(xsd:short, between(-32768,32767), integer). 1271xsd_numerical(xsd:unsignedByte, between(0,255), integer). 1272xsd_numerical(xsd:unsignedInt, between(0,4294967295), integer). 1273xsd_numerical(xsd:unsignedLong, between(0,18446744073709551615), integer). 1274xsd_numerical(xsd:unsignedShort, between(0,65535), integer).
1280:- rdf_meta 1281 xsd_date_time_type(r). 1282 1283xsd_date_time_type(xsd:date). 1284xsd_date_time_type(xsd:dateTime). 1285xsd_date_time_type(xsd:gDay). 1286xsd_date_time_type(xsd:gMonth). 1287xsd_date_time_type(xsd:gMonthDay). 1288xsd_date_time_type(xsd:gYear). 1289xsd_date_time_type(xsd:gYearMonth). 1290xsd_date_time_type(xsd:time).
1300in_xml_literal(Type, Val, Val0) :- 1301 xml_is_dom(Val), 1302 !, 1303 write_xml_literal(Type, Val, Val0). 1304in_xml_literal(xml, Val, Val0) :- 1305 parse_partial_xml(load_xml, Val, DOM), 1306 write_xml_literal(xml, DOM, Val0). 1307in_xml_literal(html, Val, Val0) :- 1308 parse_partial_xml(load_html, Val, DOM), 1309 write_xml_literal(html, DOM, Val0). 1310 1311parse_partial_xml(Parser, Val, DOM) :- 1312 setup_call_cleanup( 1313 new_memory_file(MF), 1314 ( setup_call_cleanup( 1315 open_memory_file(MF, write, Out), 1316 format(Out, "<xml>~w</xml>", [Val]), 1317 close(Out)), 1318 setup_call_cleanup( 1319 open_memory_file(MF, read, In), 1320 call(Parser, stream(In), [element(xml, _, DOM)], []), 1321 close(In)) 1322 ), 1323 free_memory_file(MF)). 1324 1325 1326write_xml_literal(xml, DOM, Text) :- 1327 with_output_to(atom(Text), 1328 xml_write_canonical(current_output, DOM, [])). 1329write_xml_literal(html, DOM, Text) :- 1330 with_output_to(atom(Text), 1331 html_write(current_output, DOM, 1332 [ header(false), 1333 layout(false) 1334 ])).
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'.
1362rdf_canonical_literal(In, Literal) :- 1363 ground(In), 1364 !, 1365 pre_ground_object(In, DBTerm), 1366 post_object(Literal, DBTerm). 1367rdf_canonical_literal(In, _) :- 1368 must_be(ground, In).
1381% For example, 1382% 1383% == 1384% ?- rdf_lexical_form(2.3^^xsd:double, L). 1385% L = "2.3E0"^^'http://www.w3.org/2001/XMLSchema#double'. 1386% == 1387 1388rdf_lexical_form(Literal, Lexical) :- 1389 pre_ground_object(Literal, literal(Lit0)), 1390 !, 1391 text_of0(Lit0, Lexical). 1392rdf_lexical_form(Literal, _) :- 1393 type_error(rdf_literal, Literal). 1394 1395text_of0(type(TypeA, LexicalA), LexicalS^^TypeA) :- 1396 atom_string(LexicalA, LexicalS). 1397text_of0(lang(LangA, LexicalA), LexicalS@LangA) :- 1398 atom_string(LexicalA, LexicalS). 1399 1400 1401 /******************************* 1402 * POST PROCESSING * 1403 *******************************/ 1404 1405:- rdf_meta 1406 post_object(o,o), 1407 out_type(r,-,+). 1408 1409post_object(Val, _) :- 1410 ground(Val), 1411 !. % already specified and matched 1412post_object(URI, URI0) :- 1413 atom(URI0), 1414 !, 1415 URI = URI0. 1416post_object(Val@Lang, literal(lang(Lang, Val0))) :- 1417 nonvar(Lang), % lang(Lang,Text) returns var(Lang) if no lang 1418 !, 1419 atom_string(Val0, Val). 1420post_object(Val^^Type, literal(type(Type, Val0))) :- 1421 !, 1422 out_type(Type, Val, Val0). 1423post_object(Val^^xsd:string, literal(Plain)) :- 1424 !, 1425 atomic(Plain), 1426 atom_string(Plain, Val). 1427post_object(Val@Lang, literal(_, lang(Lang, Val0))) :- 1428 nonvar(Lang), 1429 !, 1430 atom_string(Val0, Val). 1431post_object(Val^^Type, literal(_, type(Type, Val0))) :- 1432 !, 1433 out_type(Type, Val, Val0). 1434post_object(Val^^xsd:string, literal(_, Plain)) :- 1435 atomic(Plain), 1436 atom_string(Plain, Val). 1437 1438out_type(xsd:string, Val, Val0) :- % catches unbound type too 1439 !, 1440 atom_string(Val0, Val). 1441out_type(Type, Val, Val0) :- 1442 out_type_hook(Type, Val, Val0), 1443 !. 1444out_type(IntType, Val, Val0) :- 1445 xsd_numerical(IntType, _Domain, _BasicType), 1446 !, 1447 xsd_number_string(Val, Val0). 1448out_type(DateTimeType, Val, Val0) :- 1449 xsd_date_time_type(DateTimeType), 1450 !, 1451 out_date_time(DateTimeType, Val, Val0). 1452out_type(xsd:boolean, Val, Val0) :- 1453 !, 1454 Val = Val0. 1455out_type(rdf:'XMLLiteral', XML, DOM) :- 1456 xml_is_dom(DOM), 1457 !, 1458 with_output_to(string(XML), 1459 xml_write(DOM, [header(false)])). 1460out_type(_Unknown, Val, Val0) :- 1461 atom_string(Val0, Val).
1469out_date_time(Type, Prolog, Lexical) :-
1470 catch(xsd_time_string(Prolog, Type, Lexical),
1471 error(_,_),
1472 invalid_lexical_form_hook(Type, Lexical, Prolog)).
1482 /******************************* 1483 * ENUMERATION * 1484 *******************************/
1493rdf_term(N) :- 1494 ground(N), 1495 !, 1496 pre_object(N, N0), 1497 visible_term(N0). 1498rdf_term(N) :- 1499 gen_term(N). 1500 1501gen_term(N) :- 1502 resource(N), 1503 visible_term(N). 1504gen_term(O) :- % performs double conversion! 1505 rdf_literal(O), 1506 (rdf(_,_,O) -> true).
1514rdf_literal(Term) :- 1515 ground(Term), 1516 !, 1517 pre_ground_object(Term, Object), 1518 (rdf_db:rdf(_,_,Object)->true). 1519rdf_literal(Term) :- 1520 pre_object(Term,literal(Lit0)), 1521 rdf_db:rdf_current_literal(Lit0), 1522 (rdf_db:rdf(_,_,literal(Lit0))->true), 1523 post_object(Term, literal(Lit0)).
1530rdf_bnode(BNode) :- 1531 atom(BNode), 1532 !, 1533 current_bnode(BNode). 1534rdf_bnode(BNode) :- 1535 rdf_db:rdf_resource(BNode), 1536 current_bnode(BNode). 1537 1538current_bnode(BNode) :- 1539 rdf_is_bnode(BNode), 1540 visible_node(BNode). % Assumes BNodes cannot be predicates
1547rdf_iri(IRI) :- 1548 atom(IRI), 1549 !, 1550 \+ rdf_is_bnode(IRI), 1551 visible_term(IRI). 1552rdf_iri(IRI) :- 1553 resource(IRI), 1554 \+ rdf_is_bnode(IRI), 1555 visible_term(IRI).
1562rdf_name(Name) :- 1563 atom(Name), \+ boolean(Name), 1564 !, 1565 \+ rdf_is_bnode(Name), 1566 visible_term(Name). 1567rdf_name(Name) :- 1568 ground(Name), 1569 !, 1570 pre_ground_object(Name, Name0), 1571 (rdf_db:rdf(_,_,Name0)->true). 1572rdf_name(Name) :- 1573 rdf_iri(Name). 1574rdf_name(Name) :- 1575 rdf_literal(Name).
1590rdf_predicate(P) :- 1591 atom(P), 1592 !, 1593 (rdf(_,P,_) -> true). 1594rdf_predicate(P) :- 1595 rdf_db:rdf_current_predicate(P), 1596 (rdf(_,P,_) -> true).
1605rdf_object(O) :- 1606 ground(O), 1607 !, 1608 ( atom(O), \+ boolean(O) 1609 -> (rdf_db:rdf(_,_,O) -> true) 1610 ; rdf_literal(O) 1611 ). 1612rdf_object(O) :- 1613 rdf_db:rdf_resource(O), 1614 (rdf_db:rdf(_,_,O) -> true). 1615rdf_object(O) :- 1616 rdf_literal(O).
1623rdf_node(N) :- 1624 var(N), 1625 !, 1626 gen_node(N). 1627rdf_node(N) :- 1628 pre_ground_object(N, N0), 1629 visible_node(N0). 1630 1631gen_node(N) :- 1632 rdf_db:rdf_resource(N), 1633 visible_node(N). 1634gen_node(O) :- % performs double conversion! 1635 rdf_literal(O), 1636 (rdf(_,_,O) -> true).
1644resource(R) :- 1645 var(R), 1646 !, 1647 gen_resource(R). 1648resource(R) :- 1649 rdf_db:rdf_resource(R), 1650 !. 1651resource(R) :- 1652 rdf_db:rdf_current_predicate(R), 1653 !. 1654 1655gen_resource(R) :- 1656 rdf_db:rdf_resource(R). 1657gen_resource(R) :- 1658 rdf_db:rdf_current_predicate(R), 1659 \+ rdf_db:rdf_resource(R). 1660 1661visible_node(Term) :- 1662 atom(Term), 1663 !, 1664 ( rdf_db:rdf(Term,_,_) 1665 ; rdf_db:rdf(_,_,Term) 1666 ), 1667 !. 1668visible_node(Term) :- 1669 rdf_db:rdf(_,_,Term). 1670 1671visible_term(Term) :- 1672 atom(Term), 1673 !, 1674 ( rdf_db:rdf(Term,_,_) 1675 ; rdf_db:rdf(_,Term,_) 1676 ; rdf_db:rdf(_,_,Term) 1677 ), 1678 !. 1679visible_term(Term) :- 1680 rdf_db:rdf(_,_,Term).
_:
. Blank nodes generated by this predicate are of the form
_:genid
followed by a unique integer.1688rdf_create_bnode(BNode) :- 1689 var(BNode), 1690 !, 1691 rdf_db:rdf_bnode(BNode). 1692rdf_create_bnode(BNode) :- 1693 uninstantiation_error(BNode). 1694 1695 1696 /******************************* 1697 * TYPE CHECKING * 1698 *******************************/
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).
1713rdf_is_iri(IRI) :-
1714 atom(IRI),
1715 \+ 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).
1743rdf_is_literal(Literal) :- 1744 literal_form(Literal), 1745 !, 1746 ground(Literal). 1747 1748literal_form(_@_). 1749literal_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).
1760rdf_is_name(T) :- rdf_is_iri(T), !. 1761rdf_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.
1775rdf_is_object(T) :- rdf_is_subject(T), !. 1776rdf_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.
1789rdf_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)
.
1805rdf_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).
1815rdf_is_term(N) :- rdf_is_subject(N), !. 1816rdf_is_term(N) :- rdf_is_literal(N). 1817 1818 1819 /******************************* 1820 * COLLECTIONS * 1821 *******************************/
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)
.
1833rdf_list(L) :- 1834 var(L), 1835 !, 1836 rdf_has(L, rdf:first, _), 1837 \+ rdf_has(_, rdf:rest, L), 1838 rdf_list_g(L). 1839rdf_list(L) :- 1840 rdf_list_g(L), 1841 !. 1842 1843rdf_list_g(rdf:nil) :- !. 1844rdf_list_g(L) :- 1845 once(rdf_has(L, rdf:first, _)), 1846 rdf_has(L, rdf:rest, Rest), 1847 ( rdf_equal(rdf:nil, Rest) 1848 -> true 1849 ; rdf_list_g(Rest) 1850 ).
1859rdf_list(RDFList, Prolog) :- 1860 rdf_is_subject(RDFList), 1861 !, 1862 rdf_list_to_prolog(RDFList, Prolog). 1863rdf_list(RDFList, _Prolog) :- 1864 type_error(rdf_subject, RDFList). 1865 1866:- rdf_meta 1867 rdf_list_to_prolog(r,-). 1868 1869rdf_list_to_prolog(rdf:nil, Prolog) :- 1870 !, 1871 Prolog = []. 1872rdf_list_to_prolog(RDF, [H|T2]) :- 1873 ( rdf_has(RDF, rdf:first, H0), 1874 rdf_has(RDF, rdf:rest, T1) 1875 *-> H = H0, 1876 rdf_list_to_prolog(T1, T2) 1877 ; type_error(rdf_list, RDF) 1878 ).
1889rdf_length(RDFList, Len) :- 1890 rdf_is_subject(RDFList), 1891 !, 1892 rdf_length(RDFList, 0, Len). 1893 1894:- rdf_meta 1895 rdf_length(r,+,-). 1896 1897rdf_length(rdf:nil, Len, Len) :- !. 1898rdf_length(RDF, Len0, Len) :- 1899 ( rdf_has(RDF, rdf:rest, T) 1900 *-> Len1 is Len0+1, 1901 rdf_length(T, Len1, Len) 1902 ; type_error(rdf_list, RDF) 1903 ).
1910rdf_member(M, L) :- 1911 ground(M), 1912 !, 1913 ( rdf_member2(M, L) 1914 -> true 1915 ). 1916rdf_member(M, L) :- 1917 rdf_member2(M, L). 1918 1919rdf_member2(M, L) :- 1920 rdf_has(L, rdf:first, M). 1921rdf_member2(M, L) :- 1922 rdf_has(L, rdf:rest, L1), 1923 rdf_member2(M, L1).
1931rdf_nextto(X, Y) :- 1932 distinct(X-Y, rdf_nextto(X, Y, _)). 1933 1934 1935rdf_nextto(X, Y, L) :- 1936 var(X), ground(Y), 1937 !, 1938 rdf_nextto(Y, X, L). 1939rdf_nextto(X, Y, L) :- 1940 rdf_has(L, rdf:first, X), 1941 rdf_has(L, rdf:rest, T), 1942 rdf_has(T, rdf:first, Y).
1952rdf_nth0(I, L, X) :- 1953 rdf_nth(0, I, L, X). 1954 1955rdf_nth1(I, L, X) :- 1956 rdf_nth(1, I, L, X). 1957 1958rdf_nth(Offset, I, L, X) :- 1959 rdf_is_subject(L), 1960 !, 1961 ( var(I) 1962 -> true 1963 ; must_be(nonneg, I) 1964 ), 1965 rdf_nth_(I, Offset, L, X). 1966rdf_nth(_, _, L, _) :- 1967 type_error(rdf_subject, L). 1968 1969rdf_nth_(I, I0, L, X) :- 1970 ( I0 == I 1971 -> ! 1972 ; I0 = I 1973 ), 1974 rdf_has(L, rdf:first, X). 1975rdf_nth_(I, I0, L, X) :- 1976 rdf_has(L, rdf:rest, T), 1977 I1 is I0+1, 1978rdf_nth_(I, I1, T, X).
1987rdf_last(L, Last) :- 1988 rdf_is_subject(L), 1989 !, 1990 rdf_has(L, rdf:rest, T), 1991 ( rdf_equal(T, rdf:nil) 1992 -> rdf_has(L, rdf:first, Last) 1993 ; rdf_last(T, Last) 1994 ). 1995rdf_last(L, _) :- 1996 type_error(rdf_subject, L).
2001rdf_estimate_complexity(S, P, O, Estimate) :-
2002 pre_object(O,O0),
2003 rdf_db:rdf_estimate_complexity(S,P,O0,Estimate).
2015rdf_assert_list(Prolog, RDF) :- 2016 rdf_default_graph(G), 2017 rdf_assert_list(Prolog, RDF, G). 2018 2019rdf_assert_list(Prolog, RDF, G) :- 2020 must_be(list, Prolog), 2021 rdf_transaction(rdf_assert_list_(Prolog, RDF, G)). 2022 2023rdf_assert_list_([], Nil, _) :- 2024 rdf_equal(rdf:nil, Nil). 2025rdf_assert_list_([H|T], L2, G) :- 2026 (var(L2) -> rdf_create_bnode(L2) ; true), 2027 rdf_assert(L2, rdf:type, rdf:'List', G), 2028 rdf_assert(L2, rdf:first, H, G), 2029 ( T == [] 2030 -> rdf_assert(L2, rdf:rest, rdf:nil, G) 2031 ; rdf_create_bnode(T2), 2032 rdf_assert(L2, rdf:rest, T2, G), 2033 rdf_assert_list_(T, T2, G) 2034 ).
2043rdf_retract_list(L) :- 2044 rdf_is_subject(L), 2045 !, 2046 rdf_transaction(rdf_retract_list_(L)). 2047rdf_retract_list(L) :- 2048 type_error(rdf_subject, L). 2049 2050:- rdf_meta 2051 rdf_retract_list_(r). 2052 2053rdf_retract_list_(rdf:nil) :- !. 2054rdf_retract_list_(L) :- 2055 rdf_retractall(L, rdf:first, _), 2056 forall(rdf_has(L, rdf:rest, L1), 2057 rdf_retract_list_(L1)), 2058 rdf_retractall(L, rdf:rest, _), 2059 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 bylibrary(semweb/rdf_db)
. For example, the following query returns literals with prefix "ams", exploiting the RDF literal index.