Functional patterns in Prolog

216 Views Asked by At

How do I create a predicate that takes another predicate and returns a derived version of it?

For example, pairwise predicates can be fairly mechanically extended to apply to lists:

all_whatever(_, []).
all_whatever(X, [Y|T]) :- 
    whatever(X, Y), 
    all_whatever(X, T).

What would be the definition of

pairwise_listwise(whatever, all_whatever).

If it's not possible/common/clunky/violates principles, what would be the alternative pattern?

1

There are 1 best solutions below

9
jnmonette On BEST ANSWER

There are two different ways to achieve what you want. The simplest, and likely preferred, way is to define a meta-predicate that takes any binary predicate and applies it to all elements of the list like so:

listwise(_,_,[]).
listwise(P,Y,[X|Xs]) :-
    call(P,Y,X),
    listwise(P,Y,Xs).

You can then call this as listwise(whatever, Y1, Xs1) to apply whatever to Y1 and each element of Xs1.

This is made possible thanks to the call/N meta-predicate. Note that this meta-predicate can also take partially constructed goals as first argument, so that an alternative formulation could be:

listwise(_,[]).
listwise(P,[X|Xs]) :-
    call(P,X),
    listwise(P,Xs).

Which is then called as listwise(whatever(Y1),Xs1). This version of the predicate is actually known as maplist/2 instead of listwise, at least in SWI-Prolog (in module library(apply)) and SICStus Prolog (in module library(lists)).

The second way to achieve what you want (actually closer to what you where asking for) is to actually define a new predicate all_whatever/2 using term expansion. Term expansion is a mechanism to rewrite terms when they are loaded (see e.g. for more details in SWI-Prolog: https://www.swi-prolog.org/pldoc/doc_for?object=term_expansion/2). I am showing here the SWI-Prolog version, which is by defining a clause for the term_expansion/2 predicate. This mechanism works differently in different systems or is altogether missing.

term_expansion(pairwise_listwise(PairPred,ListPred), ExpandedTerm) :-
    TerminalCall =.. [ListPred,_,[]],
    RecursiveCall =.. [ListPred,Y,[X|Xs]],
    SingleCall =.. [PairPred,Y,X],
    FinalCall =.. [ListPred,Y,Xs],
    ExpandedTerm = [TerminalCall, (RecursiveCall :- (SingleCall, FinalCall))].

In this clause, ExpandedTerm is a list defining the two clauses we want to define and all the terms in it are built from the predicate names using =... One can then define the new predicate as follows:

pairwise_listwise(whatever, all_whatever).

When this code is loaded, that clause will be expanded and replaced by two clauses defining the new predicate all_whatever. And now one can call for instance all_whatever(Y1,Xs1).

My preference goes to the first approach (conceptually simpler and works across Prolog versions) but I think it is also useful to be aware of the existence of the term expansion mechanism as well.