1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2017, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(prolog_signature,
   36          [ goal_signature/2,           % :Goal, -Signature
   37            goal_signature/3,           % :Goal, -Signature, -Vars
   38            deep_predicate_hash/2,      % :Head, -Hash
   39            predicate_callees/2,        % :Head, -Callees
   40            predicate_dependencies/2,   % :Head, -Dependencies
   41
   42            sig_clean_cache/0,
   43            sig_clean_cache/1           % +Module
   44          ]).   45:- use_module(library(prolog_codewalk)).   46:- use_module(library(ordsets)).   47:- use_module(library(apply)).   48
   49:- meta_predicate
   50    goal_signature(:, -),
   51    goal_signature(:, -, -),
   52    predicate_callees(:, -),
   53    deep_predicate_hash(:, -),
   54    predicate_dependencies(:, -).   55
   56:- multifile
   57    hook_predicate_hash/2.              % :Head, -Hash

Create signatures for a program

This module is concerned with creating signatures for a predicate. The signature guarantees that neither the predicate itself, not one of its callees has changed. This is used to support persistent result caching. */

 goal_signature(:Goal, -Term) is det
 goal_signature(:Goal, -Term, -Vars) is det
Replace the module and functor of Goal with a hash. For example,
user:between(1, 5, X),

becomes something like this:

'931be36e3ed89e766d332277a61664ff3c08d56a'(1, 5, X).

The hash is based on the predicate and predicates reachable though the call graph for the most generic form.

Arguments:
Vars- is a term holding the variables in Goal/Term (these are the same).
   83:- dynamic goal_signature_c/3.   84
   85goal_signature(M:Goal, Term) :-
   86    goal_signature_c(Goal, M, Term0),
   87    predicate_dependencies_not_changed(M:Goal),
   88    !,
   89    Term = Term0.
   90goal_signature(Goal0, Term) :-
   91    generalise(Goal0, M:Goal),
   92    retractall(goal_signature_c(Goal, M, _)),
   93    goal_signature_nc(M:Goal, Term0),
   94    assertz(goal_signature_c(Goal, M, Term0)),
   95    _:Goal = Goal0,
   96    Term = Term0.
   97
   98goal_signature_nc(M:Goal, Term) :-
   99    deep_predicate_hash(M:Goal, Hash),
  100    Goal =.. [_|Args],
  101    Term =.. [Hash|Args].
  102
  103goal_signature(Goal, Term, Vars) :-
  104    goal_signature(Goal, Term),
  105    term_variables(Term, VarList),
  106    Vars =.. [v|VarList].
 deep_predicate_hash(:Head, -Hash) is det
Compute the predicate hash of Head and all its callees and combine this into a single hash.
To be done
- Could be faster by keeping track of the combined dependent hashes of predicates per module.
  116deep_predicate_hash(Head, Hash) :-
  117    predicate_dependencies(Head, Callees),
  118    maplist(predicate_hash, Callees, Hashes),
  119    variant_sha1(Hashes, Hash).
 predicate_hash(:Head, -Hash) is det
Compute the hash for a single predicate. If the predicates clauses can be accessed, this is the variant hash of all clauses, otherwise it is the variant hash of the head.

This predicate can be hooked using hook_predicate_hash/2.

 hook_predicate_hash(:Head, -Hash) is semidet
