View source with raw comments or as raw
    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)  2001-2020, University of Amsterdam
    7                              SWI-Prolog Solutions b.v.
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(occurs,
   37          [ contains_term/2,            % +SubTerm, +Term
   38            contains_var/2,             % +SubTerm, +Term
   39            free_of_term/2,             % +SubTerm, +Term
   40            free_of_var/2,              % +SubTerm, +Term
   41            occurrences_of_term/3,      % +SubTerm, +Term, ?Tally
   42            occurrences_of_var/3,       % +SubTerm, +Term, ?Tally
   43            sub_term/2,                 % -SubTerm, +Term
   44            sub_var/2,                  % -SubTerm, +Term (SWI extra)
   45            sub_term_shared_variables/3 % +Sub, +Term, -Vars
   46          ]).

Finding and counting sub-terms

This is a SWI-Prolog implementation of the corresponding Quintus library, based on the generalised arg/3 predicate of SWI-Prolog.

See also
- library(terms) provides similar predicates and is probably more wide-spread than this library. */
 contains_term(+Sub, +Term) is semidet
Succeeds if Sub is contained in Term (=, deterministically)
   61contains_term(X, X) :- !.
   62contains_term(X, Term) :-
   63    compound(Term),
   64    arg(_, Term, Arg),
   65    contains_term(X, Arg),
   66    !.
 contains_var(+Sub, +Term) is det
Succeeds if Sub is contained in Term (==, deterministically)
   73contains_var(X0, X1) :-
   74    X0 == X1,
   75    !.
   76contains_var(X, Term) :-
   77    compound(Term),
   78    arg(_, Term, Arg),
   79    contains_var(X, Arg),
   80    !.
 free_of_term(+Sub, +Term)
Succeeds of Sub does not unify to any subterm of Term
   86free_of_term(Sub, Term) :-
   87    \+ contains_term(Sub, Term).
 free_of_var(+Sub, +Term)
Succeeds of Sub is not equal (==) to any subterm of Term
   93free_of_var(Sub, Term) :-
   94    \+ contains_var(Sub, Term).
 occurrences_of_term(+SubTerm, +Term, ?Count)
Count the number of SubTerms in Term
  100occurrences_of_term(Sub, Term, Count) :-
  101    count(sub_term(Sub, Term), Count).
 occurrences_of_var(+SubTerm, +Term, ?Count)
Count the number of SubTerms in Term
  107occurrences_of_var(Sub, Term, Count) :-
  108    count(sub_var(Sub, Term), Count).
 sub_term(-Sub, +Term)
Generates (on backtracking) all subterms of Term.
  114sub_term(X, X).
  115sub_term(X, Term) :-
  116    compound(Term),
  117    arg(_, Term, Arg),
  118    sub_term(X, Arg).
 sub_var(-Sub, +Term)
Generates (on backtracking) all subterms (==) of Term.
  124sub_var(X0, X1) :-
  125    X0 == X1.
  126sub_var(X, Term) :-
  127    compound(Term),
  128    arg(_, Term, Arg),
  129    sub_var(X, Arg).
 sub_term_shared_variables(+Sub, +Term, -Vars) is det
If Sub is a sub term of Term, Vars is bound to the list of variables in Sub that also appear outside Sub in Term. Note that if Sub appears twice in Term, its variables are all considered shared.

An example use-case is refactoring a large clause body by introducing intermediate predicates. This predicate can be used to find the arguments that must be passed to the new predicate.

  142sub_term_shared_variables(Sub, Term, Vars) :-
  143    term_replace_first(Term, Sub, true, Term2),
  144    term_variables(Term2, AllVars),
  145    term_variables(Sub, SubVars),
  146    intersection_eq(SubVars, AllVars, Vars).
  147
  148term_replace_first(TermIn, From, To, TermOut) :-
  149    term_replace_(TermIn, From, To, TermOut, done(_)).
  150
  151%term_replace(TermIn, From, To, TermOut) :-
  152%    term_replace_(TermIn, From, To, TermOut, all).
 term_replace_(+From, +To, +TermIn, -TermOut, +Done)
Replace instances (==/2) of From inside TermIn by To.
  158term_replace_(TermIn, _From, _To, TermOut, done(Done)) :-
  159    Done == true,
  160    !,
  161    TermOut = TermIn.
  162term_replace_(TermIn, From, To, TermOut, Done) :-
  163    From == TermIn,
  164    !,
  165    TermOut = To,
  166    (   Done = done(Var)
  167    ->  Var = true
  168    ;   true
  169    ).
  170term_replace_(TermIn, From, To, TermOut, Done) :-
  171    compound(TermIn),
  172    compound_name_arity(TermIn, Name, Arity),
  173    Arity > 0,
  174    !,
  175    compound_name_arity(TermOut, Name, Arity),
  176    term_replace_compound(1, Arity, TermIn, From, To, TermOut, Done).
  177term_replace_(Term, _, _, Term, _).
  178
  179term_replace_compound(I, Arity, TermIn, From, To, TermOut, Done) :-
  180    I =< Arity,
  181    !,
  182    arg(I, TermIn, A1),
  183    arg(I, TermOut, A2),
  184    term_replace_(A1, From, To, A2, Done),
  185    I2 is I+1,
  186    term_replace_compound(I2, Arity, TermIn, From, To, TermOut, Done).
  187term_replace_compound(_I, _Arity, _TermIn, _From, _To, _TermOut, _).
 intersection_eq(+Small, +Big, -Shared) is det
Shared are the variables in Small that also appear in Big. The variables in Shared are in the same order as Small.
  194intersection_eq([], _, []).
  195intersection_eq([H|T0], L, List) :-
  196    (   member_eq(H, L)
  197    ->  List = [H|T],
  198        intersection_eq(T0, L, T)
  199    ;   intersection_eq(T0, L, List)
  200    ).
  201
  202member_eq(E, [H|T]) :-
  203    (   E == H
  204    ->  true
  205    ;   member_eq(E, T)
  206    ).
  207
  208
  209                 /*******************************
  210                 *              UTIL            *
  211                 *******************************/
 count(:Goal, -Count)
Count number of times Goal succeeds.
  217:- meta_predicate count(0,-).  218
  219count(Goal, Count) :-
  220    State = count(0),
  221    (   Goal,
  222        arg(1, State, N0),
  223        N is N0 + 1,
  224        nb_setarg(1, State, N),
  225        fail
  226    ;   arg(1, State, Count)
  227    )