diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/dml_data.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,92 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(dml_data, 
+      [ p2r_import/1
+      , humdrum_import/1
+      , load_everything/0
+      , hum_uri_path/2
+      , not_functional/3
+      , rdf_pair/4
+      ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_zlib_plugin)).
+:- use_module(library(mo_schema)).
+:- use_module(library(dbpedia)).
+:- use_module(library(humdrum_p2r)).
+:- use_module(library(beets_p2r)).
+:- use_module(library(memo_p2r)).
+:- use_module(library(bl_p2r)).
+:- use_module(library(ilm_p2r)).
+:- use_module(library(charm_p2r)).
+:- use_module(library(mazurka_p2r)).
+:- use_module(library(vamp)).
+:- use_module(library(termutils)).
+:- use_module(library(p2r)).
+:- use_module(entailment(p2r)).
+
+
+load_everything :-
+   maplist(p2r_import,[humdrum_p2r,memo_p2r,beets_p2r,bl_p2r,charm_p2r,vamp]).
+
+:- meta_predicate not_functional(2,-,-).
+
+not_functional(G,X,Ys) :-
+   writeln('Compiling...'),
+   setof(X-Y,call(G,X,Y),Pairs),
+   writeln('Grouping...'),
+   group_pairs_by_key(Pairs,Grouped),
+   writeln('Checking...'),
+   Ys=[_,_|_], member(X-Ys,Grouped).
+
+:- rdf_meta rdf_pair(r,r,o,o).
+rdf_pair(P1,P2,X1,X2) :-
+   rdf(Y,P1,X1),
+   rdf(Y,P2,X2).
+
+:- rdf_meta assert_subproperty(r,r).
+
+%% assert_subproperty(P1,P2) is det.
+%  Asserts that P1 is a sub-property of P2.
+assert_subproperty(P1,P2) :- rdf_assert(P1,rdfs:subPropertyOf,P2).
+
+rdf_assertions :-
+   rdf_assert(event:sub_event,rdf:type,owl:'TransitiveProperty'),
+   assert_subproperty(charm:composer,dml:composer),
+   assert_subproperty(hum:'refcode/COM',dml:composer),
+   assert_subproperty(charm:title,dml:title),
+   assert_subproperty(charm:performer,dml:performer),
+   assert_subproperty(marcrel:cmp,dml:composer),
+   assert_subproperty(marcrel:prf,dml:performer),
+   assert_subproperty(beets:title,dml:title),
+   assert_subproperty(beets:composer,dml:composer),
+   assert_subproperty(dc:title,dml:title).
+
+rdf_loads :-
+   rdf_load(rdf('silvet.n3')),
+%   rdf_load('http://id.loc.gov/vocabulary/relators'),
+%   rdf_load(['http://id.loc.gov/vocabulary/countries.rdf','http://id.loc.gov/vocabulary/languages.rdf'], [register_namespaces(true)]).
+   rdf_load('http://purl.org/ontology/vamp/',[register_namespaces(true)]),
+   rdf_load('http://vamp-plugins.org/rdf/plugins/qm-vamp-plugins'),
+   rdf_load('http://vamp-plugins.org/rdf/plugins/nnls-chroma'),
+   rdf_load('http://vamp-plugins.org/rdf/plugins/beatroot-vamp').
+
+:- initialization rdf_assertions.
+%:- initialization rdf_loads.
+