View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2011, University of Amsterdam,
    7		   VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(rdf_schema,
   32	  [ rdf_graph_schema/2		% +DataGraph, +SchemaGraph
   33	  ]).   34:- use_module(library(semweb/rdf_db)).   35:- use_module(library(semweb/rdfs)).   36
   37:- thread_local
   38	schema_triple/3.   39:- multifile
   40	known_schema_prefix/1.
 rdf_graph_schema(+Graph, +SchemaTriples) is det
Create an initial schema by providing definitions for all predicates and types (classes) used in Graph. The schema is dumped into the graph SchemaGraph.
   48rdf_graph_schema(Data, Schema) :-
   49	retractall(schema_triple(_,_,_)),
   50	make_schema(Data),
   51	findall(rdf(S,P,O), retract(schema_triple(S,P,O)), Schema).
   52
   53:- rdf_meta
   54	assert_schema(r,r,o).   55
   56assert_schema(S,P,O) :-
   57	schema_triple(S,P,O), !.
   58assert_schema(S,P,O) :-
   59	assert(schema_triple(S,P,O)).
   60
   61
   62make_schema(Data) :-
   63	forall(predicate_in_graph(Data, P),
   64	       define_predicate(P, Data)),
   65	forall(type_in_graph(Data, Class),
   66	       define_type(Class)).
   67
   68known_schema_prefix(rdf).
   69known_schema_prefix(rdfs).
   70known_schema_prefix(owl).
   71known_schema_prefix(skos).
   72known_schema_prefix(dc).
   73known_schema_prefix(dcterms).
   74
   75known_url(P) :-
   76	known_schema_prefix(Prefix),
   77	rdf_global_id(Prefix:_, P), !.
   78
   79define_predicate(P, _) :-
   80	known_url(P), !.
   81define_predicate(P, DataGraph) :-
   82	copy_data(P),
   83	assert_schema(P, rdf:type, rdf:'Property'),
   84	assign_label(P),
   85	predicate_statistics(DataGraph, P, _C,
   86			     _Subjects, _Objects,
   87			     Domains, Ranges),
   88	(   Domains = [Dom]
   89	->  assert_schema(P, rdfs:domain, Dom)
   90	;   true
   91	),
   92	(   Ranges = [Range]
   93	->  assert_schema(P, rdfs:range, Range)
   94	;   true
   95	).
   96
   97
   98define_type(C) :-
   99	known_url(C), !.
  100define_type(C) :-
  101	copy_data(C),
  102	assert_schema(C, rdf:type, rdfs:'Class'),
  103	assign_label(C).
  104
  105
  106assign_label(S) :-
  107	(   rdf(S, rdfs:label, _)
  108	->  true
  109	;   rdfs_label(S, Label),
  110	    Label \== S
  111	->  assert_schema(S, rdfs:label, literal(Label))
  112	;   true
  113	).
  114
  115
  116copy_data(S) :-
  117	retractall(schema_triple(S,_,_)),
  118	forall(rdf(S,P,O),
  119	       assert_schema(S,P,O)).
  120
  121
  122		 /*******************************
  123		 *	        QUERY		*
  124		 *******************************/
  125
  126predicate_in_graph(Graph, P) :-
  127	rdf_current_predicate(P),
  128	once(rdf(_,P,_,Graph)).
 type_in_graph(+Graph, -Class)
Generate the unique types in Graph
  134:- thread_local
  135	type_seen/1.  136
  137type_in_graph(Graph, Class) :-
  138	call_cleanup(type_in_graph2(Graph, Class),
  139		     retractall(type_seen(_))).
  140
  141type_in_graph2(Graph, Class) :-
  142	subject_in_graph(Graph, S),
  143	(   rdf(S, rdf:type, Class)
  144	*-> true
  145	;   rdf_equal(Class, rdfs:'Resource')
  146	),
  147	(   type_seen(Class)
  148	->  fail
  149	;   assert(type_seen(Class))
  150	).
  151
  152
  153subject_in_graph(Graph, S) :-
  154	rdf_subject(S),
  155	once(rdf(S, _, _, Graph)).
  156
  157predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  158	findall(S-O, rdf(S,P,O,Graph), Pairs),
  159	length(Pairs, C),
  160	pairs_keys_values(Pairs, Ss, Os),
  161	sort(Ss, Subjects),
  162	sort(Os, Objects),
  163	resources_types(Subjects, Graph, Domains),
  164	resources_types(Objects, Graph, Ranges).
  165
  166resources_types(URIs, Graph, Types) :-
  167	findall(T, resource_type_in(URIs, Graph, T), TList),
  168	sort(TList, Types).
  169
  170resource_type_in(List, Graph, T) :-
  171	member(URI, List),
  172	resource_type(URI, Graph, T).
 resource_type(+URI, +Graph, -Type) is det
  176resource_type(URI, Graph, T) :-
  177	(   URI = literal(Lit)
  178	->  (   Lit = type(T, _)
  179	    ->	true
  180	    ;	rdf_equal(T, rdfs:'Literal')
  181	    )
  182	;   rdf(URI, rdf:type, T, Graph)
  183	*-> true
  184	;   rdf_equal(T, rdfs:'Resource')
  185	)