Next: , Previous: , Up: The Prolog Library   [Contents][Index]


10.47 Term Utilities—library(terms)

This library module provides miscellaneous operations on terms. Exported predicates:

subsumeschk(+General, +Specific)

is true when Specific is an instance of General. It does not bind any variables.

This predicate is identical to the built-in subsumes_term/2 and it is only present for backwards compatibility.

subsumes(+General, +Specific)

is true when Specific is an instance of General. It will bind variables in General (but not those in Specific, except when +General and +Specific share variables) so that General becomes identical to Specific.

In many cases, binding variable is not really desirable, in which case subsumes_term/2 should be used instead. If unification is in fact wanted, it may be better to make this explicit in your code by using subsumes_term/2 followed by an explicit unification, e.g. subsumes_term(G,S), G=S.

variant(+Term, +Variant)

is true when Term and Variant are identical modulo renaming of variables, provided Term and Variant have no variables in common.

term_subsumer(+Term1, +Term2, -Term)

binds Term to a most specific generalization of Term1 and Term2. Using Plotkin’s algorithm [Machine Intelligence 5, 1970], extended by Dan Sahlin to handle cyclic structures.

term_hash(+Term, -Hash)

Equivalent to term_hash(Term, [], Hash).

term_hash(+Term, +Options, -Hash)

term_hash/[2,3,4] is provided primarily as a tool for the construction of sophisticated Prolog clause access schemes. Its intended use is to generate hash values for terms that will be used with first argument clause indexing, yielding compact and efficient multi-argument or deep argument indexing. Options is a list of options,

algorithm(Algorithm)

Algorithm specifies which hash function to use. An atom, one of,

default

This is currently the same as jenkins. This is the default. If we ever see a need to change the default hash algorithm again then the algorithm denoted by default may change but the algorithm denoted by the other names, like 'sicstus-4.0.5', will not change.

jenkins

Based on the algorithm “lookup3” by Bob Jenkins, see http://burtleburtle.net/bob/hash/doobs.html.

hsieh

Based on the algorithm “SuperFastHash” by Paul Hsieh, see http://www.azillionmonkeys.com/qed/hash.html. Despite the name neither this nor any other choice of algorithm significantly affects the speed of term_hash/3.

sdbm

Based on the well known algorithm “sdbm”.

'sicstus-4.0.4'

This is the algorithm used up to SICStus Prolog 4.0.4 (inclusive). It is only present to provide backwards compatibility. It is not as good as any of the above algorithms. Note that this atom needs to be quoted.

This algorithm produces hash values that may differ between platforms.

'sicstus-4.0.5'

This is the same as jenkins. I.e. the default since SICStus Prolog 4.0.5. Note that this atom needs to be quoted.

there are some other (not as good) algorithms available for the curious, see the source for detail.

Unless otherwise noted, the hash value will be identical across runs and platforms.

range(Range)

The resulting hash value will be non-negative and less than the upper bound specified by Range. Range should be either a positive integer, or an atom, one of,

infinite

Do not constrain the hash value. Currently all hash algorithms produce an unsigned 32-bit integer.

smallint

Ensure the resulting hash value is a small integer. This is the same as specifying a range of 2^28 on 32-bit platforms and 2^60 on 64-bit platforms.

smallint32

Ensure the resulting hash value is in the 32-bit platform range of small integers, i.e. the same as a range of 2^28.

default

The same as smallint32. This is the default. This ensures that, by default, the same hash value is computed for the same term on both 32-bit and 64-bit platforms.

depth(Depth)

Specifies how deep to descend into the term when calculating the hash value. If Depth is a non-negative integer the subterms up to depth Depth of Term are used in the computation. Alternatively, if Depth is the atom infinite, all subterms of Term are relevant in computing Hash. In the latter case Term must be acyclic. In this context the depth of a term is defined as follows: the (principal functor of) the term itself has depth 1, and an argument of a term with depth i has depth i+1. Note that this is similar to, but not the same as, the value computed by term_depth/2. For legacy reasons a Depth of -1 is treated the same a infinite.

if_var(IfVar)

Specifies what to do if a variable is encountered in the term (i.e. to the specified depth). IfVar should be an atom, one of,

error

An instantiation error is thrown.

ignore

The variable is ignored and the hash algorithm continues with the other parts of the term.

value(Value)

The hash algorithm stops, the intermediate hash result is discarded and Hash is bound to Value. There is no restrictions on Value, it need not be an integer or even be ground.

default

This is the same as value(_), i.e. term_hash/3 just succeeds without binding Hash. This is the default. This is useful when the hash value us used for first-argument indexing. This ensures that if the (possibly variable-valued) hash values for Term1 and Term2 are Hash1 and Hash2, respectively, then if Term1 and Term2 are unifiable (to the specified depth) then so are Hash1 and Hash2. For other use cases it is probably more appropriate to specify if_var(error).

term_hash(+Term, +Depth, +Range, -Hash)

Equivalent to term_hash(Term, [depth(Depth), range(Range)], Hash).

