diff cpack/dml/lib/beets_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/beets_p2r.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,160 @@
+/* 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(beets_p2r, []).
+
+/** <module> Access to beets database
+ */
+
+
+:- use_module(library(prosqlite)).
+:- use_module(library(musicbrainz)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(rdfutils)).
+:- use_module(entailment(p2r)).
+
+:- set_prolog_flag(double_quotes,string).
+
+:- rdf_register_prefix(beets,'http://dml.org/beets/props/item/').
+:- rdf_register_prefix(beets_album,'http://dml.org/beets/props/album/').
+:- rdf_register_prefix(audio,'audio:').
+:- rdf_register_prefix(dml,'http://dml.org/dml/').
+:- rdf_register_prefix(mb,'http://musicbrainz.org/').
+
+:- setting(db_file,string,"~/lib/beets/music-ro.db","Location of beets database").
+:- setting(audio_root,string,"/usr/local/share/Music/","Root of audio file directory tree").
+
+
+rdf(audio:tail(Rel), rdf:type, mo:'AudioFile'),
+rdf(audio:tail(Rel), mo:encoding, literal(Enc)) <==
+   setting(audio_root,Root),
+   expand_file_name(Root,[Root1]),
+   item(Id,path,Path),
+   item(Id,format,Enc),
+   atom_concat(Root1,Rel,Path).
+
+rdf(audio:tail(Rel), beets:enc(Prop), literal(Val)) <==
+   audio_item_path(Id,Rel),
+   item(Id,Prop,Val1), 
+   (  Prop=path -> exists_file(Val1); true),
+   as_typed_literal(Val1,Val).
+
+rdf(Signal,rdf:type,mo:'Signal') <==
+   item(_,mb_trackid,ID), % track id is actually a Recording.
+   mb_id_uri(recording,ID,Signal).
+
+rdf(Signal,mo:available_as,audio:tail(Rel)) <==
+   setting(audio_root,Root),
+   expand_file_name(Root,[Root1]),
+   item(Id,path,Path),
+   exists_file(Path),
+   atom_concat(Root1,Rel,Path),
+   item(Id,mb_trackid,ID), % track id is actually a Recording.
+  % need to ask Linkedbrainz to get Signal URI
+   mb_id_uri(recording,ID,Signal).
+   
+rdf(audio:tail(Rel), dml:file_artist, URI) <==
+   audio_item_path(Id,Rel),
+   item(Id,mb_artistid,ID),
+   mb_id_uri(artist,ID,URI).
+
+rdf(audio:tail(Rel), dml:file_release, URI) <==
+   audio_item_path(Id,Rel),
+   item(Id,mb_albumid,ID),
+   mb_id_uri(release,ID,URI).
+
+rdf(audio:tail(Rel), dml:file_recording, URI) <==
+   audio_item_path(Id,Rel),
+   item(Id,mb_trackid,ID),
+   mb_id_uri(recording,ID,URI).
+
+% rdf(URI,mo:release_type,mo:
+rdf(URI,rdf:type,mo:'Release') <==
+   item(_,mb_albumid,ID),
+   mb_id_uri(release,ID,URI).
+
+audio_item_path(Id,Rel) :-
+   setting(audio_root,Root),
+   expand_file_name(Root,[Root1]),
+   item(Id,path,Path),
+   atom_concat(Root1,Rel,Path).
+
+:- public import/0.
+import :- with_beets_db(assert_all(beets_p2r)).
+
+with_beets_db(Goal) :-
+   setting(db_file,DBFile),
+   expand_file_name(DBFile,[Path|_]),
+   setup_call_cleanup(
+      sqlite_connect(Path,Con,[alias(beets),ext(''),as_predicates(true),arity(unary),at_module(beets)]),
+      Goal,
+      sqlite_disconnect(Con)).
+
+:- dynamic beets:items/1.
+item(Id) :- beets:items([id=Id]).
+
+item(Id,path,Path) :-
+   (  var(Path) -> beets:items([id=Id,path=Path])
+   ;  var(Id)   -> sqlite_format_query(beets,"select id from items where path like '~s'"-[Path],row(Id))
+   ;  sqlite_format_query(beets,"select null from items where id=~w and path like '~s'"-[Id,Path],row(_))
+   ).
+
+item(Id,Prop,Val) :-
+   table_column(items,Prop), Prop\=path, Prop\=comp,
+   beets:items([id=Id,Prop=Val]), 
+   \+invalid(Prop,Val).
+   
+
+% album(Id) :- beets:albums([id=Id]).
+% album(Id,Prop,Val) :-
+%    table_column(albums,Prop),
+%    beets:albums([id=Id,Prop=Val]), Val\=''.
+
+table_column(T,C) :-
+   sqlite_table_column(beets,T,C1), C=C1.
+
+invalid(_,'').
+invalid(Prop,0) :- nonzero(Prop).
+invalid(mtime,0.0).
+
+nonzero(bitdepth).
+nonzero(bitrate).
+nonzero(samplerate).
+nonzero(track).
+nonzero(tracktotal).
+nonzero(disc).
+nonzero(disctotal).
+nonzero(bpm).
+nonzero(day).
+nonzero(month).
+nonzero(year).
+nonzero(original_day).
+nonzero(original_month).
+nonzero(original_year).
+
+:- public audio_file/3.
+
+audio_file(URI,File,just(T0)) :-
+   rdf(URI,beets:path,literal(File)), !,
+   rdf(URI,beets:format,literal(F0)),
+   format_type(F0,T0).
+
+format_type('MP3',mp3).
+format_type('OGG',ogg).
+format_type('AAC',aac).
+format_type('ALAC',mp4). % !!! ??