1/* Part of sparkle
    2	Copyright 2014-2015 Samer Abdallah (UCL)
    3	 
    4	This program is free software; you can redistribute it and/or
    5	modify it under the terms of the GNU Lesser General Public License
    6	as published by the Free Software Foundation; either version 2
    7	of the License, or (at your option) any later version.
    8
    9	This program is distributed in the hope that it will be useful,
   10	but WITHOUT ANY WARRANTY; without even the implied warranty of
   11	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   12	GNU Lesser General Public License for more details.
   13
   14	You should have received a copy of the GNU Lesser General Public
   15	License along with this library; if not, write to the Free Software
   16	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   17*/
   18
   19:- module(sparql_dcg,[
   20      select//3
   21   ,  construct//3
   22   ,  describe//1
   23   ,  describe//2
   24   ,  ask//1
   25	]).

A simple DCG for generating a subset of SPARQL

sparql_goal ---> (sparql_goal, sparql_goal) % conjunction
               ; (sparql_goal; sparql_goal) % disjunction
               ; rdf(resource,resource,object)
               ; filter(cond)
               .

resource :< object. % any resource is an object

literal(+literal)   :: object.  % any ground literal is an object
atomic              :< literal. % any atomic can be a plain literal
lang(atom,atom)     :: literal. % literal with language
type(resource,atom) :: literal. % typed literal

object   :< expr. % any object is an expr
number   :< expr. % Prolog numerical values can also be expressions

condition ---> (cond , cond)
             ; (cond ; cond)
             ; \+ cond
             ; expr == expr
             ; expr \= expr
             ; expr >= expr
             ; expr =< expr
             ; expr < expr
             ; expr > expr
             ; between(expr,expr,expr)
             ; in(object,list(object))
             ; regex(pattern,value)
             ; bound(object)
             ; blank(resource)
             ; uri(object)
             ; literal(object)
             .

expr ---> expr + expr
        ; expr - expr
        ; expr * expr
        ; expr / expr
        ; +expr
        ; -expr
        ; str(expr)
        ; lang(expr)
        ; datatype(expr)
        .

var ---> '$VAR'(integer)
       ; '@'        % anonymous blank node
       ; '@'(atom)  % nonymous blank node
       .

var :< resource
var :< literal

Samer Abdallah, Dept. of Computer Science, UCL (2014) /

   88%:- use_module(library(semweb/rdf_db), [rdf_global_object/2, rdf_global_id/2]).
   89:- use_module(library(semweb/rdf11)).   90:- use_module(library(dcg_core)).   91:- use_module(library(dcg_codes)).   92
   93:- set_prolog_flag(double_quotes, codes).
 select(+Vars:list(expr), +Goal:sparql_goal, +Options:list(option))// is det
Any variables in the query must be represented by '$VAR'/1 terms as generated by numbervars/3.
  100select(_Vars,Goal,Options) -->
  101        {
  102         (   Goal=aggregate_group(_,_,_,_)
  103         ;   Goal=aggregate_group(_,_,_,_,_)
  104         ;   Goal=aggregate(_,_,_))
  105        },
  106        !,
  107        % TODO
  108        if_option(distinct(Distinct), if(Distinct=true, " "),Options,O1),
  109        goal(Goal),
  110        if_option(order_by(OB), (" ORDER BY ", expr(OB)), O1,O2),
  111        if_option(limit(Limit), (" LIMIT ", at(Limit)), O2,O3),
  112        if_option(offset(Offs), (" OFFSET ", at(Offs)), O3,O4),
  113        {check_remaining_options(O4)}.
  114        
  115select(Vars,Goal,Options) -->
  116   "SELECT ", 
  117   if_option(distinct(Distinct), if(Distinct=true, " DISTINCT "),Options,O1),
  118   seqmap_with_sep(" ",expr,Vars), " ",
  119   where(Goal),
  120   if_option(order_by(OB), (" ORDER BY ", expr(OB)), O1,O2),
  121   if_option(limit(Limit), (" LIMIT ", at(Limit)), O2,O3),
  122   if_option(offset(Offs), (" OFFSET ", at(Offs)), O3,O4),
  123   {check_remaining_options(O4)}.
  124
  125construct(Head,Goal,Options) -->
  126   {O1=Options},
  127   "CONSTRUCT ", brace(goal(Head)), " ",
  128   where(Goal),
  129   if_option(order_by(OB), (" ORDER BY ", expr(OB)), O1,O2),
  130   if_option(limit(Limit), (" LIMIT ", at(Limit)), O2,O3),
  131   if_option(offset(Offs), (" OFFSET ", at(Offs)), O3,O4),
  132   {check_remaining_options(O4)}.
  133
  134check_remaining_options([]) :- !.
  135check_remaining_options([Opt|Opts]) :- ignore_option(Opt), !, check_remaining_options(Opts).
  136check_remaining_options(Opts) :- throw(unrecognised_options(Opts)).
  137
  138ignore_option(rule(_)).
  139
  140edgeprops([]) --> "".
  141edgeprops([EP]) -->
  142        !,
  143        edgeprop(EP).
  144edgeprops([EP|EPs]) -->
  145        edgeprop(EP),
  146        " ; ",
  147        edgeprops(EPs).
  148
  149edgeprop(P=O) -->
  150        { rdf_global_object(O,OO) },
  151        property(P), " ",
  152        object(OO).
  153        
  154
  155
  156if_option(Opt,Phrase,O1,O2) -->
  157   ( {select_option(Opt,O1,O2)} -> call_dcg(Phrase); {O2=O1}).
 ask(+Goal:sparql_goal)// is det
