Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(resolve,
|
Daniel@0
|
20 [ agent_uri/3
|
Daniel@0
|
21 ]).
|
Daniel@0
|
22
|
Daniel@0
|
23 /** <module> Tools for resolving named entities to URIs
|
Daniel@0
|
24
|
Daniel@0
|
25 NEW RESOLUTION RESOLUTION
|
Daniel@0
|
26 Start from the facts. Resolve entities in the background
|
Daniel@0
|
27 1. Introduce nodes tagged 'unresolved'
|
Daniel@0
|
28 2. Attach facts to nodes.
|
Daniel@0
|
29 3. Resolve later
|
Daniel@0
|
30
|
Daniel@0
|
31 */
|
Daniel@0
|
32 :- use_module(library(memo)).
|
Daniel@0
|
33 :- use_module(library(musicbrainz)).
|
Daniel@0
|
34 :- use_module(library(sparkle)).
|
Daniel@0
|
35 :- use_module(library(listutils)).
|
Daniel@0
|
36 :- use_module(library(readutil)).
|
Daniel@0
|
37 :- use_module(library(dcg_core)).
|
Daniel@0
|
38
|
Daniel@0
|
39 :- persistent_memo composer_uri(+composer:atomic,-uri:atom).
|
Daniel@0
|
40
|
Daniel@0
|
41 :- initialization memo_attach(memo(resolve),[]).
|
Daniel@0
|
42
|
Daniel@0
|
43
|
Daniel@0
|
44 agent_uri(composer,Name,URI) :- ground(URI), !, browse(composer_uri(Name,URI)).
|
Daniel@0
|
45 agent_uri(composer,Name,URI) :-
|
Daniel@0
|
46 memo(composer_uri(Name,URI),_-Status),
|
Daniel@0
|
47 ( Status=ok -> true
|
Daniel@0
|
48 ; Status=fail -> clear_all(composer_uri(Name,_)), fail
|
Daniel@0
|
49 ; Status=ex(Ex) -> clear_all(composer_uri(Name,_)), throw(Ex)
|
Daniel@0
|
50 ).
|
Daniel@0
|
51
|
Daniel@0
|
52 composer_uri(Name,URI) :-
|
Daniel@0
|
53 member(Source,[mb,dbp]),
|
Daniel@0
|
54 source_composer_uri(Source,Name,URI).
|
Daniel@0
|
55
|
Daniel@0
|
56 source_composer_uri(mb,Name,URI) :-
|
Daniel@0
|
57 format("Searching Musicbrainz for composer '~w'...\n",[Name]),
|
Daniel@0
|
58 mb_lazy_query(artist,search([Name,type:person]),[],Matches),
|
Daniel@0
|
59 take_while(score_at_least(98),Matches,TopMatches),
|
Daniel@0
|
60 process_matches(TopMatches,Matches,URI).
|
Daniel@0
|
61
|
Daniel@0
|
62 source_composer_uri(dbp,SearchName,URI) :-
|
Daniel@0
|
63 format("Searching DBPedia for '~w'...\n",[SearchName]),
|
Daniel@0
|
64 catch(
|
Daniel@0
|
65 ( (dbp ?? rdf(URI,rdf:type,foaf:'Person'), rdf(URI,foaf:name,Name), filter(regex(SearchName,Name))),
|
Daniel@0
|
66 format("\nFound '~w'...\n",[URI]),
|
Daniel@0
|
67 findall(Class,(dbp ?? rdf(URI,rdf:type,Class)),Classes),
|
Daniel@0
|
68 format("\nMember of these classes: ~p\n",[Classes]),
|
Daniel@0
|
69 format("\nIs this the right one? [y=yes/n=no/a=abort]",[]), flush_output,
|
Daniel@0
|
70 get_key_char(Char), nl,
|
Daniel@0
|
71 (Char='a' -> throw(lookup_aborted); Char='y')
|
Daniel@0
|
72 ), lookup_aborted, fail).
|
Daniel@0
|
73
|
Daniel@0
|
74 process_matches([E],_,URI) :-
|
Daniel@0
|
75 mb_facet(E,score(Score)),
|
Daniel@0
|
76 format("\nMatch (score=~d):\n\n",[Score]),
|
Daniel@0
|
77 forall(mb_facet(E,Facet),writeln(Facet)), nl,
|
Daniel@0
|
78 mb_uri(E,URI).
|
Daniel@0
|
79
|
Daniel@0
|
80 process_matches([],Matches,URI) :- user_scan(Matches,URI).
|
Daniel@0
|
81 process_matches(Top,Matches,URI) :-
|
Daniel@0
|
82 length(Top,N), N>1,
|
Daniel@0
|
83 format("Found ~d matches: \n",[N]),
|
Daniel@0
|
84 nl, seqmap(print_match,Top,0,_),
|
Daniel@0
|
85 once((repeat,
|
Daniel@0
|
86 format("Enter the number of the correct item, or 0 for none of the above: ",[]), flush_output,
|
Daniel@0
|
87 read(K), number(K),
|
Daniel@0
|
88 % read_line_to_codes(user_input,Codes),
|
Daniel@0
|
89 % number_codes(K,Codes),
|
Daniel@0
|
90 between(0,N,K)
|
Daniel@0
|
91 )),
|
Daniel@0
|
92 ( nth1(K,Top,E) -> mb_uri(E,URI)
|
Daniel@0
|
93 ; append(Top,Tail,Matches),
|
Daniel@0
|
94 process_matches([],Tail,URI)
|
Daniel@0
|
95 ).
|
Daniel@0
|
96
|
Daniel@0
|
97 print_match(E,I,J) :-
|
Daniel@0
|
98 succ(I,J),
|
Daniel@0
|
99 format('~` t~d~2+. ~p\n',[J,E]),
|
Daniel@0
|
100 forall(mb_facet(E,Facet),format(" ~p\n",[Facet])),
|
Daniel@0
|
101 nl.
|
Daniel@0
|
102
|
Daniel@0
|
103 user_scan([E|Es],URI) :-
|
Daniel@0
|
104 nl, forall(mb_facet(E,Facet),format(" ~p\n",[Facet])),
|
Daniel@0
|
105 format("Is this the right one? [y=yes/n=no/a=abort/t=new search term]",[]), flush_output,
|
Daniel@0
|
106 get_key_char(Char), nl,
|
Daniel@0
|
107 ( Char=y -> mb_uri(E,URI)
|
Daniel@0
|
108 ; Char=n -> user_scan(Es,URI)
|
Daniel@0
|
109 ; Char=a -> fail
|
Daniel@0
|
110 ; Char=t -> nl, read_line_to_string(user_input,Name), source_composer_uri(mb,Name,URI)
|
Daniel@0
|
111 ).
|
Daniel@0
|
112
|
Daniel@0
|
113
|
Daniel@0
|
114 score_at_least(Thresh,Element) :- mb_facet(Element,score(S)), S>=Thresh.
|
Daniel@0
|
115
|
Daniel@0
|
116 % :- volatile_memo work_uri(+terms:list(ground),-uri:atom).
|
Daniel@0
|
117 % work_uri(Terms,URI) :-
|
Daniel@0
|
118 % file_work_terms(File,WorkTerms,[]),
|
Daniel@0
|
119 % file_composer_terms(File,ComposerTerms,[]),
|
Daniel@0
|
120 % mb_search(work,[phrase(WorkTerms),artist:phrase(ComposerTerms)],Score,E),
|
Daniel@0
|
121 % sleep(0.05),
|
Daniel@0
|
122 % format("Match (score=~d):\n",[Score]),
|
Daniel@0
|
123 % forall(mb_facet(E,Facet),writeln(Facet)),
|
Daniel@0
|
124 % ( Score>98
|
Daniel@0
|
125 % -> mb_uri(E,URI)
|
Daniel@0
|
126 % ; format("Is this the right one? [y/n/a]",[]), flush_output,
|
Daniel@0
|
127 % get_key_char(Char),
|
Daniel@0
|
128 % (Char='a' -> throw(lookup_aborted(work))),
|
Daniel@0
|
129 % Char='y'
|
Daniel@0
|
130 % ).
|
Daniel@0
|
131
|
Daniel@0
|
132
|
Daniel@0
|
133 get_key_char(Char) :- get_single_char(Code), char_code(Char,Code).
|