/* This file is part of ClioPatria.
Author:
HTTP: http://e-culture.multimedian.nl/
GITWEB: http://gollem.science.uva.nl/git/ClioPatria.git
GIT: git://gollem.science.uva.nl/home/git/ClioPatria.git
GIT: http://gollem.science.uva.nl/home/git/ClioPatria.git
Copyright: 2007, E-Culture/MultimediaN
ClioPatria is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 2 of the License, or
(at your option) any later version.
ClioPatria is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with ClioPatria. If not, see .
*/
:- module(rdf_full_search,
[ rdf_full_search/4 % +KeyWord, +TargetCond, -State, +Options
]).
:- use_module(rdf_search).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(option)).
:- use_module(library(semweb/rdf_db)).
:- use_module(library(semweb/rdfs)).
/** Full search on RDF graph
@author Michiel Hildebrand, based on util(rdf_search.pl)
*/
:- meta_predicate
rdf_full_search(+, 1, -, +).
%% rdf_full_search(+Keyword, :TargetCond, -State, +Options)
%
% Initiate a full graph search by traversing resources in all
% possible ways.
%
% Options: see rdf_search/4
rdf_full_search(Keyword, TargetCond, State, Options) :-
Expand = rdf_full_search:edge,
setting(cluster_search:steps, DefSteps),
option(steps(Steps0), Options, DefSteps),
( Steps0 == 0
-> Steps = -1
; Steps = Steps0
),
rdf_keyword_search(Keyword, TargetCond, State,
[expand_node(Expand)|Options]),
steps(0, Steps, State).
steps(Steps, Steps, _) :- !.
steps(I, Steps, Graph) :-
I2 is I + 1,
( rdf_extend_search(Graph)
-> ( debugging(rdf_search)
-> debug(rdf_search, 'After cycle ~D', [I2]),
forall(debug_property(P),
( rdf_search_property(Graph, P),
debug(rdf_search, '\t~p', [P])))
; true
),
steps(I2, Steps, Graph)
; debug(rdf_search, 'Agenda is empty after ~D steps~n', [I])
).
debug_property(target_count(_)).
debug_property(graph_size(_)).
%% edge(+Node, -Link) is nondet.
%
% Generate links from Node.
edge(O, i(S,P,W)) :-
i_edge(O, S, P, W),
debug(myedge, 'Expanding ~2f ~p ~p ~p~n', [W, O, P, S]),
W > 0.0001.
edge(O, f(S,P,W)) :-
f_edge(O, S, P, W),
debug(myedge, 'Expanding ~2f ~p ~p ~p~n', [W, O, P, S]),
W > 0.0001.
i_edge(O, S, P, W) :-
setof(S, rdf(S, P, O), Ss),
( predicate_weight(P, W)
-> member(S, Ss)
; length(Ss, Len),
member(S, Ss),
subject_weight(S, Len, W)
).
f_edge(O, S, P, W) :-
setof(S, f_rdf(O, P, S), Ss),
( predicate_weight(P, W)
-> member(S, Ss)
; length(Ss, Len),
member(S, Ss),
subject_weight(S, Len, W)
).
f_rdf(O, P, S) :-
rdf(O,P,S),
atom(S),
\+ rdf_equal(P,skos:inScheme).
%% predicate_weight(+Predicate, -Weight) is semidet.
%
% Weight based on the meaning of Predicate. This predicate deals
% with RDF predicates that have a well defined meaning.
%
% Additional weights (or overwrites) can be defined in
% cliopatria:predicate_weight/2,
%
% Note that rdfs:comment is not searched as it is supposed to
% be comment about the graph, and not part of the graph itself.
%predicate_weight(P, 1) :-
%rdfs_subproperty_of(P, rdfs:label), !.
predicate_weight(P, 1) :-
rdfs_subproperty_of(P, rdf:value), !.
predicate_weight(P, 1) :-
rdf_equal(P, owl:sameAs), !.
predicate_weight(P, 1) :-
rdf_equal(P, skos:exactMatch), !.
predicate_weight(P, 0) :-
rdfs_subproperty_of(P, rdfs:comment), !.
subject_weight(S, _, 1) :-
rdf_is_bnode(S), !.
subject_weight(_, Count, W) :-
W is 1/max(3, Count).