:- module(rdf_backward_search, [ rdf_backward_search/4, % +KeyWord, +TargetCond, -State, +Options predicate_weight/2 ]). :- 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)). :- use_module(owl_ultra_lite). /** Direct metadata search on RDF graph @author Michiel Hildebrand, on top of search facilities from rdf_search.pl */ :- multifile cluster_search:predicate_weight/2. :- meta_predicate rdf_backward_search(+, 1, -, +). :- rdf_register_prefix(oa, 'http://www.w3.org/ns/oa#'). %% rdf_backward_search(+Keyword, :TargetCond, -State, +Options) % % Initiate a graph search by traversing resources in backwards fashion, % thus only considing the triple where the current node is an object. % % Options: see rdf_search/4 rdf_backward_search(Keyword, TargetCond, State, Options) :- Expand = rdf_backward_search:edge, setting(cluster_search:steps, DefSteps), option(steps(Steps0), Options, DefSteps), ( Steps0 == 0 -> Steps = -1 ; Steps = Steps0 ), debug(query, 'rdf_backward_search Query: ~p', [Keyword]), 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, +Score, -Link) is nondet. % % Generate links from Object Node, consisting of a Subject, % Predicate and Weight. edge(O, _, i(S,P,W)) :- edge(O, S, P, W), debug(myedge, 'Expanding ~2f ~p ~p ~p~n', [W, O, P, S]), W > 0.0001. edge(O, S, P, W) :- setof(S, i_edge(O, S, P), Ss), ( predicate_weight(P, W) -> member(S, Ss) ; length(Ss, Len), member(S, Ss), subject_weight(S, Len, W) ). %% i_edge(+O, -S, -P) % % Find Subject that is connected through Predicate. % annotation edge hack: translate the connection between object and % subject through an annotation into a dc:subject predicate. i_edge(O, S, P) :- rdf(Annotation, oa:hasBody, O), rdf(Annotation, oa:hasTarget, S), rdf_equal(P, dc:subject). i_edge(O, S, P) :- rdf(S, P, O), % ignore annotations connected by hasTarget \+ rdf_equal(S, oa:hasTarget). i_edge(O, S, P) :- rdf(O, P0, S), atom(S), ( owl_ultra_lite:inverse_predicate(P0, P) -> true ; predicate_weight(P0, 1) -> P = P0 ), % ignore annotations connected by hasTarget \+ rdf_equal(S, oa:hasTarget). %% 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 % cluster_search: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, Weight) :- catch(cluster_search:predicate_weight(P, Weight), _, fail), !. 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), !. /* predicate_weight(_, Weight) :- catch(cliopatria:default_weight(Weight), _, fail). */ subject_weight(S, _, 1) :- rdf_is_bnode(S), !. subject_weight(_, Count, W) :- W is 1/max(3, Count).