Reputation: 91
How to get list of atom variables from a term
For example-
Term = (h-5)* (h-5)+ (k- -2)* (k- -2)- (h-3)* (h-3)- (k-4)* (k-4)=0,
get_variables(Term, Var_list).
For above term, the answer would be Var_list = [h,k].
Upvotes: 4
Views: 1049
Reputation: 18726
The following code runs with both SICStus Prolog 4.5.0 and SWI-Prolog 8.0.0.
It is based on library(terms)
and iwhen/2
:
:- use_module(library(terms)).
atoms_in(As, T) :-
( \+ acyclic_term(T)
-> throw(error(type_error(acyclic_term, T), _))
; iwhen(ground(T), setof(A, (sub_term(A,T),atom(A)), As))
-> true
; As = []
).
Using SWI-Prolog 8.0.0:
?- atoms_in(Xs, (h-5)*(h-5)+(k- -2)*(k- -2)-(h-3)*(h-3)-(k-4)*(k-4)=0).
Xs = [h, k].
?- atoms_in(Xs, f(g(a,b),h(c,d))).
Xs = [a, b, c, d].
?- atoms_in(Xs, f(g(1,2),3)).
Xs = [].
?- atoms_in(Xs, 1).
Xs = [].
Note how invalid uses are caught and reported:
?- atoms_in(_, _). ERROR: Arguments are not sufficiently instantiated ?- atoms_in(_, f(_)). ERROR: Arguments are not sufficiently instantiated ?- Term = f(a,Term), atoms_in(_, Term). ERROR: Type error: `acyclic_term' expected, found `@(S_1,[S_1=f(a,S_1)])' (a cyclic)
Upvotes: 3
Reputation: 311
This should work (a nice problem by the way):
variables(T,V):-
variables(T,[],V1),
sort(V1,V).
variables(T,Acc,[T|V]):-
var(T), !,
variables(Acc,[],V).
variables([],[],[]).
variables([],Acc,V):-
variables(Acc,[],V).
variables([H|T],Acc,V):-
append(T,Acc,NewAcc),
variables(H,NewAcc,V).
variables(T,Acc,V):-
atom(T),
variables(Acc,[],V).
variables(T,Acc,V):-
T=.. [_F|AL],
variables(AL,Acc,V).
Your query would be
?- variables((H-5)* (H-5)+ (K- -2)* (K- -2)- (H-3)* (H-3)- (K-4)* (K-4)=0,VL).
Upvotes: 1