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(dml_crawler, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 :- use_module(library(http/html_write)).
|
Daniel@0
|
22 :- use_module(library(semweb/rdf_db)).
|
Daniel@0
|
23 :- use_module(library(semweb/rdfs)).
|
Daniel@0
|
24 :- use_module(library(semweb/rdf_label)).
|
Daniel@0
|
25 :- use_module(library(sparkle)).
|
Daniel@0
|
26 :- use_module(library(crawler)).
|
Daniel@0
|
27 :- use_module(library(musicbrainz)).
|
Daniel@0
|
28 :- use_module(library(memo)).
|
Daniel@0
|
29 :- use_module(applications(browse)).
|
Daniel@0
|
30 :- use_module(api(lod_crawler)).
|
Daniel@0
|
31 :- use_module(cliopatria(hooks)).
|
Daniel@0
|
32
|
Daniel@0
|
33 :- sparql_endpoint(mb, 'http://dbtune.org/musicbrainz/sparql').
|
Daniel@0
|
34 :- sparql_endpoint(lb, 'http://linkedbrainz.org/sparql/').
|
Daniel@0
|
35 :- sparql_endpoint(dbp, 'http://dbpedia.org/sparql/').
|
Daniel@0
|
36 :- sparql_endpoint(self, 'http://localhost:3020/sparql/').
|
Daniel@0
|
37
|
Daniel@0
|
38 % :- sparql_endpoint(bbc, 'http://dbtune.org/bbc/programmes/sparql/').
|
Daniel@0
|
39 % :- sparql_endpoint(peel,'http://dbtune.org/bbc/peel/sparql/'),
|
Daniel@0
|
40 % :- sparql_endpoint(classical,'http://dbtune.org/classical/sparql/'),
|
Daniel@0
|
41 % :- sparql_endpoint(jamendo,'http://dbtune.org/jamendo/sparql/'),
|
Daniel@0
|
42 % :- sparql_endpoint(magnatune,'http://dbtune.org/magnatune/sparql/'),
|
Daniel@0
|
43 % :- sparql_endpoint(henry,'http://dbtune.org/henry/sparql/'),
|
Daniel@0
|
44
|
Daniel@0
|
45
|
Daniel@0
|
46 crawler:source(dbp, dml_crawler:sparql_crawler(dbp), []).
|
Daniel@0
|
47 crawler:source(lbz, dml_crawler:sparql_crawler(lb), []).
|
Daniel@0
|
48 crawler:source(mbz, dml_crawler:mbz_crawler, []).
|
Daniel@0
|
49 crawler:source(lod, dml_crawler:lod_crawler, []).
|
Daniel@0
|
50
|
Daniel@0
|
51 crawler:authority( begins('http://dbpedia.org'), dbp, [auto(true)]).
|
Daniel@0
|
52 crawler:authority( begins('http://musicbrainz.org'), lbz, [auto(true)]).
|
Daniel@0
|
53 crawler:authority( begins('http://musicbrainz.org'), mbz, [auto(true)]).
|
Daniel@0
|
54 crawler:authority( begins('http://id.loc.gov/vocabulary'), lod, [auto(true)]).
|
Daniel@0
|
55 crawler:authority( begins('http://yago-knowledge.org'), lod, [auto(true)]).
|
Daniel@0
|
56 crawler:authority( ( (begins('http://'); begins('https://')),
|
Daniel@0
|
57 \+begins('http://dbpedia.org/'),
|
Daniel@0
|
58 \+begins('http://musicbrainz.org/'),
|
Daniel@0
|
59 \+begins('http://dml.org/'),
|
Daniel@0
|
60 \+begins('http://sounds.bl.uk/')
|
Daniel@0
|
61 ), lod, [auto(false)]).
|
Daniel@0
|
62
|
Daniel@0
|
63 :- volatile_memo instrument(+label:atom,-uri:atom).
|
Daniel@0
|
64
|
Daniel@0
|
65 instrument(Label,Instr) :-
|
Daniel@0
|
66 rdf(Instr,skos:prefLabel,literal(exact(Label),_)).
|
Daniel@0
|
67
|
Daniel@0
|
68 :- rdf_meta censor(+,t).
|
Daniel@0
|
69 censor(lb, rdf(_,'http://purl.org/muto/core#taggedResource',_)).
|
Daniel@0
|
70 censor(lb, rdf(_,mo:musicbrainz_guid,_)).
|
Daniel@0
|
71 censor(lb, rdf(_,foaf:made,_)).
|
Daniel@0
|
72
|
Daniel@0
|
73 % not needed after all: it was me giving the recordings type 'Signal', not lb.
|
Daniel@0
|
74 % sparql_crawler:modify(lb,Tin,Tout) :-
|
Daniel@0
|
75 % debug(sparql_crawler,"checking ~q",[Tin]),
|
Daniel@0
|
76 % once(relink_brainz(Tin,Tout)).
|
Daniel@0
|
77
|
Daniel@0
|
78 % :- rdf_meta relink_brainz(t,t).
|
Daniel@0
|
79 % relink_brainz(rdf(MBZRecording,rdf:type,mo:'Track'),rdf(MBZRecording,rdf:type,mo:'Signal')):-
|
Daniel@0
|
80 % mb_id_uri(recording,_,MBZRecording).
|
Daniel@0
|
81
|
Daniel@0
|
82 % connects patched ClioPatria resource viewer to sparql_crawler module
|
Daniel@0
|
83 cliopatria:resource_crawler(URI,NT) --> html(div(class(crawler),\crawl_ui(URI,NT))).
|
Daniel@0
|
84
|
Daniel@0
|
85 % --------- SPARQL crawler using sparkle ---------------
|
Daniel@0
|
86
|
Daniel@0
|
87 sparql_crawler(dbp,name('DBPedia')).
|
Daniel@0
|
88 sparql_crawler(lb,name('LinkedBrainz')).
|
Daniel@0
|
89
|
Daniel@0
|
90 sparql_crawler(EP,uri_graph(_,Graph)) :-
|
Daniel@0
|
91 current_sparql_endpoint(EP,Host,Port,Path,_),
|
Daniel@0
|
92 parse_url(Graph,[protocol(http),host(Host),port(Port),path(Path)]).
|
Daniel@0
|
93
|
Daniel@0
|
94 sparql_crawler(EP,describe(URI,Triple)) :-
|
Daniel@0
|
95 describe(EP,URI,Triple),
|
Daniel@0
|
96 \+censor(EP,Triple).
|
Daniel@0
|
97
|
Daniel@0
|
98
|
Daniel@0
|
99 describe(EP,URI,rdf(Subj,Pred,URI)) :- EP ?? rdf(Subj,Pred,URI).
|
Daniel@0
|
100 describe(EP,URI,rdf(URI,Pred,Obj)) :- EP ?? rdf(URI,Pred,Obj).
|
Daniel@0
|
101 % !!! FIXME This was to slow for URIs with many linked resources
|
Daniel@0
|
102 % Need to get asynchronous crawling working first..
|
Daniel@0
|
103 % describe(EP,URI,rdf(Subj,Pred,Obj)) :-
|
Daniel@0
|
104 % (EP ?? rdf(URI,P1,O1)),
|
Daniel@0
|
105 % ( Subj=URI, Pred=P1, Obj=O1
|
Daniel@0
|
106 % ; Subj=O1, Pred=P2, Obj=O2,
|
Daniel@0
|
107 % O1\=literal(_),
|
Daniel@0
|
108 % (EP ?? rdf(O1,P2,O2))
|
Daniel@0
|
109 % ).
|
Daniel@0
|
110
|
Daniel@0
|
111 % ----------- LOD crawler ---------------------------
|
Daniel@0
|
112 lod_crawler(name('LOD Cloud')).
|
Daniel@0
|
113 lod_crawler(uri_graph(URI,Graph)) :-
|
Daniel@0
|
114 uri_components(URI, uri_components(Sch,Auth,_,_,_)),
|
Daniel@0
|
115 uri_components(Graph, uri_components(Sch,Auth,_,_,_)).
|
Daniel@0
|
116
|
Daniel@0
|
117 lod_crawler(crawl(URI,Graph)) :-
|
Daniel@0
|
118 lod_uri_graph(URI,URL),
|
Daniel@0
|
119 rdf_load(URL,[graph(Graph)]).
|
Daniel@0
|
120
|
Daniel@0
|
121 % ----------- MusicBrainz crawler -------------------
|
Daniel@0
|
122 mbz_crawler(uri_graph(_,'http://musicbrainz.org/ws/2')).
|
Daniel@0
|
123 mbz_crawler(name('MusicBrainz')).
|
Daniel@0
|
124 mbz_crawler(describe(URI,Triple)) :-
|
Daniel@0
|
125 debug(crawler,'Doing ~q.',[mbz_crawler(describe(URI,Triple))]),
|
Daniel@0
|
126 ( mb_id_uri(Type,_,URI) -> Context=Type
|
Daniel@0
|
127 ; event_uri(URI,EvType,BaseURI,Extra),
|
Daniel@0
|
128 mb_id_uri(BaseType,_,BaseURI)
|
Daniel@0
|
129 -> Context=event(BaseType,BaseURI,EvType,Extra)
|
Daniel@0
|
130 ; debug(crawler,'Unrecognised URI: ~w',[URI]),
|
Daniel@0
|
131 fail
|
Daniel@0
|
132 ),
|
Daniel@0
|
133 mbz_triple(Context,URI,Triple1),
|
Daniel@0
|
134 rdf_global_term(Triple1,Triple).
|
Daniel@0
|
135
|
Daniel@0
|
136
|
Daniel@0
|
137 mbz_triple(artist,URI,rdf(URI,rdf:type,mo:'MusicArtist')).
|
Daniel@0
|
138 mbz_triple(artist,URI,Triple) :-
|
Daniel@0
|
139 mb_lookup(URI,[inc([aliases]), rels([recording,work,artist])],Artist),
|
Daniel@0
|
140 subject_triple(Artist-URI,artist,Triple).
|
Daniel@0
|
141
|
Daniel@0
|
142 mbz_triple(recording,URI,rdf(URI,rdf:type,mo:'Signal')).
|
Daniel@0
|
143 mbz_triple(recording,URI,rdf(Event,rdf:type,mo:'Recording')) :-
|
Daniel@0
|
144 event_uri(Event,production,URI).
|
Daniel@0
|
145
|
Daniel@0
|
146 mbz_triple(recording,URI,Triple) :-
|
Daniel@0
|
147 mb_lookup(URI,[inc([artists,'artist-credits']),rels([artist,work])],Recording),
|
Daniel@0
|
148 event_uri(Event,production,URI),
|
Daniel@0
|
149 subject_triple(Recording-URI, recording(Event), Triple).
|
Daniel@0
|
150
|
Daniel@0
|
151 mbz_triple(work,URI,rdf(URI,rdf:type,mo:'MusicalWork')).
|
Daniel@0
|
152 mbz_triple(work,URI,Triple) :-
|
Daniel@0
|
153 mb_lookup(URI,[inc([aliases]),rels([recording,artist,work])],Work),
|
Daniel@0
|
154 subject_triple(Work-URI, work, Triple).
|
Daniel@0
|
155
|
Daniel@0
|
156 mbz_triple(event(work,_,composition,''),Event,rdf(Event,rdf:type:mo:'Composition')).
|
Daniel@0
|
157 mbz_triple(event(work,W,composition,''),Event,Triple) :-
|
Daniel@0
|
158 mb_lookup(W,[rels([artist,work])],Work), % need work rels here?
|
Daniel@0
|
159 event_uri(Event,composition,WorkURI),
|
Daniel@0
|
160 subject_triple(Work-WorkURI, work, Triple).
|
Daniel@0
|
161
|
Daniel@0
|
162 mbz_triple(event(recording,Signal,production,''),Event,Triple) :-
|
Daniel@0
|
163 production_triple(Signal,Event,Triple).
|
Daniel@0
|
164
|
Daniel@0
|
165 production_triple(_, Ev, rdf(Ev,rdf:type,mo:'Performance')).
|
Daniel@0
|
166 production_triple(_, Ev, rdf(Ev,rdf:type,mo:'Recording')).
|
Daniel@0
|
167 production_triple(S, Ev, rdf(Ev,mo:produced_signal,S)).
|
Daniel@0
|
168 production_triple(S, Ev, T) :-
|
Daniel@0
|
169 mb_lookup(S,[inc([artists,'artist-credits']),rels([work,artist])],Recording),
|
Daniel@0
|
170 mb_uri(Recording,Signal),
|
Daniel@0
|
171 subject_triple(Recording-Signal,recording(Ev),T).
|
Daniel@0
|
172
|
Daniel@0
|
173 %% subject_triple( +Subj:pair(element,resource), +Content:ground, -T:triple) is nondet.
|
Daniel@0
|
174 % Produce triples relating to this subject without doing any more musicbrainz queries.
|
Daniel@0
|
175
|
Daniel@0
|
176 % first deal with the non-relation facets
|
Daniel@0
|
177 subject_triple(E-URI, Context, T) :-
|
Daniel@0
|
178 dif(Facet,relation(_,_)),
|
Daniel@0
|
179 mb_facet(E,Facet),
|
Daniel@0
|
180 facet_triple(URI, Context, Facet, T).
|
Daniel@0
|
181
|
Daniel@0
|
182 % then deal with relations
|
Daniel@0
|
183 subject_triple(E1-URI1, _Context, T) :-
|
Daniel@0
|
184 mb_relation(E1, E2, Name, Dir, Opts),
|
Daniel@0
|
185 mb_uri(E2,URI2),
|
Daniel@0
|
186 ( mb_class(E2,C2),
|
Daniel@0
|
187 subject_triple(E2-URI2, C2, T) % do all facets of related object
|
Daniel@0
|
188 ; normalise_direction(Dir,URI1,URI2,URI_A,URI_B),
|
Daniel@0
|
189 relation_triple(Name,URI_A,URI_B,Opts,T)
|
Daniel@0
|
190 ).
|
Daniel@0
|
191
|
Daniel@0
|
192 normalise_direction(fwd,E1,E2,E1,E2).
|
Daniel@0
|
193 normalise_direction(bwd,E1,E2,E2,E1).
|
Daniel@0
|
194
|
Daniel@0
|
195
|
Daniel@0
|
196 facet_triple(_, _, credit(A), T) :- mb_uri(A,Agent), subject_triple(A-Agent,artist,T).
|
Daniel@0
|
197 facet_triple(URI, _, title(T), rdf(URI,dc:title,literal(T))).
|
Daniel@0
|
198 facet_triple(URI, artist, name(N), rdf(URI,foaf:name,literal(N))).
|
Daniel@0
|
199 facet_triple(URI, artist, alias(A), rdf(URI,dml:alias,literal(A))).
|
Daniel@0
|
200 facet_triple(URI, artist, gender(G), rdf(URI,foaf:gender,literal(GG))) :- downcase_atom(G,GG).
|
Daniel@0
|
201 facet_triple(URI, artist, type(Type), rdf(URI,rdf:type,foaf:Type)) :- member(Type,['Person','Group']).
|
Daniel@0
|
202 facet_triple(URI, artist, born(X), T) :- life_event_triple(URI,birth,time(X),T).
|
Daniel@0
|
203 facet_triple(URI, artist, died(X), T) :- life_event_triple(URI,death,time(X),T).
|
Daniel@0
|
204 facet_triple(URI, artist, birth_place(X), T) :- life_event_triple(URI,birth,area(X),T).
|
Daniel@0
|
205 facet_triple(URI, artist, death_place(X), T) :- life_event_triple(URI,death,area(X),T).
|
Daniel@0
|
206
|
Daniel@0
|
207 facet_triple(_, recording(E), credit(A), rdf(E,event:agent,Agent)) :- mb_uri(A,Agent).
|
Daniel@0
|
208 facet_triple(URI, recording(_), length(L), rdf(URI,mo:duration,literal(type(xsd:float,LenA)))) :-
|
Daniel@0
|
209 atom_number(LenA,L).
|
Daniel@0
|
210
|
Daniel@0
|
211 life_event_triple(Agent,Type,Property,T) :-
|
Daniel@0
|
212 event_uri(Event,Type,Agent),
|
Daniel@0
|
213 ( T=rdf(Event,rdf:type,event:'Event')
|
Daniel@0
|
214 ; T=rdf(Event,event:agent,Agent)
|
Daniel@0
|
215 ; life_event_property_triple(Event,Property,T)
|
Daniel@0
|
216 ).
|
Daniel@0
|
217
|
Daniel@0
|
218
|
Daniel@0
|
219 life_event_property_triple(Event,area(A),rdf(Event,event:place,URI)) :- mb_uri(A,URI).
|
Daniel@0
|
220 life_event_property_triple(Event,time(T),Triple) :-
|
Daniel@0
|
221 prefix_uri('/time',Event,Time),
|
Daniel@0
|
222 ( Triple=rdf(Event,event:time,Time)
|
Daniel@0
|
223 ; time_instant_triple(Time-T,Triple)
|
Daniel@0
|
224 ).
|
Daniel@0
|
225
|
Daniel@0
|
226 % -----------------------------------------------------------------------------
|
Daniel@0
|
227 % relation_triple
|
Daniel@0
|
228
|
Daniel@0
|
229 relation_triple(parts, Whole, Part, _, rdf(Part,dml:part_of,Whole)).
|
Daniel@0
|
230 relation_triple(composer, Agent, Work, _, rdf(Work,dml:composer,Agent)).
|
Daniel@0
|
231 relation_triple('is person', Agent, Person, _, rdf(Agent,dml:persona_of,Person)).
|
Daniel@0
|
232 relation_triple('performing orchestra', _, Group, _, rdf(Group,rdf:type,mo:'Orchestra')).
|
Daniel@0
|
233 relation_triple(Name, _, Group, _, rdf(Group,rdf:type,mo:'MusicGroup')) :- membership_role(Name).
|
Daniel@0
|
234 relation_triple(Name, Agent, Group, _, rdf(Group,mo:member,Agent)) :- membership_role(Name).
|
Daniel@0
|
235
|
Daniel@0
|
236 relation_triple(Role, Agent, _, _, rdf(Agent,rdf:type,mo:'MusicArtist')) :-
|
Daniel@0
|
237 musical_role(Role).
|
Daniel@0
|
238 relation_triple(Name, R1, R2, Opts, T) :-
|
Daniel@0
|
239 relation_event(Name, R1, R2, Opts, Event, Relation),
|
Daniel@0
|
240 relation_event_triple(Relation, Event, T).
|
Daniel@0
|
241
|
Daniel@0
|
242 relation_event( based_on, Orig, Deriv, _, Ev, based_on(Orig)) :- event_uri(Ev,composition,Deriv).
|
Daniel@0
|
243 relation_event( composer, A, W, O, Ev, composition(composer,A,W,O)) :- event_uri(Ev,composition,W).
|
Daniel@0
|
244 relation_event( lyricist, A, W, _, Ev, composition(lyricist,A,W,[])) :- event_uri(Ev,composition,W).
|
Daniel@0
|
245 relation_event( writer, A, W, _, Ev, composition(writer,A,W,[])) :- event_uri(Ev,composition,W).
|
Daniel@0
|
246 relation_event( arrangement, W1, W2, O, Ev, arrangement(W1,W2,O)) :- event_uri(Ev,arrangement,W2).
|
Daniel@0
|
247 relation_event( performance, Sig, W, O, Ev, performance(W,O)) :- event_uri(Ev,production,Sig).
|
Daniel@0
|
248 relation_event( performance, Sig, _, _, Ev, recording(Sig)) :- event_uri(Ev,production,Sig).
|
Daniel@0
|
249 relation_event( performer, _, Sig, _, Ev, recording(Sig)) :- event_uri(Ev,production,Sig).
|
Daniel@0
|
250 relation_event( 'performing orchestra', _, Sig, _, Ev, recording(Sig)) :- event_uri(Ev,production,Sig).
|
Daniel@0
|
251 relation_event( vocal, Ag, Sig, O, Ev, ED) :- relation_event( instrument, Ag, Sig, [attribute(voice)|O], Ev, ED).
|
Daniel@0
|
252 relation_event( 'instrument arranger', Ag, Sig, O, Ev, ED) :- relation_event(instrument,Ag,Sig,O,Ev,ED).
|
Daniel@0
|
253 relation_event( 'instrument arranger', Ag, Sig, O, Ev, ED) :- relation_event(arranger,Ag,Sig,O,Ev,ED).
|
Daniel@0
|
254 relation_event( instrument, _, Sig, _, Ev, recording(Sig)) :- event_uri(Ev,production,Sig).
|
Daniel@0
|
255 relation_event( instrument, Ag, Sig, O, Ev, instrument(Prod,Ag,O)) :-
|
Daniel@0
|
256 mb_id_uri(_,PerformerID,Ag),
|
Daniel@0
|
257 event_uri(Prod,production,Sig),
|
Daniel@0
|
258 event_uri(Ev,performance,Sig,PerformerID).
|
Daniel@0
|
259 relation_event( Name, Agent, Sig, _, Ev, role(Pred,Agent)) :-
|
Daniel@0
|
260 production_role(Name,Pred),
|
Daniel@0
|
261 mb_id_uri(recording,_,Sig),
|
Daniel@0
|
262 event_uri(Ev,production,Sig).
|
Daniel@0
|
263
|
Daniel@0
|
264 relation_event( Name, Agent, Group, Opts, Ev, membership(Agent,Group,[role(Role)|Opts])) :-
|
Daniel@0
|
265 membership_role(Name,Role),
|
Daniel@0
|
266 mb_id_uri(_,AID,Agent),
|
Daniel@0
|
267 term_hash(t(AID,Role,Opts),Hash),
|
Daniel@0
|
268 number_string(Hash,HashString),
|
Daniel@0
|
269 event_uri(Ev,membership,Group,HashString).
|
Daniel@0
|
270
|
Daniel@0
|
271 production_role(producer,mo:producer).
|
Daniel@0
|
272 production_role(arranger,mo:arranger).
|
Daniel@0
|
273 production_role(conductor,mo:conductor).
|
Daniel@0
|
274 production_role(performer,mo:performer).
|
Daniel@0
|
275 production_role('performing orchestra',mo:performer).
|
Daniel@0
|
276 production_role(vocal,mo:performer).
|
Daniel@0
|
277
|
Daniel@0
|
278 membership_role(Name) :- membership_role(Name,_).
|
Daniel@0
|
279 membership_role('member of band',member).
|
Daniel@0
|
280 membership_role('conductor position',conductor).
|
Daniel@0
|
281 membership_role('vocal supporting musician',vocal_support).
|
Daniel@0
|
282
|
Daniel@0
|
283 musical_role(composer).
|
Daniel@0
|
284 musical_role(arranger).
|
Daniel@0
|
285 musical_role(lyricist).
|
Daniel@0
|
286 musical_role(instrument).
|
Daniel@0
|
287 musical_role(performer).
|
Daniel@0
|
288 musical_role('performing orchestra').
|
Daniel@0
|
289 musical_role('vocal supporting musician').
|
Daniel@0
|
290 musical_role(Name) :- membership_role(Name).
|
Daniel@0
|
291
|
Daniel@0
|
292 relation_event_triple( based_on(_), Ev, rdf(Ev,rdf:type,mo:'Composition')).
|
Daniel@0
|
293 relation_event_triple( based_on(Orig), Ev, rdf(Ev,event:factor,Orig)).
|
Daniel@0
|
294
|
Daniel@0
|
295 relation_event_triple( membership(_,_,_), Ev, rdf(Ev,rdf:type,mo:'Membership')).
|
Daniel@0
|
296 relation_event_triple( membership(A,_,_), Ev, rdf(Ev,mo:artist,A)).
|
Daniel@0
|
297 relation_event_triple( membership(_,G,_), Ev, rdf(Ev,mo:group,G)).
|
Daniel@0
|
298 relation_event_triple( membership(_,_,O), Ev, T) :- membership_triple(Ev,O,T).
|
Daniel@0
|
299 relation_event_triple( membership(_,_,O), Ev, T) :- event_time_triple(Ev,O,T).
|
Daniel@0
|
300
|
Daniel@0
|
301 relation_event_triple( composition(_,_,_,_), Ev, rdf(Ev,rdf:type,mo:'Composition')).
|
Daniel@0
|
302 relation_event_triple( composition(_,_,W,_), Ev, rdf(Ev,mo:produced_work,W)).
|
Daniel@0
|
303 relation_event_triple( composition(R,A,_,_), Ev, rdf(Ev,mo:R,A)).
|
Daniel@0
|
304 relation_event_triple( composition(_,_,_,O), Ev, T) :- event_time_triple(Ev,O,T).
|
Daniel@0
|
305
|
Daniel@0
|
306 relation_event_triple( arrangement(_,_,_), Ev, rdf(Ev,rdf:type,mo:'Arrangement')).
|
Daniel@0
|
307 relation_event_triple( arrangement(W,_,_), Ev, rdf(Ev,mo:arrangement_of,W)).
|
Daniel@0
|
308 relation_event_triple( arrangement(_,W,_), Ev, rdf(Ev,mo:produced_work,W)).
|
Daniel@0
|
309 relation_event_triple( arrangement(_,_,O), Ev, T) :- event_time_triple(Ev,O,T).
|
Daniel@0
|
310
|
Daniel@0
|
311 relation_event_triple( performance(_,_), Ev, rdf(Ev,rdf:type,mo:'Performance')).
|
Daniel@0
|
312 relation_event_triple( performance(_,O), Ev, T) :- event_time_triple(Ev,O,T).
|
Daniel@0
|
313 relation_event_triple( performance(W,O), Ev, rdf(Ev,Pred,W)) :-
|
Daniel@0
|
314 ( member(attribute(partial),O)
|
Daniel@0
|
315 -> Pred=mo:partial_performance_of
|
Daniel@0
|
316 ; Pred=mo:performance_of
|
Daniel@0
|
317 ).
|
Daniel@0
|
318
|
Daniel@0
|
319 relation_event_triple( recording(_), Ev, rdf(Ev,rdf:type,mo:'Recording')).
|
Daniel@0
|
320 relation_event_triple( recording(S), Ev, rdf(Ev,mo:produced_signal,S)).
|
Daniel@0
|
321
|
Daniel@0
|
322 relation_event_triple( instrument(_,_,_), Ev, rdf(Ev,rdf:type,mo:'Performance')).
|
Daniel@0
|
323 relation_event_triple( instrument(_,A,_), Ev, rdf(Ev,mo:performer,A)).
|
Daniel@0
|
324 relation_event_triple( instrument(P,_,_), Ev, rdf(P,event:sub_event,Ev)).
|
Daniel@0
|
325 relation_event_triple( instrument(_,_,O), Ev, T) :- event_time_triple(Ev,O,T).
|
Daniel@0
|
326 % relation_event_triple( instrument(_,_,O), Ev, rdf(Ev,mo:instrument,literal(Instr))) :-
|
Daniel@0
|
327 % member(attribute(Instr),O).
|
Daniel@0
|
328 relation_event_triple( instrument(_,_,O), Ev, rdf(Ev,mo:instrument,Instr)) :-
|
Daniel@0
|
329 member(attribute(Label),O),
|
Daniel@0
|
330 ( instrument(Label,Instr) -> true
|
Daniel@0
|
331 ; Instr=literal(Label)
|
Daniel@0
|
332 ).
|
Daniel@0
|
333
|
Daniel@0
|
334 membership_triple(E, O, rdf(E,dml:role,literal(R))) :- member(role(R),O), R\=member.
|
Daniel@0
|
335 membership_triple(E, O, rdf(E,dml:modifier,literal(A))) :- member(attribute(A),O).
|
Daniel@0
|
336
|
Daniel@0
|
337 event_time_triple(Event,Opts,T) :-
|
Daniel@0
|
338 (memberchk(begin(_),Opts); memberchk(end(_),Opts); memberchk(in(_),Opts)),
|
Daniel@0
|
339 prefix_uri('/time',Event,Time),
|
Daniel@0
|
340 ( T=rdf(Event,event:time,Time)
|
Daniel@0
|
341 ; ( member(in(DT),Opts)
|
Daniel@0
|
342 -> time_instant_triple(Time-DT,T)
|
Daniel@0
|
343 ; ( member(begin(DT),Opts), prefix_uri('/begin',Time,Pt), Pred=time:hasBeginning
|
Daniel@0
|
344 ; member(end(DT),Opts), prefix_uri('/end',Time,Pt), Pred=time:hasEnd
|
Daniel@0
|
345 ),
|
Daniel@0
|
346 time_interval_triple(Time,Pred,Pt-DT,T)
|
Daniel@0
|
347 )
|
Daniel@0
|
348 ).
|
Daniel@0
|
349
|
Daniel@0
|
350 time_instant_triple(Time-_, rdf(Time,rdf:type,time:'Instant')).
|
Daniel@0
|
351 time_instant_triple(Time-DT, rdf(Time,time:inXSDDateTime,literal(type(xsd:dateTime,DT)))).
|
Daniel@0
|
352
|
Daniel@0
|
353 time_interval_triple(T, _, _, rdf(T,rdf:type, time:'Interval')).
|
Daniel@0
|
354 time_interval_triple(T, Pred, Pt-_, rdf(T,Pred,Pt)).
|
Daniel@0
|
355 time_interval_triple(_, _, PtDT, T) :- time_instant_triple(PtDT,T).
|
Daniel@0
|
356
|
Daniel@0
|
357
|
Daniel@0
|
358 %% event_uri(-EventURI,+Type,+BaseURI) is det.
|
Daniel@0
|
359 %% event_uri(-EventURI,+Type,+BaseURI) is det.
|
Daniel@0
|
360 event_uri(EventURI,Type,BaseURI) :- event_uri(EventURI,Type,BaseURI,'').
|
Daniel@0
|
361
|
Daniel@0
|
362 %% event_uri(+EventURI,-Type,-BaseURI,-Extra) is det.
|
Daniel@0
|
363 %% event_uri(-EventURI,+Type,+BaseURI,+Extra) is det.
|
Daniel@0
|
364 event_uri(EventURI,Type,BaseURI,Extra) :-
|
Daniel@0
|
365 ( var(EventURI)
|
Daniel@0
|
366 -> uri_components(BaseURI,uri_components(Sc,Ho,Pa,Extra,'_')),
|
Daniel@0
|
367 uri_components(EventURI,uri_components(Sc,Ho,Pa,Extra,Type)), Type\='_'
|
Daniel@0
|
368 ; uri_components(EventURI,uri_components(Sc,Ho,Pa,Extra,Type)), Type\='_',
|
Daniel@0
|
369 uri_components(BaseURI,uri_components(Sc,Ho,Pa,Extra,'_'))
|
Daniel@0
|
370 ).
|
Daniel@0
|
371
|
Daniel@0
|
372 % prefix_uri(_,_,N) :- rdf_bnode(N), !.
|
Daniel@0
|
373 prefix_uri(Prefix,URI,PURI) :-
|
Daniel@0
|
374 uri_components(URI,uri_components(Sc,Ho,Pa,Extra,Type)), atom_concat(Prefix,Pa,TPa),
|
Daniel@0
|
375 uri_components(PURI,uri_components(Sc,Ho,TPa,Extra,Type)).
|
Daniel@0
|
376
|
Daniel@0
|
377 % -------------- display hooks ---------------
|
Daniel@0
|
378 :- rdf_meta label(r,r,-).
|
Daniel@0
|
379 label(time:'Instant',URI, Label) :-
|
Daniel@0
|
380 ( rdf_has(URI,time:inXSDDateTime,literal(type(xsd:dateTime,DT)))
|
Daniel@0
|
381 -> format(string(Label),'~w',[DT])
|
Daniel@0
|
382 ; Label='<unknown>'
|
Daniel@0
|
383 ).
|
Daniel@0
|
384
|
Daniel@0
|
385 label(time:'Interval',URI, Label) :-
|
Daniel@0
|
386 (rdf_has(URI,time:hasBeginning,Begin) -> rdf_display_label(Begin,L1); L1='<unknown>'),
|
Daniel@0
|
387 (rdf_has(URI,time:hasEnd,End) -> rdf_display_label(End,L2); L2='<unknown>'),
|
Daniel@0
|
388 ( L1=L2
|
Daniel@0
|
389 -> format(string(Label),'~s',[L1])
|
Daniel@0
|
390 ; format(string(Label),'~s to ~s',[L1,L2])
|
Daniel@0
|
391 ).
|
Daniel@0
|
392
|
Daniel@0
|
393 label(mo:'Recording',Ev, Label) :-
|
Daniel@0
|
394 rdf_has(Ev,mo:produced_signal,Sig), !,
|
Daniel@0
|
395 rdf_display_label(Sig,Title),
|
Daniel@0
|
396 ( rdf_has(Ev,event:agent,Agent)
|
Daniel@0
|
397 -> rdf_display_label(Agent,Name),
|
Daniel@0
|
398 format(string(Label),'Recording of ~w by ~w',[Title,Name])
|
Daniel@0
|
399 ; format(string(Label),'Recording of ~w',[Title])
|
Daniel@0
|
400 ).
|
Daniel@0
|
401
|
Daniel@0
|
402 label(mo:'Membership',Ev, Label) :-
|
Daniel@0
|
403 rdf_has(Ev,mo:artist,A),
|
Daniel@0
|
404 rdf_has(Ev,mo:group,G), !,
|
Daniel@0
|
405 rdf_display_label(A,AL),
|
Daniel@0
|
406 rdf_display_label(G,GL),
|
Daniel@0
|
407 format(string(Label),'Membership of ~w in ~w',[AL,GL]).
|
Daniel@0
|
408
|
Daniel@0
|
409 label(mo:'Performance',Ev, Label) :-
|
Daniel@0
|
410 ( rdf_has(Ev,mo:produced_signal,Sig)
|
Daniel@0
|
411 ; rdf_has(SEv,event:sub_event,Ev),
|
Daniel@0
|
412 rdf_has(SEv,mo:produced_signal,Sig)
|
Daniel@0
|
413 ), !,
|
Daniel@0
|
414 rdf_display_label(Sig,Title),
|
Daniel@0
|
415 rdf_has(Ev,mo:performer,Performer), rdf_display_label(Performer,Name),
|
Daniel@0
|
416 rdf_has(Ev,mo:instrument,Instr), rdf_display_label(Instr,IName),
|
Daniel@0
|
417 format(string(Label),'~w playing ~w on ~w',[Name,IName,Title]).
|
Daniel@0
|
418
|
Daniel@0
|
419
|
Daniel@0
|
420 label(mo:'Composition',E,Label) :-
|
Daniel@0
|
421 rdf_has(E,mo:produced_work,Work),
|
Daniel@0
|
422 rdfs_individual_of(Work,mo:'MusicalWork'), !,
|
Daniel@0
|
423 rdf_display_label(Work,Title),
|
Daniel@0
|
424 format(string(Label),'Composition of ~w',[Title]).
|
Daniel@0
|
425
|
Daniel@0
|
426 rdf_label:display_label_hook(URI, _, Label) :-
|
Daniel@0
|
427 rdf(URI,rdf:type,Class),
|
Daniel@0
|
428 label(Class,URI,Label).
|
Daniel@0
|
429
|
Daniel@0
|
430 rdf_label:display_label_hook(URI, _, Label) :-
|
Daniel@0
|
431 atom(URI),
|
Daniel@0
|
432 sub_atom(URI,0,_,_,'http://musicbrainz.org'),
|
Daniel@0
|
433 event_uri(URI,EvType,Base),
|
Daniel@0
|
434 event_label(EvType,URI,Base,Label).
|
Daniel@0
|
435
|
Daniel@0
|
436 event_label(birth,_,Person,Label) :-
|
Daniel@0
|
437 rdfs_individual_of(Person,foaf:'Person'), !,
|
Daniel@0
|
438 rdf_display_label(Person,Name),
|
Daniel@0
|
439 format(string(Label),'Birth of ~w',[Name]).
|
Daniel@0
|
440 event_label(death,_,Person,Label) :-
|
Daniel@0
|
441 rdfs_individual_of(Person,foaf:'Person'), !,
|
Daniel@0
|
442 rdf_display_label(Person,Name),
|
Daniel@0
|
443 format(string(Label),'Death of ~w',[Name]).
|
Daniel@0
|
444
|
Daniel@0
|
445
|