Daniel@0: /* Part of DML (Digital Music Laboratory) Daniel@0: Copyright 2014-2015 Samer Abdallah, University of London Daniel@0: Daniel@0: This program is free software; you can redistribute it and/or Daniel@0: modify it under the terms of the GNU General Public License Daniel@0: as published by the Free Software Foundation; either version 2 Daniel@0: of the License, or (at your option) any later version. Daniel@0: Daniel@0: This program is distributed in the hope that it will be useful, Daniel@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Daniel@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Daniel@0: GNU General Public License for more details. Daniel@0: Daniel@0: You should have received a copy of the GNU General Public Daniel@0: License along with this library; if not, write to the Free Software Daniel@0: Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Daniel@0: */ Daniel@0: Daniel@0: :- module(humdrum_p2r, [ humdrum_import/1, hum_uri_path/2 ]). Daniel@0: Daniel@0: /** Manages a database of Humdrum files and mappings to RDF. Daniel@0: */ Daniel@0: Daniel@0: :- use_module(library(memo)). Daniel@0: :- use_module(library(humdrum)). Daniel@0: :- use_module(library(humdrum/humdrum_world), [with_kern_module/4]). Daniel@0: :- use_module(library(fileutils)). Daniel@0: :- use_module(library(termutils)). Daniel@0: :- use_module(library(typedef)). Daniel@0: :- use_module(library(dcg_core)). Daniel@0: :- use_module(library(musiclab)). Daniel@0: :- use_module(library(settings)). Daniel@0: :- use_module(entailment(p2r)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: Daniel@0: :- rdf_register_prefix(humdb,'http://dml.org/humdrum/data/'). Daniel@0: :- rdf_register_prefix(hum,'http://dml.org/humdrum/schema/'). Daniel@0: :- rdf_register_prefix(kern,'kern:'). Daniel@0: Daniel@0: :- setting(kern_root,string,"~/lib/kern","Root of kern lib tree"). Daniel@0: :- setting(kern_subdirs,list(atom),[classical,lorraine,jrp,ragtime,ireland,pentatonic,idyom],"Kern library directories to import"). Daniel@0: Daniel@0: uripattern:def( work(Opus), humdb:work/enc(Opus)). Daniel@0: uripattern:def( trefcode(C), hum:refcode/trans/enc(C)). Daniel@0: uripattern:def( refcode(C), hum:refcode/enc(C)). Daniel@0: uripattern:def( kernfile(F), kern:tail(F)). Daniel@0: Daniel@0: % Humdrum schema Daniel@0: rdf(hum:refcode('OTL'), rdfs:subPropertyOf, dc:title), Daniel@0: rdf(hum:composer, rdfs:subPropertyOf, foaf:maker), Daniel@0: rdf(hum:opus, rdfs:subPropertyOf, mo:opus), Daniel@0: rdf(hum:'Work', rdfs:subClassOf, mo:'MusicalWork'), Daniel@0: rdf(hum:'File', rdfs:subClassOf, mo:'Score'), Daniel@0: rdf(hum:encodedBy, rdfs:type, rdf:'ObjectProperty'), Daniel@0: % rdf(hum:encodedBy, owl:inverseOf, hum:encodes) <== true. Daniel@0: Daniel@0: rdf(\refcode(C), rdfs:subPropertyOf, \trefcode(C)) <== Daniel@0: setof(C, translated_refcode(C), Codes), Daniel@0: member(C, Codes). Daniel@0: Daniel@0: rdf(\trefcode(C), rdf:comment, Desc1) <== Daniel@0: setof(C, translated_refcode(C), Codes), Daniel@0: member(C, Codes), Daniel@0: hum_prop_desc(C,Desc), Daniel@0: atom_concat(Desc,' (translated)',Desc1). Daniel@0: Daniel@0: translated_refcode(Code) :- Daniel@0: browse(file_props(_,Props)), Daniel@0: member(Code-((sec-_)-_),Props). Daniel@0: Daniel@0: hum_prop_desc(C,_) ==> Daniel@0: rdf(\refcode(C), rdf:type, rdf:'ObjectProperty'), Daniel@0: rdf(\refcode(C), rdf:domain, hum:'File'). Daniel@0: Daniel@0: hum_prop_desc(C,Desc) ==> Daniel@0: rdf(\refcode(C), rdf:comment, literal(Desc)). Daniel@0: Daniel@0: % -- mappings that use file_opus/2 --------------- Daniel@0: Daniel@0: %% file(-File) is nondet. Daniel@0: % True when File is a Humdrum file that has been imported into Daniel@0: % the current database. Daniel@0: :- dynamic file/1. Daniel@0: Daniel@0: %% file_opus(-File,-Opus) is nondet. Daniel@0: % True when Humdrum file File contains an SCT refcode Daniel@0: % (scholarly catalog number) Opus. Daniel@0: file_opus(F,O) :- file(F), file_prop(F,'SCT',_,O). Daniel@0: Daniel@0: rdf(\kernfile(F), \trefcode(C), literal(Value)) <== Daniel@0: call_with_mode(browse,file_prop(F,C,sec,Value)). Daniel@0: Daniel@0: rdf(\kernfile(F), \refcode(C), literal(Value)) <== Daniel@0: call_with_mode(browse,file_prop(F,C,pri,Value)). Daniel@0: Daniel@0: rdf(\kernfile(F), hum:directory, literal(Dir1)) <== Daniel@0: file(F), Daniel@0: file_directory_name(F,Dir), Daniel@0: atom_concat('/',Dir1,Dir). Daniel@0: Daniel@0: file(F) ==> Daniel@0: % rdf(\kernfile(F), hum:language, hum:language/humdrum), Daniel@0: rdf(\kernfile(F), rdf:type, hum:'File'). Daniel@0: Daniel@0: file_opus(_,O) ==> Daniel@0: rdf(\work(O), rdf:type, hum:'Work'), Daniel@0: rdf(\work(O), hum:opus, literal(O)). Daniel@0: Daniel@0: % file_opus(F,O) ==> Daniel@0: % rdf(\kernfile(F), hum:encodes, \work(O)). Daniel@0: Daniel@0: Daniel@0: % rdf(\work(O), dc:title, literal(Title)) <== Daniel@0: % file_opus(F,O), Daniel@0: % (file_has(F,'OTL',Title); file_has(F,'OTP',Title)). Daniel@0: Daniel@0: % rdf(\work(O), dc:title, literal(lang(Lang,Title))) <== Daniel@0: % file_opus(F,O), Daniel@0: % file_has(F,'OTL',Title), Daniel@0: % file_has(F,'TXO',Lang). Daniel@0: Daniel@0: % rdf(\work(O), hum:partOf, humdb:parent_work/enc(P)) <== Daniel@0: % file_opus(F,O), Daniel@0: % (file_has(F,'OPT',P); file_has(F,'OPR',P)). Daniel@0: Daniel@0: % rdf(\work(O), hum:composer, humdb:agent/enc(C)) <== Daniel@0: % file_opus(F,O), file_has(F,'COM',C). Daniel@0: Daniel@0: % rdf(\work(O), hum:number, literal(Num)) <== Daniel@0: % file_opus(F,O), file_has(F,'ONM',Num). Daniel@0: Daniel@0: % ----- mappings using composers/1 -------- Daniel@0: Daniel@0: % rdf(humdb:agent/enc(C), foaf:name, literal(C)), Daniel@0: % rdf(humdb:agent/enc(C), rdf:type, mo:'MusicArtist') <== Daniel@0: % composers(Composers), Daniel@0: % member(C,Composers). Daniel@0: Daniel@0: % ----- mappings using parent_works/1 -------- Daniel@0: Daniel@0: % rdf(humdb:parent_work/enc(P), rdf:type, hum:'Work'), Daniel@0: % rdf(humdb:parent_work/enc(P), dc:title, literal(P)) <== Daniel@0: % parent_works(Works), Daniel@0: % member(P,Works). Daniel@0: Daniel@0: Daniel@0: has_stripped(Recs,Prop,Status,Literal) :- Daniel@0: member(ref(Prop,Lang,RawValue),Recs), Daniel@0: split_string(RawValue,""," ",[String]), Daniel@0: String\="", atom_string(Value,String), Daniel@0: refcode_literal(Lang,Value,Status,Literal). Daniel@0: Daniel@0: refcode_literal(def, Val, pri, Val). Daniel@0: refcode_literal(P-Lang, Val, P, lang(L,Val)) :- lang(Lang,L). Daniel@0: Daniel@0: :- type prop ---> prop(atom,atom,ground). Daniel@0: :- volatile_memo file_props(+file:atomic,-props:list(prop)). Daniel@0: Daniel@0: file_props(File,Props) :- Daniel@0: setting(kern_root,Root0), Daniel@0: expand_file_name(Root0,[Root]), Daniel@0: string_concat(Root,File,Abs), Daniel@0: % !!! FIXME: will barf if Root contains funny characters Daniel@0: format(string(Cmd),"grep '^!!!' \"~w\"",[Abs]), Daniel@0: hum_read(pipe(Cmd),utf8,Recs), Daniel@0: setof(prop(Prop,Status,Lit),has_stripped(Recs,Prop,Status,Lit),Props). Daniel@0: Daniel@0: Daniel@0: :- volatile_memo parent_works(-works:list(ground)). Daniel@0: parent_works(Works) :- Daniel@0: writeln('% Compiling list of parent works...'), Daniel@0: setof(P, F^O^(file_opus(F,O),file_prop(F,'OPR',_,P)), Works). Daniel@0: Daniel@0: :- volatile_memo composers(-composers:list(atom)). Daniel@0: Daniel@0: %% composers(-Composers:list(atom)) is det. Daniel@0: % Compiles a list of composer names referenced in the current Daniel@0: % Humdrum file property database file_props/2. Daniel@0: composers(Composers) :- Daniel@0: writeln('% Compiling list of composers...'), Daniel@0: findall(C, call_with_mode(browse,file_prop(_,'COM',_,C)), CList), Daniel@0: sort(CList,Composers). Daniel@0: Daniel@0: % rdf(URI,rdf:type,mo:'MusicArtist') <== Daniel@0: % composers(Comps), Daniel@0: % member(C,Comps), Daniel@0: % agent_uri(composer,C,URI). Daniel@0: Daniel@0: % rdf(URI,hum:name,literal(Name)) <== Daniel@0: % agent_uri(composer,Name,URI). Daniel@0: Daniel@0: % rdf(\kernfile(F), hum:composer, literal(Name)) <== Daniel@0: % call_with_mode(browse,file_prop(F,'COM',pri,Name)), Daniel@0: % agent_uri(composer,Name,URI). Daniel@0: Daniel@0: Daniel@0: file_work_terms(File) --> Daniel@0: if(file_prop(File,'OTL',_,Title), [Title]), Daniel@0: if(file_prop(File,'OPR',_,Parent), [Parent]), Daniel@0: if(file_prop(File,'OPN',_,Opus), [Opus]), Daniel@0: if(file_prop(File,'SCT',_,Cat), [Cat]). Daniel@0: Daniel@0: Daniel@0: file_prop(File,Prop,Status,Lit) :- Daniel@0: file_props(File,Props), Daniel@0: member(prop(Prop,Status,Lit),Props). Daniel@0: Daniel@0: Daniel@0: hum_uri_path(URI,Path) :- Daniel@0: atom_concat('kern:',Rel,URI), Daniel@0: setting(kern_root,Root), Daniel@0: expand_file_name(Root,[Root1]), Daniel@0: string_concat(Root1,Rel,Path). Daniel@0: Daniel@0: Daniel@0: %% humdrum_import(+Path:atom) is det. Daniel@0: % Daniel@0: % Searches for files in the directory tree beneath Daniel@0: % =|/Path|=, where =| Status=ok Daniel@0: ; Status=fail), Daniel@0: Ex, Status=ex(Ex)). Daniel@0: Daniel@0: Daniel@0: humdrum_check :- Daniel@0: with_status_line( Daniel@0: forall( (rdf_db:rdf(X,rdf:type,hum:'File'), hum_uri_path(X,Path)), Daniel@0: ( humfile_status(Path,Status), Daniel@0: ( Status=ok -> true Daniel@0: ; Status=fail -> format('\nFailed on: ~w\n',[Path]) Daniel@0: ; Status=ex(Ex) -> format('\nException on: ~w\n',[Path]), Daniel@0: print_message(error,Ex) Daniel@0: ) Daniel@0: ))). Daniel@0: Daniel@0: kern_file(Findspec,File) :- Daniel@0: find_files(Findspec,File), Daniel@0: extension_in(File,[krn,kern,'KRN','KERN']). Daniel@0: Daniel@0: id_assert(Fact) :- call(Fact) -> true; assert(Fact). Daniel@0: Daniel@0: lang('ENG',en). Daniel@0: lang('EN',en). Daniel@0: lang('FRA',fr). Daniel@0: lang('FRE',fr). Daniel@0: lang('FR',fr). Daniel@0: lang('DE',de). Daniel@0: lang('DEU',de). Daniel@0: lang('GER',de). Daniel@0: lang('ITA',it). Daniel@0: lang('IT',it). Daniel@0: lang('NO',no). Daniel@0: lang('NOR',no). Daniel@0: lang('LAT',la). Daniel@0: lang('LA',la). Daniel@0: lang('RU',ru). Daniel@0: lang('RUS',ru).