Mercurial > hg > dml-open-cliopatria
diff cpack/dml/lib/ilm_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/ilm_p2r.pl Tue Feb 09 21:05:06 2016 +0100 @@ -0,0 +1,168 @@ +/* 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(ilm_p2r, []). + +/** <module> Access to ILM database + */ + + +:- use_module(library(odbc)). +:- use_module(library(musicbrainz)). +:- use_module(library(semweb/rdf_db)). +:- use_module(library(termutils)). +:- use_module(library(odbcutils)). +:- use_module(library(rdfutils)). +:- use_module(library(dcg_core)). +:- use_module(library(dcg/basics)). +:- use_module(entailment(p2r)). +:- use_module(cliopatria(hooks)). + +:- set_prolog_flag(double_quotes,string). + +:- rdf_register_prefix(ilm,'http://dml.org/ilm/'). + +:- setting( ilm_genres,list(atom), + ['Classical','Jazz','Latin','Blues','Folk','Electronic','Reggae','Rock & Roll'], + "List of ILM genre names to import"). + +:- public import/0. +import :- with_odbc(ilm, assert_all(ilm_p2r)). + +:- rdf_meta map(+,r,+,o). + +% ---------------------------- utilities ----------------------------- + +%% genre_list_member(-Genre:uri, +GenreList:atom) is nondet. +genre_list_member(Genre,Atom) :- + parse_list_member(';',Atom,GenreName), + number_string(GenreId,GenreName), + uripattern:pattern_uri(ilm:genre/num(5,GenreId),Genre). + +%% parse_list_member(+Sep:text,+Text:text,-Item:string) is nondet. +parse_list_member(Sep,Atom,Item) :- + split_string(Atom,Sep,'',Items), + member(Item,Items). +% ---------------------- getting stuff out of database --------------------- + +genre_album(Genre,AlbumId) :- + qsql(ilm,"select distinct album_id from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId)). + +album_facet(AlbumId,Prop-Val) :- entity_facet(album,AlbumId,Prop,Val). + +genre_track(Genre,AlbumId-TrackNo) :- + qsql(ilm,"select album_id, track_no from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId,TrackNo)). + +track_facet(AlbumId-TrackNo,Prop-Val) :- entity_facet(track,AlbumId-TrackNo,Prop,Val). + +query_columns(album, + [ album_title, product_artist, product_classifications, product_genre, + product_release_year, product_label, product_upc ]). +query_columns(track, + [ assets_online, artist_name, comment, genre_id, release_year, song_title, + track_classifications, track_duration, track_isrc]). + +entity_facet(Type,Id,Prop,Val) :- + query_columns(Type,Cols), + pairs_keys_values(Pairs,Cols,Vals), + Row =.. [row|Vals], + phrase(entity_query(Type,Id,Cols),Codes,[]), + qsql(ilm,'~s',[Codes],Row), + member(Prop-Val,Pairs), + Val\='$null$', + Val\=''. + +entity_query(album,AlbumId,Cols) --> + "select ", + seqmap_with_sep(",",atom,Cols), + " from assets where album_id=", number(AlbumId). + +entity_query(track,AlbumId-TrackNo,Cols) --> + "select ", + seqmap_with_sep(",",atom,Cols), + " from assets where album_id=", number(AlbumId), + " and track_no=", number(TrackNo). + +include_genre(GenreId,Genre) :- + setting(ilm_genres,Genres), + member(Genre,Genres), + qsql(ilm,"select ID from classifications where name='~s'",[Genre],row(GenreId)). + + +% -------------------- mapping to rdf ---------------------------------- + + +rdf(ilm:genre/num(5,GenreID),rdf:type,mo:'Genre'), +rdf(ilm:genre/num(5,GenreID),rdfs:label,literal(GenreName)) <== + odbc_query(ilm,"select ID, name from classifications",row(GenreID,GenreName)). + +rdf(ilm:album/num(AlbumId), Pred, Obj) <== + include_genre(GenreId,GenreName), + status("Querying albums of genre ~w...",[GenreName]), + genre_album(GenreId,AlbumId), + status("Importing ILM albums, genre ~w: ~d",[GenreName, AlbumId]), + album_facet(AlbumId,Facet), + map(Facet,Pred,Obj). + +rdf(ilm:track/num(AlbumId)/num(TrackNo), Pred, Obj) <== + include_genre(GenreId,GenreName), + status("Querying tracks of genre ~w...",[GenreName]), + genre_track(GenreId,AlbumId-TrackNo), + status("Importing ILM tracks, genre ~w: ~d/~d",[GenreName, AlbumId, TrackNo]), + ( Facet=track_no-TrackNo + ; Facet=album_id-AlbumId + ; track_facet(AlbumId-TrackNo,Facet) + ), + map(Facet,Pred,Obj). + +map(Prop-Val,Pred,Obj) :- + ( map(Prop,Pred,Val,Obj) *-> true + ; print_message(warning,ilm_p2r:unrecognized_column(Prop,Val)), fail + ). + + +% album level +map(album_title , dc:title, X, literal(X)). +map(product_label , mo:label, X, literal(X)). +map(product_artist , ilm:artist, X, literal(X)). +map(product_upc , ilm:upc, X, literal(X)). +map(product_release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y). +map(product_classifications, mo:genre, Atom, Genre) :- genre_list_member(Genre,Atom). +map(product_genre, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj). + +% track level +map(genre_id, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj). +map(album_id, ilm:album, X, Album) :- uripattern:pattern_uri(ilm:album/num(X),Album). +map(track_no, mo:track_number, X, literal(type(xsd:nonNegativeInteger,X))). +map(track_isrc, mo:isrc, X, literal(type(xsd:string,X))). +map(song_title, dc:title, X, literal(X)). +map(comment, ilm:comment, X, literal(X)). +map(artist_name, ilm:artist, X, literal(X)). +map(track_classifications, mo:genre, X, Genre) :- genre_list_member(Genre,X). +map(track_duration, mo:duration, X, literal(type(xsd:float,Millis))) :- + parse_duration_millis(X,Millis). + +map(release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y). +map(assets_online, ilm:asset_online, Atom, literal(Type)) :- + parse_list_member(',',Atom,TypeS), + atom_string(Type,TypeS). + +% map(P,ilm:P,date(Y,M,D),literal(type(xsd:date,Date))) :- +% format_time(atom(Date),'%F',date(Y,M,D)). +% map(P,ilm:P,timestamp(YY,MM,DD,H,M,S,_),literal(type(xsd:dateTime, DateTime))) :- !, +% format_time(atom(DateTime),'%FT%T',date(YY,MM,DD,H,M,S,0,-,-)).