Format an ASK query.
  162ask(Goal) --> "ASK ", brace(goal(Goal)).
 describe(+Resource:resource)// is det
 describe(+Resource:resource, +Goal:sparql_goal)// is det
  167describe(R) --> "DESCRIBE ", resource(R).
  168describe(RS,Goal) --> 
  169   "DESCRIBE ", 
  170   seqmap_with_sep(" ",resource,RS),
  171   where(Goal).
 where(+Goal:sparql_goal)// is det
  174where(Goal) --> "WHERE ", brace(goal(Goal)).
 goal(+Goal)// is det
  178% simplify/normalize
  179goal((G,true)) --> !, goal(G).
  180goal((true,G)) --> !, goal(G).
  181
  182
  183goal(G1;G2)   --> brace(goal(G1)), " UNION ", brace(goal(G2)).
  184goal(\+G)     --> "FILTER NOT EXISTS ", brace(goal(G)). %NB consider MINUS { ... } also
  185goal((G1,G2)) --> goal(G1), " . ", goal(G2).
  186goal(conj(GS)) --> seqmap_with_sep(" , ",goal,GS).
  187goal(optional(G))     --> "OPTIONAL ", brace(goal(G)).
  188goal(exists(G))     --> "FILTER(EXISTS ", brace(goal(G)),")".
  189
  190goal(service(S,G)) --> "SERVICE ",{(sparql_endpoint_url(S,URL)->true;URL=S)}, resource(URL)," ",brace(goal(G)).
  191
  192goal(rdf_path(S,P,O,G)) --> goal(rdf(S,P,O,G)).
  193goal(rdf_path(S,P,O)) --> goal(rdf(S,P,O)).
  194
  195
  196goal(rdf(S,P,O)) -->
  197   { rdf_global_object(O,OO) },
  198   resource(S), " ",
  199   property(P), " ",
  200   object(OO).
  201
  202
  203goal(rdf(S,P,O,G)) --> "GRAPH ", resource(G), " ", brace(goal(rdf(S,P,O))).
  204
  205% RDF*. See https://github.com/blazegraph/database/wiki/Reification_Done_Right
  206goal(rdfstar(S,P,O,EdgeProps)) -->
  207        { rdf_global_object(O,OO) },
  208        "<<",
  209        resource(S), " ",
  210        property(P), " ",
  211        object(OO),
  212        ">> ",
  213        edgeprops(EdgeProps).
  214
  215
  216% this does not work on many triplestores
  217% https://stackoverflow.com/questions/32274562/what-is-the-sparql-query-to-get-the-name-of-all-graphs-existing-in-my-triplestor
  218goal(rdf_graph(G)) --> "GRAPH ", resource(G), " {}".
  219
  220goal(rdf_graph_goals(G,Goals)) --> "GRAPH ", resource(G), " ", brace(goal(Goals)).
  221
  222goal(rdf_predicate(P)) --> "SELECT DISTINCT ", expr(P), " ", where(rdf(_,P,_)).
  223
  224goal(aggregate(Expr,G,Result)) --> "SELECT (", expr(Expr), " AS ", variable(Result), ") ", where(G).
  225goal(aggregate_group(Expr, GroupVars, G, Result)) -->
  226        "SELECT (",
  227        expr(Expr), " AS ", variable(Result),") ",
  228        seqmap_with_sep(" ",expr,GroupVars),
  229        " ",
  230        where(G),
  231        " GROUP BY ", seqmap_with_sep(" ",expr,GroupVars).
  232goal(aggregate_group(Expr, GroupVars, G, Having, Result)) -->
  233        "SELECT (",
  234        expr(Expr), " AS ", variable(Result),") ",
  235        seqmap_with_sep(" ",head_expr,GroupVars),
  236        " ",
  237        where(G),
  238        " GROUP BY ", seqmap_with_sep(" ",head_expr_val,GroupVars),
  239        " HAVING ", cond(Having).
  240
  241
  242
  243goal(is(V,Expr)) --> goal(bind(Expr,V)).
  244goal(bind(Expr,V)) --> "BIND( ", expr(Expr), " AS ", variable(V), " )".
  245goal(filter(Cond)) --> "FILTER ", cond(Cond).
  246
  247% support for rdf_where/1 in semweb/rdf11    
  248goal({Cond}) --> "FILTER ", cond(Cond).
  249goal(rdf_where(Cond)) --> "FILTER ", cond(Cond).
  250
  251goal(member(Var,Vals)) -->
  252        {ground(Vals)},
  253        !,
  254        goal(values(Var,Vals)).
  255goal(values(Var,Vals)) -->
  256        {\+ is_list(Var)},!,
  257        "VALUES ",expr(Var)," {",
  258        seqmap_with_sep(" ",expr,Vals), " }".
  259%goal(values(Var,Tuples)) --> "VALUES (",
  260%        {writeln(var=Var),writeln(tups=Tuples),trace,compound(Var), Var =.. [Pred|Args],Tuples},
  261%        seqmap_with_sep(" ",expr,Args), ") {",
  262%        seqmap_with_sep(" ",tuple,Tuples), " }".
  263goal(values(Vars,Tuples)) --> "VALUES (",
  264        seqmap_with_sep(" ",expr,Vars), ") {",
  265        seqmap_with_sep(" ",tuple,Tuples), " }".
  266
  267
  268goal(true) --> "true" .
  269
  270% TODO: put this in its own section
  271goal(str_before(Str, Sep, Sub)) --> goal(bind(str_before(Str, Sep), Sub)).
  272goal(replace(Str, Match, Rep, V)) --> goal(bind(replace(Str, Match, Rep), V)).
  273
  274% allow conditions not wrapped by rdf_where/1
  275goal(G) --> goal(filter(G)).
  276
  277% this is necessary for assigning variables in GROUP BY querie
  278head_expr(is(V,Expr)) --> !, "BIND( ", expr(Expr), " AS ", variable(V), " )".
  279head_expr(X) --> expr(X).
  280
  281head_expr_val(is(_V,Expr)) --> !, expr(Expr).
  282head_expr_val(X) --> expr(X).
  283
  284
  285tuple(Vals) --> "(", seqmap_with_sep(" ",expr,Vals), ")".
  286
  287
  288:- op(1150,fx,p).  289p(X) --> paren(X).
  290
  291cond(\+C)   --> p  "! ", cond(C).
  292cond((X,Y)) --> p cond(X), " && ", cond(Y).
  293cond((X;Y)) --> p cond(X), " || ", cond(Y).
  294cond(X=Y)  --> p expr(X), " = ", expr(Y).
  295cond(X==Y)  --> p expr(X), " = ", expr(Y).
  296cond(X\=Y)  --> p expr(X), " != ", expr(Y).
  297cond(X=<Y)  --> p expr(X), " <= ", expr(Y).
  298cond(X>=Y)  --> p expr(X), " >= ", expr(Y).
  299cond(X>Y)   --> p expr(X), " > ", expr(Y).
  300cond(X<Y)   --> p expr(X), " < ", expr(Y).
  301cond(X@<Y)   --> p expr(str(X)), " < ", expr(str(Y)).
  302cond(X@=<Y)   --> p expr(str(X)), " <= ", expr(str(Y)).
  303cond(X@>Y)   --> p expr(str(X)), " > ", expr(str(Y)).
  304cond(X@>=Y)   --> p expr(str(X)), " >= ", expr(str(Y)).
  305cond(between(L,U,X)) --> cond((L=<X,X=<U)).
  306
  307% 17.4.1.9 IN
  308cond(in(X,Ys))     --> p expr(X), " in ", (p seqmap_with_sep(", ",expr,Ys)).
  309cond(contains(X,Y))   --> p "contains(", string_literal_expr(X), ",", string_literal_expr(Y), ")".
  310cond(str_starts(X,Y))   --> p "strStarts(", string_literal_expr(X), ",", string_literal_expr(Y), ")".
  311cond(str_ends(X,Y))   --> p "strEnds(", string_literal_expr(X), ",", string_literal_expr(Y), ")".
  312cond(regex(S,P))   --> p "regex(", expr(S), ",", quote(at(P)), ")".
  313cond(regex(S,P,F)) --> p "regex(", expr(S), ",", quote(at(P)),  ",", quote(at(F)), ")".
  314cond(regex_str(S,P))   --> "regex(", expr(str(S)), ",", quote(at(P)), ")".
  315cond(regex_str(S,P,F)) --> "regex(", expr(str(S)), ",", quote(at(P)),  ",", quote(at(F)), ")".
  316cond(bound(V))     --> "bound(", object(V), ")".
  317
  318% 17.4.2.1 isIRI
  319% defined in rdf11
  320cond(rdf_is_iri(V))       --> "isIRI(", object(V), ")".
  321cond(is_uri(V))       --> "isURI(", object(V), ")".
  322
  323% 17.4.2.2 isBlank
  324% defined in rdf11
  325cond(rdf_bnode(V))     --> "isBLANK(", object(V), ")".
  326cond(is_blank(V))     --> "isBLANK(", object(V), ")".
  327cond(rdf_is_bnode(V))     --> "isBLANK(", object(V), ")".
  328
  329% 17.4.2.3 isLiteral
  330% defined in rdf11
  331cond(rdf_is_literal(V))   --> "isLITERAL(", object(V), ")".
  332cond(is_literal(V))   --> "isLITERAL(", object(V), ")".
  333
  334% 17.4.2.4 isNumeric
  335cond(number(V))   --> "isNumeric(", object(V), ")".
  336
  337
  338% rdf_where/1
  339cond(lang_matches(V,W))      --> "LANGMATCHES(", expr(lang(V)), ",", object(W), ")".
  340
  341cond(G)            --> {throw(error(cond(G)))}.
  342
  343
  344
  345string_literal_expr(A) --> {atomic(A),atom_string(A,S)},expr(S).
  346string_literal_expr(S) --> expr(S).
  347
  348% 17.4.1.2 IF
  349expr(if(Expr,Yes,No)) --> "IF(", cond(Expr), ", ", expr(Yes), ", ", expr(No), ")".
  350
  351expr('*') --> "*".
  352
  353
  354% [121] builtin call
  355expr(str(V))       --> "STR(", object(V), ")".
  356expr(strlang(V,L))       --> "STRLANG(", object(V), ",", object(L), ")".
  357expr(lang(V))      --> "LANG(", object(V), ")".
  358expr(langmatches(V,W))      --> "LANGMATCHES(", object(V), ",", object(W), ")".
  359expr(datatype(V))      --> "DATATYPE(", object(V), ")".
  360expr(bound(V))      --> "BOUND(", object(V), ")".
  361expr(uri(V))       --> "URI(", expr(V), ")".
  362expr(iri(V))       --> "IRI(", expr(V), ")".
  363expr(rand)       --> "RAND()" .
  364expr(abs(V))       --> "ABS(", expr(V), ")".
  365expr(ceil(V))       --> "CEIL(", expr(V), ")".
  366expr(floor(V))       --> "FLOOR(", expr(V), ")".
  367expr(round(V))       --> "ROUND(", expr(V), ")".
  368
  369expr(str_before(Str,Sep)) --> "strBefore(", string_literal_expr(Str), ", ", string_literal_expr(Sep), ")".
  370expr(str_after(Str,Sep)) --> "strAfter(", string_literal_expr(Str), ", ", string_literal_expr(Sep), ")".
  371expr(concat(A,B)) --> "concat(", string_literal_expr(A), ", ", string_literal_expr(B), ")".
  372expr(strlen(V))       --> "STRLEN(", expr(V), ")".
  373expr(substr(V,W))     --> "SUBSTR(", expr(V), ", ", expr(W), ")". % [123]
  374expr(substr(V,W,X))   --> "SUBSTR(", expr(V), ", ", expr(W), ", ", expr(X), ")". % [123]
  375expr(replace(S,P,R)) --> "replace(", string_literal_expr(S), ", ", string_literal_expr(P), ", ", string_literal_expr(R), ")". % [124]
  376expr(replace(S,P,R,Z)) --> "replace(", string_literal_expr(S), ", ", string_literal_expr(P), ", ", string_literal_expr(R),
  377        ", ", string_literal_expr(Z), ")".                    % [124]
  378
  379expr(ucase(A)) --> "ucase(", string_literal_expr(A), ")".
  380expr(lcase(A)) --> "lcase(", string_literal_expr(A), ")".
  381
  382expr(lang(V))     --> "lang(", object(V), ")".
  383
  384% TODO more of 121
  385
  386expr(S)            --> {string(S)},"\"", at(S), "\"".
  387expr('^^'(S,T))    --> "\"", at(S), "\"^^", resource(T).
  388expr('@'(S,Lang))    --> "\"", at(S), "\"@", at(Lang).
  389expr(distinct(X))     --> "DISTINCT ", expr(X), " ".
  390expr(quote(V))     --> quote(at(V)).
  391
  392% [127] Aggregate
  393expr(max(X))   --> "max(", expr(X), ")".
  394expr(min(X))   --> "min(", expr(X), ")".
  395expr(sum(X))   --> "sum(", expr(X), ")".
  396expr(count(X))     --> "COUNT(", expr(X), ")".
  397expr(sample(X))     --> "SAMPLE(", expr(X), ")".
  398expr(group_concat(X))     --> "GROUP_CONCAT(", expr(X), ")".
  399expr(group_concat(X, S))     --> "GROUP_CONCAT(", expr(X), " ;  SEPARATOR = ", expr(S), ")".
  400
  401expr(+X) -->  p "+ ", expr(X), ")".
  402expr(-X) -->  p "- ", expr(X), ")".
  403expr(X+Y) --> p expr(X), " + ", expr(Y).
  404expr(X-Y) --> p expr(X), " - ", expr(Y).
  405expr(X*Y) --> p expr(X), " * ", expr(Y).
  406expr(X/Y) --> p expr(X), " / ", expr(Y).
  407expr((X,Y)) --> p expr(X), " ", expr(Y).
  408expr(X) --> {number(X)}, at(X).
  409expr(X) --> object(X).
  410
  411% https://www.w3.org/TR/sparql11-query/#pp-language
  412property(oneOrMore(R)) --> property(R),"+".
  413property(zeroOrMore(R)) --> property(R),"*".
  414property(zeroOrOne(R)) --> property(R),"?".
  415property(inverse(R)) --> "^", property(R).
  416property(\+R) --> "!(", property(R), ")".
  417property(\R) --> "^(", property(R), ")".
  418property(R1/R2) --> "(",property(R1),"/",property(R2),")".
  419property(R1|R2) --> "(",property(R1),"|",property(R2),")".
  420
  421property(R) --> resource(R).
  422
  423resource(R) --> variable(R).
  424resource(R) --> {rdf_global_id(R,RR)}, uri(RR).
  425
  426object(literal(Lit)) --> literal(Lit).
  427object('^^'(Val,Type)) --> quote(wr(Val)), "^^", resource(Type).
  428object('@'(Val,Lang)) --> quote(at(Val)), "@", at(Lang).
  429object(S) --> {string(S)}, quote(at(S)).
  430object(Resource) --> resource(Resource).
  431
  432% old-style literals
  433literal(lang(Lang,Val)) --> quote(at(Val)), "@", at(Lang).
  434literal(type(Type,Val)) --> quote(wr(Val)), "^^", resource(Type).
  435literal(Lit) --> {atomic(Lit)}, quote(at(Lit)).
  436
  437uri(U) --> {atom(U)}, "<", at(U), ">".
  438quote(P) --> "\"", escape_with(0'\\,0'",P), "\"".
  439variable(v(V))  --> "?", at(V).
  440variable(V)  --> {var_number(V,N)}, "?v", at(N).
  441variable('@'(V)) --> "_:", {atomic(V) -> N=V; var_number(V,N)}, at(N).
  442variable(@)  --> "[]"