Mercurial > hg > dml-open-cliopatria
comparison 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 |
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(ilm_p2r, []). | |
20 | |
21 /** <module> Access to ILM database | |
22 */ | |
23 | |
24 | |
25 :- use_module(library(odbc)). | |
26 :- use_module(library(musicbrainz)). | |
27 :- use_module(library(semweb/rdf_db)). | |
28 :- use_module(library(termutils)). | |
29 :- use_module(library(odbcutils)). | |
30 :- use_module(library(rdfutils)). | |
31 :- use_module(library(dcg_core)). | |
32 :- use_module(library(dcg/basics)). | |
33 :- use_module(entailment(p2r)). | |
34 :- use_module(cliopatria(hooks)). | |
35 | |
36 :- set_prolog_flag(double_quotes,string). | |
37 | |
38 :- rdf_register_prefix(ilm,'http://dml.org/ilm/'). | |
39 | |
40 :- setting( ilm_genres,list(atom), | |
41 ['Classical','Jazz','Latin','Blues','Folk','Electronic','Reggae','Rock & Roll'], | |
42 "List of ILM genre names to import"). | |
43 | |
44 :- public import/0. | |
45 import :- with_odbc(ilm, assert_all(ilm_p2r)). | |
46 | |
47 :- rdf_meta map(+,r,+,o). | |
48 | |
49 % ---------------------------- utilities ----------------------------- | |
50 | |
51 %% genre_list_member(-Genre:uri, +GenreList:atom) is nondet. | |
52 genre_list_member(Genre,Atom) :- | |
53 parse_list_member(';',Atom,GenreName), | |
54 number_string(GenreId,GenreName), | |
55 uripattern:pattern_uri(ilm:genre/num(5,GenreId),Genre). | |
56 | |
57 %% parse_list_member(+Sep:text,+Text:text,-Item:string) is nondet. | |
58 parse_list_member(Sep,Atom,Item) :- | |
59 split_string(Atom,Sep,'',Items), | |
60 member(Item,Items). | |
61 % ---------------------- getting stuff out of database --------------------- | |
62 | |
63 genre_album(Genre,AlbumId) :- | |
64 qsql(ilm,"select distinct album_id from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId)). | |
65 | |
66 album_facet(AlbumId,Prop-Val) :- entity_facet(album,AlbumId,Prop,Val). | |
67 | |
68 genre_track(Genre,AlbumId-TrackNo) :- | |
69 qsql(ilm,"select album_id, track_no from assets where genre_id=~d and track_no!=0",[Genre],row(AlbumId,TrackNo)). | |
70 | |
71 track_facet(AlbumId-TrackNo,Prop-Val) :- entity_facet(track,AlbumId-TrackNo,Prop,Val). | |
72 | |
73 query_columns(album, | |
74 [ album_title, product_artist, product_classifications, product_genre, | |
75 product_release_year, product_label, product_upc ]). | |
76 query_columns(track, | |
77 [ assets_online, artist_name, comment, genre_id, release_year, song_title, | |
78 track_classifications, track_duration, track_isrc]). | |
79 | |
80 entity_facet(Type,Id,Prop,Val) :- | |
81 query_columns(Type,Cols), | |
82 pairs_keys_values(Pairs,Cols,Vals), | |
83 Row =.. [row|Vals], | |
84 phrase(entity_query(Type,Id,Cols),Codes,[]), | |
85 qsql(ilm,'~s',[Codes],Row), | |
86 member(Prop-Val,Pairs), | |
87 Val\='$null$', | |
88 Val\=''. | |
89 | |
90 entity_query(album,AlbumId,Cols) --> | |
91 "select ", | |
92 seqmap_with_sep(",",atom,Cols), | |
93 " from assets where album_id=", number(AlbumId). | |
94 | |
95 entity_query(track,AlbumId-TrackNo,Cols) --> | |
96 "select ", | |
97 seqmap_with_sep(",",atom,Cols), | |
98 " from assets where album_id=", number(AlbumId), | |
99 " and track_no=", number(TrackNo). | |
100 | |
101 include_genre(GenreId,Genre) :- | |
102 setting(ilm_genres,Genres), | |
103 member(Genre,Genres), | |
104 qsql(ilm,"select ID from classifications where name='~s'",[Genre],row(GenreId)). | |
105 | |
106 | |
107 % -------------------- mapping to rdf ---------------------------------- | |
108 | |
109 | |
110 rdf(ilm:genre/num(5,GenreID),rdf:type,mo:'Genre'), | |
111 rdf(ilm:genre/num(5,GenreID),rdfs:label,literal(GenreName)) <== | |
112 odbc_query(ilm,"select ID, name from classifications",row(GenreID,GenreName)). | |
113 | |
114 rdf(ilm:album/num(AlbumId), Pred, Obj) <== | |
115 include_genre(GenreId,GenreName), | |
116 status("Querying albums of genre ~w...",[GenreName]), | |
117 genre_album(GenreId,AlbumId), | |
118 status("Importing ILM albums, genre ~w: ~d",[GenreName, AlbumId]), | |
119 album_facet(AlbumId,Facet), | |
120 map(Facet,Pred,Obj). | |
121 | |
122 rdf(ilm:track/num(AlbumId)/num(TrackNo), Pred, Obj) <== | |
123 include_genre(GenreId,GenreName), | |
124 status("Querying tracks of genre ~w...",[GenreName]), | |
125 genre_track(GenreId,AlbumId-TrackNo), | |
126 status("Importing ILM tracks, genre ~w: ~d/~d",[GenreName, AlbumId, TrackNo]), | |
127 ( Facet=track_no-TrackNo | |
128 ; Facet=album_id-AlbumId | |
129 ; track_facet(AlbumId-TrackNo,Facet) | |
130 ), | |
131 map(Facet,Pred,Obj). | |
132 | |
133 map(Prop-Val,Pred,Obj) :- | |
134 ( map(Prop,Pred,Val,Obj) *-> true | |
135 ; print_message(warning,ilm_p2r:unrecognized_column(Prop,Val)), fail | |
136 ). | |
137 | |
138 | |
139 % album level | |
140 map(album_title , dc:title, X, literal(X)). | |
141 map(product_label , mo:label, X, literal(X)). | |
142 map(product_artist , ilm:artist, X, literal(X)). | |
143 map(product_upc , ilm:upc, X, literal(X)). | |
144 map(product_release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y). | |
145 map(product_classifications, mo:genre, Atom, Genre) :- genre_list_member(Genre,Atom). | |
146 map(product_genre, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj). | |
147 | |
148 % track level | |
149 map(genre_id, ilm:genre, Id, Obj) :- uripattern:pattern_uri(ilm:genre/num(5,Id),Obj). | |
150 map(album_id, ilm:album, X, Album) :- uripattern:pattern_uri(ilm:album/num(X),Album). | |
151 map(track_no, mo:track_number, X, literal(type(xsd:nonNegativeInteger,X))). | |
152 map(track_isrc, mo:isrc, X, literal(type(xsd:string,X))). | |
153 map(song_title, dc:title, X, literal(X)). | |
154 map(comment, ilm:comment, X, literal(X)). | |
155 map(artist_name, ilm:artist, X, literal(X)). | |
156 map(track_classifications, mo:genre, X, Genre) :- genre_list_member(Genre,X). | |
157 map(track_duration, mo:duration, X, literal(type(xsd:float,Millis))) :- | |
158 parse_duration_millis(X,Millis). | |
159 | |
160 map(release_year, ilm:release_date, Y, literal(type(xsd:date,YA))) :- atom_number(YA,Y). | |
161 map(assets_online, ilm:asset_online, Atom, literal(Type)) :- | |
162 parse_list_member(',',Atom,TypeS), | |
163 atom_string(Type,TypeS). | |
164 | |
165 % map(P,ilm:P,date(Y,M,D),literal(type(xsd:date,Date))) :- | |
166 % format_time(atom(Date),'%F',date(Y,M,D)). | |
167 % map(P,ilm:P,timestamp(YY,MM,DD,H,M,S,_),literal(type(xsd:dateTime, DateTime))) :- !, | |
168 % format_time(atom(DateTime),'%FT%T',date(YY,MM,DD,H,M,S,0,-,-)). |