View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2013-2022, University of Amsterdam
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(turtle,
   38          [ rdf_load_turtle/3,                  % +Input, -Triples, +Options
   39            rdf_read_turtle/3,                  % +Input, -Triples, +Options
   40            rdf_process_turtle/3,               % +Input, :OnObject, +Options
   41                                                % re-exports
   42            rdf_save_turtle/2,                  % +File, +Options
   43            rdf_save_canonical_turtle/2,        % +File, +Options
   44            rdf_save_trig/2,                    % +File, +Options
   45            rdf_save_canonical_trig/2,          % +File, +Options
   46            rdf_save_ntriples/2                 % +File, +Options
   47          ]).   48:- use_module(library(semweb/rdf_turtle_write)). % re-exports
   49:- if(exists_source(library(semweb/rdf_db))).   50:- use_module(library(semweb/rdf_db),
   51              [rdf_transaction/2,rdf_set_graph/2,rdf_assert/4]).   52:- endif.   53
   54:- autoload(library(memfile),
   55	    [atom_to_memory_file/2,open_memory_file/4]).   56:- autoload(library(option),[option/3,option/2]).   57:- autoload(library(uri),
   58	    [uri_file_name/2,uri_is_global/1,uri_normalized/2]).   59:- autoload(library(http/http_open),[http_open/3]).   60
   61% re-exports
   62:- meta_predicate
   63    rdf_process_turtle(+,2,+).   64
   65:- predicate_options(rdf_load_turtle/3, 3,
   66                     [pass_to(rdf_read_turtle/3, 3)]).   67:- predicate_options(rdf_process_turtle/3, 3,
   68                     [ anon_prefix(atom),
   69                       base_uri(atom),
   70                       base_used(-atom),
   71                       db(atom),
   72                       error_count(-integer),
   73                       namespaces(-list),
   74                       on_error(oneof([warning,error])),
   75                       prefixes(-list),
   76                       resources(oneof([uri,iri]))
   77                     ]).   78:- predicate_options(rdf_read_turtle/3, 3,
   79                     [ anon_prefix(atom),
   80                       base_uri(atom),
   81                       base_used(-atom),
   82                       db(atom),
   83                       error_count(-integer),
   84                       namespaces(-list),
   85                       on_error(oneof([warning,error])),
   86                       prefixes(-list),
   87                       resources(oneof([uri,iri]))
   88                     ]).   89
   90:- use_foreign_library(foreign(turtle)).   91:- public                               % used by the writer
   92    turtle_pn_local/1,
   93    turtle_write_quoted_string/2,
   94    turtle_write_uri/2.

Turtle: Terse RDF Triple Language

This module implements the Turtle language for representing the RDF triple model as defined by Dave Beckett from the Institute for Learning and Research Technology University of Bristol and later standardized by the W3C RDF working group.

This module acts as a plugin to rdf_load/2, for processing files with one of the extensions .ttl or .n3.

See also
- http://www.w3.org/TR/turtle/ (used W3C Recommendation 25 February 2014) */
 rdf_read_turtle(+Input, -Triples, +Options)
Read a stream or file into a set of triples or quadruples (if faced with TriG input) of the format
rdf(Subject, Predicate, Object [, Graph])

The representation is consistent with the SWI-Prolog RDF/XML and ntriples parsers. Provided options are:

