comparison cpack/dml/lib/mazurka_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(mazurka_p2r, []).
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(entailment(p2r)).
34 :- use_module(library(memo)).
35
36 :- set_prolog_flag(double_quotes,string).
37
38 :- rdf_register_prefix(mazurka,'http://dml.org/mazurka/').
39
40 :- setting(csv_database,string,"~/lib/mazurka/mazurka-discography.txt","Location of Mazurka tab-separated-values").
41 :- setting(audio_root,ground,nothing,"Location of Mazurka audio files").
42
43 % :- rdf_meta convert(+,+,o).
44 % convert(string,X,literal(X)).
45 % convert(atom,X,literal(Y)) :- atom_string(Y,X).
46 % convert(number,X,literal(Y)) :- number_string(Y,X).
47 % convert(date(E),X,literal(Date)) :- string_to_date(E,X,Date).
48
49 rdf(mazurka:title, rdfs:subPropertyOf, dc:title) <== true.
50 rdf(mazurka:enc(Id), Prop, Obj) <==
51 setting(csv_database,Pattern),
52 expand_file_name(Pattern,[DBFile]),
53 csv_to_rdf(DBFile,Id,Prop,Obj).
54
55 csv_to_rdf(DBFile,Id,Prop,Obj) :-
56 once(csv_read_file_row(DBFile,Header,[convert(false),separator(0'\t), line(1)])),
57 functor(Header,row,NumCols),
58 functor(Row,row,NumCols),
59 row_field(Header-Row,pid,Id),
60 csv_read_file_row(DBFile,Row,[convert(false),separator(0'\t), line(L)]), L>1,
61 status("Importing mazurka: ~w",[Id]),
62 row_triple(Header-Row,Prop,Obj).
63 % rdf_global_object(Obj1,Obj).
64
65 :- rdf_meta row_triple(+,r,o).
66 row_triple(_,mazurka:composer,literal('Chopin')).
67 row_triple(HR,mazurka:pid,literal(PID)) :- row_field(HR,pid,PID).
68 row_triple(HR,Prop,Val) :-
69 row_field(HR,opus,OpusNum),
70 row_field(HR,key,Key),
71 atomic_list_concat([Opus,Number],'.',OpusNum),
72 work_triple(Key,Opus,Number,Prop,Val).
73
74 row_triple(HR,mazurka:performer,literal(Perf)) :- row_field(HR,performer,Perf).
75 row_triple(HR,mazurka:recording_date,literal(type(T,Year))) :- row_field(HR,year,Year), rdf_global_id(xsd:gYear,T).
76 row_triple(HR,mazurka:duration,literal(type(T,X))) :- row_field(HR,seconds,A), atom_number(A,X), rdf_global_id(xsd:int,T).
77 row_triple(HR,mazurka:label,literal(Label)) :- row_field(HR,label,Label).
78
79 :- rdf_meta work_triple(+,+,+,r,o).
80 work_triple(K,O,N,mazurka:title,literal(T)) :- format(atom(T),"Mazurka in ~w, op.~w, no.~w",[K,O,N]).
81 work_triple(K,_,_,mazurka:key,literal(K)).
82 work_triple(_,O,_,mazurka:opus,literal(O)).
83 work_triple(_,_,N,mazurka:number,literal(N)).
84 work_triple(_,O,N,mazurka:score,Score) :-
85 format(atom(Score),"kern:/classical/chopin/mazurka/mazurka~|~`0t~w~2+-~w.krn",[O,N]).
86
87
88 row_field(Header-Row,Name,Value) :- arg(N,Header,Name), arg(N,Row,Value).
89 % null_value("-").
90
91 :- public import/0.
92 import :- assert_all(mazurka_p2r).
93
94 :- public audio_file/3.
95 audio_file(URI,Path,just(Fmt)) :-
96 rdf(URI,mazurka:pid,literal(PID)),
97 rdf(URI,mazurka:opus,literal(Opus)),
98 rdf(URI,mazurka:number,literal(Number)),
99 setting(audio_root,just(RootPatt)),
100 expand_file_name(RootPatt,[Root]),
101 member(Fmt-Ext,[aac-mp4,wav-wav]),
102 format(atom(Path),"~w/mazurka~|~`0t~w~2+-~w/pid~w.~w",[Root,Opus,Number,PID,Ext]),
103 exists_file(Path).
104
105 % audio_link(Type,URI,URL) :-
106 % member(Type,[mp3,flac]),
107 % rdf(URI,charm:file_name,literal(Filename)),
108 % ( sub_atom(Filename,_,_,_,'£')
109 % -> atom_codes(Filename,C1),
110 % fix_url(C1,C2),
111 % atom_codes(Filename2,C2)
112 % ; Filename2=Filename
113 % ),
114 % format(atom(URL),'http://charm.cchcdn.net/audio/~w/~w.~w',[Type,Filename2,Type]).
115