annotate cpack/dml/lib/charm_p2r.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
rev   line source
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(charm_p2r, [ audio_link/3 ]).
Daniel@0 20
Daniel@0 21 /** <module> Access to beets database
Daniel@0 22 */
Daniel@0 23
Daniel@0 24
Daniel@0 25 % :- use_module(library(odbc)).
Daniel@0 26 :- use_module(library(csv)).
Daniel@0 27 :- use_module(library(musicbrainz)).
Daniel@0 28 :- use_module(library(semweb/rdf_db)).
Daniel@0 29 :- use_module(library(termutils)).
Daniel@0 30 :- use_module(library(rdfutils)).
Daniel@0 31 :- use_module(library(stringutils)).
Daniel@0 32 :- use_module(library(dcg/basics)).
Daniel@0 33 % :- use_module(library(odbcutils)).
Daniel@0 34 :- use_module(entailment(p2r)).
Daniel@0 35 :- use_module(library(memo)).
Daniel@0 36 % :- use_module(library(resolve)).
Daniel@0 37
Daniel@0 38 :- set_prolog_flag(double_quotes,string).
Daniel@0 39
Daniel@0 40 :- rdf_register_prefix(charm,'http://dml.org/charm/').
Daniel@0 41
Daniel@0 42 :- setting(csv_database,string,"~/lib/charm/charm-1.csv","Location of CHARM colon-separated-values").
Daniel@0 43 :- setting(audio_root,ground,nothing,"Location of CHARM audio files").
Daniel@0 44 % item(Id) :-
Daniel@0 45 % odbc_query(charm,"select id from cmr",row(Id)).
Daniel@0 46
Daniel@0 47 % item(Id,Prop,Val) :-
Daniel@0 48 % odbc_table_column(charm,cmr,Prop),
Daniel@0 49 % \+ignore_column(Prop),
Daniel@0 50 % qsql(charm,"select ~w from cmr where id=~d and ~w is not null and ~w!=''",[Prop,Id,Prop,Prop], row(Val)).
Daniel@0 51
Daniel@0 52 % ignore_column(id).
Daniel@0 53 % ignore_column(digital_eq).
Daniel@0 54 % ignore_column(eq_base).
Daniel@0 55 % ignore_column(eq_mid).
Daniel@0 56 % ignore_column(eq_top).
Daniel@0 57 % ignore_column(old_id).
Daniel@0 58
Daniel@0 59 map('TNo',tno). %?
Daniel@0 60
Daniel@0 61 % work
Daniel@0 62 map('Title',title,list(";",atom)).
Daniel@0 63 map('Composer(s)',composer,list("/",composer)).
Daniel@0 64
Daniel@0 65 % performance
Daniel@0 66 map('Artist',performer,list("/",set(";",performer))).
Daniel@0 67 map('Conductor',conductor,atom).
Daniel@0 68
Daniel@0 69 map('Label',label,atom).
Daniel@0 70 map('Series',series,atom).
Daniel@0 71 map('Cat No.',cat_no,atom).
Daniel@0 72 map('Size',size,number).
Daniel@0 73 % map('Matrix No.',matrix_no,atom).
Daniel@0 74 % map('Single Side No. (or other ref.)',single_side_no).
Daniel@0 75 map('File Name',file_name,atom).
Daniel@0 76 map('Notes',notes,atom).
Daniel@0 77 map('Rec.Date (dd/mm/yyyy)', recording_date, date(old)).
Daniel@0 78
Daniel@0 79 % transfer event (recording from vinyl to digital signal)
Daniel@0 80 map('Speed', speed, number).
Daniel@0 81
Daniel@0 82 % No need for this much detail really..
Daniel@0 83 % map('Stylus',stylus_size, number).
Daniel@0 84 % map('Weight',stylus_weight, number).
Daniel@0 85 % map('EQ bass',eq_bass).
Daniel@0 86 % map('EQ mid',eq_mid).
Daniel@0 87 % map('EQ top',eq_top).
Daniel@0 88 % map('Digital EQ','digital_eq').
Daniel@0 89 % map('turnover',turnover).
Daniel@0 90 map('tech notes', technical_notes, atom).
Daniel@0 91 map('x-fer date', transfer_date, date(new)).
Daniel@0 92 map('Transfer Engineer', transfer_engineer, atom).
Daniel@0 93
Daniel@0 94 :- volatile_memo string_to_date(+atom,+string,-ground).
Daniel@0 95 string_to_date(Era,X,Date) :-
Daniel@0 96 string_codes(X,Codes),
Daniel@0 97 once(phrase(charm_interval(Era,DD),Codes)),
Daniel@0 98 charm_date_to_time(DD,Date).
Daniel@0 99
Daniel@0 100 :- rdf_meta convert(+,+,o).
Daniel@0 101 convert(string,X,literal(X)).
Daniel@0 102 convert(atom,X,literal(Y)) :- atom_string(Y,X).
Daniel@0 103 convert(number,X,literal(Y)) :- number_string(Y,X).
Daniel@0 104 convert(date(E),X,literal(Date)) :- string_to_date(E,X,Date).
Daniel@0 105 convert(set(Sep,Type),X,Y) :-
Daniel@0 106 split_string(X,Sep,"\s",Xs),
Daniel@0 107 member(Z,Xs),
Daniel@0 108 convert(Type,Z,Y).
Daniel@0 109 convert(list(Sep,Type),X,Y) :-
Daniel@0 110 split_string(X,Sep,"\s",Xs),
Daniel@0 111 member(Z,Xs),
Daniel@0 112 convert(Type,Z,Y).
Daniel@0 113
Daniel@0 114 convert(performer,X,Y) :- convert(atom,X,Y).
Daniel@0 115 % convert(performer,X,literal(Y)) :-
Daniel@0 116 % porter_stem:tokenize_atom(X,Tokens),
Daniel@0 117 % phrase(charm_performer(Perf),Tokens),
Daniel@0 118 % phrase(performer(Perf),Codes1),
Daniel@0 119 % atom_codes(Y,Codes1).
Daniel@0 120
Daniel@0 121
Daniel@0 122 convert(arranger,X,literal(Y)) :- atom_concat(X,' [arranger]',Y).
Daniel@0 123 convert(writer,X,literal(Y)) :- atom_concat(X,' [writer]',Y).
Daniel@0 124
Daniel@0 125 convert(composer,X,Y) :-
Daniel@0 126 split_string_around(" arr. ",X,Composer,Arranger), !,
Daniel@0 127 ( convert(composer,Composer,Y)
Daniel@0 128 ; convert(arranger,Arranger,Y)
Daniel@0 129 ).
Daniel@0 130
Daniel@0 131 convert(composer,X,Y) :-
Daniel@0 132 split_string_around(" - ",X,Composer,Writer), !,
Daniel@0 133 ( convert(composer,Composer,Y)
Daniel@0 134 ; convert(writer,Writer,Y)
Daniel@0 135 ).
Daniel@0 136
Daniel@0 137 convert(composer,X,literal(Y)) :- traditional(X,Z), !, format(atom(Y),'[traditional:~s]',[Z]).
Daniel@0 138 convert(composer,X,literal(Y)) :- anonymous(X,Z), !, format(atom(Y),'[anonymous:~s]',[Z]).
Daniel@0 139 convert(composer,X,literal(Y)) :- atom_string(Y,X).
Daniel@0 140
Daniel@0 141 % charm_performer(agent(Tokens)) -->
Daniel@0 142
Daniel@0 143 anonymous(X,Z) :- (string_concat("Anon",Y,X); string_concat("anon",Y,X)), strip_string(Y,Z).
Daniel@0 144 traditional(X,Z) :- string_concat("Trad.",Y,X), strip_string(Y,Z).
Daniel@0 145
Daniel@0 146
Daniel@0 147 pad_int(L,N,C1,C2) :- format(codes(C1,C2),'~`0t~d~*+',[N,L]).
Daniel@0 148
Daniel@0 149 xsd_time(ymd(Y,M,D),xsd:date) --> pad_int(4,Y), "-", pad_int(2,M), "-", pad_int(2,D).
Daniel@0 150 xsd_time(ym(Y,M),xsd:gYearMonth) --> pad_int(4,Y), "-", pad_int(2,M).
Daniel@0 151 xsd_time(y(Y),xsd:gYear) --> pad_int(4,Y).
Daniel@0 152 xsd_time(range(D1,_),Type) --> xsd_time(D1,Type).
Daniel@0 153
Daniel@0 154 charm_date_to_time(Date,type(Type,Value)) :-
Daniel@0 155 phrase(xsd_time(Date,Type1),Codes),
Daniel@0 156 rdf_global_id(Type1,Type),
Daniel@0 157 atom_codes(Value,Codes).
Daniel@0 158
Daniel@0 159 year(old,Y) --> integer(YY), { YY>=100 -> Y=YY ; Y is YY+1900 }.
Daniel@0 160 year(new,Y) --> integer(YY), { YY>=100 -> Y=YY ; Y is YY+2000 }.
Daniel@0 161 month(M) --> integer(M), {between(1,12,M)}.
Daniel@0 162 day(D) --> integer(D), {between(1,31,D)}.
Daniel@0 163
Daniel@0 164 charm_date(E,ymd(Y,M,D)) --> year(E,Y), "-", month(M), "-", day(D).
Daniel@0 165 charm_date(E,ymd(Y,M,D)) --> day(D), "-", month(M), "-", year(E,Y).
Daniel@0 166 charm_date(E,ymd(Y,M,D)) --> day(D), "/", month(M), "/", year(E,Y).
Daniel@0 167 charm_date(E,ymd(Y,M,D)) --> day(D), ".", month(M), ".", year(E,Y).
Daniel@0 168 charm_date(E,ym(Y,M)) --> year(E,Y), "-", month(M).
Daniel@0 169 charm_date(E,ym(Y,M)) --> month(M), "/", year(E,Y).
Daniel@0 170 charm_date(E,y(Y)) --> year(E,Y).
Daniel@0 171
Daniel@0 172 charm_interval(_,range(y(Y1),y(Y2))) -->
Daniel@0 173 integer(Y1), {Y1>=100}, "-",
Daniel@0 174 integer(YY), {YY>12},
Daniel@0 175 { YY<100 -> Y2=1900+YY; Y2=YY }.
Daniel@0 176
Daniel@0 177 charm_interval(E,Int) -->
Daniel@0 178 charm_date(E,D1),
Daniel@0 179 ( "--", charm_date(E,D2), {Int=range(D1,D2)}
Daniel@0 180 ; {Int=D1}
Daniel@0 181 ).
Daniel@0 182
Daniel@0 183
Daniel@0 184 rdf(charm:title, rdfs:subPropertyOf, dc:title) <== true.
Daniel@0 185 rdf(charm:enc(Id), charm:enc(Prop), Obj) <==
Daniel@0 186 setting(csv_database,Pattern),
Daniel@0 187 expand_file_name(Pattern,[DBFile]),
Daniel@0 188 csv_to_rdf(DBFile,Id,Prop,Obj).
Daniel@0 189
Daniel@0 190 csv_to_rdf(DBFile,Id,Prop,Obj) :-
Daniel@0 191 once(csv_read_file_row(DBFile,Header,[convert(false),line(1)])),
Daniel@0 192 functor(Header,row,NumCols),
Daniel@0 193 functor(Row,row,NumCols),
Daniel@0 194 arg(N,Header,' I.D.'),
Daniel@0 195 arg(N,Row,Id),
Daniel@0 196 csv_read_file_row(DBFile,Row,[convert(false),line(L)]), L>1,
Daniel@0 197 status("Importing charm: ~w",[Id]),
Daniel@0 198 map_row(Header,Row,Prop,Obj).
Daniel@0 199
Daniel@0 200 null_value("").
Daniel@0 201 null_value("na").
Daniel@0 202 null_value("n/a").
Daniel@0 203 null_value("#VALUE!").
Daniel@0 204
Daniel@0 205 map_row(Header,Row,Pred,Obj) :-
Daniel@0 206 arg(I,Header,Col), arg(I,Row,Val1),
Daniel@0 207 map(Col,Pred,Type),
Daniel@0 208 strip_string(Val1,Val), \+null_value(Val),
Daniel@0 209 ( convert(Type,Val,Obj) *-> true
Daniel@0 210 ; print_message(warning,conversion_failed(Col,Type,Val)),
Daniel@0 211 format(atom(Lit),'FAILED(~q)',[Val]), % fail
Daniel@0 212 Obj=literal(Lit)
Daniel@0 213 ).
Daniel@0 214
Daniel@0 215 % Old MYSQL version
Daniel@0 216 % rdf(charm:num(4,Id), charm:enc(Prop), literal(Val)) <==
Daniel@0 217 % item(Id),
Daniel@0 218 % status("Importing charm:~d",[Id]),
Daniel@0 219 % item(Id,Prop,Val).
Daniel@0 220
Daniel@0 221
Daniel@0 222 :- public import/0.
Daniel@0 223 % import :- with_odbc(charm, assert_all(charm_p2r)).
Daniel@0 224 import :- assert_all(charm_p2r).
Daniel@0 225
Daniel@0 226 :- public audio_file/3.
Daniel@0 227 audio_file(URI,Path,just(flac)) :-
Daniel@0 228 rdf(URI,charm:file_name,literal(FileName)),
Daniel@0 229 setting(audio_root,just(Root)),
Daniel@0 230 atomic_list_concat([Root,'/',FileName,'.',flac],Path).
Daniel@0 231
Daniel@0 232 audio_link(Type,URI,URL) :-
Daniel@0 233 member(Type,[mp3,flac]),
Daniel@0 234 rdf(URI,charm:file_name,literal(Filename)),
Daniel@0 235 ( sub_atom(Filename,_,_,_,'£')
Daniel@0 236 -> atom_codes(Filename,C1),
Daniel@0 237 fix_url(C1,C2),
Daniel@0 238 atom_codes(Filename2,C2)
Daniel@0 239 ; Filename2=Filename
Daniel@0 240 ),
Daniel@0 241 format(atom(URL),'http://charm.cchcdn.net/audio/~w/~w.~w',[Type,Filename2,Type]).
Daniel@0 242
Daniel@0 243 fix_url([],[]).
Daniel@0 244 fix_url([0'£|C1],[0'%, 0'A, 0'3|C2]) :- !, fix_url(C1,C2).
Daniel@0 245 fix_url([C|C1],[C|C2]) :- !, fix_url(C1,C2).