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-2016, VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35 36:- module(rdf11, 37 [ rdf/3, % ?S, ?P, ?O 38 rdf/4, % ?S, ?P, ?O, ?G 39 rdf_has/3, % ?S, ?P, ?O 40 rdf_has/4, % ?S, ?P, ?O, -RealP 41 rdf_update/4, % +S, +P, +O, +Action 42 rdf_update/5, % +S, +P, +O, +G, +Action 43 rdf_reachable/3, % ?S, ?P, ?O 44 rdf_reachable/5, % ?S, ?P, ?O, +MaxD, -D 45 46 rdf_assert/3, % +S, +P, +O 47 rdf_assert/4, % +S, +P, +O, ?G 48 rdf_retractall/3, % ?S, ?P, ?O 49 rdf_retractall/4, % ?S, ?P, ?O, ?G 50 51 {}/1, % +Where 52 rdf_where/1, % +Where 53 rdf_compare/3, % -Diff, +Left, +Right 54 55 rdf_term/1, % ?Term 56 rdf_literal/1, % ?Term 57 rdf_bnode/1, % ?Term 58 rdf_iri/1, % ?Term 59 rdf_name/1, % ?Term 60 61 rdf_is_iri/1, % @Term 62 rdf_is_bnode/1, % @Term 63 rdf_is_literal/1, % @Term 64 rdf_is_name/1, % @Term 65 rdf_is_object/1, % @Term 66 rdf_is_predicate/1, % @Term 67 rdf_is_subject/1, % @Term 68 rdf_is_term/1, % @Term 69 70 rdf_subject/1, % ?Term 71 rdf_predicate/1, % ?Term 72 rdf_object/1, % ?Term 73 rdf_node/1, % ?Term 74 75 rdf_create_bnode/1, % ?Term 76 77 rdf_canonical_literal/2, % +In, -Canonical 78 rdf_lexical_form/2, % +Literal, -Lexical 79 80 rdf_default_graph/1, % -Graph 81 rdf_default_graph/2, % -Old, +New 82 83 rdf_estimate_complexity/4, % ?S, ?P, ?O, -Estimate 84 rdf_assert_list/2, % +PrologList, ?RDFList 85 rdf_assert_list/3, % +PrologList, ?RDFList, +G 86 rdf_last/2, % +RDFList, ?Last 87 rdf_list/1, % ?RDFList 88 rdf_list/2, % +RDFList, -PrologList 89 rdf_length/2, % ?RDFList, ?Length 90 rdf_member/2, % ?Member, +RDFList 91 rdf_nextto/2, % ?X, ?Y 92 rdf_nextto/3, % ?X, ?Y, ?RdfList 93 rdf_nth0/3, % ?Index, +RDFList, ?X 94 rdf_nth1/3, % ?Index, +RDFList, ?X 95 rdf_retract_list/1, % +RDFList 96 97 op(110, xfx, @), % must be above . 98 op(650, xfx, ^^), % must be above : 99 op(1150, fx, rdf_meta) 100 ]). 101:- use_module(library(c14n2)). 102:- use_module(library(debug)). 103:- use_module(library(error)). 104:- use_module(library(lists)). 105:- use_module(library(memfile)). 106:- reexport(library(semweb/rdf_db), 107 except([ rdf/3, 108 rdf/4, 109 rdf_assert/3, 110 rdf_assert/4, 111 rdf_current_literal/1, 112 rdf_current_predicate/1, 113 rdf_has/3, 114 rdf_has/4, 115 rdf_update/4, 116 rdf_update/5, 117 rdf_reachable/3, 118 rdf_reachable/5, 119 rdf_retractall/3, 120 rdf_retractall/4, 121 rdf_node/1, 122 rdf_bnode/1, 123 rdf_is_literal/1, 124 rdf_is_resource/1, 125 rdf_literal_value/2, 126 rdf_compare/3, 127 rdf_estimate_complexity/4 128 ]) 129 ). 130:- use_module(library(sgml)). 131:- use_module(library(solution_sequences)).
172:- multifile 173 in_ground_type_hook/3, % +Type, +Input, -Lexical:atom 174 out_type_hook/3. % +Type, -Output, +Lexical:atom 175 176:- meta_predicate 177 parse_partial_xml( , , ). 178 179:- rdf_meta 180 rdf(r,r,o), 181 rdf(r,r,o,r), 182 rdf_assert(r,r,o), 183 rdf_assert(r,r,o,r), 184 rdf_has(r,r,o), 185 rdf_has(r,r,o,-), 186 rdf_update(r,r,o,t), 187 rdf_update(r,r,o,r,t), 188 rdf_reachable(r,r,o), 189 rdf_reachable(r,r,o,+,-), 190 rdf_retractall(r,r,o), 191 rdf_retractall(r,r,o,r), 192 {}(t), 193 rdf_where(t), 194 rdf_canonical_literal(o,-), 195 rdf_lexical_form(o,-), 196 rdf_compare(-,o,o), 197 rdf_iri(r), 198 rdf_is_iri(r), 199 rdf_is_literal(o), 200 rdf_is_name(o), 201 rdf_is_object(o), 202 rdf_is_predicate(r), 203 rdf_is_subject(r), 204 rdf_is_term(o), 205 rdf_term(o), 206 rdf_literal(o), 207 rdf_name(o), 208 rdf_object(o), 209 rdf_estimate_complexity(r,r,o,-), 210 rdf_assert_list(t,r), 211 rdf_assert_list(t,r,r), 212 rdf_last(r,o), 213 rdf_list(r), 214 rdf_list(r,-), 215 rdf_length(r,-), 216 rdf_member(o,r), 217 rdf_nextto(o,o), 218 rdf_nth0(?,r,o), 219 rdf_nth1(?,r,o), 220 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.
303rdf(S,P,O) :- 304 pre_object(O,O0), 305 rdf_db:rdf(S,P,O0), 306 post_object(O,O0). 307 308rdf(S,P,O,G) :- 309 pre_object(O,O0), 310 pre_graph(G,G0), 311 rdf_db:rdf(S,P,O0,G0), 312 post_graph(G, G0), 313 post_object(O,O0).
inverse_of
and
symmetric
. See rdf_set_predicate/2.323rdf_has(S,P,O) :- 324 pre_object(O,O0), 325 rdf_db:rdf_has(S,P,O0), 326 post_object(O,O0). 327 328rdf_has(S,P,O,RealP) :- 329 pre_object(O,O0), 330 rdf_db:rdf_has(S,P,O0,RealP), 331 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')).
368rdf_update(S, P, O, Action) :- 369 rdf_update(S, P, O, _, Action). 370rdf_update(S, P, O, G, Action) :- 371 must_be(ground, Action), 372 ( update_column(Action, S,P,O,G, On) 373 -> must_be(ground, On), 374 arg(1, Action, Old), 375 ( On == Old 376 -> true 377 ; rdf_transaction(rdf_update_(S, P, O, G, Action), update) 378 ) 379 ; domain_error(rdf_update_action, Action) 380 ). 381 382update_column(subject(_), S,_,_,_, S). 383update_column(predicate(_), _,P,_,_, P). 384update_column(object(_), _,_,O,_, O). 385update_column(graph(_), _,_,_,G, G). 386 387rdf_update_(S1, P, O, G, subject(S2)) :- 388 !, 389 forall(rdf(S1, P, O, G), 390 ( rdf_retractall(S1, P, O, G), 391 rdf_assert(S2, P, O, G) 392 )). 393rdf_update_(S, P1, O, G, predicate(P2)) :- 394 !, 395 forall(rdf(S, P1, O, G), 396 ( rdf_retractall(S, P1, O, G), 397 rdf_assert(S, P2, O, G) 398 )). 399rdf_update_(S, P, O1, G, object(O2)) :- 400 !, 401 forall(rdf(S, P, O1, G), 402 ( rdf_retractall(S, P, O1, G), 403 rdf_assert(S, P, O2, G) 404 )). 405rdf_update_(S, P, O, G1, graph(G2)) :- 406 !, 407 forall(rdf(S, P, O, G1), 408 ( rdf_retractall(S, P, O, G1), 409 rdf_assert(S, P, O, G2) 410 )).
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.
427rdf_reachable(S,P,O) :- 428 pre_object(O,O0), 429 rdf_db:rdf_reachable(S,P,O0), 430 post_object(O,O0). 431 432rdf_reachable(S,P,O,MaxD,D) :- 433 pre_object(O,O0), 434 rdf_db:rdf_reachable(S,P,O0,MaxD,D), 435 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.
450rdf_assert(S,P,O) :- 451 rdf_default_graph(G), 452 rdf_assert(S,P,O,G). 453 454rdf_assert(S,P,O,G) :- 455 must_be(ground, O), 456 pre_ground_object(O,O0), 457 rdf_db:rdf_assert(S,P,O0,G).
466rdf_retractall(S,P,O) :- 467 pre_object(O,O0), 468 rdf_db:rdf_retractall(S,P,O0). 469 470rdf_retractall(S,P,O,G) :- 471 pre_object(O,O0), 472 pre_graph(G,G0), 473 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.
494rdf_compare(Diff, Left, Right) :-
495 pre_ground_object(Left, Left0),
496 pre_ground_object(Right, Right0),
497 rdf_db:rdf_compare(Diff, Left0, Right0).
{ Date >= "2000-01-01"^^xsd:dateTime }, 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:{...}
.
540{}(Where) :- 541 rdf_where(Where). 542 543rdf_where(Var) :- 544 var(Var), 545 !, 546 instantiation_error(Var). 547rdf_where((A,B)) :- 548 !, 549 rdf_where(A), 550 rdf_where(B). 551rdf_where(Constraint) :- 552 rdf_constraint(Constraint, Goal), 553 !, 554 call(). 555rdf_where(Constraint) :- 556 existence_error(rdf_constraint, Constraint). 557 558% Comparison operators 559rdf_constraint(Term >= Value, 560 add_value_constraint(Term, >=, Value)). 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)). 569% String selection 570rdf_constraint(prefix(Term, Pattern), 571 add_text_constraint(Term, prefix(PatternA))) :- 572 atom_string(PatternA, Pattern). 573rdf_constraint(substring(Term, Pattern), 574 add_text_constraint(Term, substring(PatternA))) :- 575 atom_string(PatternA, Pattern). 576rdf_constraint(word(Term, Pattern), 577 add_text_constraint(Term, word(PatternA))) :- 578 atom_string(PatternA, Pattern). 579rdf_constraint(like(Term, Pattern), 580 add_text_constraint(Term, like(PatternA))) :- 581 atom_string(PatternA, Pattern). 582rdf_constraint(icase(Term, Pattern), 583 add_text_constraint(Term, icase(PatternA))) :- 584 atom_string(PatternA, Pattern). 585% Lang selection 586rdf_constraint(lang_matches(Term, Pattern), 587 add_lang_constraint(Term, lang_matches(Pattern))). 588 589add_text_constraint(Var, Cond) :- 590 var(Var), 591 !, 592 ( get_attr(Var, rdf11, Cond0) 593 -> put_attr(Var, rdf11, [Cond|Cond0]) 594 ; put_attr(Var, rdf11, [Cond]) 595 ). 596add_text_constraint(Text^^_Type, Cond) :- 597 !, 598 add_text_constraint(Text, Cond). 599add_text_constraint(Text@_Lang, Cond) :- 600 !, 601 add_text_constraint(Text, Cond). 602add_text_constraint(Var, Cond) :- 603 eval_condition(Cond, Var).
609add_lang_constraint(Var, Constraint) :- 610 var(Var), 611 !, 612 ( get_attr(Var, rdf11, Cond0) 613 -> put_attr(Var, rdf11, [Constraint|Cond0]) 614 ; put_attr(Var, rdf11, [Constraint]) 615 ). 616add_lang_constraint(_Text@Lang, Constraint) :- 617 !, 618 add_lang_constraint(Lang, Constraint). 619add_lang_constraint(_Text^^_Type, _Constraint) :- 620 !, 621 fail. 622add_lang_constraint(Term, Constraint) :- 623 eval_condition(Constraint, Term).
629add_value_constraint(Term, Constraint, ValueIn) :- 630 constraint_literal_value(ValueIn, Value), 631 add_value_constraint_cann(Value, Constraint, Term). 632 633constraint_literal_value(Value, Value^^_Type) :- 634 number(Value), 635 !. 636constraint_literal_value(Value, Literal) :- 637 rdf_canonical_literal(Value, Literal). 638 639add_value_constraint_cann(RefVal^^Type, Constraint, Term) :- 640 var(Term), var(Type), 641 !, 642 add_text_constraint(Term, value(Constraint, RefVal, Type)). 643add_value_constraint_cann(RefVal^^Type, Constraint, Val^^Type2) :- 644 !, 645 Type = Type2, 646 add_text_constraint(Val, value(Constraint, RefVal, Type)). 647add_value_constraint_cann(RefVal@Lang, Constraint, Val@Lang) :- 648 !, 649 add_text_constraint(Val, value(Constraint, RefVal, lang(Lang))). 650add_value_constraint_cann(RefVal^^Type, Constraint, Val) :- 651 !, 652 ground(Val), 653 Val \= _@_, 654 eval_condition(value(Constraint, RefVal, Type), Val). 655 656put_cond(Var, []) :- 657 !, 658 del_attr(Var, rdf11). 659put_cond(Var, List) :- 660 put_attr(Var, rdf11, List). 661 662eval_condition(Cond, Literal) :- 663 text_condition(Cond), 664 !, 665 text_of(Literal, Text), 666 text_condition(Cond, Text). 667eval_condition(Cond, Literal) :- 668 lang_condition(Cond), 669 !, 670 lang_of(Literal, Lang), 671 lang_condition(Cond, Lang). 672eval_condition(value(Comp, Ref, _Type), Value) :- 673 ( number(Ref) 674 -> number(Value), 675 compare_numeric(Comp, Ref, Value) 676 ; compare_std(Comp, Ref, Value) 677 ). 678 679compare_numeric(<, Ref, Value) :- Value < Ref. 680compare_numeric(=<, Ref, Value) :- Value =< Ref. 681compare_numeric(==, Ref, Value) :- Value =:= Ref. 682compare_numeric(>=, Ref, Value) :- Value >= Ref. 683compare_numeric( >, Ref, Value) :- Value > Ref. 684 685compare_std(<, Ref, Value) :- Value @< Ref. 686compare_std(=<, Ref, Value) :- Value @=< Ref. 687compare_std(==, Ref, Value) :- Value == Ref. 688compare_std(>=, Ref, Value) :- Value @>= Ref. 689compare_std( >, Ref, Value) :- Value @> Ref. 690 691text_condition(prefix(_)). 692text_condition(substring(_)). 693text_condition(word(_)). 694text_condition(like(_)). 695text_condition(icase(_)). 696 697text_of(Literal, Text) :- 698 atomic(Literal), 699 !, 700 Text = Literal. 701text_of(Text@_Lang, Text). 702text_of(Text^^_Type, Text). 703 704text_condition(prefix(Pattern), Text) :- 705 rdf_match_label(prefix, Pattern, Text). 706text_condition(substring(Pattern), Text) :- 707 rdf_match_label(substring, Pattern, Text). 708text_condition(word(Pattern), Text) :- 709 rdf_match_label(word, Pattern, Text). 710text_condition(like(Pattern), Text) :- 711 rdf_match_label(like, Pattern, Text). 712text_condition(icase(Pattern), Text) :- 713 rdf_match_label(icase, Pattern, Text). 714 715lang_condition(lang_matches(_)). 716 717lang_of(_Text@Lang0, Lang) :- 718 !, 719 Lang = Lang0. 720lang_of(Lang, Lang) :- 721 atom(Lang). 722 723lang_condition(lang_matches(Pattern), Lang) :- 724 rdf_db:lang_matches(Lang, Pattern).
literal(Cond, _Value)
.
Translated constraints are removed from object.732literal_condition(Object, Cond) :- 733 var(Object), 734 !, 735 get_attr(Object, rdf11, Cond0), 736 best_literal_cond(Cond0, Cond, Rest), 737 put_cond(Object, Rest). 738literal_condition(Text@_Lang, Cond) :- 739 get_attr(Text, rdf11, Cond0), 740 !, 741 best_literal_cond(Cond0, Cond, Rest), 742 put_cond(Text, Rest). 743literal_condition(Text^^_Type, Cond) :- 744 get_attr(Text, rdf11, Cond0), 745 best_literal_cond(Cond0, Cond, Rest), 746 put_cond(Text, Rest).
literal(Search, Value)
.
755best_literal_cond(Conditions, Best, Rest) :- 756 sort(Conditions, Unique), 757 best_literal_cond2(Unique, Best, Rest). 758 759best_literal_cond2(Conds, Best, Rest) :- 760 select(Cond, Conds, Rest0), 761 rdf10_cond(Cond, Best, Rest0, Rest), 762 !. 763 764rdf10_cond(value(=<, URef, UType), Cond, Rest0, Rest) :- 765 ( select(value(>=, LRef, LType), Rest0, Rest) 766 -> true 767 ; memberchk(value(>, LRef, LType), Rest0) 768 -> Rest = Rest0 769 ), 770 !, 771 in_constaint_type(LType, SLType, LRef, LRef0), 772 in_constaint_type(UType, SUType, URef, URef0), 773 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 774rdf10_cond(value(<, URef, UType), Cond, Rest0, Rest) :- 775 ( select(value(>=, LRef, LType), Rest0, Rest1) 776 -> true 777 ; memberchk(value(>, LRef, LType), Rest0) 778 -> Rest1 = Rest0 779 ), 780 !, 781 Rest = [value(<, URef, UType)|Rest1], 782 in_constaint_type(LType, SLType, LRef, LRef0), 783 in_constaint_type(UType, SUType, URef, URef0), 784 Cond = between(type(SLType, LRef0), type(SUType, URef0)). 785rdf10_cond(value(Cmp, Ref, Type), Pattern, Rest, Rest) :- 786 !, 787 rdf10_compare(Cmp, Ref, Type, Pattern). 788rdf10_cond(lang_matches(_), _, _, _) :- !, fail. 789rdf10_cond(Cond, Cond, Rest, Rest). 790 791rdf10_compare(Cmp, Ref, Type, Pattern) :- 792 nonvar(Type), Type = lang(Lang), 793 !, 794 atom_string(Ref0, Ref), 795 rdf10_lang_cond(Cmp, Ref0, Lang, Pattern). 796rdf10_compare(Cmp, Ref, Type, Pattern) :- 797 in_constaint_type(Type, SType, Ref, Ref0), 798 rdf10_type_cond(Cmp, Ref0, SType, Pattern). 799 800rdf10_lang_cond( <, Ref, Lang, lt(lang(Lang,Ref))). 801rdf10_lang_cond(=<, Ref, Lang, le(lang(Lang,Ref))). 802rdf10_lang_cond(==, Ref, Lang, eq(lang(Lang,Ref))). 803rdf10_lang_cond(>=, Ref, Lang, ge(lang(Lang,Ref))). 804rdf10_lang_cond(>, Ref, Lang, gt(lang(Lang,Ref))). 805 806rdf10_type_cond( <, Ref, Type, lt(type(Type,Ref))). 807rdf10_type_cond(=<, Ref, Type, le(type(Type,Ref))). 808rdf10_type_cond(==, Ref, Type, eq(type(Type,Ref))). 809rdf10_type_cond(>=, Ref, Type, ge(type(Type,Ref))). 810rdf10_type_cond( >, Ref, Type, gt(type(Type,Ref))).
815in_constaint_type(Type, SType, Val, Val0) :- 816 nonvar(Type), ground(Val), 817 !, 818 SType = Type, 819 in_ground_type(Type, Val, Val0). 820in_constaint_type(Type, SType, Val, Val0) :- 821 var(Type), number(Val), 822 !, 823 ( integer(Val) 824 -> rdf_equal(SType, xsd:integer), 825 in_ground_type(xsd:integer, Val, Val0) 826 ; float(Val) 827 -> rdf_equal(SType, xsd:double), 828 in_ground_type(xsd:double, Val, Val0) 829 ; assertion(fail) 830 ).
838literal_class(Term, Class) :-
839 get_attr(Term, rdf11, Conds),
840 select(Cond, Conds, Rest),
841 lang_condition(Cond),
842 !,
843 Term = Text@Lang,
844 put_attr(Lang, rdf11, [Cond]),
845 put_cond(Text, Rest),
846 ( var(Text)
847 -> true
848 ; atom_string(Text2, Text)
849 ),
850 Class = lang(Lang, Text2).
854attr_unify_hook(Cond, Value) :- 855 get_attr(Value, rdf11, Cond2), 856 !, 857 append(Cond, Cond2, CondJ), 858 sort(CondJ, Unique), 859 put_cond(Value, Unique). 860attr_unify_hook(Cond, Text^^_Type) :- 861 var(Text), 862 !, 863 put_cond(Text, Cond). 864attr_unify_hook(Cond, Text@Lang) :- 865 var(Text), var(Lang), 866 !, 867 partition(lang_condition, Cond, LangCond, TextCond), 868 put_cond(Text, TextCond), 869 put_cond(Lang, LangCond). 870attr_unify_hook(Cond, Value) :- 871 sort(Cond, Unique), 872 propagate_conditions(Unique, Value). 873 874propagate_conditions([], _). 875propagate_conditions([H|T], Val) :- 876 propagate_condition(H, Val), 877 propagate_conditions(T, Val). 878 879propagate_condition(value(Comp, Ref, Type), Value) :- 880 !, 881 ( Value = Plain^^VType 882 -> VType = Type 883 ; Plain = Value 884 ), 885 cond_compare(Comp, Ref, Plain). 886propagate_condition(lang_matches(Pattern), Value) :- 887 !, 888 ( Value = _@Lang 889 -> true 890 ; Lang = Value 891 ), 892 rdf_db:lang_matches(Lang, Pattern). 893propagate_condition(Cond, Value) :- 894 Cond =.. [Name|Args], 895 Constraint =.. [Name,Value|Args], 896 rdf_constraint(Constraint, Continuation), 897 call(). 898 899cond_compare(>, Ref, Value) :- Value @> Ref. 900cond_compare(>=, Ref, Value) :- Value @>= Ref. 901cond_compare(==, Ref, Value) :- Value == Ref. 902cond_compare(=<, Ref, Value) :- Value @=< Ref. 903cond_compare( <, Ref, Value) :- Value @< Ref.
913:- create_prolog_flag(rdf_default_graph, default, 914 [ type(atom), 915 keep(true) 916 ]). 917 918rdf_default_graph(Graph) :- 919 current_prolog_flag(rdf_default_graph, Graph). 920rdf_default_graph(Old, New) :- 921 current_prolog_flag(rdf_default_graph, Old), 922 ( New == Old 923 -> true 924 ; set_prolog_flag(rdf_default_graph, New) 925 ). 926 927 928pre_graph(G, _G0) :- 929 var(G), 930 !. 931pre_graph(G, G) :- 932 atom(G), 933 !. 934pre_graph(G, _) :- 935 type_error(rdf_graph, G). 936 937post_graph(G, G0:_) :- 938 !, 939 G = G0. 940post_graph(G, G). 941 942 943pre_object(Literal, literal(Cond, Value)) :- 944 literal_condition(Literal, Cond), 945 !, 946 debug(literal_index, 'Search literal using ~p', [literal(Cond, Value)]), 947 literal_value0(Literal, Value). 948pre_object(Literal, literal(Value)) :- 949 literal_class(Literal, Value), 950 !, 951 debug(literal_index, 'Search literal using ~p', [literal(Value)]). 952pre_object(Var, _Var) :- 953 var(Var), 954 !. 955pre_object(Atom, URI) :- 956 atom(Atom), 957 \+ boolean(Atom), 958 !, 959 URI = Atom. 960pre_object(Val@Lang, literal(lang(Lang, Val0))) :- 961 !, 962 in_lang_string(Val, Val0). 963pre_object(Val^^Type, literal(Literal)) :- 964 !, 965 in_type(Type, Val, Type0, Val0), 966 ( var(Type0), var(Val0) 967 -> true 968 ; Literal = type(Type0, Val0) 969 ). 970pre_object(Obj, Val0) :- 971 ground(Obj), 972 !, 973 pre_ground_object(Obj, Val0). 974pre_object(Obj, _) :- 975 type_error(rdf_object, Obj). 976 977literal_value0(Var, _) :- 978 var(Var), 979 !. 980literal_value0(_ @Lang, lang(Lang, _)). 981literal_value0(_^^Type, type(Type, _)).
date(Y,M,D)
^^xsd:datedate_time(Y,M,D,HH,MM,SS)
^^xsd:dateTimedate_time(Y,M,D,HH,MM,SS,TZ)
^^xsd:dateTimemonth_day(M,D)
^^xsd:gMonthDayyear_month(Y,M)
^^xsd:gYearMonthtime(HH,MM,SS)
^^xsd:timetrue
and false
are considered
URIs.1024:- rdf_meta 1025 pre_ground_object(+, o). 1026 1027% Interpret Prolog integer as xsd:integer. 1028pre_ground_object(Int, Object) :- 1029 integer(Int), 1030 !, 1031 rdf_equal(Object, literal(type(xsd:integer, Atom))), 1032 atom_number(Atom, Int). 1033% Interpret Prolog floating-point value as xsd:double. 1034pre_ground_object(Float, Object) :- 1035 float(Float), 1036 !, 1037 rdf_equal(Object, literal(type(xsd:double, Atom))), 1038 xsd_number_string(Float, String), 1039 atom_string(Atom, String). 1040% Interpret SWI string as xsd:string. 1041pre_ground_object(String, Object) :- 1042 string(String), 1043 !, 1044 rdf_equal(Object, literal(type(xsd:string, Atom))), 1045 atom_string(Atom, String). 1046% Interpret `false' and `true' as the Boolean values. 1047pre_ground_object(false, literal(type(xsd:boolean, false))) :- !. 1048pre_ground_object(true, literal(type(xsd:boolean, true))) :- !. 1049% Interpret date(Y,M,D) as xsd:date, 1050% date_time(Y,M,D,HH,MM,SS) as xsd:dateTime, 1051% date_time(Y,M,D,HH,MM,SS,TZ) as xsd:dateTime, 1052% month_day(M,D) as xsd:gMonthDay, 1053% year_month(Y,M) as xsd:gYearMonth, and 1054% time(HH,MM,SS) as xsd:time. 1055pre_ground_object(Term, literal(type(Type, Atom))) :- 1056 xsd_date_time_term(Term), 1057 !, 1058 xsd_time_string(Term, Type, Atom). 1059pre_ground_object(Val@Lang, literal(lang(Lang0, Val0))) :- 1060 !, 1061 downcase_atom(Lang, Lang0), 1062 in_lang_string(Val, Val0). 1063pre_ground_object(Val^^Type, literal(type(Type0, Val0))) :- 1064 !, 1065 in_type(Type, Val, Type0, Val0). 1066pre_ground_object(Atom, URI) :- 1067 atom(Atom), 1068 !, 1069 URI = Atom. 1070%pre_ground_object(NS:Local, URI) :- % still leaves S and P. 1071% atom(NS), atom(Local), !, 1072% rdf_global_id(NS:Local, URI). 1073pre_ground_object(literal(Lit0), literal(Lit)) :- 1074 old_literal(Lit0, Lit), 1075 !. 1076pre_ground_object(Value, _) :- 1077 type_error(rdf_object, Value). 1078 1079xsd_date_time_term(date(_,_,_)). 1080xsd_date_time_term(date_time(_,_,_,_,_,_)). 1081xsd_date_time_term(date_time(_,_,_,_,_,_,_)). 1082xsd_date_time_term(month_day(_,_)). 1083xsd_date_time_term(year_month(_,_)). 1084xsd_date_time_term(time(_,_,_)). 1085 1086old_literal(Lit0, Lit) :- 1087 old_literal(Lit0), 1088 !, 1089 Lit = Lit0. 1090old_literal(Atom, Lit) :- 1091 atom(Atom), 1092 rdf_equal(xsd:string, XSDString), 1093 Lit = type(XSDString, Atom). 1094 1095old_literal(type(Type, Value)) :- 1096 atom(Type), atom(Value). 1097old_literal(lang(Lang, Value)) :- 1098 atom(Lang), atom(Value). 1099 1100in_lang_string(Val, Val0) :- 1101 atomic(Val), 1102 !, 1103 atom_string(Val0, Val). 1104in_lang_string(_, _). 1105 1106in_type(Type, Val, Type, Val0) :- 1107 nonvar(Type), ground(Val), 1108 !, 1109 in_ground_type(Type, Val, Val0). 1110in_type(VarType, Val, VarType, Val0) :- 1111 ground(Val), 1112 \+ catch(xsd_number_string(_, Val), _, fail), 1113 !, 1114 atom_string(Val0, Val). 1115in_type(_, _, _, _). 1116 1117:- rdf_meta 1118 in_ground_type(r,?,?), 1119 in_date_component(r, +, +, -).
1127in_ground_type(Type, Input, Lex) :- 1128 \+ string(Input), 1129 in_ground_type_hook(Type, Input, Lex), 1130 !. 1131in_ground_type(IntType, Val, Val0) :- 1132 xsd_numerical(IntType, Domain, PrologType), 1133 !, 1134 in_number(PrologType, Domain, IntType, Val, Val0). 1135in_ground_type(xsd:boolean, Val, Val0) :- 1136 !, 1137 ( in_boolean(Val, Val0) 1138 -> true 1139 ; type_error(rdf_boolean, Val) 1140 ). 1141in_ground_type(rdf:langString, _Val0, _) :- 1142 !, 1143 domain_error(rdf_data_type, rdf:langString). 1144in_ground_type(DateTimeType, Val, Val0) :- 1145 xsd_date_time_type(DateTimeType), 1146 !, 1147 in_date_time(DateTimeType, Val, Val0). 1148in_ground_type(rdf:'XMLLiteral', Val, Val0) :- 1149 !, 1150 in_xml_literal(xml, Val, Val0). 1151in_ground_type(rdf:'HTML', Val, Val0) :- 1152 !, 1153 in_xml_literal(html, Val, Val0). 1154in_ground_type(_Unknown, Val, Val0) :- 1155 atom_string(Val0, Val).
1162:- rdf_meta 1163 in_date_time(r,+,-). 1164 1165in_date_time(Type, Text, Text0) :- 1166 atom(Text), 1167 !, 1168 xsd_time_string(_, Type, Text), 1169 Text0 = Text. 1170in_date_time(Type, Text, Text0) :- 1171 string(Text), 1172 !, 1173 xsd_time_string(_, Type, Text), 1174 atom_string(Text0, Text). 1175in_date_time(xsd:dateTime, Stamp, Text0) :- 1176 number(Stamp), 1177 !, 1178 format_time(atom(Text0), '%FT%T%:z', Stamp). 1179in_date_time(Type, Term, Text0) :- 1180 !, 1181 xsd_time_string(Term, Type, String), 1182 atom_string(Text0, String).
1189in_boolean(true, true). 1190in_boolean(false, false). 1191in_boolean("true", true). 1192in_boolean("false", false). 1193in_boolean(1, true). 1194in_boolean(0, false). 1195 1196boolean(false). 1197boolean(true).
1206in_number(integer, Domain, XSDType, Val, Val0) :- 1207 integer(Val), 1208 !, 1209 check_integer_domain(Domain, XSDType, Val), 1210 atom_number(Val0, Val). 1211in_number(integer, Domain, XSDType, Val, Val0) :- 1212 atomic(Val), 1213 atom_number(Val, Num), 1214 integer(Num), 1215 !, 1216 check_integer_domain(Domain, XSDType, Num), 1217 atom_number(Val0, Num). 1218in_number(double, _Domain, _, Val, Val0) :- 1219 number(Val), 1220 !, 1221 ValF is float(Val), 1222 xsd_number_string(ValF, ValS), 1223 atom_string(Val0, ValS). 1224in_number(double, _Domain, _, Val, Val0) :- 1225 atomic(Val), 1226 xsd_number_string(Num, Val), 1227 ValF is float(Num), 1228 !, 1229 xsd_number_string(ValF, ValS), 1230 atom_string(Val0, ValS). 1231in_number(PrologType, _, _, Val, _) :- 1232 type_error(PrologType, Val). 1233 1234check_integer_domain(PLType, _, Val) :- 1235 is_of_type(PLType, Val), 1236 !. 1237check_integer_domain(_, XSDType, Val) :- 1238 domain_error(XSDType, Val). 1239 1240errorhas_type(nonpos, T):- 1241 integer(T), 1242 T =< 0. 1243 1244%check_integer_domain(between(Low, High), XSDType, Val) :- 1245% ( between(Low, High, Val) 1246% -> true 1247% ; domain_error(XSDType, Val) 1248% ). 1249%check_integer_domain(integer, _, _).
1253:- rdf_meta 1254 xsd_numerical(r, ?, ?). 1255 1256xsd_numerical(xsd:byte, between(-128,127), integer). 1257xsd_numerical(xsd:double, float, double). 1258xsd_numerical(xsd:decimal, float, double). 1259xsd_numerical(xsd:float, float, double). 1260xsd_numerical(xsd:int, between(-2147483648,2147483647), integer). 1261xsd_numerical(xsd:integer, integer, integer). 1262xsd_numerical(xsd:long, between(-9223372036854775808, 1263 9223372036854775807), integer). 1264xsd_numerical(xsd:negativeInteger, negative_integer, integer). 1265xsd_numerical(xsd:nonNegativeInteger, nonneg, integer). 1266xsd_numerical(xsd:nonPositiveInteger, nonpos, integer). 1267xsd_numerical(xsd:positiveInteger, positive_integer, integer). 1268xsd_numerical(xsd:short, between(-32768,32767), integer). 1269xsd_numerical(xsd:unsignedByte, between(0,255), integer). 1270xsd_numerical(xsd:unsignedInt, between(0,4294967295), integer). 1271xsd_numerical(xsd:unsignedLong, between(0,18446744073709551615), integer). 1272xsd_numerical(xsd:unsignedShort, between(0,65535), integer).
1278:- rdf_meta 1279 xsd_date_time_type(r). 1280 1281xsd_date_time_type(xsd:date). 1282xsd_date_time_type(xsd:dateTime). 1283xsd_date_time_type(xsd:gDay). 1284xsd_date_time_type(xsd:gMonth). 1285xsd_date_time_type(xsd:gMonthDay). 1286xsd_date_time_type(xsd:gYear). 1287xsd_date_time_type(xsd:gYearMonth). 1288xsd_date_time_type(xsd:time).
1298in_xml_literal(Type, Val, Val0) :- 1299 xml_is_dom(Val), 1300 !, 1301 write_xml_literal(Type, Val, Val0). 1302in_xml_literal(xml, Val, Val0) :- 1303 parse_partial_xml(load_xml, Val, DOM), 1304 write_xml_literal(xml, DOM, Val0). 1305in_xml_literal(html, Val, Val0) :- 1306 parse_partial_xml(load_html, Val, DOM), 1307 write_xml_literal(html, DOM, Val0). 1308 1309parse_partial_xml(Parser, Val, DOM) :- 1310 setup_call_cleanup( 1311 new_memory_file(MF), 1312 ( setup_call_cleanup( 1313 open_memory_file(MF, write, Out), 1314 format(Out, "<xml>~w</xml>", [Val]), 1315 close(Out)), 1316 setup_call_cleanup( 1317 open_memory_file(MF, read, In), 1318 call(Parser, stream(In), [element(xml, _, DOM)], []), 1319 close(In)) 1320 ), 1321 free_memory_file(MF)). 1322 1323 1324write_xml_literal(xml, DOM, Text) :- 1325 with_output_to(atom(Text), 1326 xml_write_canonical(current_output, DOM, [])). 1327write_xml_literal(html, DOM, Text) :- 1328 with_output_to(atom(Text), 1329 html_write(current_output, DOM, 1330 [ header(false), 1331 layout(false) 1332 ])).
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'.
1360rdf_canonical_literal(In, Literal) :- 1361 ground(In), 1362 !, 1363 pre_ground_object(In, DBTerm), 1364 post_object(Literal, DBTerm). 1365rdf_canonical_literal(In, _) :- 1366 must_be(ground, In).
1379% For example, 1380% 1381% == 1382% ?- rdf_lexical_form(2.3^^xsd:double, L). 1383% L = "2.3E0"^^'http://www.w3.org/2001/XMLSchema#double'. 1384% == 1385 1386rdf_lexical_form(Literal, Lexical) :- 1387 pre_ground_object(Literal, literal(Lit0)), 1388 !, 1389 text_of0(Lit0, Lexical). 1390rdf_lexical_form(Literal, _) :- 1391 type_error(rdf_literal, Literal). 1392 1393text_of0(type(TypeA, LexicalA), LexicalS^^TypeA) :- 1394 atom_string(LexicalA, LexicalS). 1395text_of0(lang(LangA, LexicalA), LexicalS@LangA) :- 1396 atom_string(LexicalA, LexicalS). 1397 1398 1399 /******************************* 1400 * POST PROCESSING * 1401 *******************************/ 1402 1403:- rdf_meta 1404 post_object(o,o), 1405 out_type(r,-,+). 1406 1407post_object(Val, _) :- 1408 ground(Val), 1409 !. % already specified and matched 1410post_object(URI, URI0) :- 1411 atom(URI0), 1412 !, 1413 URI = URI0. 1414post_object(Val@Lang, literal(lang(Lang, Val0))) :- 1415 nonvar(Lang), % lang(Lang,Text) returns var(Lang) if no lang 1416 !, 1417 atom_string(Val0, Val). 1418post_object(Val^^Type, literal(type(Type, Val0))) :- 1419 !, 1420 out_type(Type, Val, Val0). 1421post_object(Val^^xsd:string, literal(Plain)) :- 1422 !, 1423 atomic(Plain), 1424 atom_string(Plain, Val). 1425post_object(Val@Lang, literal(_, lang(Lang, Val0))) :- 1426 nonvar(Lang), 1427 !, 1428 atom_string(Val0, Val). 1429post_object(Val^^Type, literal(_, type(Type, Val0))) :- 1430 !, 1431 out_type(Type, Val, Val0). 1432post_object(Val^^xsd:string, literal(_, Plain)) :- 1433 atomic(Plain), 1434 atom_string(Plain, Val). 1435 1436out_type(xsd:string, Val, Val0) :- % catches unbound type too 1437 !, 1438 atom_string(Val0, Val). 1439out_type(Type, Val, Val0) :- 1440 out_type_hook(Type, Val, Val0), 1441 !. 1442out_type(IntType, Val, Val0) :- 1443 xsd_numerical(IntType, _Domain, _BasicType), 1444 !, 1445 xsd_number_string(Val, Val0). 1446out_type(DateTimeType, Val, Val0) :- 1447 xsd_date_time_type(DateTimeType), 1448 !, 1449 out_date_time(DateTimeType, Val, Val0). 1450out_type(xsd:boolean, Val, Val0) :- 1451 !, 1452 Val = Val0. 1453out_type(rdf:'XMLLiteral', XML, DOM) :- 1454 xml_is_dom(DOM), 1455 !, 1456 with_output_to(string(XML), 1457 xml_write(DOM, [header(false)])). 1458out_type(_Unknown, Val, Val0) :- 1459 atom_string(Val0, Val).
1467out_date_time(Type, Prolog, Lexical) :- 1468 xsd_time_string(Prolog, Type, Lexical). 1469 1470 1471 /******************************* 1472 * ENUMERATION * 1473 *******************************/
1482rdf_term(N) :- 1483 ground(N), 1484 !, 1485 pre_object(N, N0), 1486 visible_term(N0). 1487rdf_term(N) :- 1488 gen_term(N). 1489 1490gen_term(N) :- 1491 resource(N), 1492 visible_term(N). 1493gen_term(O) :- % performs double conversion! 1494 rdf_literal(O), 1495 (rdf(_,_,O) -> true).
1503rdf_literal(Term) :- 1504 ground(Term), 1505 !, 1506 pre_ground_object(Term, Object), 1507 (rdf_db:rdf(_,_,Object)->true). 1508rdf_literal(Term) :- 1509 pre_object(Term,literal(Lit0)), 1510 rdf_db:rdf_current_literal(Lit0), 1511 (rdf_db:rdf(_,_,literal(Lit0))->true), 1512 post_object(Term, literal(Lit0)).
1519rdf_bnode(BNode) :- 1520 atom(BNode), 1521 !, 1522 current_bnode(BNode). 1523rdf_bnode(BNode) :- 1524 rdf_db:rdf_resource(BNode), 1525 current_bnode(BNode). 1526 1527current_bnode(BNode) :- 1528 rdf_is_bnode(BNode), 1529 visible_node(BNode). % Assumes BNodes cannot be predicates
1536rdf_iri(IRI) :- 1537 atom(IRI), 1538 !, 1539 \+ rdf_is_bnode(IRI), 1540 visible_term(IRI). 1541rdf_iri(IRI) :- 1542 resource(IRI), 1543 \+ rdf_is_bnode(IRI), 1544 visible_term(IRI).
1551rdf_name(Name) :- 1552 atom(Name), \+ boolean(Name), 1553 !, 1554 \+ rdf_is_bnode(Name), 1555 visible_term(Name). 1556rdf_name(Name) :- 1557 ground(Name), 1558 !, 1559 pre_ground_object(Name, Name0), 1560 (rdf_db:rdf(_,_,Name0)->true). 1561rdf_name(Name) :- 1562 rdf_iri(Name). 1563rdf_name(Name) :- 1564 rdf_literal(Name).
1579rdf_predicate(P) :- 1580 atom(P), 1581 !, 1582 (rdf(_,P,_) -> true). 1583rdf_predicate(P) :- 1584 rdf_db:rdf_current_predicate(P), 1585 (rdf(_,P,_) -> true).
1594rdf_object(O) :- 1595 ground(O), 1596 !, 1597 ( atom(O), \+ boolean(O) 1598 -> (rdf_db:rdf(_,_,O) -> true) 1599 ; rdf_literal(O) 1600 ). 1601rdf_object(O) :- 1602 rdf_db:rdf_resource(O), 1603 (rdf_db:rdf(_,_,O) -> true). 1604rdf_object(O) :- 1605 rdf_literal(O).
1612rdf_node(N) :- 1613 var(N), 1614 !, 1615 gen_node(N). 1616rdf_node(N) :- 1617 pre_ground_object(N, N0), 1618 visible_node(N0). 1619 1620gen_node(N) :- 1621 rdf_db:rdf_resource(N), 1622 visible_node(N). 1623gen_node(O) :- % performs double conversion! 1624 rdf_literal(O), 1625 (rdf(_,_,O) -> true).
1633resource(R) :- 1634 var(R), 1635 !, 1636 gen_resource(R). 1637resource(R) :- 1638 rdf_db:rdf_resource(R), 1639 !. 1640resource(R) :- 1641 rdf_db:rdf_current_predicate(R), 1642 !. 1643 1644gen_resource(R) :- 1645 rdf_db:rdf_resource(R). 1646gen_resource(R) :- 1647 rdf_db:rdf_current_predicate(R), 1648 \+ rdf_db:rdf_resource(R). 1649 1650visible_node(Term) :- 1651 atom(Term), 1652 !, 1653 ( rdf_db:rdf(Term,_,_) 1654 ; rdf_db:rdf(_,_,Term) 1655 ), 1656 !. 1657visible_node(Term) :- 1658 rdf_db:rdf(_,_,Term). 1659 1660visible_term(Term) :- 1661 atom(Term), 1662 !, 1663 ( rdf_db:rdf(Term,_,_) 1664 ; rdf_db:rdf(_,Term,_) 1665 ; rdf_db:rdf(_,_,Term) 1666 ), 1667 !. 1668visible_term(Term) :- 1669 rdf_db:rdf(_,_,Term).
_:
. Blank nodes generated by this predicate are of the form
_:genid
followed by a unique integer.1677rdf_create_bnode(BNode) :- 1678 var(BNode), 1679 !, 1680 rdf_db:rdf_bnode(BNode). 1681rdf_create_bnode(BNode) :- 1682 uninstantiation_error(BNode). 1683 1684 1685 /******************************* 1686 * TYPE CHECKING * 1687 *******************************/
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).
1702rdf_is_iri(IRI) :-
1703 atom(IRI),
1704 \+ 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).
1732rdf_is_literal(Literal) :- 1733 literal_form(Literal), 1734 !, 1735 ground(Literal). 1736 1737literal_form(_@_). 1738literal_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).
1749rdf_is_name(T) :- rdf_is_iri(T), !. 1750rdf_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.
1764rdf_is_object(T) :- rdf_is_subject(T), !. 1765rdf_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.
1778rdf_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)
.
1794rdf_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).
1804rdf_is_term(N) :- rdf_is_subject(N), !. 1805rdf_is_term(N) :- rdf_is_literal(N). 1806 1807 1808 /******************************* 1809 * COLLECTIONS * 1810 *******************************/
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)
.
1822rdf_list(L) :- 1823 var(L), 1824 !, 1825 rdf_has(L, rdf:first, _), 1826 \+ rdf_has(_, rdf:rest, L), 1827 rdf_list_g(L). 1828rdf_list(L) :- 1829 rdf_list_g(L), 1830 !. 1831 1832rdf_list_g(rdf:nil) :- !. 1833rdf_list_g(L) :- 1834 once(rdf_has(L, rdf:first, _)), 1835 rdf_has(L, rdf:rest, Rest), 1836 ( rdf_equal(rdf:nil, Rest) 1837 -> true 1838 ; rdf_list_g(Rest) 1839 ).
1848rdf_list(RDFList, Prolog) :- 1849 rdf_is_subject(RDFList), 1850 !, 1851 rdf_list_to_prolog(RDFList, Prolog). 1852rdf_list(RDFList, _Prolog) :- 1853 type_error(rdf_subject, RDFList). 1854 1855:- rdf_meta 1856 rdf_list_to_prolog(r,-). 1857 1858rdf_list_to_prolog(rdf:nil, Prolog) :- 1859 !, 1860 Prolog = []. 1861rdf_list_to_prolog(RDF, [H|T2]) :- 1862 ( rdf_has(RDF, rdf:first, H0), 1863 rdf_has(RDF, rdf:rest, T1) 1864 *-> H = H0, 1865 rdf_list_to_prolog(T1, T2) 1866 ; type_error(rdf_list, RDF) 1867 ).
1878rdf_length(RDFList, Len) :- 1879 rdf_is_subject(RDFList), 1880 !, 1881 rdf_length(RDFList, 0, Len). 1882 1883:- rdf_meta 1884 rdf_length(r,+,-). 1885 1886rdf_length(rdf:nil, Len, Len) :- !. 1887rdf_length(RDF, Len0, Len) :- 1888 ( rdf_has(RDF, rdf:rest, T) 1889 *-> Len1 is Len0+1, 1890 rdf_length(T, Len1, Len) 1891 ; type_error(rdf_list, RDF) 1892 ).
1899rdf_member(M, L) :- 1900 ground(M), 1901 !, 1902 ( rdf_member2(M, L) 1903 -> true 1904 ). 1905rdf_member(M, L) :- 1906 rdf_member2(M, L). 1907 1908rdf_member2(M, L) :- 1909 rdf_has(L, rdf:first, M). 1910rdf_member2(M, L) :- 1911 rdf_has(L, rdf:rest, L1), 1912 rdf_member2(M, L1).
1920rdf_nextto(X, Y) :- 1921 distinct(X-Y, rdf_nextto(X, Y, _)). 1922 1923 1924rdf_nextto(X, Y, L) :- 1925 var(X), ground(Y), 1926 !, 1927 rdf_nextto(Y, X, L). 1928rdf_nextto(X, Y, L) :- 1929 rdf_has(L, rdf:first, X), 1930 rdf_has(L, rdf:rest, T), 1931 rdf_has(T, rdf:first, Y).
1941rdf_nth0(I, L, X) :- 1942 rdf_nth(0, I, L, X). 1943 1944rdf_nth1(I, L, X) :- 1945 rdf_nth(1, I, L, X). 1946 1947rdf_nth(Offset, I, L, X) :- 1948 rdf_is_subject(L), 1949 !, 1950 ( var(I) 1951 -> true 1952 ; must_be(nonneg, I) 1953 ), 1954 rdf_nth_(I, Offset, L, X). 1955rdf_nth(_, L, _) :- 1956 type_error(rdf_subject, L). 1957 1958rdf_nth_(I, I0, L, X) :- 1959 ( I0 == I 1960 -> ! 1961 ; I0 = I 1962 ), 1963 rdf_has(L, rdf:first, X). 1964rdf_nth_(I, I0, L, X) :- 1965 rdf_has(L, rdf:rest, T), 1966 I1 is I0+1, 1967rdf_nth_(I, I1, T, X).
1976rdf_last(L, Last) :- 1977 rdf_is_subject(L), 1978 !, 1979 rdf_has(L, rdf:rest, T), 1980 ( rdf_equal(T, rdf:nil) 1981 -> rdf_has(L, rdf:first, Last) 1982 ; rdf_last(T, Last) 1983 ). 1984rdf_last(L, _) :- 1985 type_error(rdf_subject, L).
1990rdf_estimate_complexity(S, P, O, Estimate) :-
1991 pre_object(O,O0),
1992 rdf_db:rdf_estimate_complexity(S,P,O0,Estimate).
2004rdf_assert_list(Prolog, RDF) :- 2005 rdf_default_graph(G), 2006 rdf_assert_list(Prolog, RDF, G). 2007 2008rdf_assert_list(Prolog, RDF, G) :- 2009 must_be(list, Prolog), 2010 rdf_transaction(rdf_assert_list_(Prolog, RDF, G)). 2011 2012rdf_assert_list_([], Nil, _) :- 2013 rdf_equal(rdf:nil, Nil). 2014rdf_assert_list_([H|T], L2, G) :- 2015 (var(L2) -> rdf_create_bnode(L2) ; true), 2016 rdf_assert(L2, rdf:type, rdf:'List', G), 2017 rdf_assert(L2, rdf:first, H, G), 2018 ( T == [] 2019 -> rdf_assert(L2, rdf:rest, rdf:nil, G) 2020 ; rdf_create_bnode(T2), 2021 rdf_assert(L2, rdf:rest, T2, G), 2022 rdf_assert_list_(T, T2, G) 2023 ).
2032rdf_retract_list(L) :- 2033 rdf_is_subject(L), 2034 !, 2035 rdf_transaction(rdf_retract_list_(L)). 2036rdf_retract_list(L) :- 2037 type_error(rdf_subject, L). 2038 2039:- rdf_meta 2040 rdf_retract_list_(r). 2041 2042rdf_retract_list_(rdf:nil) :- !. 2043rdf_retract_list_(L) :- 2044 rdf_retractall(L, rdf:first, _), 2045 forall(rdf_has(L, rdf:rest, L1), 2046 rdf_retract_list_(L1)), 2047 rdf_retractall(L, rdf:rest, _), 2048 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.