/* 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_direct_search,
[ rdf_concept_search/4, % +KeyWord, +TargetCond, -State, +Options
rdf_literal_search/4 % +KeyWord, +TargetCond, -State, +Options
]).
:- use_module(library(record)).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(option)).
:- use_module(library(semweb/rdf_db)).
:- use_module(library(semweb/rdfs)).
:- use_module(rdf_search).
/** Direct metadata search on RDF graph
@author Michiel Hildebrand, on top of search facilities from rdf_search.pl
*/
:- meta_predicate
rdf_direct_search(+, 1, -, +).
:- record
expand(description = false,
initial_eq = false,
equivalent = false,
narrower = false,
narrower1 = false,
broader = false,
related = false,
specific = false,
rdf_value = true,
forward = false
).
%% rdf_direct_search(+Keyword, :TargetCond, -State, +Options)
%
% Initiate a graph search by traversing only direct links between
% keyword and target resources.
%
% Options: see rdf_search/4
rdf_concept_search(Keyword, TargetCond, State, Options) :-
make_expand([], Expand0),
set_expand_options(Expand0, Expand, Options),
Edge = rdf_direct_search:edge(Expand, TargetCond),
rdf_keyword_search(Keyword, TargetCond, State,
[expand_node(Edge),target_expand(false)|Options]),
steps(State).
rdf_literal_search(Keyword, TargetCond, State, Options) :-
Expand = rdf_direct_search:literal_edge,
rdf_keyword_search(Keyword, TargetCond, State,
[expand_node(Expand),target_expand(false)|Options]),
steps(State).
set_expand_options(Expand0, Expand, Options) :-
option(expand(Es0), Options, []),
maplist(atom_to_option, Es0, Es),
set_expand_fields(Es, Expand0, Expand, _).
atom_to_option(H, Opt) :-
atom(H),
Opt =.. [H,true].
%% steps(+State)
%
% Recursively call rdf_extend_search/1 until it fails.
steps(State) :-
rdf_extend_search(State), !,
( debugging(rdf_search)
-> forall(debug_property(P),
( rdf_search_property(State, P),
debug(rdf_search, '\t~p', [P])))
; true
),
steps(State).
steps(_).
debug_property(target_count(_)).
debug_property(graph_size(_)).
%% edge(+Expand, +Cond, +Graph, +Object, -Link) is nondet.
%
% Default predicate to generate edges.
edge(Expand, Cond, O, Score, i(S,P,W)) :-
setof(S, edge_i(O, S, P), Ss),
( O = literal(_)
-> ( rdfs_subproperty_of(P, rdfs:label)
-> W = 1
; expand_description(Expand, true)
-> W = 0.5
),
member(S, Ss)
; cond_predicate_weight(P, Expand, Score, W)
-> member(S, Ss)
; W = 0.5,
member(S, Ss),
call(Cond, S)
).
edge(Expand, _Cond, O, Score, i(S,P,W)) :-
expand_forward(Expand, true),
setof(S, edge_i(S, O, P), Ss),
( cond_f_predicate_weight(P, Expand, Score, W)
-> member(S, Ss)
).
edge_i(O, S, P) :-
rdf(S, P, O).
edge_i(O, S, P) :-
rdf(O, P0, S),
rdf_inverse_property(P, P0).
%% cond_predicate_weight(+Pred, +ExpandState, +Score, -Weight)
%
% Weight is the weight of Pred if ExpandState and Score allow.
cond_predicate_weight(P, Expand, _Score, 1) :-
rdf_equal(P, rdf:value), !,
expand_rdf_value(Expand, true).
cond_predicate_weight(P, Expand, Score, 1) :-
eq_predicate(P), !,
( expand_equivalent(Expand, true)
-> true
; Score > 0.9,
expand_initial_eq(Expand, true)
).
cond_predicate_weight(_P, Expand, Score, 0.5) :-
Score > 0.5, !,
expand_specific(Expand, true).
%% cond_f_predicate_weight(+Pred, +ExpandState, +Score, -Weight)
%
% Weight is the weight of Pred if ExpandState and Score allow.
cond_f_predicate_weight(P, Expand, _Score, 1) :-
rdf_equal(P, rdf:value), !,
expand_rdf_value(Expand, true).
eq_predicate(P) :-
rdfs_subproperty_of(P, owl:sameAs).
eq_predicate(P) :-
rdfs_subproperty_of(P, skos:exactMatch).
literal_edge(literal(L), _Score, i(S,P,1)) :-
rdf(S, P, literal(L)).