diff cpack/dml/lib/dml_misc.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_misc.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,73 @@
+/* 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_misc, [ periodically/2, current_periodical/3, remove_periodical/1 ]).
+/** <module> Miscellaneous hooks and initialisations
+
+   This module implements some hooks for managing the context graphs
+   which appear at the bottom of individual resource pages.
+
+   It also loads some miscellanous RDF graphs.
+
+*/
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(memo)).
+:- use_module(cliopatria(hooks)).
+
+:- rdf_meta context_graph_class(r).
+
+:- meta_predicate periodically(+,0).
+:- meta_predicate current_periodical(-,0,-).
+
+cliopatria:context_graph(URI, Triples, _) :-
+   context_graphable(URI), !,
+   maplist(rdf_global_id,[rdf:type, prov:wasDerivedFrom],Excludes),
+   findall(T, context_triple(Excludes,URI,[],T), T1),
+   sort(T1,Triples).
+
+context_triple(Excludes,URI,Visited,T) :-
+   edge(URI,Pred,URI1,Triple),
+   \+member(Pred,Excludes),
+   (  T=Triple
+   ;  \+member(URI1,Visited), 
+      %context_graphable(URI1), % this follows a lot of link
+      rdfs_individual_of(URI1,event:'Event'),
+      context_triple(Excludes,URI1,[URI|Visited],T)
+   ).
+
+edge(URI,Pred,URI1,rdf(URI,Pred,URI1)) :- rdf(URI,Pred,URI1), URI1\=literal(_).
+edge(URI,Pred,URI1,rdf(URI1,Pred,URI)) :- rdf(URI1,Pred,URI).
+
+context_graphable(URI) :-
+   context_graph_class(Class),
+   rdfs_individual_of(URI,Class).
+
+context_graph_class(event:'Event').
+context_graph_class(mo:'Signal').
+context_graph_class(mo:'MusicalWork').
+context_graph_class(mo:'MusicGroup').
+
+current_periodical(Interval,Goal,Id) :- current_alarm(_,periodically(Interval,Goal),Id,_).
+remove_periodical(Id) :- remove_alarm(Id).
+
+periodically(Interval,Goal) :-
+   memo:reify(Goal,Status),
+   (Status=ok -> true; debug(cron,'Periodic goal ~q failed with ~q',[Goal,Status])),
+   alarm(Interval,periodically(Interval,Goal),_,[remove(true)]).
+