diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/mazurka_p2r.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,115 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(mazurka_p2r, []).
+
+/** <module> Access to beets database
+ */
+
+
+% :- use_module(library(odbc)).
+:- use_module(library(csv)).
+:- use_module(library(musicbrainz)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(termutils)).
+:- use_module(library(rdfutils)).
+:- use_module(library(stringutils)).
+:- use_module(library(dcg/basics)).
+:- use_module(entailment(p2r)).
+:- use_module(library(memo)).
+
+:- set_prolog_flag(double_quotes,string).
+
+:- rdf_register_prefix(mazurka,'http://dml.org/mazurka/').
+
+:- setting(csv_database,string,"~/lib/mazurka/mazurka-discography.txt","Location of Mazurka tab-separated-values").
+:- setting(audio_root,ground,nothing,"Location of Mazurka audio files").
+
+% :- rdf_meta convert(+,+,o).
+% convert(string,X,literal(X)).
+% convert(atom,X,literal(Y)) :- atom_string(Y,X).
+% convert(number,X,literal(Y)) :- number_string(Y,X).
+% convert(date(E),X,literal(Date)) :- string_to_date(E,X,Date).
+
+rdf(mazurka:title, rdfs:subPropertyOf, dc:title) <== true.
+rdf(mazurka:enc(Id), Prop, Obj) <==
+   setting(csv_database,Pattern),
+   expand_file_name(Pattern,[DBFile]),
+   csv_to_rdf(DBFile,Id,Prop,Obj).
+
+csv_to_rdf(DBFile,Id,Prop,Obj) :-
+   once(csv_read_file_row(DBFile,Header,[convert(false),separator(0'\t), line(1)])),
+   functor(Header,row,NumCols),
+   functor(Row,row,NumCols),
+   row_field(Header-Row,pid,Id),
+   csv_read_file_row(DBFile,Row,[convert(false),separator(0'\t), line(L)]), L>1,
+   status("Importing mazurka: ~w",[Id]),
+   row_triple(Header-Row,Prop,Obj).
+   % rdf_global_object(Obj1,Obj).
+
+:- rdf_meta row_triple(+,r,o).
+row_triple(_,mazurka:composer,literal('Chopin')).
+row_triple(HR,mazurka:pid,literal(PID)) :- row_field(HR,pid,PID).
+row_triple(HR,Prop,Val) :-
+   row_field(HR,opus,OpusNum),
+   row_field(HR,key,Key),
+   atomic_list_concat([Opus,Number],'.',OpusNum),
+   work_triple(Key,Opus,Number,Prop,Val).
+
+row_triple(HR,mazurka:performer,literal(Perf)) :- row_field(HR,performer,Perf).
+row_triple(HR,mazurka:recording_date,literal(type(T,Year))) :- row_field(HR,year,Year), rdf_global_id(xsd:gYear,T).
+row_triple(HR,mazurka:duration,literal(type(T,X))) :- row_field(HR,seconds,A), atom_number(A,X), rdf_global_id(xsd:int,T).
+row_triple(HR,mazurka:label,literal(Label)) :- row_field(HR,label,Label).
+
+:- rdf_meta work_triple(+,+,+,r,o).
+work_triple(K,O,N,mazurka:title,literal(T)) :- format(atom(T),"Mazurka in ~w, op.~w, no.~w",[K,O,N]).
+work_triple(K,_,_,mazurka:key,literal(K)).
+work_triple(_,O,_,mazurka:opus,literal(O)).
+work_triple(_,_,N,mazurka:number,literal(N)).
+work_triple(_,O,N,mazurka:score,Score) :- 
+   format(atom(Score),"kern:/classical/chopin/mazurka/mazurka~|~`0t~w~2+-~w.krn",[O,N]).
+   
+
+row_field(Header-Row,Name,Value) :- arg(N,Header,Name), arg(N,Row,Value).
+% null_value("-").
+
+:- public import/0.
+import :- assert_all(mazurka_p2r).
+
+:- public audio_file/3.
+audio_file(URI,Path,just(Fmt)) :-
+   rdf(URI,mazurka:pid,literal(PID)),
+   rdf(URI,mazurka:opus,literal(Opus)),
+   rdf(URI,mazurka:number,literal(Number)),
+   setting(audio_root,just(RootPatt)),
+   expand_file_name(RootPatt,[Root]),
+   member(Fmt-Ext,[aac-mp4,wav-wav]),
+   format(atom(Path),"~w/mazurka~|~`0t~w~2+-~w/pid~w.~w",[Root,Opus,Number,PID,Ext]),
+   exists_file(Path).
+
+% audio_link(Type,URI,URL) :-
+%    member(Type,[mp3,flac]),
+%    rdf(URI,charm:file_name,literal(Filename)),
+%    (  sub_atom(Filename,_,_,_,'£')
+%    -> atom_codes(Filename,C1),
+%       fix_url(C1,C2),
+%       atom_codes(Filename2,C2)
+%    ;  Filename2=Filename
+%    ),
+%    format(atom(URL),'http://charm.cchcdn.net/audio/~w/~w.~w',[Type,Filename2,Type]).
+