rdf-mt/commit

Define basic RDF properties

authorJan Wielemaker
Mon Dec 16 16:04:00 2013 +0100
committerJan Wielemaker
Mon Dec 16 16:04:00 2013 +0100
commit51d9849b58eef99ac1bb837b6920a3fbeb64cb32
tree2cbabb4009e17490c1382b37bbe6678d4dcc8aa7
parent19d035c32f4053cfb8a4714c7682ef9f0f670d60
Diff style: patch stat
diff --git a/lib/rdf_mt/graph_properties.pl b/lib/rdf_mt/graph_properties.pl
index cfd698a..00df69b 100644
--- a/lib/rdf_mt/graph_properties.pl
+++ b/lib/rdf_mt/graph_properties.pl
@@ -29,14 +29,136 @@
 */
 
 :- module(graph_properties,
-	  [ empty_graph/1
+	  [ empty_graph/1,		% +Graph
+	    ground_graph/1,		% +Graph
+	    lean_graph/1,		% +Graph
+	    isomorphic_graphs/2,	% +Graph1, +Graph2
+	    is_subgraph/2,		% +SubGraph, +Graph
+	    is_proper_subgraph/2,	% +SubGraph, +Graph
+	    is_instance_of_graph/2,	% +Instance, +Graph
+	    is_proper_instance_of_graph/2, % +Instance, +Graph
+	    simply_entails/2		% +Graph, E
 	  ]).
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(terms)).
+:- use_module(library(pairs)).
+:- use_module(library(ordsets)).
 
 /** <module> Predicates that prove properties about RDF graphs
 */
 
+		 /*******************************
+		 *	 GRAPH PROPERTIES	*
+		 *******************************/
+
 %%	empty_graph(?Graph)
 %
 %	True when Graph is the empty graph
 
 empty_graph([]).
+
+%%	ground_graph(?Graph)
+%
+%	True if Graph is ground (holds no blank nodes)
+
+ground_graph(Graph) :-
+	ground(Graph).
+
+%%	lean_graph(Graph) is semidet.
+
+lean_graph(Graph) :-
+	partition(ground, Graph, Ground, NonGround),
+	\+ (   member(Gen, NonGround),
+	       (   member(Spec, Ground)
+	       ;   member(Spec, NonGround)
+	       ),
+	       Gen \== Spec,
+	       subsumes_term(Gen, Spec)
+	   ).
+
+
+		 /*******************************
+		 *	  GRAPH RELATIONS	*
+		 *******************************/
+
+%%	equal_graphs(Graph1, Graph2) is semidet.
+%
+%	True if both graphs are equal.
+
+equal_graphs(Graph1, Graph2) :-
+	sort(Graph1, Graph),
+	sort(Graph2, Graph).
+
+%%	isomorphic_graphs(+Graph1, +Graph2)
+%
+%	Is true if there is a consistent  mapping between of blank nodes
+%	in Graph1 to blank nodes in Graph2 that makes both graphs equal.
+%	This maps to the Prolog  notion  of   _variant_  if  there was a
+%	canonical ordering of triples.
+
+isomorphic_graphs(Graph1, Graph2) :-
+	once(graph_permutation(Graph1, Ordered1)),
+	graph_permutation(Graph2, Ordered2),
+	variant(Ordered1, Ordered2), !.
+
+graph_permutation(Graph1, Graph) :-
+	partition(ground, Graph1, Ground, NonGround),
+	sort(Ground, Sorted),
+	append(Sorted, NonGroundPermutation, Graph),
+	permutation(NonGround, NonGroundPermutation).
+
+%%	is_subgraph(+Sub, +Super) is semidet.
+
+is_subgraph(Sub, Super) :-
+	sort(Sub, SubSorted),
+	sort(Super, SuperSorted),
+	ord_subset(SubSorted, SuperSorted).
+
+%%	subgraph(+Sub, +Super) is nondet.
+
+subgraph([], _).
+subgraph([H|T0], [H|T]) :-
+	subgraph(T0, T).
+
+%%	is_proper_subgraph(+Sub, +Super) is semidet.
+
+is_proper_subgraph(Sub, Super) :-
+	sort(Sub, SubSorted),
+	sort(Super, SuperSorted),
+	ord_subset(SubSorted, SuperSorted),
+	length(SubSorted, SubLen),
+	length(SuperSorted, SuperLen),
+	SubLen < SuperLen.
+
+%%	is_instance_of_graph(+Instance, +Graph) is semidet.
+%
+%	Instance is an instance of Graph, which   means that there is an
+%	assignment of blank nodes in Instance   that makes it equivalent
+%	to Graph. This is cose to  subsumes_term/2 with similar ordering
+%	issues as with isomorphic_graphs/2.  First, we remove the ground
+%	part of the Graph from Instance.
+
+is_instance_of_graph(Instance, Graph) :-
+	partition(ground, Graph, Ground, GNonGround),
+	sort(Instance, ISorted),
+	ord_subtract(ISorted, Ground, RestInstance),
+	permutation(RestInstance, Permutation),
+	subsumes_term(GNonGround, Permutation), !.
+
+%%	is_proper_instance_of_graph(+Instance, +Graph) is semidet.
+
+is_proper_instance_of_graph(Instance, Graph) :-
+	\+ equal_graphs(Instance, Graph),
+	is_instance_of_graph(Instance, Graph).
+
+
+		 /*******************************
+		 *	    ENTAILMENT		*
+		 *******************************/
+
+%%	simply_entails(+Graph1, +Graph2) is semidet.
+
+simply_entails(G, E) :-
+	subgraph(Sub, G),
+	is_instance_of_graph(Sub, E), !.