diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/resolve.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,133 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program 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.
+
+	This program 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 this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(resolve, 
+      [  agent_uri/3
+      ]).
+
+/** <module> Tools for resolving named entities to URIs
+
+ NEW RESOLUTION RESOLUTION
+ Start from the facts. Resolve entities in the background
+ 1. Introduce nodes tagged 'unresolved'
+ 2. Attach facts to nodes.
+ 3. Resolve later
+
+*/
+:- use_module(library(memo)).
+:- use_module(library(musicbrainz)).
+:- use_module(library(sparkle)).
+:- use_module(library(listutils)).
+:- use_module(library(readutil)).
+:- use_module(library(dcg_core)).
+
+:- persistent_memo composer_uri(+composer:atomic,-uri:atom).
+
+:- initialization memo_attach(memo(resolve),[]).
+
+
+agent_uri(composer,Name,URI) :- ground(URI), !, browse(composer_uri(Name,URI)).
+agent_uri(composer,Name,URI) :-
+   memo(composer_uri(Name,URI),_-Status),
+   (  Status=ok -> true
+   ;  Status=fail -> clear_all(composer_uri(Name,_)), fail
+   ;  Status=ex(Ex) -> clear_all(composer_uri(Name,_)), throw(Ex)
+   ).
+
+composer_uri(Name,URI) :-
+   member(Source,[mb,dbp]),
+   source_composer_uri(Source,Name,URI).
+
+source_composer_uri(mb,Name,URI) :-
+   format("Searching Musicbrainz for composer '~w'...\n",[Name]),
+   mb_lazy_query(artist,search([Name,type:person]),[],Matches), 
+   take_while(score_at_least(98),Matches,TopMatches),
+   process_matches(TopMatches,Matches,URI).
+
+source_composer_uri(dbp,SearchName,URI) :-
+   format("Searching DBPedia for '~w'...\n",[SearchName]),
+   catch( 
+      (  (dbp ?? rdf(URI,rdf:type,foaf:'Person'), rdf(URI,foaf:name,Name), filter(regex(SearchName,Name))), 
+         format("\nFound '~w'...\n",[URI]),
+         findall(Class,(dbp ?? rdf(URI,rdf:type,Class)),Classes),
+         format("\nMember of these classes: ~p\n",[Classes]),
+         format("\nIs this the right one? [y=yes/n=no/a=abort]",[]), flush_output,
+         get_key_char(Char), nl,
+         (Char='a' -> throw(lookup_aborted); Char='y')
+      ), lookup_aborted, fail).
+
+process_matches([E],_,URI) :- 
+   mb_facet(E,score(Score)),
+   format("\nMatch (score=~d):\n\n",[Score]),
+   forall(mb_facet(E,Facet),writeln(Facet)), nl,
+   mb_uri(E,URI).
+
+process_matches([],Matches,URI) :- user_scan(Matches,URI).
+process_matches(Top,Matches,URI) :-
+   length(Top,N), N>1,
+   format("Found ~d matches: \n",[N]),
+   nl, seqmap(print_match,Top,0,_),
+   once((repeat, 
+      format("Enter the number of the correct item, or 0 for none of the above: ",[]), flush_output,
+      read(K), number(K),
+      % read_line_to_codes(user_input,Codes), 
+      % number_codes(K,Codes),
+      between(0,N,K)
+   )),
+   (  nth1(K,Top,E) -> mb_uri(E,URI)
+   ;  append(Top,Tail,Matches), 
+      process_matches([],Tail,URI)
+   ).
+   
+print_match(E,I,J) :- 
+   succ(I,J), 
+   format('~` t~d~2+. ~p\n',[J,E]),
+   forall(mb_facet(E,Facet),format("      ~p\n",[Facet])),
+   nl.
+
+user_scan([E|Es],URI) :-
+   nl, forall(mb_facet(E,Facet),format("    ~p\n",[Facet])),
+   format("Is this the right one? [y=yes/n=no/a=abort/t=new search term]",[]), flush_output,
+   get_key_char(Char), nl,
+   (  Char=y -> mb_uri(E,URI)
+   ;  Char=n -> user_scan(Es,URI)
+   ;  Char=a -> fail
+   ;  Char=t -> nl, read_line_to_string(user_input,Name), source_composer_uri(mb,Name,URI)
+   ).
+
+
+score_at_least(Thresh,Element) :- mb_facet(Element,score(S)), S>=Thresh.
+
+% :- volatile_memo work_uri(+terms:list(ground),-uri:atom).
+% work_uri(Terms,URI) :-
+%    file_work_terms(File,WorkTerms,[]),
+%    file_composer_terms(File,ComposerTerms,[]),
+%    mb_search(work,[phrase(WorkTerms),artist:phrase(ComposerTerms)],Score,E), 
+%    sleep(0.05),
+%    format("Match (score=~d):\n",[Score]),
+%    forall(mb_facet(E,Facet),writeln(Facet)),
+%    (  Score>98 
+%    -> mb_uri(E,URI)
+%    ;  format("Is this the right one? [y/n/a]",[]), flush_output,
+%       get_key_char(Char),
+%       (Char='a' -> throw(lookup_aborted(work))),
+%       Char='y'
+%    ).
+   
+
+get_key_char(Char) :- get_single_char(Code), char_code(Char,Code).