% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(terms): Term manipulation} \label{sec:terms} \begin{tags} \tag{Compatibility} YAP, SICStus, Quintus. Not all versions of this library define exactly the same set of predicates, but defined predicates are compatible. \end{tags} Compatibility library for term manipulation predicates. Most predicates in this library are provided as SWI-Prolog built-ins.\vspace{0.7cm} \begin{description} \predicate[det]{term_size}{2}{@Term, -Size} True if \arg{Size} is the size in \textit{cells} occupied by \arg{Term} on the global (term) stack. A \textit{cell} is 4 bytes on 32-bit machines and 8 bytes on 64-bit machines. The calculation does take \textit{sharing} into account. For example: \begin{code} ?- A = a(1,2,3), term_size(A,S). S = 4. ?- A = a(1,2,3), term_size(a(A,A),S). S = 7. ?- term_size(a(a(1,2,3), a(1,2,3)), S). S = 11. \end{code} Note that small objects such as atoms and small integers have a size 0. Space is allocated for floats, large integers, strings and compound terms. \predicate[semidet]{variant}{2}{@Term1, @Term2} Same as SWI-Prolog \verb$Term1 =@= Term2$. \predicate{subsumes_chk}{2}{@Generic, @Specific} True if \arg{Generic} can be made equivalent to \arg{Specific} without changing \arg{Specific}. \begin{tags} \tag{deprecated} Replace by \predref{subsumes_term}{2}. \end{tags} \predicate{subsumes}{2}{+Generic, @Specific} True if \arg{Generic} is unified to \arg{Specific} without changing \arg{Specific}. \begin{tags} \tag{deprecated} It turns out that calls to this predicate almost always should have used \predref{subsumes_term}{2}. Also the name is misleading. In case this is really needed, one is adviced to follow \predref{subsumes_term}{2} with an explicit unification. \end{tags} \predicate[det]{term_subsumer}{3}{+Special1, +Special2, -General} \arg{General} is the most specific term that is a generalisation of \arg{Special1} and \arg{Special2}. The implementation can handle cyclic terms. \begin{tags} \tag{author} Inspired by LOGIC.PRO by Stephen Muggleton \tag{Compatibility} SICStus \end{tags} \predicate{term_factorized}{3}{+Term, -Skeleton, -Substiution} Is true when \arg{Skeleton} is \arg{Term} where all subterms that appear multiple times are replaced by a variable and Substitution is a list of Var=Value that provides the subterm at the location Var. I.e., After unifying all substitutions in Substiutions, \arg{Term} \Sequal{} \arg{Skeleton}. \arg{Term} may be cyclic. For example: \begin{code} ?- X = a(X), term_factorized(b(X,X), Y, S). Y = b(_G255, _G255), S = [_G255=a(_G255)]. \end{code} \predicate{mapargs}{3}{:Goal, ?Term1, ?Term2} \arg{Term1} and \arg{Term2} have the same functor (name/arity) and for each matching pair of arguments \verb$call(Goal, A1, A2)$ is true. \predicate[det]{mapsubterms}{3}{:Goal, +Term1, -Term2} \nodescription \predicate[det]{mapsubterms_var}{3}{:Goal, +Term1, -Term2} Recursively map sub terms of \arg{Term1} into subterms of \arg{Term2} for every pair for which \verb$call(Goal, ST1, ST2)$ succeeds. Procedurably, the mapping for each (sub) term pair \verb$T1/T2$ is defined as: \begin{itemize} \item If \arg{T1} is a variable \begin{shortlist} \item \predref{mapsubterms}{3} unifies \arg{T2} with \arg{T1}. \item \predref{mapsubterms_var}{3} treats variables as other terms. \end{shortlist} \item If \verb$call(Goal, T1, T2)$ succeeds we are done. Note that the mapping does not continue in \arg{T2}. If this is desired, \arg{Goal} must call \predref{mapsubterms}{3} explicitly as part of its conversion. \item If \arg{T1} is a dict, map all values, i.e., the \textit{tag} and \textit{keys} are left untouched. \item If \arg{T1} is a list, map all elements, i.e., the list structure is left untouched. \item If \arg{T1} is a compound, use \predref{same_functor}{3} to instantiate \arg{T2} and recurse over the term arguments left to right. \item Otherwise \arg{T2} is unified with \arg{T1}. \end{itemize} Both predicates are implemented using \predref{foldsubterms}{5}. \predicate[semidet]{foldsubterms}{4}{:Goal3, +Term1, +State0, -State} \nodescription \predicate[semidet]{foldsubterms}{5}{:Goal4, +Term1, ?Term2, +State0, -State} The predicate \predref{foldsubterms}{5} calls \verb$call(Goal4, SubTerm1, SubTerm2, StateIn, StateOut)$ for each subterm, including variables, in \arg{Term1}. If this call fails, \arg{StateIn} and \arg{StateOut} are the same. This predicate may be used to map subterms in a term while collecting state about the mapped subterms. The \predref{foldsubterms}{4} variant does not map the term. \predicate[semidet]{same_functor}{2}{?Term1, ?Term2} \nodescription \predicate[semidet]{same_functor}{3}{?Term1, ?Term2, -Arity} \nodescription \predicate[semidet]{same_functor}{4}{?Term1, ?Term2, ?Name, ?Arity} True when \arg{Term1} and \arg{Term2} are terms that have the same functor (\arg{Name}/\arg{Arity}). The arguments must be sufficiently instantiated, which means either \arg{Term1} or \arg{Term2} must be bound or both \arg{Name} and \arg{Arity} must be bound. If \arg{Arity} is 0, \arg{Term1} and \arg{Term2} are unified with \arg{Name} for compatibility. \begin{tags} \tag{Compatibility} SICStus \end{tags} \end{description}