Hook that can be used to define the signature of a predicate. Hash must be an SHA1 hash key (see variant_sha1/2). Defining this hook has two effects:
  1. The predicate is claimed to have no dependencies. This in itself can be exploited to prune dependency tracking.
  2. The signature is Hash. A typical use case is a fact base that is derived from a file.
  140:- dynamic predicate_hash_c/4.  141
  142predicate_hash(Head, Hash) :-
  143    hook_predicate_hash(Head, Hash),
  144    !.
  145predicate_hash(M:Head, Hash) :-
  146    predicate_hash_c(Head, M, Gen, Hash0),
  147    predicate_generation(M:Head, Gen),
  148    !,
  149    Hash = Hash0.
  150predicate_hash(M:Head, Hash) :-
  151    retractall(predicate_hash_c(Head, M, _, _)),
  152    predicate_hash_nc(M:Head, Hash0),
  153    predicate_generation(M:Head, Gen),
  154    assertz(predicate_hash_c(Head, M, Gen, Hash0)),
  155    Hash = Hash0.
  156
  157predicate_hash_nc(Head, Hash) :-
  158    implementation(Head, Head1),
  159    (   predicate_property(Head1, interpreted)
  160    ->  Head1 = _:Head2,
  161        findall((Head2:-Body), clause(Head1,Body), Clauses),
  162        variant_sha1(Clauses, Hash)
  163    ;   variant_sha1(Head1, Hash)
  164    ).
  165
  166implementation(M0:Head, M:Head) :-
  167    predicate_property(M0:Head, imported_from(M1)),
  168    !,
  169    M = M1.
  170implementation(Head, Head).
  171
  172:- dynamic
  173    predicate_dependencies_mc/3,
  174    predicate_dependencies_c/3.
 predicate_dependencies_not_changed(:Head) is semidet
True when the dependencies of a predicate may have been changed.
  180predicate_dependencies_not_changed(M:Head) :-
  181    predicate_dependencies_mc(Head, M, Modules),
  182    maplist(module_not_modified, Modules).
 predicate_dependencies(:Head, -Callees:list(callable)) is det
True when Callees is a set (ordered list) of all predicates that are directly or indirectly reachable through Head.
  189predicate_dependencies(Goal, Callees) :-
  190    generalise(Goal, M:Head),
  191    (   hook_predicate_hash(Head, _Hash)
  192    ->  Callees = []
  193    ;   predicate_dependencies_mc(Head, M, Modules),
  194        predicate_dependencies_c(Head, M, Callees0),
  195        (   maplist(module_not_modified, Modules)
  196        ->  true
  197        ;   maplist(predicate_not_modified, Callees0)
  198        ->  callee_modules(Callees0, Modules),
  199            retractall(predicate_dependencies_mc(Head, M, _)),
  200            assertz(predicate_dependencies_mc(Head, M, Modules))
  201        )
  202    ->  true
  203    ;   retractall(predicate_dependencies_mc(Head, M, _)),
  204        retractall(predicate_dependencies_c(Head, M, _)),
  205        predicate_dependencies_nc(M:Head, Callees0),
  206        callee_modules(Callees0, Modules),
  207        assertz(predicate_dependencies_c(Head, M, Callees0)),
  208        assertz(predicate_dependencies_mc(Head, M, Modules))
  209    ),
  210    Callees = Callees0.
  211
  212predicate_not_modified(M:Head) :-
  213    predicate_callees_c(Head, M, Gen, _Callees0),
  214    predicate_generation(M:Head, Gen).
  215
  216module_not_modified(M-Gen) :-
  217    (   module_property(M, last_modified_generation(Gen0))
  218    ->  Gen0 == Gen
  219    ;   Gen == 0
  220    ).
  221
  222callee_modules(Callees, Modules) :-
  223    maplist(arg(1), Callees, MList0),
  224    sort(MList0, MList),
  225    maplist(module_gen, MList, Modules).
  226
  227module_gen(M, M-Gen) :-
  228    module_property(M, last_modified_generation(Gen)),
  229    !.
  230module_gen(M, M-0).
  231
  232predicate_dependencies_nc(Head, Callees) :-
  233    ground(Head, GHead),
  234    predicate_dependencies(Head, [GHead], Callees0),
  235    maplist(generalise, Callees0, Callees1),
  236    order_callees(Callees1, Callees).
 order_callees(+Callees1, -Callees) is det
Order the callees such that the ordering remains consistent in the presence of a temporary, anonymous module. We first order by Head and then if there are module conflicts we place the temporary module last.
To be done
- an alternative might be to use the deep hash for ordering, such that the hash becomes completely independent from predicate and module naming.
  249order_callees(Callees1, Callees) :-
  250    sort(2, @>=, Callees1, Callees2),
  251    tmp_order(Callees2, Callees).
  252
  253tmp_order([], []).
  254tmp_order([M1:H,M2:H|T0], L) :-
  255    tmp_module(M1),
  256    !,
  257    L = [M2:H|T],
  258    tmp_order([M1:H|T0], T).
  259tmp_order([H|T0], [H|T]) :-
  260    tmp_order(T0, T).
 predicate_dependencies(+Head, +Callees0, -Callees)
