view cpack/dml/lib/memo_p2r.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 source
/* 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(memo_p2r, []).

:- use_module(library(memo)).
:- use_module(entailment(p2r)).

uripattern:def( func(Mod,Pred,Arity), dml:function/enc(Mod)/enc(Pred)/num(Arity)).

% Memoisation schema
:- rdf_register_prefix(memo,'http://dml.org/memo/',[force(true)]).

:- public import/0.
import :- assert_all(memo_p2r).

rdf(memo:'Module', rdfs:subClassOf, owl:'Thing'),
rdf(memo:'Function', rdfs:subClassOf, owl:'Thing'),
rdf(memo:'Computation', rdfs:subClassOf, event:'Event'),
rdf(memo:function, rdfs:domain, memo:'Computation'),
rdf(memo:function, rdfs:range, memo:'Function'),
rdf(memo:module,   rdfs:domain, memo:'Function'),
rdf(memo:module,   rdfs:range,  memo:'Module'),
rdf(time:duration, rdfs:domain, event:'Event'),
rdf(time:duration, rdfs:range, xsd:decimal),
rdf(memo:type,     rdfs:domain, memo:'Function') <== true.
rdf(memo:storage,  rdfs:domain, memo:'Function') <== true.

rdf(dml: module/prolog/enc(Mod), rdf:type, memo:'Module'),
rdf(\func(Mod,Pred,Arity), rdf:type, memo:'Function'),
rdf(\func(Mod,Pred,Arity), memo:module, dml:module/prolog/enc(Mod)) <== 
   memo_function(Mod,Pred,Arity).

rdf(\func(Mod,Pred,Arity), rdfs:label, literal(Label)) <==
   memo_function(Mod,Pred,Arity),
   term_to_atom(Pred/Arity,Label).

rdf(\func(Mod,Pred,Arity), memo:type, literal(TypeAtom)) <==
   memo_property(Mod:Head,type(Type)),
   functor(Head,Pred,Arity),
   Type =.. [_|Types],
   term_to_atom(Types,TypeAtom).

rdf(\func(Mod,Pred,Arity), memo:storage, literal(Storage)) <==
   memo_property(Mod:Head,storage(Storage)),
   functor(Head,Pred,Arity).

% alternative duration type is xsd:duration,
% format as 'PT~fS'
% rdf(dml:computation/enc(Hash), rdf:type, memo:'Computation'),

% REMOVE COMPUTATIONS FOR NOW
% rdf(dml:computation/enc(Hash), time:duration, literal(type(xsd:double,Dur))),
% rdf(dml:computation/enc(Hash), memo:status, literal(StatusAtom)),
% rdf(dml:computation/enc(Hash), memo:function, \func(Mod,Pred,Arity)) <==
%    memo:computer(Mod,Head,_,_),
%    memo:browse(Mod:Head,Ev-Status),
%    variant_sha1(t(Mod,Head,Ev,Status),Hash),
%    (Ev=comp(_,_,Dur); Ev=comp(_,Dur)), % for time:duration
%    term_to_atom(Status,StatusAtom),    % for memo:status
%    functor(Head,Pred,Arity).           % for memo:function

% rdf(dml:computation/enc(Hash), memo:host, literal(Host)) <==
%    memo:computer(Mod,Head,_,_),
%    memo:browse(Mod:Head,Ev-Status),
%    variant_sha1(t(Mod,Head,Ev,Status),Hash),
%    (Ev=comp(Host,_,_); Ev=comp(Host,_)),
%    Host\='unknown'.

memo_function(Mod,Pred,Arity) :-
   memo_property(Mod:Head,storage(_)),
   functor(Head,Pred,Arity).