annotate cpack/dml/lib/dml_data.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
rev   line source
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_data,
Daniel@0 20 [ p2r_import/1
Daniel@0 21 , humdrum_import/1
Daniel@0 22 , load_everything/0
Daniel@0 23 , hum_uri_path/2
Daniel@0 24 , not_functional/3
Daniel@0 25 , rdf_pair/4
Daniel@0 26 ]).
Daniel@0 27
Daniel@0 28 :- use_module(library(semweb/rdf_db)).
Daniel@0 29 :- use_module(library(semweb/rdf_zlib_plugin)).
Daniel@0 30 :- use_module(library(mo_schema)).
Daniel@0 31 :- use_module(library(dbpedia)).
Daniel@0 32 :- use_module(library(humdrum_p2r)).
Daniel@0 33 :- use_module(library(beets_p2r)).
Daniel@0 34 :- use_module(library(memo_p2r)).
Daniel@0 35 :- use_module(library(bl_p2r)).
Daniel@0 36 :- use_module(library(ilm_p2r)).
Daniel@0 37 :- use_module(library(charm_p2r)).
Daniel@0 38 :- use_module(library(mazurka_p2r)).
Daniel@0 39 :- use_module(library(vamp)).
Daniel@0 40 :- use_module(library(termutils)).
Daniel@0 41 :- use_module(library(p2r)).
Daniel@0 42 :- use_module(entailment(p2r)).
Daniel@0 43
Daniel@0 44
Daniel@0 45 load_everything :-
Daniel@0 46 maplist(p2r_import,[humdrum_p2r,memo_p2r,beets_p2r,bl_p2r,charm_p2r,vamp]).
Daniel@0 47
Daniel@0 48 :- meta_predicate not_functional(2,-,-).
Daniel@0 49
Daniel@0 50 not_functional(G,X,Ys) :-
Daniel@0 51 writeln('Compiling...'),
Daniel@0 52 setof(X-Y,call(G,X,Y),Pairs),
Daniel@0 53 writeln('Grouping...'),
Daniel@0 54 group_pairs_by_key(Pairs,Grouped),
Daniel@0 55 writeln('Checking...'),
Daniel@0 56 Ys=[_,_|_], member(X-Ys,Grouped).
Daniel@0 57
Daniel@0 58 :- rdf_meta rdf_pair(r,r,o,o).
Daniel@0 59 rdf_pair(P1,P2,X1,X2) :-
Daniel@0 60 rdf(Y,P1,X1),
Daniel@0 61 rdf(Y,P2,X2).
Daniel@0 62
Daniel@0 63 :- rdf_meta assert_subproperty(r,r).
Daniel@0 64
Daniel@0 65 %% assert_subproperty(P1,P2) is det.
Daniel@0 66 % Asserts that P1 is a sub-property of P2.
Daniel@0 67 assert_subproperty(P1,P2) :- rdf_assert(P1,rdfs:subPropertyOf,P2).
Daniel@0 68
Daniel@0 69 rdf_assertions :-
Daniel@0 70 rdf_assert(event:sub_event,rdf:type,owl:'TransitiveProperty'),
Daniel@0 71 assert_subproperty(charm:composer,dml:composer),
Daniel@0 72 assert_subproperty(hum:'refcode/COM',dml:composer),
Daniel@0 73 assert_subproperty(charm:title,dml:title),
Daniel@0 74 assert_subproperty(charm:performer,dml:performer),
Daniel@0 75 assert_subproperty(marcrel:cmp,dml:composer),
Daniel@0 76 assert_subproperty(marcrel:prf,dml:performer),
Daniel@0 77 assert_subproperty(beets:title,dml:title),
Daniel@0 78 assert_subproperty(beets:composer,dml:composer),
Daniel@0 79 assert_subproperty(dc:title,dml:title).
Daniel@0 80
Daniel@0 81 rdf_loads :-
Daniel@0 82 rdf_load(rdf('silvet.n3')),
Daniel@0 83 % rdf_load('http://id.loc.gov/vocabulary/relators'),
Daniel@0 84 % rdf_load(['http://id.loc.gov/vocabulary/countries.rdf','http://id.loc.gov/vocabulary/languages.rdf'], [register_namespaces(true)]).
Daniel@0 85 rdf_load('http://purl.org/ontology/vamp/',[register_namespaces(true)]),
Daniel@0 86 rdf_load('http://vamp-plugins.org/rdf/plugins/qm-vamp-plugins'),
Daniel@0 87 rdf_load('http://vamp-plugins.org/rdf/plugins/nnls-chroma'),
Daniel@0 88 rdf_load('http://vamp-plugins.org/rdf/plugins/beatroot-vamp').
Daniel@0 89
Daniel@0 90 :- initialization rdf_assertions.
Daniel@0 91 %:- initialization rdf_loads.
Daniel@0 92