Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(ilm_p2r, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 /** <module> Access to ILM database
|
Daniel@0
|
22 */
|
Daniel@0
|
23
|
Daniel@0
|
24
|
Daniel@0
|
25 :- use_module(library(odbc)).
|
Daniel@0
|
26 :- use_module(library(musicbrainz)).
|
Daniel@0
|
27 :- use_module(library(semweb/rdf_db)).
|
Daniel@0
|
28 :- use_module(library(termutils)).
|
Daniel@0
|
29 :- use_module(library(odbcutils)).
|
Daniel@0
|
30 :- use_module(library(rdfutils)).
|
Daniel@0
|
31 :- use_module(library(dcg_core)).
|
Daniel@0
|
32 :- use_module(library(dcg/basics)).
|
Daniel@0
|
33 :- use_module(entailment(p2r)).
|
Daniel@0
|
34 :- use_module(cliopatria(hooks)).
|
Daniel@0
|
35
|
Daniel@0
|
36 :- set_prolog_flag(double_quotes,string).
|
Daniel@0
|
37
|
Daniel@0
|
38 :- rdf_register_prefix(ilm,'http://dml.org/ilm/').
|
Daniel@0
|
39
|
Daniel@0
|
40 :- setting( ilm_genres,list(atom),
|
Daniel@0
|
41 ['Classical','Jazz','Latin','Blues','Folk','Electronic','Reggae','Rock & Roll'],
|
Daniel@0
|
42 "List of ILM genre names to import").
|
Daniel@0
|
43
|
Daniel@0
|
44 :- public import/0.
|
Daniel@0
|
45 import :- with_odbc(ilm, assert_all(ilm_p2r)).
|
Daniel@0
|
46
|
Daniel@0
|
47 :- rdf_meta map(+,r,+,o).
|
Daniel@0
|
48
|
Daniel@0
|
49 % ---------------------------- utilities -----------------------------
|
Daniel@0
|
50
|
Daniel@0
|
51 %% genre_list_member(-Genre:uri, +GenreList:atom) is nondet.
|
Daniel@0
|
52 genre_list_member(Genre,Atom) :-
|
Daniel@0
|
53 parse_list_member(';',Atom,GenreName),
|
Daniel@0
|
54 number_string(GenreId,GenreName),
|
Daniel@0
|
55 uripattern:pattern_uri(ilm:genre/num(5,GenreId),Genre).
|
Daniel@0
|
56
|
Daniel@0
|
57 %% parse_list_member(+Sep:text,+Text:text,-Item:string) is nondet.
|
Daniel@0
|
58 parse_list_member(Sep,Atom,Item) :-
|
Daniel@0
|
59 split_string(Atom,Sep,'',Items),
|
Daniel@0
|
60 member(Item,Items).
|
Daniel@0
|
61 % ---------------------- getting stuff out of database ---------------------
|
Daniel@0
|
62
|
Daniel@0
|
63 genre_album(Genre,AlbumId) :-
|
Daniel@0
|
64 qsql(ilm,"select distinct album_id from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId)).
|
Daniel@0
|
65
|
Daniel@0
|
66 album_facet(AlbumId,Prop-Val) :- entity_facet(album,AlbumId,Prop,Val).
|
Daniel@0
|
67
|
Daniel@0
|
68 genre_track(Genre,AlbumId-TrackNo) :-
|
Daniel@0
|
69 qsql(ilm,"select album_id, track_no from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId,TrackNo)).
|
Daniel@0
|
70
|
Daniel@0
|
71 track_facet(AlbumId-TrackNo,Prop-Val) :- entity_facet(track,AlbumId-TrackNo,Prop,Val).
|
Daniel@0
|
72
|
Daniel@0
|
73 query_columns(album,
|
Daniel@0
|
74 [ album_title, product_artist, product_classifications, product_genre,
|
Daniel@0
|
75 product_release_year, product_label, product_upc ]).
|
Daniel@0
|
76 query_columns(track,
|
Daniel@0
|
77 [ assets_online, artist_name, comment, genre_id, release_year, song_title,
|
Daniel@0
|
78 track_classifications, track_duration, track_isrc]).
|
Daniel@0
|
79
|
Daniel@0
|
80 entity_facet(Type,Id,Prop,Val) :-
|
Daniel@0
|
81 query_columns(Type,Cols),
|
Daniel@0
|
82 pairs_keys_values(Pairs,Cols,Vals),
|
Daniel@0
|
83 Row =.. [row|Vals],
|
Daniel@0
|
84 phrase(entity_query(Type,Id,Cols),Codes,[]),
|
Daniel@0
|
85 qsql(ilm,'~s',[Codes],Row),
|
Daniel@0
|
86 member(Prop-Val,Pairs),
|
Daniel@0
|
87 Val\='$null$',
|
Daniel@0
|
88 Val\=''.
|
Daniel@0
|
89
|
Daniel@0
|
90 entity_query(album,AlbumId,Cols) -->
|
Daniel@0
|
91 "select ",
|
Daniel@0
|
92 seqmap_with_sep(",",atom,Cols),
|
Daniel@0
|
93 " from assets where album_id=", number(AlbumId).
|
Daniel@0
|
94
|
Daniel@0
|
95 entity_query(track,AlbumId-TrackNo,Cols) -->
|
Daniel@0
|
96 "select ",
|
Daniel@0
|
97 seqmap_with_sep(",",atom,Cols),
|
Daniel@0
|
98 " from assets where album_id=", number(AlbumId),
|
Daniel@0
|
99 " and track_no=", number(TrackNo).
|
Daniel@0
|
100
|
Daniel@0
|
101 include_genre(GenreId,Genre) :-
|
Daniel@0
|
102 setting(ilm_genres,Genres),
|
Daniel@0
|
103 member(Genre,Genres),
|
Daniel@0
|
104 qsql(ilm,"select ID from classifications where name='~s'",[Genre],row(GenreId)).
|
Daniel@0
|
105
|
Daniel@0
|
106
|
Daniel@0
|
107 % -------------------- mapping to rdf ----------------------------------
|
Daniel@0
|
108
|
Daniel@0
|
109
|
Daniel@0
|
110 rdf(ilm:genre/num(5,GenreID),rdf:type,mo:'Genre'),
|
Daniel@0
|
111 rdf(ilm:genre/num(5,GenreID),rdfs:label,literal(GenreName)) <==
|
Daniel@0
|
112 odbc_query(ilm,"select ID, name from classifications",row(GenreID,GenreName)).
|
Daniel@0
|
113
|
Daniel@0
|
114 rdf(ilm:album/num(AlbumId), Pred, Obj) <==
|
Daniel@0
|
115 include_genre(GenreId,GenreName),
|
Daniel@0
|
116 status("Querying albums of genre ~w...",[GenreName]),
|
Daniel@0
|
117 genre_album(GenreId,AlbumId),
|
Daniel@0
|
118 status("Importing ILM albums, genre ~w: ~d",[GenreName, AlbumId]),
|
Daniel@0
|
119 album_facet(AlbumId,Facet),
|
Daniel@0
|
120 map(Facet,Pred,Obj).
|
Daniel@0
|
121
|
Daniel@0
|
122 rdf(ilm:track/num(AlbumId)/num(TrackNo), Pred, Obj) <==
|
Daniel@0
|
123 include_genre(GenreId,GenreName),
|
Daniel@0
|
124 status("Querying tracks of genre ~w...",[GenreName]),
|
Daniel@0
|
125 genre_track(GenreId,AlbumId-TrackNo),
|
Daniel@0
|
126 status("Importing ILM tracks, genre ~w: ~d/~d",[GenreName, AlbumId, TrackNo]),
|
Daniel@0
|
127 ( Facet=track_no-TrackNo
|
Daniel@0
|
128 ; Facet=album_id-AlbumId
|
Daniel@0
|
129 ; track_facet(AlbumId-TrackNo,Facet)
|
Daniel@0
|
130 ),
|
Daniel@0
|
131 map(Facet,Pred,Obj).
|
Daniel@0
|
132
|
Daniel@0
|
133 map(Prop-Val,Pred,Obj) :-
|
Daniel@0
|
134 ( map(Prop,Pred,Val,Obj) *-> true
|
Daniel@0
|
135 ; print_message(warning,ilm_p2r:unrecognized_column(Prop,Val)), fail
|
Daniel@0
|
136 ).
|
Daniel@0
|
137
|
Daniel@0
|
138
|
Daniel@0
|
139 % album level
|
Daniel@0
|
140 map(album_title , dc:title, X, literal(X)).
|
Daniel@0
|
141 map(product_label , mo:label, X, literal(X)).
|
Daniel@0
|
142 map(product_artist , ilm:artist, X, literal(X)).
|
Daniel@0
|
143 map(product_upc , ilm:upc, X, literal(X)).
|
Daniel@0
|
144 map(product_release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y).
|
Daniel@0
|
145 map(product_classifications, mo:genre, Atom, Genre) :- genre_list_member(Genre,Atom).
|
Daniel@0
|
146 map(product_genre, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj).
|
Daniel@0
|
147
|
Daniel@0
|
148 % track level
|
Daniel@0
|
149 map(genre_id, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj).
|
Daniel@0
|
150 map(album_id, ilm:album, X, Album) :- uripattern:pattern_uri(ilm:album/num(X),Album).
|
Daniel@0
|
151 map(track_no, mo:track_number, X, literal(type(xsd:nonNegativeInteger,X))).
|
Daniel@0
|
152 map(track_isrc, mo:isrc, X, literal(type(xsd:string,X))).
|
Daniel@0
|
153 map(song_title, dc:title, X, literal(X)).
|
Daniel@0
|
154 map(comment, ilm:comment, X, literal(X)).
|
Daniel@0
|
155 map(artist_name, ilm:artist, X, literal(X)).
|
Daniel@0
|
156 map(track_classifications, mo:genre, X, Genre) :- genre_list_member(Genre,X).
|
Daniel@0
|
157 map(track_duration, mo:duration, X, literal(type(xsd:float,Millis))) :-
|
Daniel@0
|
158 parse_duration_millis(X,Millis).
|
Daniel@0
|
159
|
Daniel@0
|
160 map(release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y).
|
Daniel@0
|
161 map(assets_online, ilm:asset_online, Atom, literal(Type)) :-
|
Daniel@0
|
162 parse_list_member(',',Atom,TypeS),
|
Daniel@0
|
163 atom_string(Type,TypeS).
|
Daniel@0
|
164
|
Daniel@0
|
165 % map(P,ilm:P,date(Y,M,D),literal(type(xsd:date,Date))) :-
|
Daniel@0
|
166 % format_time(atom(Date),'%F',date(Y,M,D)).
|
Daniel@0
|
167 % map(P,ilm:P,timestamp(YY,MM,DD,H,M,S,_),literal(type(xsd:dateTime, DateTime))) :- !,
|
Daniel@0
|
168 % format_time(atom(DateTime),'%FT%T',date(YY,MM,DD,H,M,S,0,-,-)).
|