annotate 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
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_misc, [ periodically/2, current_periodical/3, remove_periodical/1 ]).
Daniel@0 20 /** <module> Miscellaneous hooks and initialisations
Daniel@0 21
Daniel@0 22 This module implements some hooks for managing the context graphs
Daniel@0 23 which appear at the bottom of individual resource pages.
Daniel@0 24
Daniel@0 25 It also loads some miscellanous RDF graphs.
Daniel@0 26
Daniel@0 27 */
Daniel@0 28 :- use_module(library(semweb/rdf_db)).
Daniel@0 29 :- use_module(library(semweb/rdfs)).
Daniel@0 30 :- use_module(library(memo)).
Daniel@0 31 :- use_module(cliopatria(hooks)).
Daniel@0 32
Daniel@0 33 :- rdf_meta context_graph_class(r).
Daniel@0 34
Daniel@0 35 :- meta_predicate periodically(+,0).
Daniel@0 36 :- meta_predicate current_periodical(-,0,-).
Daniel@0 37
Daniel@0 38 cliopatria:context_graph(URI, Triples, _) :-
Daniel@0 39 context_graphable(URI), !,
Daniel@0 40 maplist(rdf_global_id,[rdf:type, prov:wasDerivedFrom],Excludes),
Daniel@0 41 findall(T, context_triple(Excludes,URI,[],T), T1),
Daniel@0 42 sort(T1,Triples).
Daniel@0 43
Daniel@0 44 context_triple(Excludes,URI,Visited,T) :-
Daniel@0 45 edge(URI,Pred,URI1,Triple),
Daniel@0 46 \+member(Pred,Excludes),
Daniel@0 47 ( T=Triple
Daniel@0 48 ; \+member(URI1,Visited),
Daniel@0 49 %context_graphable(URI1), % this follows a lot of link
Daniel@0 50 rdfs_individual_of(URI1,event:'Event'),
Daniel@0 51 context_triple(Excludes,URI1,[URI|Visited],T)
Daniel@0 52 ).
Daniel@0 53
Daniel@0 54 edge(URI,Pred,URI1,rdf(URI,Pred,URI1)) :- rdf(URI,Pred,URI1), URI1\=literal(_).
Daniel@0 55 edge(URI,Pred,URI1,rdf(URI1,Pred,URI)) :- rdf(URI1,Pred,URI).
Daniel@0 56
Daniel@0 57 context_graphable(URI) :-
Daniel@0 58 context_graph_class(Class),
Daniel@0 59 rdfs_individual_of(URI,Class).
Daniel@0 60
Daniel@0 61 context_graph_class(event:'Event').
Daniel@0 62 context_graph_class(mo:'Signal').
Daniel@0 63 context_graph_class(mo:'MusicalWork').
Daniel@0 64 context_graph_class(mo:'MusicGroup').
Daniel@0 65
Daniel@0 66 current_periodical(Interval,Goal,Id) :- current_alarm(_,periodically(Interval,Goal),Id,_).
Daniel@0 67 remove_periodical(Id) :- remove_alarm(Id).
Daniel@0 68
Daniel@0 69 periodically(Interval,Goal) :-
Daniel@0 70 memo:reify(Goal,Status),
Daniel@0 71 (Status=ok -> true; debug(cron,'Periodic goal ~q failed with ~q',[Goal,Status])),
Daniel@0 72 alarm(Interval,periodically(Interval,Goal),_,[remove(true)]).
Daniel@0 73