base_uri(+BaseURI)
Initial base URI. Defaults to file://<file> for loading files.
anon_prefix(+Prefix)
Blank nodes are generated as <Prefix>1, <Prefix>2, etc. If Prefix is not an atom blank nodes are generated as node(1), node(2), ...
format(+Format)
One of auto (default), turtle or trig. The auto mode switches to TriG format of there is a { before the first triple. Finally, of the format is explicitly stated as turtle and the file appears to be a TriG file, a warning is printed and the data is loaded while ignoring the graphs.
resources(URIorIRI)
Officially, Turtle resources are IRIs. Quite a few applications however send URIs. By default we do URI->IRI mapping because this rarely causes errors. To force strictly conforming mode, pass iri.
prefixes(-Pairs)
Return encountered prefix declarations as a list of Alias-URI
namespaces(-Pairs)
Same as prefixes(Pairs). Compatibility to rdf_load/2.
base_used(-Base)
Base URI used for processing the data. Unified to [] if there is no base-uri.
on_error(+ErrorMode)
In warning (default), print the error and continue parsing the remainder of the file. If error, abort with an exception on the first error encountered.
error_count(-Count)
If on_error(warning) is active, this option cane be used to retrieve the number of generated errors.
Arguments:
Input- is one of stream(Stream), atom(Atom), a http, https or file url or a filename specification as accepted by absolute_file_name/3.
  167rdf_read_turtle(In, Triples, Options) :-
  168    base_uri(In, BaseURI, Options),
  169    setup_call_cleanup(
  170        ( open_input(In, Stream, Close),
  171          create_turtle_parser(Parser, Stream,
  172                               [ base_uri(BaseURI)
  173                               | Options
  174                               ])
  175        ),
  176        ( turtle_parse(Parser, Triples,
  177                       [ parse(document)
  178                       | Options
  179                       ]),
  180          post_options(Parser, Options)
  181        ),
  182        ( destroy_turtle_parser(Parser),
  183          call(Close)
  184        )).
 rdf_load_turtle(+Input, -Triples, +Options)
deprecated
- Use rdf_read_turtle/3
  190rdf_load_turtle(Input, Triples, Options) :-
  191    rdf_read_turtle(Input, Triples, Options).
 rdf_process_turtle(+Input, :OnObject, +Options) is det
Streaming Turtle parser. The predicate rdf_process_turtle/3 processes Turtle data from Input, calling OnObject with a list of triples for every Turtle statement found in Input. OnObject is called as below, where ListOfTriples is a list of rdf(S,P,O) terms for a normal Turtle file or rdf(S,P,O,G) terms if the GRAPH keyword is used to associate a set of triples in the document with a particular graph. The Graph argument provides the default graph for storing the triples and Line is the line number where the statement started.
call(OnObject, ListOfTriples, Graph:Line)

This predicate supports the same Options as rdf_load_turtle/3.

Errors encountered are sent to print_message/2, after which the parser tries to recover and parse the remainder of the data.

See also
- This predicate is normally used by load_rdf/2 for processing RDF data.
  218rdf_process_turtle(In, OnObject, Options) :-
  219    base_uri(In, BaseURI, Options),
  220    option(graph(Graph), Options, BaseURI),
  221    setup_call_cleanup(
  222        ( open_input(In, Stream, Close),
  223          create_turtle_parser(Parser, Stream, Options)
  224        ),
  225        ( process_turtle(Parser, Stream, OnObject, Graph,
  226                         [ parse(statement)
  227                         ]),
  228          post_options(Parser, Options)
  229        ),
  230        ( destroy_turtle_parser(Parser),
  231          call(Close)
  232        )).
  233
  234post_options(Parser, Options) :-
  235    prefix_option(Parser, Options),
  236    namespace_option(Parser, Options),
  237    base_option(Parser, Options),
  238    error_option(Parser, Options).
  239
  240prefix_option(Parser, Options) :-
  241    (   option(prefixes(Pairs), Options)
  242    ->  turtle_prefixes(Parser, Pairs)
  243    ;   true
  244    ).
  245namespace_option(Parser, Options) :-
  246    (   option(namespaces(Pairs), Options)
  247    ->  turtle_prefixes(Parser, Pairs)
  248    ;   true
  249    ).
  250base_option(Parser, Options) :-
  251    (   option(base_used(Base), Options)
  252    ->  turtle_base(Parser, Base)
  253    ;   true
  254    ).
  255error_option(Parser, Options) :-
  256    (   option(error_count(Count), Options)
  257    ->  turtle_error_count(Parser, Count)
  258    ;   true
  259    ).
  260
  261
  262process_turtle(_Parser, Stream, _OnObject, _Graph, _Options) :-
  263    at_end_of_stream(Stream),
  264    !.
  265process_turtle(Parser, Stream, OnObject, Graph, Options) :-
  266    stream_pair(Stream, In, _),
  267    line_count(In, LineNo),
  268    turtle_parse(Parser, Triples,
  269                 [ parse(statement)
  270                 | Options
  271                 ]),
  272    call(OnObject, Triples, Graph:LineNo),
  273    process_turtle(Parser, Stream, OnObject, Graph, Options).
 open_input(+Input, -Stream, -Close) is det
Open given input.
Arguments:
Close- goal to undo the open action
Errors
- existence_error, permission_error
To be done
- Synchronize with input handling of rdf_db.pl.
  284open_input(stream(Stream), Stream, Close) :-
  285    !,
  286    stream_property(Stream, encoding(Old)),
  287    (   (   unicode_encoding(Old)
  288        ;   stream_property(Stream, type(text))
  289        )
  290    ->  Close = true
  291    ;   set_stream(Stream, encoding(utf8)),
  292        Close = set_stream(Stream, encoding(Old))
  293    ).
  294open_input(Stream, Stream, Close) :-
  295    is_stream(Stream),
  296    !,
  297    open_input(stream(Stream), Stream, Close).
  298open_input(atom(Atom), Stream, close(Stream)) :-
  299    !,
  300    atom_to_memory_file(Atom, MF),
  301    open_memory_file(MF, read, Stream, [free_on_close(true)]).
  302open_input(URL, Stream, close(Stream)) :-
  303    (   sub_atom(URL, 0, _, _, 'http://')
  304    ;   sub_atom(URL, 0, _, _, 'https://')
  305    ),
  306    !,
  307    http_open(URL, Stream, []),
  308    set_stream(Stream, encoding(utf8)).
  309open_input(URL, Stream, close(Stream)) :-
  310    uri_file_name(URL, Path),
  311    !,
  312    open(Path, read, Stream, [encoding(utf8)]).
  313open_input(File, Stream, close(Stream)) :-
  314    absolute_file_name(File, Path,
  315                       [ access(read),
  316                         extensions([ttl, ''])
  317                       ]),
  318    open(Path, read, Stream, [encoding(utf8)]).
  319
  320unicode_encoding(utf8).
  321unicode_encoding(wchar_t).
  322unicode_encoding(unicode_be).
  323unicode_encoding(unicode_le).
 base_uri(+Input, -BaseURI, +Options)
Determine the base uri to use for processing.
  329base_uri(_Input, BaseURI, Options) :-
  330    option(base_uri(BaseURI), Options),
  331    !.
  332base_uri(_Input, BaseURI, Options) :-
  333    option(graph(BaseURI), Options),
  334    !.
  335base_uri(stream(Input), BaseURI, _Options) :-
  336    stream_property(Input, file_name(Name)),
  337    !,
  338    name_uri(Name, BaseURI).
  339base_uri(Stream, BaseURI, Options) :-
  340    is_stream(Stream),
  341    !,
  342    base_uri(stream(Stream), BaseURI, Options).
  343base_uri(Name, BaseURI, _Options) :-
  344    atom(Name),
  345    !,
  346    name_uri(Name, BaseURI).
  347base_uri(_, 'http://www.example.com/', _).
  348
  349name_uri(Name, BaseURI) :-
  350    uri_is_global(Name),
  351    !,
  352    uri_normalized(Name, BaseURI).
  353name_uri(Name, BaseURI) :-
  354    uri_file_name(BaseURI, Name).
  355
  356
  357                 /*******************************
  358                 *          WRITE SUPPORT       *
  359                 *******************************/
 turtle_pn_local(+Atom:atom) is semidet
True if Atom is a valid Turtle PN_LOCAL name. The PN_LOCAL name is what can follow the : in a resource. In the new Turtle, this can be anything and this function becomes meaningless. In the old turtle, PN_LOCAL is defined similar (but not equal) to an XML name. This predicate is used by rdf_save_turtle/2 to write files such that can be read by old parsers.
See also
- xml_name/2.
 turtle_write_quoted_string(+Out, +Value, ?WriteLong) is det
Write Value (an atom) as a valid Turtle string. WriteLong determines wether the string is written as a short or long string. It takes the following values:
true
Use Turtle's long string syntax. Embeded newlines and single or double quotes are are emitted verbatim.
false
Use Turtle's short string syntax.
Var
If WriteLong is unbound, this predicate uses long syntax if newlines appear in the string and short otherwise. WriteLong is unified with the decision taken.
 turtle_write_quoted_string(+Out, +Value) is det
Same as turtle_write_quoted_string(Out, Value, false), writing a string with only a single ". Embedded newlines are escapes as \n.
  394turtle_write_quoted_string(Out, Text) :-
  395    turtle_write_quoted_string(Out, Text, false).
 turtle_write_uri(+Out, +Value) is det
Write a URI as <...>
  402                 /*******************************
  403                 *          RDF-DB HOOK         *
  404                 *******************************/
  405
  406:- if(current_predicate(rdf_transaction/2)).  407:- multifile
  408    rdf_db:rdf_load_stream/3,
  409    rdf_db:rdf_file_type/2.
 rdf_db:rdf_load_stream(+Format, +Stream, :Options)
(Turtle clauses)
  415rdf_db:rdf_load_stream(turtle, Stream, Options) :-
  416    load_turtle_stream(Stream, Options).
  417rdf_db:rdf_load_stream(trig, Stream, Options) :-
  418    load_turtle_stream(Stream, Options).
  419
  420load_turtle_stream(Stream, _Module:Options) :-
  421    rdf_db:graph(Options, Graph),
  422    atom_concat('_:', Graph, BNodePrefix),
  423    rdf_transaction((  rdf_process_turtle(Stream, assert_triples,
  424                                          [ anon_prefix(BNodePrefix)
  425                                          | Options
  426                                          ]),
  427                       rdf_set_graph(Graph, modified(false))
  428                    ),
  429                    parse(Graph)).
  430
  431assert_triples([], _).
  432assert_triples([H|T], Location) :-
  433    assert_triple(H, Location),
  434    assert_triples(T, Location).
  435
  436assert_triple(rdf(S,P,O), Location) :-
  437    rdf_assert(S,P,O,Location).
  438assert_triple(rdf(S,P,O,G), _) :-
  439    rdf_assert(S,P,O,G).
  440
  441
  442rdf_db:rdf_file_type(ttl,  turtle).
  443rdf_db:rdf_file_type(n3,   turtle).     % not really, but good enough
  444rdf_db:rdf_file_type(trig, trig).
  445:- endif.  446
  447
  448                 /*******************************
  449                 *             MESSAGES         *
  450                 *******************************/
  451
  452:- multifile prolog:error_message//1.  453
  454prolog:error_message(existence_error(turtle_prefix, '')) -->
  455    [ 'Turtle empty prefix (:) is not defined' ]