Compute the transitive closure of predicates called from Head. Predicates are represented as M:C, where C is a numbervars-ed ground term.
  268predicate_dependencies(Head, Callees0, Callees) :-
  269    predicate_callees(Head, Called),
  270    maplist(ground, Called, GCalled),
  271    ord_subtract(GCalled, Callees0, New),
  272    (   New == []
  273    ->  Callees = Callees0
  274    ;   ord_union(Callees0, GCalled, Callees1),
  275        foldl(predicate_dependencies, New, Callees1, Callees)
  276    ).
  277
  278ground(Term, Ground) :-
  279    generalise(Term, Term2),
  280    copy_term(Term2, Ground),
  281    numbervars(Ground, 0, _).
  282
  283:- thread_local
  284    calls/1.  285
  286:- dynamic predicate_callees_c/4.  287
  288predicate_callees(M:Head, Callees) :-
  289    predicate_callees_c(Head, M, Gen, Callees0),
  290    predicate_generation(M:Head, Gen),
  291    !,
  292    Callees = Callees0.
  293predicate_callees(M:Head, Callees) :-
  294    retractall(predicate_callees_c(Head, M, _, _)),
  295    predicate_callees_nc(M:Head, Callees0),
  296    predicate_generation(M:Head, Gen),
  297    assertz(predicate_callees_c(Head, M, Gen, Callees0)),
  298    Callees = Callees0.
  299
  300predicate_callees_nc(Head0, Callees) :-
  301    generalise(Head0, Head),
  302    findall(CRef, nth_clause(Head, _, CRef), CRefs),
  303    prolog_walk_code(
  304        [ clauses(CRefs),
  305          autoload(true),
  306          trace_reference(_:_),
  307          on_trace(track_ref),
  308          source(false)
  309        ]),
  310    findall(Callee, retract(calls(Callee)), Callees0),
  311    sort(Callees0, Callees).
  312
  313:- public track_ref/3.  314
  315track_ref(Callee0, Caller, _Location) :-
  316    generalise(Callee0, Callee1),
  317    implementation(Callee1, Callee),
  318    (   calls(Callee)
  319    ->  true
  320    ;   \+ Callee \= Caller                     % exclude recursion
  321    ->  true
  322    ;   Callee = M:_,
  323        module_property(M, class(Class)),
  324        nodep_module_class(Class)
  325    ->  true
  326    ;   assertz(calls(Callee))
  327    ).
  328
  329nodep_module_class(system).
  330nodep_module_class(library).
  331
  332
  333generalise(M:Head0, M:Head) :-
  334    functor(Head0, Name, Arity),
  335    functor(Head, Name, Arity).
  336
  337predicate_generation(Head, Gen) :-
  338    predicate_property(Head, last_modified_generation(Gen0)),
  339    !,
  340    Gen = Gen0.
  341predicate_generation(_, 0).
 sig_clean_cache is det
 sig_clean_cache(+M) is det
Cleanup cached signatures and dependencies. If a module is given, only the depedencies for the matching module are removed.
  349sig_clean_cache :-
  350    sig_clean_cache(_).
  351
  352sig_clean_cache(M) :-
  353    retractall(goal_signature_c(_,M,_)),
  354    retractall(predicate_callees_c(_,M,_,_)),
  355    retractall(predicate_hash_c(_,M,_,_)),
  356    retractall(predicate_dependencies_c(_,M,_)),
  357    retractall(predicate_dependencies_mc(_,M,_)).
 tmp_module(+M) is semidet
True if M is a module that may be switched while the result should still be the same. These are also modules that can be removed from the cache.
  365tmp_module(M) :-
  366    module_property(M, class(temporary)).
  367
  368
  369		 /*******************************
  370		 *            SANDBOX		*
  371		 *******************************/
  372
  373:- multifile sandbox:safe_meta_predicate/1.  374
  375sandbox:safe_meta_predicate(prolog_signature:goal_signature/2).
  376sandbox:safe_meta_predicate(prolog_signature:goal_signature/3).
  377sandbox:safe_meta_predicate(prolog_signature:deep_predicate_hash/2)