1:- module(
    2  term_ext,
    3  [
    4    ascii_id/1,            % -Id
    5    ascii_id/2,            % +Term, -Id
    6    compound_arguments/2,  % +Term, -Arguments
    7    compound_arity/2,      % +Term, -Arity
    8    compound_name/2,       % +Term, ?Name
    9    number_of_variables/2, % +Term, -NumberOfVariables
   10    replace_blobs/2,       % +Term1, -Term2
   11    shared_vars/2,         % +Terms, -SharedVariables
   12    shared_vars/3,         % +Term1, +Term2, -SharedVariables
   13    write_fact/1,          % @Term
   14    write_term/1           % @Term
   15  ]
   16).

Extended support for terms

Extends the support for terms in the SWI-Prolog standard library.

*/

   24:- use_module(library(apply)).   25:- use_module(library(dialect/sicstus4/terms)).   26:- use_module(library(dict)).   27:- use_module(library(ordsets)).   28:- use_module(library(uuid)).   29
   30:- use_module(library(hash_ext)).
 ascii_id(-Id:atom) is det
   36ascii_id(Id) :-
   37  uuid(Id0, [format(integer)]),
   38  atom_concat(n, Id0, Id).
 ascii_id(+Term:term, -Id:atom) is det
Generates an Id for the given Prolog term. The Id is guarantee to only contain ASCII letter and digits to ensure that it can be used by many programs.

Prolog terms can contain many characters and can have arbitrary size. For these reasons, this predicate generates the Id based on the MD5 hash of a serialization of the given Prolog term.

MD5 hashes sometimes start with an ASCII digit, which is not supported in some languages/context (for example, the DOT language does not allow IDs to start with a digit). For this reason, an arbitrary ASCII letter is prefixed at the beginning of the Id.

   57ascii_id(Term, Id) :-
   58  md5(Term, Hash),
   59  atomic_concat(n, Hash, Id).
 compound_arguments(+Term:term, -Arguments:list(term)) is det
   65compound_arguments(Term, Args) :-
   66  compound_name_arguments(Term, _, Args).
 compound_arity(+Term:term, -Arity:nonneg) is det
   72compound_arity(Term, Arity) :-
   73  compound_name_arity(Term, _, Arity).
 compound_name(+Term:term, +Name:atom) is semidet
compound_name(+Term:term, -Name:atom) is det
   80compound_name(Term, Name) :-
   81  compound_name_arity(Term, Name, _).
 number_of_variables(+Term:term, -NumberOfVariables:nonneg) is det
   87number_of_variables(Term, N) :-
   88  term_variables(Term, Vars),
   89  length(Vars, N).
 replace_blobs(+Term1, -Term2) is det
Copy Term1 to Term2, replacing non-text blobs. This is required for error messages that may hold streams and other handles to non-readable objects.
   99replace_blobs(X, X) :-
  100  var(X), !.
  101replace_blobs([], []) :- !.
  102replace_blobs(Atom, Atom) :-
  103  atom(Atom), !.
  104replace_blobs(Blob, Atom) :-
  105  blob(Blob, Type),
  106  Type \== text, !,
  107  format(atom(Atom), '~p', [Blob]).
  108replace_blobs(Term0, Term) :-
  109  compound(Term0), !,
  110  compound_name_arguments(Term0, Pred, Args0),
  111  maplist(replace_blobs, Args0, Args),
  112  compound_name_arguments(Term, Pred, Args).
  113replace_blobs(Term, Term).
 shared_vars(+Terms:list(term), -SharedVariables:ordset(var)) is det
  119shared_vars(Terms, Shared) :-
  120  maplist(term_variables_set, Terms, Sets),
  121  ord_intersection(Sets, Shared).
 shared_vars(+Term1:term, +Term2:term, -SharedVariables:ordset(var)) is det
  126shared_vars(Term1, Term2, Shared) :-
  127  shared_vars([Term1,Term2], Shared).
 write_fact(@Term) is det
  133write_fact(Term) :-
  134  write_term(Term),
  135  write(.),
  136  nl.
 write_term(@Term) is det
Alternative to write_canonical/[1,2] that lives up to the promise that "terms written with this predicate can always be read back".
  145write_term(Term) :-
  146  replace_blobs(Term, BloblessTerm),
  147  write_term(BloblessTerm, [numbervars(true),quoted(true)])