Predicates as Arguments

So far we have only seen predicate calls of a static nature. That is, the predicates being called as subgoals are specified satirically in the source code. However, in many cases it may be desirable to call different predicates, depending on previous events and evaluations, from the same place, to avoid large-scale duplication of code. To this end, you can declare a predicate domain, and pass pointers to predicates of that domain as variables.

The main usage of this feature in Visual Prolog is to pass eventhandler predicates to the VPI layer.

1. Predicate Domains

The declaration for a predicate domain is of the form

(curly braces indicate "choose one", square brackets indicate optional items) where

The language specification tells the compiler which calling convention to use, and is only required when declaring domains for routines written in other languages (see the chapter 18).

The flowpattern specifies how each argument is to be used. It should be the letter i for an argument with input flow, the letter o for one with output flow, a functor and flowpattern for a compound term (e.g. (i,o,myfunc(i,i),o)), or a listflow (eg [i,myfunc(i,o),o], [o,o|i]).

You can have no more than one flowpattern declaration for a predicate pointer domain, and it must be given unless the argument list is empty.

Hence, the declaration for a group of deterministic predicates taking an integer as argument and returning an integer, would be

DOMAINS
    list_process = determ integer (integer) - (i)

This group, or class of predicates, is now known as list_process. To declare a predicate square as belonging to this group, the syntax is:

    PREDICATES
        
square: list_process

The clause for square is just like an ordinary clause, but as it's declared as a function it needs a return argument:

    CLAUSES
   
    square(E,ES):- ES = E*E.

Elaborating on the above, a domain declaration for a group of deterministic predicates, to be called ilist_p, taking an integer list and a pointer to a list_process predicate as input arguments, and an integer list as output argument, would hence be

    DOMAINS
        ilist = integer*
        list_process = determ integer (integer) - (i)
        ilist_p = determ (ilist,list_process,ilist) - (i,i,o)

2. Examples

Now look at the following program:

/* Program ch11e06.pro */

 

PREDICATES

    list_square: list_process

    list_cube: list_process

    il_process: ilist_p

 

CLAUSES

    list_square(E,ES):- ES = E*E.

    list_cube(E,EC):- EC = E*E*E.

 

    il_process([],_,[]).

    il_process([Head|Tail],L_Process,[P_Head|P_Tail]):-

        P_Head = L_Process(Head),

        il_process(Tail,L_Process,P_Tail).

 

GOAL

        List = [-12,6,24,14,-3],

        il_process(List,list_square,P_List1),

        write("P_List1 = ",P_List1,'¡¬n'),

        il_process(List,list_cube,P_List2),

        write("P_List2 = ",P_List2,'¡¬n').

This declares two functions, list_square and list_cube, belonging to the list_process group, and a predicate il_process creating a new integer list by applying the listelement-processing predicate L_Process to each element of the original list. Note that the domain declaration ilist_p is only included for illustration; il_process could equally well have been declared using:

    PREDICATES
        il_process(ilist,list_process,ilist)

since it isn't referred to as a variable.

With the goal shown, il_process is called twice, first creating a list of squares by applying the list_square function, and then a list of cubes by applying the list_cube function. Compile and run this program, and you will get:

    P_List1 = [144,36,576,196,9]
        P_List2 = [-1728,216,13824,2744,-27]

Make sure you understand the complexities of this, and, when you do, make sure you don't abuse it. It's all too easy to create totally unreadable programs. Program ch11e07, which is a somewhat elaborated version of ch11e06, illustrates the concept taken to a resonable limit:

/* Program ch11e07.pro */

 

PREDICATES

    list_same: list_process

    list_square: list_process

    list_cube: list_process

 

    elem_add: elem_process

    elem_max: elem_process

    elem_min: elem_process

 

    il_process(ilist,list_process,ilist)

    il_post_process(ilist,elem_process,integer)

 

    apply_elemprocess(ilist,elem_p_list)

    apply_listprocess(ilist,list_p_list,elem_p_list)

 

    string lpname(list_process)

    string epname(elem_process)

 

CLAUSES

    lpname(list_same,list_same).  % Map predicate pointer to its name

    lpname(list_square,list_square).

    lpname(list_cube,list_cube).

 

    epname(elem_add,elem_add).

    epname(elem_min,elem_min).

    epname(elem_max,elem_max).

 

    elem_add(E1,E2,E3):- E3 = E1+E2.

    elem_max(E1,E2,E1):- E1 >= E2, !.

    elem_max(_,E2,E2).

    elem_min(E1,E2,E1):- E1 <= E2, !.

    elem_min(_,E2,E2).

 

    list_same(E,E).

    list_square(E,ES):- ES = E*E.

    list_cube(E,EC):- EC = E*E*E.

 

    il_process([],_,[]).

    il_process([Head|Tail],E_Process,[P_Head|P_Tail]):-

        P_Head = E_Process(Head),

        il_process(Tail,E_Process,P_Tail).

 

    il_post_process([E],_,E):-!.

    il_post_process([H|T],L_Process,Result):-

        il_post_process(T,L_Process,R1),

        L_Process(H,R1,Result).

 

    apply_elemprocess(_,[]).

    apply_elemprocess(P_List,[E_Process|E_Tail]):-

        il_post_process(P_List,E_Process,PostProcess),

        NE_Process = epname(E_Process),

        write(NE_Process,": Result = ",PostProcess,'¡¬n'),

        apply_elemprocess(P_List,E_Tail).

 

apply_listprocess(_,[],_).

apply_listprocess(I_List,[L_Process|L_Tail],E_List):-

    il_process(I_List,L_Process,P_List),

    NL_Process = lpname(L_Process),

    write('¡¬n',NL_Process,":¡¬nProcessed list = ",P_List,

                                 "¡¬nPost-processing with:¡¬n"),

    apply_elemprocess(P_List,E_List),

    apply_listprocess(I_List,L_Tail,E_List).

GOAL

        List = [-12,6,24,14,-3],

        write("Processing ",List," using:¡¬n"),nl,

        apply_listprocess(List,[list_same,list_square,list_cube],

                                   [elem_add,elem_max,elem_min]).

Among other things, this program illustrates the use of lists of predicate pointers. If you run it, you'll get the following output:

 

list_same:

Processed list = [-12,6,24,14,-3]

Post-processing with:

elem_add: Result = 29

elem_max: Result = 24

elem_min: Result = -12

 

list_square:

Processed list = [144,36,576,196,9]

Post-processing with:

elem_add: Result = 961

elem_max: Result = 576

elem_min: Result = 9

 

list_cube:

Processed list = [-1728,216,13824,2744,-27]

Post-processing with:

elem_add: Result = 15029

elem_max: Result = 13824

elem_min: Result = -1728

Predicate pointers may be used like almost any other object in a program. In particular, they can appear as parts of compound terms, creating object oriented possibilities where each object carries with it a series of routines for its own management. You should take note, though, that predicate pointers is a fairly low-level mechanism. The actual value of such a pointer is simply a code-address, and it's therefore only valid in the particular program where it was created. Hence, although you can store and retrieve predicate pointers via the databases, highly unexpected and quite possibly disastrous results will occur if you try to use a predicate pointer not originating in the current program.