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