Copy_term but without maintaining variable relationships?

Is there any predicate for making a copy of a compound term and un-unifying any unified variables, so that the resulting term has only singletons? In other words, is there something like a copy_to_singletons/2 that would let me do this:

?- copy_to_singletons(foo(A, A), X).
X = foo(_1, _2).

I’ve been using this as a workaround, but it seems needlessly complex:

copy_to_singletons(Term, TermOut) :-
    copy_term(Term, Term1, _),
    numbervars(Term1),
    mapsubterms([T0,_]>>var_number(T0, _), Term1, TermOut),

I end up having to make two copies because for whatever reason, mapsubterms/3 doesn’t call the goal for variables. Not sure what the reasoning is behind that, but it does mean I have to copy and ground before calling it.

Is there a better way?

I’m curious why you want to do this. :wink:

Anyway library(varnumbers) has varnumbers/3, which might do what you want instead of mapsubterms.

Unfortunately, varnumbers/3 is going to (by design) have the same problem as copy_term, which is to say that common variables in the original will become common variables in the copy. As for what I’m trying to do, I want to reason about the structure of Prolog clauses themselves, so a non-singleton variable is significant but that does not mean the two (or more) instances will be identical.

I don’t understand that. I’ve seen a lot of things during my Prolog years, but never the desire to stop sharing two variables. As they are clause structures, they are not cyclic and thus a simple transformation as mapsubterms/3 does the job. You can’t use that as it doesn’t call the mapper for variables (it is still unclear whether that is a good decision. There are arguments both ways).

1 Like

Well, it’s always nice to be unique :joy: I want to map them into term_positions. I don’t want to use them semantically, I want to use them syntactically, and they are two different tokens in the stream.

Regardless of motivation this looks like a problem with a straight forward Prolog solution. Something like:

copy_to_singletons(X, _) :- var(X), !.
copy_to_singletons(X, X) :- atomic(X), !.
copy_to_singletons([X|Xs], [S|Ss]) :-  !,
	copy_to_singletons(X,S),
	copy_to_singletons(Xs,Ss).
copy_to_singletons(X, S) :- compound(X),
	X =.. [F|Xs],
	copy_to_singletons(Xs,Ss),
	S =.. [F|Ss].

so:

?- copy_to_singletons(foo(A,A),X).
X = foo(_4786,_4792).

Am I missing something?

These lines aren’t needed (although they might speed things up):

because:

?- [a|b] =.. F.
F = ['[|]', a, b].

and instead of (=…)/2, probably better to use compound_name_arguments/3.

Or mapargs/3 could be used:

copy_to_singletons(X, _) :- var(X), !.
copy_to_singletons(X, X) :- atomic(X), !.
copy_to_singletons(X, S) :-
    mapargs(copy_to_singletons, X, S).
1 Like

That was my first thought, but try it on the example.

Probably the best solution, but (like compound_name_arguments/3) not particularly portable.

?- copy_to_singletons(foo(A, A), X).
X = foo(_8998, _9000).

?- copy_to_singletons(foo(A,bar([A,zot(A)])), Z).
Z = foo(_7662, bar([_7696, zot(_7732)])).

That’s odd because my version doesn’t terminate:

?- copy_to_singletons(foo(A,A),X).
Action (h for help) ? goals
[1,572,043] copy_to_singletons([_7854, [[[[[[[...]]]]]]]], _31448902)
[1,572,042] copy_to_singletons([_7854, [[[[[[[...]]]]]]]], _31448882)
[1,572,041] copy_to_singletons([_7854, [[[[[[[...]]]]]]]], _31448862)
[1,572,040] copy_to_singletons([_7854, [[[[[[[...]]]]]]]], _31448842)
[1,572,039] copy_to_singletons([_7854, [[[[[[[...]]]]]]]], _31448822)
Action (h for help) ? abort
% Execution Aborted

This is because the argument list of the compound term [A,A] is [A,[A]], i.e. indefinite.

?- [A,A] =.. L.
L = ['[|]', A, [A]].

So there’s something going on here that I’m not understanding.

Bumped into explain.pl and thought of your question.

HTH