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