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