All predicatesShow sourcesparql_grammar.pl -- SPARQL Parser

See also
- SPARQL 1.1 specification
- SPARQL test cases at http://www.w3.org/2009/sparql/docs/tests/
Source 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.
Source resolve_names(+Prolog, +Query0, -Query, +Options)[private]
Turn var(Name) into Prolog variables and resolve all IRIs to absolute IRIs.
Source resolve_datasets(+Raw, -IRIs, +State)[private]
TBD: what is the difference between named and non-named?
Source 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.

Source resolve_projection(+Proj0, -VarList, -ExprQuery, +State0, State)[private]
Return actual projection as a list of Name=Var
Arguments:
ExprQuery- is the query to resolve expressions that appear in the projection.
 resolve_construct_template(+Templ0, -Templ, -Q, +State)[private]
Deal with ORDER BY clause.
Source resolve_solutions(+Solutions0, -Solutions, -Q, +State0, -State)[private]
Source resolve_order_by(+OrderBy0, -OrderBy, -Q, +State0, -State)[private]
Source resolve_group_by(+Groups0, -Groups, -Q, +State0, -State)[private]
Source resolve_having(+Having0, -Having, -Q, +State0, -State)[private]
Source resolve_state(+Prolog, -State, +Options)[private]
Create initial state.
Source resolve_graph_term(+T0, -T, -Q, +State0, -State) is det[private]
Source resolve_graph_terms(+TList0, -TList, -Q, +State0, -State) is det[private]
Source resolve_triple(+Subj, +P, +O, -Q, +S0, -S)[private]
Source 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)
Source resolve_predicate(+P0, -P, +S0, -S) is det[private]
Source 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.
Source rdf_goal(+S, +P, +O, -RDF, +State)[private]
Optionally add graph to the rdf/3 statement.
Source 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]
Source resolve_expression(+E0, -E, -Q, +State0, -State)[private]
Source 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$'.
Source 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 *.
Source 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.
Source used_prefix(+P, !State) is det[private]
Keep track of the prefixes that are actually used to support service statements.
Source resolve_values(+Values0, -Values, +State) is det[private]
Resolve a list of values for the VALUES clause.
Source 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.
Source subquery_state(OuterState, SubState) is det[private]
Create an initial state for a subquery
Source join_subquery_projection(+Proj0, -Proj, +S0, -S) is det[private]
Link the projection variables of the inner query to the outer query.
Arguments:
Proj- is a list OuterVar=InnerVar
Source 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)
Source 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.
Source 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.
Source 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.
Source 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
Source service_prefixes(+State, -List:list(pair)) is det[private]
Obtain a list of Prefix-URL pairs for the prefixes used in State.
Source query(-Prologue, -Query)//[private]
Source 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.
Source uchar(-Code)//[private]
\uXXXX or \UXXXXXXXX, returning character value
Source 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.
Source base_decl(-Base:uri)// is semidet[private]
Match "base <URI>".
Source prefix_decl(-Prefix, +Base)// is semidet[private]
Process "prefix <qname> <URI>" into a term Qname-IRI
Source select_query(-Select)// is semidet[private]
Process "select ..." into a term

select(Projection, DataSets, Query, Solutions)

Source sub_select(-SubSelect)//[private]
Source 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 of bind(Expression, Var)
Source construct_query(-Construct)// is semidet[private]
Processes "construct ..." into a term

construct(Template, DataSets, Query, Solutions)

Source describe_query(-Describe)// is semidet[private]
Processes "describe ..." into a term

describe(Projection, DataSets, Query, Solutions)

Source ask_query(Query)//[private]
Source dataset_clause(-Src)//[private]
 default_graph_clause(-Src)[private]
Source named_graph_clause(Graph)//[private]
Source source_selector(-Src)//[private]
Source where_clause(-Pattern)//[private]
Source 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
Source group_clause(-Group)// is semidet[private]
Source as_expression(-Exp)// is det[private]
Processes '(' Expression ( 'AS' Var )? ')' into one of
  • bind(Expression, Var)
  • Expression
Source having_clause(-Having)// is semidet[private]
Source order_clause(-Order)//[private]
Source order_condition(-Order)//[private]
Source limit_clause(-Limit)//[private]
Source offset_clause(Offset)//[private]
Source values_clause(-Query)// is det[private]
Query is one of
  • var_in(Var, Values)
  • vars_in(ListOfVar, ListOfValues)
  • true
Source update_query(-UpdatedInfo)// is semidet[private]
True when input is a valid SPARQL update request.
Source update1(+Keyword, -UpdatedAction)// is semidet[private]
Source modify(-Updated)//[private]
Source quads(-Quads)//[private]
Quads is a list of triples and graph(Graph,Triples)
Source 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]
Source triples_template(-Triples, Tail)//[private]
Source group_graph_pattern(P)//[private]
Source group_graph_pattern_sub(P)//[private]
Source group_graph_pattern_sub_cont(+PLeft, P)//[private]
Matches ( GraphPatternNotTriples '.'? TriplesBlock? )*
Source triples_block(-Triples, ?Tail)//[private]
Source graph_pattern_not_triples(-Pattern)//[private]
Source optional_graph_pattern(Pattern)//[private]
Source graph_graph_pattern(-Graph)// is semidet[private]
Processes a "graph ..." clause into

