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(charm_p2r, [ audio_link/3 ]). Daniel@0: Daniel@0: /** Access to beets database Daniel@0: */ Daniel@0: Daniel@0: Daniel@0: % :- use_module(library(odbc)). Daniel@0: :- use_module(library(csv)). Daniel@0: :- use_module(library(musicbrainz)). Daniel@0: :- use_module(library(semweb/rdf_db)). Daniel@0: :- use_module(library(termutils)). Daniel@0: :- use_module(library(rdfutils)). Daniel@0: :- use_module(library(stringutils)). Daniel@0: :- use_module(library(dcg/basics)). Daniel@0: % :- use_module(library(odbcutils)). Daniel@0: :- use_module(entailment(p2r)). Daniel@0: :- use_module(library(memo)). Daniel@0: % :- use_module(library(resolve)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: Daniel@0: :- rdf_register_prefix(charm,'http://dml.org/charm/'). Daniel@0: Daniel@0: :- setting(csv_database,string,"~/lib/charm/charm-1.csv","Location of CHARM colon-separated-values"). Daniel@0: :- setting(audio_root,ground,nothing,"Location of CHARM audio files"). Daniel@0: % item(Id) :- Daniel@0: % odbc_query(charm,"select id from cmr",row(Id)). Daniel@0: Daniel@0: % item(Id,Prop,Val) :- Daniel@0: % odbc_table_column(charm,cmr,Prop), Daniel@0: % \+ignore_column(Prop), Daniel@0: % qsql(charm,"select ~w from cmr where id=~d and ~w is not null and ~w!=''",[Prop,Id,Prop,Prop], row(Val)). Daniel@0: Daniel@0: % ignore_column(id). Daniel@0: % ignore_column(digital_eq). Daniel@0: % ignore_column(eq_base). Daniel@0: % ignore_column(eq_mid). Daniel@0: % ignore_column(eq_top). Daniel@0: % ignore_column(old_id). Daniel@0: Daniel@0: map('TNo',tno). %? Daniel@0: Daniel@0: % work Daniel@0: map('Title',title,list(";",atom)). Daniel@0: map('Composer(s)',composer,list("/",composer)). Daniel@0: Daniel@0: % performance Daniel@0: map('Artist',performer,list("/",set(";",performer))). Daniel@0: map('Conductor',conductor,atom). Daniel@0: Daniel@0: map('Label',label,atom). Daniel@0: map('Series',series,atom). Daniel@0: map('Cat No.',cat_no,atom). Daniel@0: map('Size',size,number). Daniel@0: % map('Matrix No.',matrix_no,atom). Daniel@0: % map('Single Side No. (or other ref.)',single_side_no). Daniel@0: map('File Name',file_name,atom). Daniel@0: map('Notes',notes,atom). Daniel@0: map('Rec.Date (dd/mm/yyyy)', recording_date, date(old)). Daniel@0: Daniel@0: % transfer event (recording from vinyl to digital signal) Daniel@0: map('Speed', speed, number). Daniel@0: Daniel@0: % No need for this much detail really.. Daniel@0: % map('Stylus',stylus_size, number). Daniel@0: % map('Weight',stylus_weight, number). Daniel@0: % map('EQ bass',eq_bass). Daniel@0: % map('EQ mid',eq_mid). Daniel@0: % map('EQ top',eq_top). Daniel@0: % map('Digital EQ','digital_eq'). Daniel@0: % map('turnover',turnover). Daniel@0: map('tech notes', technical_notes, atom). Daniel@0: map('x-fer date', transfer_date, date(new)). Daniel@0: map('Transfer Engineer', transfer_engineer, atom). Daniel@0: Daniel@0: :- volatile_memo string_to_date(+atom,+string,-ground). Daniel@0: string_to_date(Era,X,Date) :- Daniel@0: string_codes(X,Codes), Daniel@0: once(phrase(charm_interval(Era,DD),Codes)), Daniel@0: charm_date_to_time(DD,Date). Daniel@0: Daniel@0: :- rdf_meta convert(+,+,o). Daniel@0: convert(string,X,literal(X)). Daniel@0: convert(atom,X,literal(Y)) :- atom_string(Y,X). Daniel@0: convert(number,X,literal(Y)) :- number_string(Y,X). Daniel@0: convert(date(E),X,literal(Date)) :- string_to_date(E,X,Date). Daniel@0: convert(set(Sep,Type),X,Y) :- Daniel@0: split_string(X,Sep,"\s",Xs), Daniel@0: member(Z,Xs), Daniel@0: convert(Type,Z,Y). Daniel@0: convert(list(Sep,Type),X,Y) :- Daniel@0: split_string(X,Sep,"\s",Xs), Daniel@0: member(Z,Xs), Daniel@0: convert(Type,Z,Y). Daniel@0: Daniel@0: convert(performer,X,Y) :- convert(atom,X,Y). Daniel@0: % convert(performer,X,literal(Y)) :- Daniel@0: % porter_stem:tokenize_atom(X,Tokens), Daniel@0: % phrase(charm_performer(Perf),Tokens), Daniel@0: % phrase(performer(Perf),Codes1), Daniel@0: % atom_codes(Y,Codes1). Daniel@0: Daniel@0: Daniel@0: convert(arranger,X,literal(Y)) :- atom_concat(X,' [arranger]',Y). Daniel@0: convert(writer,X,literal(Y)) :- atom_concat(X,' [writer]',Y). Daniel@0: Daniel@0: convert(composer,X,Y) :- Daniel@0: split_string_around(" arr. ",X,Composer,Arranger), !, Daniel@0: ( convert(composer,Composer,Y) Daniel@0: ; convert(arranger,Arranger,Y) Daniel@0: ). Daniel@0: Daniel@0: convert(composer,X,Y) :- Daniel@0: split_string_around(" - ",X,Composer,Writer), !, Daniel@0: ( convert(composer,Composer,Y) Daniel@0: ; convert(writer,Writer,Y) Daniel@0: ). Daniel@0: Daniel@0: convert(composer,X,literal(Y)) :- traditional(X,Z), !, format(atom(Y),'[traditional:~s]',[Z]). Daniel@0: convert(composer,X,literal(Y)) :- anonymous(X,Z), !, format(atom(Y),'[anonymous:~s]',[Z]). Daniel@0: convert(composer,X,literal(Y)) :- atom_string(Y,X). Daniel@0: Daniel@0: % charm_performer(agent(Tokens)) --> Daniel@0: Daniel@0: anonymous(X,Z) :- (string_concat("Anon",Y,X); string_concat("anon",Y,X)), strip_string(Y,Z). Daniel@0: traditional(X,Z) :- string_concat("Trad.",Y,X), strip_string(Y,Z). Daniel@0: Daniel@0: Daniel@0: pad_int(L,N,C1,C2) :- format(codes(C1,C2),'~`0t~d~*+',[N,L]). Daniel@0: Daniel@0: xsd_time(ymd(Y,M,D),xsd:date) --> pad_int(4,Y), "-", pad_int(2,M), "-", pad_int(2,D). Daniel@0: xsd_time(ym(Y,M),xsd:gYearMonth) --> pad_int(4,Y), "-", pad_int(2,M). Daniel@0: xsd_time(y(Y),xsd:gYear) --> pad_int(4,Y). Daniel@0: xsd_time(range(D1,_),Type) --> xsd_time(D1,Type). Daniel@0: Daniel@0: charm_date_to_time(Date,type(Type,Value)) :- Daniel@0: phrase(xsd_time(Date,Type1),Codes), Daniel@0: rdf_global_id(Type1,Type), Daniel@0: atom_codes(Value,Codes). Daniel@0: Daniel@0: year(old,Y) --> integer(YY), { YY>=100 -> Y=YY ; Y is YY+1900 }. Daniel@0: year(new,Y) --> integer(YY), { YY>=100 -> Y=YY ; Y is YY+2000 }. Daniel@0: month(M) --> integer(M), {between(1,12,M)}. Daniel@0: day(D) --> integer(D), {between(1,31,D)}. Daniel@0: Daniel@0: charm_date(E,ymd(Y,M,D)) --> year(E,Y), "-", month(M), "-", day(D). Daniel@0: charm_date(E,ymd(Y,M,D)) --> day(D), "-", month(M), "-", year(E,Y). Daniel@0: charm_date(E,ymd(Y,M,D)) --> day(D), "/", month(M), "/", year(E,Y). Daniel@0: charm_date(E,ymd(Y,M,D)) --> day(D), ".", month(M), ".", year(E,Y). Daniel@0: charm_date(E,ym(Y,M)) --> year(E,Y), "-", month(M). Daniel@0: charm_date(E,ym(Y,M)) --> month(M), "/", year(E,Y). Daniel@0: charm_date(E,y(Y)) --> year(E,Y). Daniel@0: Daniel@0: charm_interval(_,range(y(Y1),y(Y2))) --> Daniel@0: integer(Y1), {Y1>=100}, "-", Daniel@0: integer(YY), {YY>12}, Daniel@0: { YY<100 -> Y2=1900+YY; Y2=YY }. Daniel@0: Daniel@0: charm_interval(E,Int) --> Daniel@0: charm_date(E,D1), Daniel@0: ( "--", charm_date(E,D2), {Int=range(D1,D2)} Daniel@0: ; {Int=D1} Daniel@0: ). Daniel@0: Daniel@0: Daniel@0: rdf(charm:title, rdfs:subPropertyOf, dc:title) <== true. Daniel@0: rdf(charm:enc(Id), charm:enc(Prop), Obj) <== Daniel@0: setting(csv_database,Pattern), Daniel@0: expand_file_name(Pattern,[DBFile]), Daniel@0: csv_to_rdf(DBFile,Id,Prop,Obj). Daniel@0: Daniel@0: csv_to_rdf(DBFile,Id,Prop,Obj) :- Daniel@0: once(csv_read_file_row(DBFile,Header,[convert(false),line(1)])), Daniel@0: functor(Header,row,NumCols), Daniel@0: functor(Row,row,NumCols), Daniel@0: arg(N,Header,' I.D.'), Daniel@0: arg(N,Row,Id), Daniel@0: csv_read_file_row(DBFile,Row,[convert(false),line(L)]), L>1, Daniel@0: status("Importing charm: ~w",[Id]), Daniel@0: map_row(Header,Row,Prop,Obj). Daniel@0: Daniel@0: null_value(""). Daniel@0: null_value("na"). Daniel@0: null_value("n/a"). Daniel@0: null_value("#VALUE!"). Daniel@0: Daniel@0: map_row(Header,Row,Pred,Obj) :- Daniel@0: arg(I,Header,Col), arg(I,Row,Val1), Daniel@0: map(Col,Pred,Type), Daniel@0: strip_string(Val1,Val), \+null_value(Val), Daniel@0: ( convert(Type,Val,Obj) *-> true Daniel@0: ; print_message(warning,conversion_failed(Col,Type,Val)), Daniel@0: format(atom(Lit),'FAILED(~q)',[Val]), % fail Daniel@0: Obj=literal(Lit) Daniel@0: ). Daniel@0: Daniel@0: % Old MYSQL version Daniel@0: % rdf(charm:num(4,Id), charm:enc(Prop), literal(Val)) <== Daniel@0: % item(Id), Daniel@0: % status("Importing charm:~d",[Id]), Daniel@0: % item(Id,Prop,Val). Daniel@0: Daniel@0: Daniel@0: :- public import/0. Daniel@0: % import :- with_odbc(charm, assert_all(charm_p2r)). Daniel@0: import :- assert_all(charm_p2r). Daniel@0: Daniel@0: :- public audio_file/3. Daniel@0: audio_file(URI,Path,just(flac)) :- Daniel@0: rdf(URI,charm:file_name,literal(FileName)), Daniel@0: setting(audio_root,just(Root)), Daniel@0: atomic_list_concat([Root,'/',FileName,'.',flac],Path). Daniel@0: Daniel@0: audio_link(Type,URI,URL) :- Daniel@0: member(Type,[mp3,flac]), Daniel@0: rdf(URI,charm:file_name,literal(Filename)), Daniel@0: ( sub_atom(Filename,_,_,_,'£') Daniel@0: -> atom_codes(Filename,C1), Daniel@0: fix_url(C1,C2), Daniel@0: atom_codes(Filename2,C2) Daniel@0: ; Filename2=Filename Daniel@0: ), Daniel@0: format(atom(URL),'http://charm.cchcdn.net/audio/~w/~w.~w',[Type,Filename2,Type]). Daniel@0: Daniel@0: fix_url([],[]). Daniel@0: fix_url([0'£|C1],[0'%, 0'A, 0'3|C2]) :- !, fix_url(C1,C2). Daniel@0: fix_url([C|C1],[C|C2]) :- !, fix_url(C1,C2).