Did you know ... Search Documentation:
terms.pl -- SICStus 4-compatible library(terms).
PublicShow source
See also
- https://sicstus.sics.se/sicstus/docs/4.6.0/html/sicstus.html/lib_002dterms.html
To be done
- This library is incomplete. As of SICStus 4.6.0, the following predicates are missing:
Source term_variables_set(@Term, -Variables) is det
Same as term_variables_bag/2, but Variables is an ordered set.
Source subsumeschk(+Generic, @Specific) is semidet
SICStus 4 name of subsumes_chk/2.
deprecated
- Replace by subsumes_term/2.
Source term_order(@X, @Y, -R) is det
Same as compare/3, except for the order of arguments.
deprecated
- Use the standard compare/3 instead.

Re-exported predicates

The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

Source term_variables_bag(+Term, -Variables) is det
Variables is a list of variables that appear in Term. The variables are ordered according to depth-first left-right walking of the term. Variables contains no duplicates. This is the same as SWI-Prolog's term_variables/2.
Source contains_term(+Sub, +Term) is semidet
Succeeds if Sub is contained in Term (=, deterministically)
Source contains_var(+Sub, +Term) is semidet
Succeeds if Sub is contained in Term (==, deterministically)
Source free_of_term(+Sub, +Term) is semidet
Succeeds of Sub does not unify to any subterm of Term
Source free_of_var(+Sub, +Term) is semidet
Succeeds of Sub is not equal (==) to any subterm of Term
Source occurrences_of_term(@SubTerm, @Term, ?Count) is det
Count the number of SubTerms in Term that unify with SubTerm. As this predicate is implemented using backtracking, SubTerm and Term are not further instantiated. Possible constraints are enforced. For example, we can count the integers in Term using
?- freeze(S, integer(S)), occurrences_of_term(S, f(1,2,a), C).
C = 2,
freeze(S, integer(S)).
See also
- occurrences_of_var/3 for an equality (==/2) based variant.
Source occurrences_of_var(@SubTerm, @Term, ?Count) is det
Count the number of SubTerms in Term that are equal to SubTerm. Equality is tested using ==/2. Can be used to count the occurrences of a particular variable in Term.
See also
- occurrences_of_term/3 for a unification (=/2) based variant.
Source sub_term(-Sub, +Term)
Generates (on backtracking) all subterms of Term.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

Source same_functor(Arg1, Arg2)
Source mapsubterms(Arg1, Arg2, Arg3)
 term_hash(Arg1, Arg2)
Source subsumes_chk(Arg1, Arg2)
 term_hash(Arg1, Arg2, Arg3, Arg4)
Source same_functor(Arg1, Arg2, Arg3)
Source mapsubterms_var(Arg1, Arg2, Arg3)
Source term_subsumer(Arg1, Arg2, Arg3)
Source term_size(Arg1, Arg2)
Source same_functor(Arg1, Arg2, Arg3, Arg4)
 cyclic_term(Arg1)
Source term_factorized(Arg1, Arg2, Arg3)
Source variant(Arg1, Arg2)
Source foldsubterms(Arg1, Arg2, Arg3, Arg4)
Source mapargs(Arg1, Arg2, Arg3)
Source subsumes(Arg1, Arg2)
 term_variables(Arg1, Arg2, Arg3)
Source foldsubterms(Arg1, Arg2, Arg3, Arg4, Arg5)