graph(Graph, Pattern)

Source 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>
}
 bind(P)[private]
 inline_data(Data)[private]
Source group_or_union_graph_pattern(-Pattern)//[private]
Source filter(-Filter)//[private]
Source constraint(-Filter)//[private]
Source function_call(-Function)// is semidet[private]
Processes <URI>(Arg ...) into function(IRI, Args)
Source arg_list(-List)//[private]
Source optional_distinct(-WrappedValue, -RealValue)//[private]
Wrap argument in distinct(PlainArg) if there is a distinct keyword.
Source expression_list(-Expressions)//[private]
Source construct_template(Triples)// is semidet[private]
Source construct_triples(-List)//[private]
Source triples_same_subject(-List, ?Tail)//[private]
Return list of rdf(S,P,O) from triple spec.
Source property_list(-Properties, -Triples, ?TriplesTail)//[private]
Source property_list_not_empty(-Properties, -Triples, ?TriplesTail)//[private]
Source object_list(-L, -Triples, ?TriplesTail)//[private]
Source verb(-E)//[private]
Source 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.
Source verb_object_lists(-Properties, -Triples, ?Tail)// is det[private]
Parses ( ';' ( ( VerbPath | VerbSimple ) ObjectList )? )*
 path_elt(PathElt)[private]
One of [?*+=](PathPrimary)
Source path_primary(-PathPrimary)//[private]
Source triples_node(-Subj, -Triples, ?TriplesTail)//[private]
Source blank_node_property_list(-Subj, -Triples, ?TriplesTail)//[private]
Source triples_node_path(-Subj, -Triples, ?Tail)//[private]
Source blank_node_property_list_path(-Subj, -Triples, ?TriplesTail)//[private]
Source collection(-Subj, -Triples, ?Tail)//[private]
Source collection_path(-Subj, -Triples, ?Tail)//[private]
Source graph_node(E, -Triples, ?TriplesTail)//[private]
Source graph_node_path(Node, Triples, Tail)//[private]
Source var_or_term(-E)//[private]
Source var_or_iri_ref(-E)//[private]
Source var(-Var)//[private]
Source graph_term(-T)//[private]
Source expression(-E)//[private]
Source conditional_or_expression(-E)//[private]
Source conditional_and_expression(-E)//[private]
Source value_logical(-E)//[private]
Source relational_expression(E)//[private]
Source numeric_expression(-E)//[private]
Source additive_expression(-E)//[private]
Source multiplicative_expression(-E)//[private]
Source unary_expression(-E)//[private]
Source primary_expression(-E)//[private]
Source bracketted_expression(-E)//[private]
Source built_in_call(-Call)//[private]
Source built_in_function(?Term) is nondet[private]
Fact that describes defined builtin functions. Used by resolve_expression/4.
Source regex_expression(-Regex)//[private]
Source substring_expression(Expr)//[private]
Source must_see_comma// is det[private]
Source must_see_open_bracket// is det[private]
Source must_see_close_bracket// is det[private]
Source must_see_punct(+C)// is det[private]
Demand punctuation. Throw a syntax error if the demanded punctiation is not present.
Source str_replace_expression(Expr)//[private]
Source exists_func(F)//[private]
Source aggregate_call(+Keyword, -Aggregate)//[private]
Renamed from aggregate to avoid confusion with popular predicate.
Source aggregate_op(?Op) is nondet[private]
Declaration to support resolving aggregates
Source iri_ref_or_function(-Term)//[private]
Source rdf_literal(-Literal)//[private]
Source 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.

Source boolean_literal(-TrueOrFalse)//[private]
Source string(-Atom)//[private]
Source iri_ref(IRI)//[private]
Source qname(-Term)//[private]
TBD: Looks like this is ambiguous!?
Source blank_node(-Id)//[private]
Blank node. Anonymous blank nodes are returned with unbound Id
Source q_iri_ref(-Atom)//[private]
Source qname_ns(Q)//[private]
Source blank_node_label(-Bnode)// is semidet[private]
Processes "_:..." into a bnode(Name) term.
Source var1(-Atom)// is semidet[private]
Source var2(-Atom)// is semidet[private]
Source langtag(-Tag)//[private]
Return language tag (without leading @)
Source integer(-Integer)// is semidet[private]
Match an integer and return its value.
Source integer_string(-Codes)// is semidet[private]
Extract integer value.
Source decimal_string(-Codes)//[private]
Extract float without exponent and return the matched text as a list of codes.
Source double_string(-Codes)// is semidet[private]
Extract a float number with exponent and return the result as a list of codes.
Source exponent(-Codes, ?Tail)//[private]
Float exponent. Returned as difference-list
Source string_literal1(-Atom)//[private]
Source string_literal2(-Atom)//[private]
Source string_literal_long1(-Atom)//[private]
Source string_literal_long2(-Atom)//[private]
Source echar(-Code)//[private]
Escaped character
Source hex(-Weigth)//[private]
HEX digit (returning numeric value)
Source nil(-NIL)//[private]
End-of-collection (rdf:nil)
Source pn_chars_base(-Code)//[private]
Basic identifier characters
Source pn_chars_u(?Code)[private]
Allows for _
Source varname(-Atom)//[private]
Name of a variable (after the ? or $)
Source ncname_prefix(-Atom)//[private]
Source 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