- rdf_atom_term(+Atom:atom, +Term:rdf_term) is semidet
- rdf_atom_term(+Atom:atom, -Term:rdf_term) is semidet
- rdf_atom_term(-Atom:atom, +Term:rdf_term) is semidet
- Parses the given Atom in order to extract the encoded RDF Term. The
following syntactic forms are supported:
- RDF terms defined by the N-Triples 1.1 grammar (blank nodes,
IRIs, and literals).
- Turtle 1.1 prefix notation for IRIs.
- throws
- - syntax_error if Atom cannot be parsed as a term in
Turtle-family notation.
- - type_error if the Turtle-family notation for Term cannot be
generated.
- rdf_base_uri(+BaseUri:atom) is semidet
- rdf_base_uri(-BaseUri:atom) is det
- rdf_canonical_lexical_form(+Datatype:iri, +Lex:atom, -CanonicaldLex:atom) is det
- rdf_canonical_literal(+Literal:rdf_literal, -CanonicaldLiteral:rdf_literal) is det
- rdf_container_membership_property(+P:rdf_predicate) is semidet
- rdf_container_membership_property(-P:rdf_predicate) is multi
- rdf_container_membership_property(+P:rdf_predicate, +N:positive_integer) is semidet
- rdf_container_membership_property(+P:rdf_predicate, -N:positive_integer) is det
- rdf_container_membership_property(-P:rdf_predicate, +N:positive_integer) is det
- rdf_container_membership_property(-P:rdf_predicate, -N:positive_integer) is multi
- True when Property is the Nth container membership property.
Success of this goal does not imply that Property is present in the
database.
- rdf_create_iri(+Alias, +Terms:list(term), -Iri:atom) is det
- rdf_hash_iri(+Alias:atom, +Term:term, -Iri:atom) is det
- rdf_iri(+Iri:atom)//
- rdf_iri(-Iri:atom)//
- Generates or parses an IRI in Turtle-family notation.
- rdf_is_bnode_iri(@Term) is semidet
- rdf_is_literal_dwim(+DWIM:term) is semidet
- rdf_is_name(@Term) is semidet
- rdf_is_numeric_literal(@Term) is semidet
- rdf_is_object(@Term) is semidet
- rdf_is_skip_node(@Term) is semidet
- rdf_is_term(@Term) is semidet
- rdf_language_tagged_string(+LTag:atom, +Lex:atom, -Literal:rdf_literal) is det
- rdf_language_tagged_string(-LTag:atom, -Lex:atom, +Literal:rdf_literal) is det
- rdf_lexical_value(+Datatype:atom, +Lex:atom, -Value:term) is det
- rdf_lexical_value(+Datatype:atom, -Lex:atom, +Value:term) is det
- Translate between a value (`Value') and its serialization, according
to a given datatype IRI (`Datatype'), into a lexical form (`Lex').
- rdf_literal(+Literal:rdf_literal)//
- rdf_literal(-Literal:rdf_literal)//
- Generates or parses a literal in Turtle-family notation.
- rdf_literal(+Datatype:atom, +LTag:atom, +Lex:atom, -Literal:rdf_literal) is det
- rdf_literal(-Datatype:atom, -LTag:atom, -Lex:atom, +Literal:rdf_literal) is det
- Compose/decompose literals.
- rdf_literal_datatype_iri(+Literal:rdf_literal, +Datatype:atom) is semidet
- rdf_literal_datatype_iri(+Literal:rdf_literal, -Datatype:atom) is det
- rdf_literal_dwim(+DWIM, +Literal:rdf_literal) is semidet
- rdf_literal_dwim(+DWIM, -Literal:rdf_literal) is det
- Allows literal terms to be created based on various simplified
inputs:
Input format | Datatype IRI |
-----------------------------+------------------------ |
boolean(Lex) | xsd:boolean |
date(Y,Mo,Da) | xsd:date |
date_time(Y,Mo,D,H,Mi,S) | xsd:dateTime |
date_time(Y,Mo,D,H,Mi,S,TZ) | xsd:dateTime |
day(Da) | xsd:gDay |
decimal(N) | xsd:decimal |
double(N) | xsd:double |
duration(S) | xsd:dayTimeDuration |
duration(Mo,S) | xsd:duration |
float | xsd:double |
float(N) | xsd:float |
integer | xsd:integer |
integer(N) | xsd:integer |
literal(lang(LTag,Lex)) | rdf:langString |
literal(type(Datatype,Lex)) | Datatype |
literal(Lex) | xsd:string |
month(Mo) | xsd:gMonth |
month_day(Mo,Da) | xsd:gMonthDay |
nonneg(N) | xsd:nonNegativeInteger |
oneof([false,true]) | xsd:boolean |
pair(string,list(atom)) | rdf:langString |
positive_integer(N) | xsd:positiveInteger |
shape(Z,LRS,CRS,Shape) | geo:wktLiteral |
string | xsd:string |
string(atom) | xsd:string |
time(H,Mi,S) | xsd:time |
uri(Uri) | xsd:anyURI |
year(Y) | xsd:gYear |
year_month(Y,Mo) | xsd:gYearMonth |
- rdf_literal_lexical_form(+Literal:rdf_literal, +Lex:atom) is semidet
- rdf_literal_lexical_form(+Literal:rdf_literal, -Lex:atom) is det
- rdf_literal_value(+Literal:rdf_literal, -Value:term) is det
- rdf_literal_value(+Literal:rdf_literal, -Datatype:atom, -Value:term) is det
- rdf_literal_value(-Literal:rdf_literal, +Datatype:atom, +Value:term) is det
- Notice that languages-tagged strings do not have a value.
- rdf_name_string(+Name:rdf_name, -String:string) is semidet
- Tries to return a readable String for the given RDF Term.
- rdf_object_dwim(+DWIM, +Term:rdf_term) is semidet
- rdf_object_dwim(+DWIM, -Term:rdf_term) is det
- Supports the Input formats of rdf_literal_dwim/2.
- rdf_predicate_dwim(+DWIM, -Predicate:rdf_predicate) is det
- rdf_term(+Term:rdf_term)//
- rdf_term(-Term:rdf_term)//
- Generates or parses a term in Turtle-family notation.
- rdf_term_to_string(+Term:rdf_term, -String:string) is det
- Use rdf_atom_term/2 when the serialization must be read back later.
- rdf_triple_term(+Triple:rdf_triple, +Term:rdf_term) is semidet
- rdf_triple_term(+Triple:rdf_triple, -Term:rdf_term) is multi
- rdf_typed_literal(+Datatype:atom, +Lex:atom, -Literal:rdf_literal) is det
- rdf_typed_literal(-Datatype:atom, -Lex:atom, +Literal:rdf_literal) is det
- tp_object_dwim(+DWIM:term, -O:rdf_object) is det
- tp_predicate_dwim(+DWIM:term, -P:rdf_predicate) is det
- well_known_iri(-Iri:atom) is det
- well_known_iri(+Segments:list(atom), +Iri:atom) is semidet
- well_known_iri(+Segments:list(atom), -Iri:atom) is det
- well_known_iri(-Segments:list(atom), +Iri:atom) is det
Re-exported predicates
The following predicates are re-exported from other modules
- rdf_is_bnode(+Id)
- Tests if a resource is a blank node (i.e. is an anonymous
resource). A blank node is represented as an atom that starts
with
_:
. For backward compatibility reason, __
is also
considered to be a blank node.
- See also
- - rdf_bnode/1.
- rdf_is_literal(@Term) is semidet
- True if Term is an RDF literal object. Currently only checks for
groundness and the literal functor.
- rdf_create_bnode(--BNode)
- Create a new BNode. A blank node is an atom starting with
_:
. Blank nodes generated by this predicate are of the form
_:genid
followed by a unique integer.
- rdf_default_graph(-Graph) is det
- rdf_default_graph(-Old, +New) is det
- Query/set the notion of the default graph. The notion of the
default graph is local to a thread. Threads created inherit the
default graph from their creator. See set_prolog_flag/2.
- rdf_is_iri(@IRI) is semidet
- True if IRI is an RDF IRI term.
For performance reasons, this does not check for compliance to
the syntax defined in RFC
3987. This checks
whether the term is (1) an atom and (2) not a blank node
identifier.
Success of this goal does not imply that the IRI is present in
the database (see rdf_iri/1 for that).
- rdf_is_predicate(@Term) is semidet
- True if Term can appear in the predicate position of a triple.
Success of this goal does not imply that the predicate term is
present in the database (see rdf_predicate/1 for that).
Since only IRIs can appear in the predicate position, this is
equivalent to rdf_is_iri/1.
- rdf_is_subject(@Term) is semidet
- True if Term can appear in the subject position of a triple.
Only blank nodes and IRIs can appear in the subject position.
Success of this goal does not imply that the subject term is
present in the database (see rdf_subject/1 for that).
Since blank nodes are represented by atoms that start with
`_:` and an IRIs are atoms as well, this is equivalent to
atom(Term)
.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- rdf_literal_value(Arg1, Arg2, Arg3)