34
35:- module(jena_properties, []). 36:- use_module(library(semweb/rdfs)). 37:- use_module(library(semweb/rdf_db)). 38:- use_module(library(aggregate)). 39:- use_module(sparql_runtime). 40
41:- multifile
42 sparql:functional_property/2,
43 sparql:current_functional_property/3. 44
45ns(apf, 'http://jena.hpl.hp.com/ARQ/property#').
46ns(lists, 'http://jena.hpl.hp.com/ARQ/list#').
47ns(Prefix, URI) :-
48 rdf_current_ns(Prefix, URI).
49
50alias('java:com.hp.hpl.jena.sparql.pfunction.library.',
51 'http://jena.hpl.hp.com/ARQ/property#').
52alias('java:com.hp.hpl.jena.query.pfunction.library.',
53 'http://jena.hpl.hp.com/ARQ/property#').
54
55property_alias(Prefix:Local, Global) :-
56 ns(Prefix, URI),
57 alias(AliasBase, URI),
58 atom_concat(AliasBase, Local, Global).
59
60absolute_uri(Prefix:Local, Global) :-
61 ns(Prefix, URI),
62 atom_concat(URI, Local, Global).
63
64term_expansion((sparql:functional_property(S, NS:Term0) :- Body),
65 [ (sparql:functional_property(S, Term) :- Body),
66 sparql:current_functional_property(P, P, Argc)
67 | Aliases
68 ]) :-
69 Term0 =.. [Name|Args],
70 length(Args, Argc),
71 absolute_uri(NS:Name, P),
72 Term =.. [P|Args],
73 findall(sparql:current_functional_property(P1, P, Argc),
74 property_alias(NS:Name, P1),
75 Aliases).
76
77
78 81
83
85
86sparql:functional_property(S, apf:assign(O)) :-
87 ( S = O
88 -> true
89 ; sparql_true(S=O)
90 ).
91
92
93 96
97rdf_list(S) :-
98 rdf_equal(S, rdf:nil).
99rdf_list(S) :-
100 rdf(S, rdf:first, _).
101
102rdf_container(Container) :-
103 container_class(Class),
104 rdfs_individual_of(Container, Class).
105
106:- rdf_meta container_class(r). 107
108container_class(rdf:'Bag').
109container_class(rdf:'Seq').
110container_class(rdf:'Alt').
111
114
115sparql:functional_property(S, lists:member(O)) :-
116 rdf_list(S),
117 rdfs_member(O, S).
118
119sparql:functional_property(S, rdfs:member(O)) :-
120 rdf_container(S),
121 rdfs_member(O, S).
122
123sparql:functional_property(S, apf:bag(O)) :-
124 nonvar(S),
125 rdfs_individual_of(S, rdfs:'Bag'),
126 rdfs_member(O, S).
127sparql:functional_property(S, apf:seq(O)) :-
128 nonvar(S),
129 rdfs_individual_of(S, rdfs:'Seq'),
130 rdfs_member(O, S).
131sparql:functional_property(S, apf:alt(O)) :-
132 nonvar(S),
133 rdfs_individual_of(S, rdfs:'Alt'),
134 rdfs_member(O, S).
135
136
139
140sparql:functional_property(S, lists:length(O)) :-
141 rdf_list(S),
142 aggregate_all(count, rdfs_member(_, S), Len),
143 rdf_equal(xsd:integer, IntType),
144 atom_number(String, Len),
145 O = literal(type(IntType, String)).
146
147sparql:functional_property(S, lists:index(literal(type(IntType, Index)),
148 Element)) :-
149 rdf_list(S),
150 rdf_equal(xsd:integer, IntType),
151 ( var(Index)
152 -> rdfs_nth1(I, S, Element),
153 atom_number(Index, I)
154 ; atom_number(Index, I),
155 rdfs_nth1(I, S, Element)
156 -> true
157 ).
158
159
160rdfs_nth1(0, Set, Element) :-
161 rdf_has(Set, rdf:first, Element).
162rdfs_nth1(I, Set, Element) :-
163 var(I),
164 !,
165 rdf_has(Set, rdf:rest, Tail),
166 rdfs_nth1(I0, Tail, Element),
167 I is I0 + 1.
168rdfs_nth1(I, Set, Element) :-
169 I2 is I - 1,
170 rdf_has(Set, rdf:rest, Tail),
171 rdfs_nth1(I2, Tail, Element)