Processing All Arguments of a Term

It is often the case that we wish to process each of the arguments of a term in turn. For example, to decide whether a compound term is ground, we have to check that each of its arguments is ground. One possibility is to create a list of those arguments, and traverse the list processing each element. Using this approach, a predicate to check for groundness would be

ground(T) :- atomic(T). 

ground(T) :- structure(T), T =.. [_ | Args], groundargs(Args).
groundargs([]).
groundargs([A | ARest]) :– ground(A), groundargs(ARest).

This is not the most efficient way to process all the arguments of a term, because it involves the creation of intermediate lists, which is expensive both in space and time. A much better alternative is to use arg/3 to index into the term and retrieve arguments. Using this approach, the ground/1 predicate above would be written as

ground(T) :- atomic(T). 

ground(T) :- structure(T), functor(T, P, N), groundargs(1, N, T).
groundargs(M, N, T) :-
M = < N ->
(arg(M, T, A), ground(A), M1 is M + 1, groundargs(M1, N, T)) ;
true.

The second approach is likely to be more efficient than the first in SB-Prolog.

If the arguments of the term do not need to be processed in ascending order, then it is more efficient to process them in descending order using arg/3 to access them. For example, the predicate for groundness checking could be written as

ground(T) :- atomic(T). 

ground(T) :- structure(T), functor(T, P, N), groundargs(N, T).
groundargs(M, T) :-
M =:= 0 ->
true ;
(arg(M, T, A), ground(A), M1 is M - 1, groundargs(M1, T)).

This is even more efficient than the earlier version, because (i) groundargs needs to have one fewer parameter to be passed to it at each iteration; and (ii) testing ``M =:= 0'' is simpler and more efficient than checking ``M = < N'', and takes fewer machine instructions.