18
19:- module(sparql_dcg,[
20 select//3
21 , describe//1
22 , describe//2
23 , ask//1
24 ]).
87:- use_module(library(semweb/rdf_db), [rdf_global_object/2, rdf_global_id/2]). 88:- use_module(library(dcg_core)). 89:- use_module(library(dcg_codes)). 90
91:- set_prolog_flag(double_quotes, codes).
98select(Vars,Goal,Options) -->
99 "SELECT ",
100 if_option(distinct(Distinct), if(Distinct=true, " DISTINCT "),Options,O1),
101 seqmap_with_sep(" ",expr,Vars), " ",
102 where(Goal),
103 if_option(order_by(OB), (" ORDER BY ", expr(OB)), O1,O2),
104 if_option(limit(Limit), (" LIMIT ", at(Limit)), O2,O3),
105 if_option(offset(Offs), (" OFFSET ", at(Offs)), O3,O4),
106 {check_remaining_options(O4)}.
107
108check_remaining_options([]) :- !.
109check_remaining_options(Opts) :- throw(unrecognised_options(Opts)).
110
111if_option(Opt,Phrase,O1,O2) -->
112 ( {select_option(Opt,O1,O2)} -> call_dcg(Phrase); {O2=O1}).
117ask(Goal) --> "ASK ", brace(goal(Goal)).
122describe(R) --> "DESCRIBE ", resource(R).
123describe(RS,Goal) -->
124 "DESCRIBE ",
125 seqmap_with_sep(" ",resource,RS),
126 where(Goal).
129where(Goal) --> "WHERE ", brace(goal(Goal)).
132goal(G1;G2) --> brace(goal(G1)), " UNION ", brace(goal(G2)).
133goal(\+G) --> "FILTER NOT EXISTS ", brace(goal(G)). 134goal((G1,G2)) --> goal(G1), " . ", goal(G2).
135goal(conj(GS)) --> seqmap_with_sep(" , ",goal,GS).
136
137goal(rdf(S,P,O)) -->
138 { rdf_global_object(O,OO) },
139 resource(S), " ",
140 resource(P), " ",
141 object(OO).
142
143goal(filter(Cond)) --> "FILTER ", cond(Cond).
144
145:- op(1150,fx,p). 146p(X) --> paren(X).
147
148cond(\+C) --> p "! ", cond(C).
149cond((X,Y)) --> p cond(X), " && ", cond(Y).
150cond((X;Y)) --> p cond(X), " || ", cond(Y).
151cond(X==Y) --> p expr(X), " = ", expr(Y).
152cond(X\=Y) --> p expr(X), " != ", expr(Y).
153cond(X=<Y) --> p expr(X), " <= ", expr(Y).
154cond(X>=Y) --> p expr(X), " >= ", expr(Y).
155cond(X>Y) --> p expr(X), " > ", expr(Y).
156cond(X<Y) --> p expr(X), " < ", expr(Y).
157cond(between(L,U,X)) --> cond((L=<X,X=<U)).
158cond(in(X,Ys)) --> p expr(X), " in ", (p seqmap_with_sep(", ",expr,Ys)).
159cond(regex(P,V)) --> "regex(", object(V), ",", quote(at(P)), ")".
160cond(regex(P,V,F)) --> "regex(", object(V), ",", quote(at(P)), ",", quote(at(F)), ")".
161cond(bound(V)) --> "bound(", object(V), ")".
162cond(uri(V)) --> "isURI(", object(V), ")".
163cond(blank(V)) --> "isBLANK(", object(V), ")".
164cond(literal(V)) --> "isLITERAL(", object(V), ")".
165
166expr(str(V)) --> "STR(", object(V), ")".
167expr(lang(V)) --> "LANG(", object(V), ")".
168expr(count(X)) --> "COUNT(", expr(X), ")".
169expr(datatype(V)) --> "DATATYPE(", object(V), ")".
170
171expr(+X) --> p "+ ", expr(X), ")".
172expr(-X) --> p "- ", expr(X), ")".
173expr(X+Y) --> p expr(X), " + ", expr(Y).
174expr(X-Y) --> p expr(X), " + ", expr(Y).
175expr(X*Y) --> p expr(X), " * ", expr(Y).
176expr(X/Y) --> p expr(X), " / ", expr(Y).
177expr(X) --> {number(X)}, at(X).
178expr(X) --> object(X).
179
180resource(R) --> variable(R).
181resource(R) --> {rdf_global_id(R,RR)}, uri(RR).
182
183object(literal(Lit)) --> literal(Lit).
184object(Resource) --> resource(Resource).
185
186literal(lang(Lang,Val)) --> quote(at(Val)), "@", at(Lang).
187literal(type(Type,Val)) --> quote(wr(Val)), "^^", resource(Type).
188literal(Lit) --> {atomic(Lit)}, quote(at(Lit)).
189
190uri(U) --> {atom(U)}, "<", at(U), ">".
191quote(P) --> "\"", escape_with(0'\\,0'",P), "\"".
192variable(V) --> {var_number(V,N)}, "?v", at(N).
193variable(@V) --> "_:", {atomic(V) -> N=V; var_number(V,N)}, at(N).
194variable(@) --> "[]"
A simple DCG for generating a subset of SPARQL
Samer Abdallah, Dept. of Computer Science, UCL (2014) /