term_variables_set(+Term, -Variables)   since release 4.3

True if Variables is the (ordered) set of variables occurring in Term.

This was called term_variables/2 prior to SICStus Prolog 4.3 but now term_variables/2 is a built-in with different meaning, due to alignment with the ISO Prolog standard.

term_variables_bag(+Term, -Variables)

True if Variables is the list of variables occurring in Term, in first occurrence order.

This predicate has been superseded by the built-in term_variables/2 and it is only present for backwards compatibility.

The name is an historical accident, the result is not really a bag (i.e. multiset).

cyclic_term(+X)

True if X is infinite (cyclic). Runs in linear time.

term_order(+X, +Y, -R)

is true when X and Y are arbitrary terms, and R is <, =, or > according as X @< Y, X == Y, or X @> Y. This is the same as compare/3, except for the argument order.

contains_term(+Kernel, +Expression)

is true when the given Kernel occurs somewhere in the Expression. It can only be used as a test; to generate sub-terms use sub_term/2.

free_of_term(+Kernel, +Expression)

is true when the given Kernel does not occur anywhere in the Expression. NB: if the Expression contains an unbound variable, this must fail, as the Kernel might occur there. Since there are infinitely many Kernels not contained in any Expression, and also infinitely many Expressions not containing any Kernel, it doesn’t make sense to use this except as a test.

occurrences_of_term(+Kernel, +Expression, -Tally)

is true when the given Kernel occurs exactly Tally times in Expression. It can only be used to calculate or test Tally; to enumerate Kernels you’ll have to use sub_term/2 and then test them with this routine. If you just want to find out whether Kernel occurs in Expression or not, use contains_term/2 or free_of_term/2.

contains_var(+Variable, +Term)

is true when the given Term contains at least one sub-term which is identical to the given Variable. We use == to check for the variable (contains_term/2 uses =) so it can be used to check for arbitrary terms, not just variables.

free_of_var(+Variable, +Term)

is true when the given Term contains no sub-term identical to the given Variable (which may actually be any term, not just a var). For variables, this is precisely the "occurs check" which is needed for sound unification.

occurrences_of_var(+Variable, +Term, -Tally)

is true when the given Variable occurs exactly Tally times in Term. It can only be used to calculate or test Tally; to enumerate Variables you’ll have to use sub_term/2 and then test them with this routine. If you just want to find out whether Variable occurs in Term or not, use contains_var/2 or free_of_var/2.

sub_term(?Kernel, +Term)

is true when Kernel is a sub-term of Term. It enumerates the sub-terms of Term in an arbitrary order. Well, it is defined that a sub-term of Term will be enumerated before its own sub-terms are (but of course some of those sub-terms might be elsewhere in Term as well).

depth_bound(+Term, +Bound)

is true when the term depth of Term is no greater than Bound, that is, when constructor functions are nested no more than Bound deep. Later variable bindings may invalidate this bound. To find the (current) depth, use term_depth/2.

length_bound(?List, +Bound)

is true when the length of List is no greater than Bound. It can be used to enumerate Lists up to the bound.

size_bound(+Term, +Bound)

is true when the number of constant and function symbols in Term is (currently) at most Bound. If Term is non-ground, later variable bindings may invalidate this bound. To find the (current) size, use term_size/2.

term_depth(+Term, -Depth)

calculates the Depth of a Term, using the definition

    term_depth(Var) = 0
    term_depth(Const) = 0
    term_depth(F(T1,...,Tn)) = 1+max(term_depth(T1),...,term_depth(Tn))

Could be defined as:

term_depth(X, Depth) :-
    simple(X), !, Depth = 0.
term_depth(X, Depth) :-
    (   foreacharg(A,X),
        fromto(0,D0,D,Depth0)
    do  term_depth(A, D1),
        D is max(D0,D1)
    ),
    Depth is Depth0+1.
term_size(+Term, -Size)

calculates the Size of a Term, defined to be the number of constant and function symbol occurrences in it. Could be defined as:

term_size(X, Size) :-
    var(X), !, Size = 0.
term_size(X, Size) :-
    simple(X), !, Size = 1.
term_size(X, Size) :-
    (   foreacharg(A,X),
        fromto(1,S0,S,Size)
    do  term_size(A, S1),
        S is S0+S1
    ).
same_functor(?T1, ?T2)

is true when T1 and T2 have the same principal functor. If one of the terms is a variable, it will be instantiated to a new term with the same principal functor as the other term (which should be instantiated) and with arguments being new distinct variables. If both terms are variables, an error is reported.

same_functor(?T1, ?T2, ?N)

is true when T1 and T2 have the same principal functor, and their common arity is N. Like same_functor/3, at least one of T1 and T2 must be bound, or an error will be reported.

same_functor(?T1, ?T2, ?F, ?N)

is true when T1 and T2 have the same principal functor, and their common functor is F/N. Given T1 (or T2) the remaining arguments can be computed. Given F and N, the remaining arguments can be computed. If too many arguments are unbound, an error is reported.



Send feedback on this subject.