Guide to Prolog Programming |
© Roman Barták, 1998 |
Home |
|
Meta-Programming
|
Meta-programming is a programming technique that enables manipulation with program structures. Because Prolog uses the same data structures to represent programs as well as data, Prolog is suitable for writing meta-programs.
In the
section "Prolog
Data Structures",
we discussed terms, basic Prolog data structure, and some predicates
(arg,functor,=..) which work with terms. Now we extend this
set of predicates by predicate "call" that is used to call
arbitrary Prolog goal. In fact, one can build a Prolog goal using =..
and then use call to execute this goal.
In the following code we use the features of =.. and call to design a procedure which can apply (map) given function to each element of list. The name of this function is an input parameter of the procedure.
map(FunctionName,[H|T],[NH|NT]):- Function=..[FunctionName,H,NH], call(Function), map(FunctionName,T,NT). map(_,[],[]).
Now, one can call
?-map(neg,[1,2,3],L). % result is L=[-1,-2,-3]
where neg is defined in a following way:
neg(A,B):-B is -A.
to get the procedure that negates elements of list.
The same procedure map can be used to get other list processors by adding code of functions, e.g.,
inc(A,B):-B is A+1. dec(A,B):-B is A-1.
and goal:
?-map(inc,[1,2,3],X),map(dec,X,Y). % result is X=[2,3,4], Y=[1,2,3]
Compare the above approach with generalized list processor.
In the following sections, we will discuss two particular usage of
meta-programming techniques, namely:
|
|
Designed and maintained by Roman Barták |