sparql_grammar.pl -- SPARQL Parser
- sparql_parse(+SPARQL, -Query, +Options)
- Parse the SPARQL statement Input into a Prolog representation.
Based on "SPARQL Query Language for RDF", April 6, 2006. Options
supported:
- base_uri(+Base)
- Base used if there is no BASE clause in the query.
- variable_names(+VarDict)
- Prolog Name=Var list to use as initial binding list. This option is used to support SPARQL Quasi Quotations.
- resolve_names(+Prolog, +Query0, -Query, +Options)[private]
- Turn
var(Name)
into Prolog variables and resolve all IRIs to absolute IRIs. - resolve_datasets(+Raw, -IRIs, +State)[private]
- TBD: what is the difference between named and non-named?
- resolve_query(+Q0, -Q, +State0, -State)[private]
- Create the initial translation from the output of the parser to
a Prolog query. Constructs in the output are:
- (Qa,Qb)
- (Qa;Qb)
- (Q*->true;true)
rdf(S,P,O)
rdf(S,P,O,G:_)
.sparql_true(Expression)
sparql_eval(Expression, Value)
Note that an rdf/3 object can be
literal(plain(X), X)
to demand an unqualified literal. - resolve_projection(+Proj0, -VarList, -ExprQuery, +State0, State)[private]
- Return actual projection as a list of Name=Var
- resolve_construct_template(+Templ0, -Templ, -Q, +State)[private]
- Deal with ORDER BY clause.
- resolve_solutions(+Solutions0, -Solutions, -Q, +State0, -State)[private]
- resolve_order_by(+OrderBy0, -OrderBy, -Q, +State0, -State)[private]
- resolve_group_by(+Groups0, -Groups, -Q, +State0, -State)[private]
- resolve_having(+Having0, -Having, -Q, +State0, -State)[private]
- resolve_state(+Prolog, -State, +Options)[private]
- Create initial state.
- resolve_graph_term(+T0, -T, -Q, +State0, -State) is det[private]
- resolve_graph_terms(+TList0, -TList, -Q, +State0, -State) is det[private]
- resolve_triple(+Subj, +P, +O, -Q, +S0, -S)[private]
- resolve_path(+P, +Subj, +Obj, -Q, +S0, -S) is det[private]
- Translate a property path expression into a goal.
- The argument of ! is a list of IRIs and ^(IRI)
- resolve_predicate(+P0, -P, +S0, -S) is det[private]
- resolve_negated_property_set(+PSet, -NegSet, -RevSet, +S) is det[private]
- True when NegSet is the set of forward negated properties in PSet and RevSet is the set of backward negated properties.
- rdf_goal(+S, +P, +O, -RDF, +State)[private]
- Optionally add graph to the rdf/3 statement.
- rdf_goal_object(+ObjIn, -ObjGoal) is det[private]
- Note that in SPARQL plain literals (e.g., "hello") only match
literals that have neither a language nor a type-qualifier. The
SemWeb library introduced
rdf(S,P,literal(plain(X), X))
for this purpose. - mkcollection(+Members, -CollectionSubject, -Triples)[private]
- resolve_expression(+E0, -E, -Q, +State0, -State)[private]
- resolve_var(+Name, -Var, +State0, ?State)[private]
- Resolve a variable. If State0 == State and it concerns a new variable the variable is bound to '$null$'.
- resolve_var_invisible(Name, -Var, +State0, ?State)[private]
- Similar to resolve_var/4, but does not add the variable to the set of variables visible in the projection if this is *.
- resolve_iri(+Spec, -IRI:atom, +State) is det[private]
- Translate Spec into a fully expanded IRI as used in RDF-DB. Note that we must expand %xx sequences here.
- used_prefix(+P, !State) is det[private]
- Keep track of the prefixes that are actually used to support service statements.
- resolve_values(+Values0, -Values, +State) is det[private]
- Resolve a list of values for the VALUES clause.
- resolve_bnodes(+Pattern0, -Pattern)[private]
- Blank nodes are scoped into a basic graph pattern (i.e. within
{...}). The code below does a substitution of
bnode(X)
to variables in an arbitrary term. - subquery_state(OuterState, SubState) is det[private]
- Create an initial state for a subquery
- join_subquery_projection(+Proj0, -Proj, +S0, -S) is det[private]
- Link the projection variables of the inner query to the outer query.
- resolve_updates(+UpdatesIn, -UpdatesOut, +StateIn, -StateOut)[private]
- Resolve update requests. Each update is expressed by one of the
following terms:
- insert_data(+Quads)
- Insert Quads. Quads is a list of rdf/3 or rdf/4 terms.
- delete_data(+Quads)
- Delete Quads. Quads is a list of rdf/3 or rdf/4 terms.
- delete_where(+Quads)
- Delete Quads. Quads is a list of rdf/3 or rdf/4 terms.
- add(+Silent, +FromGraph, +ToGraph)
- Copy all triples from FromGraph to ToGraph
- create(+Silent, +Graph)
- Create an empty graph
- modify(WithIRI, +InsDel, +Using, -Query)
- load(+Silent, +IRI, +Graph)
- resolve_quads(+Quads, -Query, +State0, -State) is det[private]
- This seems to be the same as resolve_query/4. It does a bit more, but that should not harm us. The output is a conjunction, which we do not want, so we convert it back into a list.
- steadfast(Q0, Q) is det[private]
- Make Q0 steadfast. The problem is that the SPARQL semantics assume bottom-up evaluation. Top-down evaluation yields the same result as long as the code is steadfast. Unfortunately, some queries are not. This applies notably to expression evaluation in BIND. We fix this by rewriting copying non-stead-fast parts of the query and a post-execution unification.
- compile_expression(+Expression, -Var, -Goal, +State0, -State)[private]
- Compile an expression into a (compound) goal that evaluates to the variable var. This version is not realy compiling. Its just the entry point for a future compiler.
- service_state(+S0, -S)[private]
- Make a resolver state for a SERVICE. We want to know
- The prefixes used by the service query
- The projection variables of the service query
- service_prefixes(+State, -List:list(pair)) is det[private]
- Obtain a list of Prefix-URL pairs for the prefixes used in State.
- query(-Prologue, -Query)//[private]
- unescape_code_points(-Unescaped)//[private]
- According to the SPARQL grammar, any code point may be escaped using \uXXXX or \UXXXXXXXX anywhere and must be decoded first.
- uchar(-Code)//[private]
- \uXXXX or \UXXXXXXXX, returning character value
- prologue(-Decls)//[private]
- The Prologue consists of zero or more BASE and PREFIX declarations. The result is the last BASE declaration and each PREFIX is resolved against the last preceeding BASE declaration.
- base_decl(-Base:uri)// is semidet[private]
- Match "base <URI>".
- prefix_decl(-Prefix, +Base)// is semidet[private]
- Process "prefix <qname> <URI>" into a term Qname-IRI
- select_query(-Select)// is semidet[private]
- Process "select ..." into a term
select(Projection, DataSets, Query, Solutions)
- sub_select(-SubSelect)//[private]
- select_projection(-Projection)// is det[private]
- Process the projection of a select query. Projection is one of
- *
- List of variables
projection(ListOfVars, Binding)
Where Binding is a conjunction ofbind(Expression, Var)
- construct_query(-Construct)// is semidet[private]
- Processes "construct ..." into a term
construct(Template, DataSets, Query, Solutions)
- describe_query(-Describe)// is semidet[private]
- Processes "describe ..." into a term
describe(Projection, DataSets, Query, Solutions)
- ask_query(Query)//[private]
- dataset_clause(-Src)//[private]
- default_graph_clause(-Src)[private]
- named_graph_clause(Graph)//[private]
- source_selector(-Src)//[private]
- where_clause(-Pattern)//[private]
- solution_modifier(-Solutions)// is det[private]
- Processes order by, limit and offet clauses into a term
solutions(Group, Having, Order, Limit, Offset)
Where
- Group
- Having
- Order
- Limit
- Offset
- group_clause(-Group)// is semidet[private]
- as_expression(-Exp)// is det[private]
- Processes '(' Expression ( 'AS' Var )? ')' into one of
bind(Expression, Var)
- Expression
- having_clause(-Having)// is semidet[private]
- order_clause(-Order)//[private]
- order_condition(-Order)//[private]
- limit_clause(-Limit)//[private]
- offset_clause(Offset)//[private]
- values_clause(-Query)// is det[private]
- Query is one of
var_in(Var, Values)
vars_in(ListOfVar, ListOfValues)
- true
- update_query(-UpdatedInfo)// is semidet[private]
- True when input is a valid SPARQL update request.
- update1(+Keyword, -UpdatedAction)// is semidet[private]
- modify(-Updated)//[private]
- quads(-Quads)//[private]
- Quads is a list of triples and
graph(Graph,Triples)
- data_block(-DataBlock)// is det[private]
- DataBlock is one of
var_in(Var, ListOfValues)
vars_in(Vars, ListOfValues)
- minus_graph_pattern(-Pattern) is det[private]
- triples_template(-Triples, Tail)//[private]
- group_graph_pattern(P)//[private]
- group_graph_pattern_sub(P)//[private]
- group_graph_pattern_sub_cont(+PLeft, P)//[private]
- Matches ( GraphPatternNotTriples '.'? TriplesBlock? )*
- triples_block(-Triples, ?Tail)//[private]
- graph_pattern_not_triples(-Pattern)//[private]
- optional_graph_pattern(Pattern)//[private]
- graph_graph_pattern(-Graph)// is semidet[private]
- Processes a "graph ..." clause into
graph(Graph, Pattern)
- service_graph_pattern(-P)//[private]
- Process a federated query. We need to find three things
- If there is a
SELECT
, the variables exposed through the projection, otherwise, the default * projection variables. - What prefixes are required to execute the query?
We issue the following query on the remote service:
PREFIX ... SELECT ?out1,?out2,... WHERE { BIND(in1 as ?v1) BIND(in2 as ?v2) ... <Original query> }
- If there is a
- bind(P)[private]
- inline_data(Data)[private]
- group_or_union_graph_pattern(-Pattern)//[private]
- filter(-Filter)//[private]
- constraint(-Filter)//[private]
- function_call(-Function)// is semidet[private]
- Processes <URI>(Arg ...) into
function(IRI, Args)
- arg_list(-List)//[private]
- optional_distinct(-WrappedValue, -RealValue)//[private]
- Wrap argument in
distinct(PlainArg)
if there is adistinct
keyword. - expression_list(-Expressions)//[private]
- construct_template(Triples)// is semidet[private]
- construct_triples(-List)//[private]
- triples_same_subject(-List, ?Tail)//[private]
- Return list of
rdf(S,P,O)
from triple spec. - property_list(-Properties, -Triples, ?TriplesTail)//[private]
- property_list_not_empty(-Properties, -Triples, ?TriplesTail)//[private]
- object_list(-L, -Triples, ?TriplesTail)//[private]
- verb(-E)//[private]
- triples_same_subject_path(-Triples, ?Tail)//[private]
- Similar to triples_same_subject//2, but the resulting property of each triple can be a path expression.
- verb_object_lists(-Properties, -Triples, ?Tail)// is det[private]
- Parses ( ';' ( ( VerbPath | VerbSimple ) ObjectList )? )*
- path_elt(PathElt)[private]
- One of [?*+=](PathPrimary)
- path_primary(-PathPrimary)//[private]
- triples_node(-Subj, -Triples, ?TriplesTail)//[private]
- blank_node_property_list(-Subj, -Triples, ?TriplesTail)//[private]
- triples_node_path(-Subj, -Triples, ?Tail)//[private]
- blank_node_property_list_path(-Subj, -Triples, ?TriplesTail)//[private]
- collection(-Subj, -Triples, ?Tail)//[private]
- collection_path(-Subj, -Triples, ?Tail)//[private]
- graph_node(E, -Triples, ?TriplesTail)//[private]
- graph_node_path(Node, Triples, Tail)//[private]
- var_or_term(-E)//[private]
- var_or_iri_ref(-E)//[private]
- var(-Var)//[private]
- graph_term(-T)//[private]
- expression(-E)//[private]
- conditional_or_expression(-E)//[private]
- conditional_and_expression(-E)//[private]
- value_logical(-E)//[private]
- relational_expression(E)//[private]
- numeric_expression(-E)//[private]
- additive_expression(-E)//[private]
- multiplicative_expression(-E)//[private]
- unary_expression(-E)//[private]
- primary_expression(-E)//[private]
- bracketted_expression(-E)//[private]
- built_in_call(-Call)//[private]
- built_in_function(?Term) is nondet[private]
- Fact that describes defined builtin functions. Used by resolve_expression/4.
- regex_expression(-Regex)//[private]
- substring_expression(Expr)//[private]
- must_see_comma// is det[private]
- must_see_open_bracket// is det[private]
- must_see_close_bracket// is det[private]
- must_see_punct(+C)// is det[private]
- Demand punctuation. Throw a syntax error if the demanded punctiation is not present.
- str_replace_expression(Expr)//[private]
- exists_func(F)//[private]
- aggregate_call(+Keyword, -Aggregate)//[private]
- Renamed from
aggregate
to avoid confusion with popular predicate. - aggregate_op(?Op) is nondet[private]
- Declaration to support resolving aggregates
- iri_ref_or_function(-Term)//[private]
- rdf_literal(-Literal)//[private]
- numeric_literal(-Number)//[private]
- Match a literal value and return it as a term
literal(type(Type, Atom))
Where Type is one of xsd:double, xsd:decimal or xsd:integer and Atom is the matched text. The value cannot always be obtained using atom_number/2 because floats and decimals can start or end with a '.', something which is not allowed in Prolog.
- boolean_literal(-TrueOrFalse)//[private]
- string(-Atom)//[private]
- iri_ref(IRI)//[private]
- qname(-Term)//[private]
- TBD: Looks like this is ambiguous!?
- blank_node(-Id)//[private]
- Blank node. Anonymous blank nodes are returned with unbound Id
- q_iri_ref(-Atom)//[private]
- qname_ns(Q)//[private]
- blank_node_label(-Bnode)// is semidet[private]
- Processes "_:..." into a
bnode(Name)
term. - var1(-Atom)// is semidet[private]
- var2(-Atom)// is semidet[private]
- langtag(-Tag)//[private]
- Return language tag (without leading @)
- integer(-Integer)// is semidet[private]
- Match an integer and return its value.
- integer_string(-Codes)// is semidet[private]
- Extract integer value.
- decimal_string(-Codes)//[private]
- Extract float without exponent and return the matched text as a list of codes.
- double_string(-Codes)// is semidet[private]
- Extract a float number with exponent and return the result as a list of codes.
- exponent(-Codes, ?Tail)//[private]
- Float exponent. Returned as difference-list
- string_literal1(-Atom)//[private]
- string_literal2(-Atom)//[private]
- string_literal_long1(-Atom)//[private]
- string_literal_long2(-Atom)//[private]
- echar(-Code)//[private]
- Escaped character
- hex(-Weigth)//[private]
- HEX digit (returning numeric value)
- nil(-NIL)//[private]
- End-of-collection (rdf:nil)
- pn_chars_base(-Code)//[private]
- Basic identifier characters
- pn_chars_u(?Code)[private]
- Allows for _
- varname(-Atom)//[private]
- Name of a variable (after the ? or $)
- ncname_prefix(-Atom)//[private]
- pn_local(-Atom)//[private]
- keyword(+Codes)[private]
- Case-insensitive match for a keyword.
- must_see_keyword(+Codes)[private]
- get_keyword(-Atom)[private]
- Get next identifier as lowercase