Prolog Guide - Data Structures

Guide to Prolog Programming

© Roman Barták, 1998

Home
Prolog in Examples

Previous | Contents | Next

Prolog Data Structures

[terms] [unification] [operators]

Term is a basic data structure in Prolog, i.e., everything including program and data is expressed in form of term. There are four basic types of terms in Prolog: variables, compound terms, atoms and numbers. The following picture shows the correlation between them as well as examples of corresponding terms:

term
       |-- var (X,Y)
 |
  -- nonvar (a,1,f(a),f(X))
       |-- compound (f(a),f(X))
       |
        -- atomic  (a,1)
             |-- atom (a)
             |
              -- number (1)


It is possible to use predicates var, nonvar, compound, atomic, atom and number to test the type of given term (see copy_term bellow). Prolog also provides build-in predicates to access structure of the nonvar terms as well to construct terms.

arg(N,Term,Arg)
- gets N th argument of term (arg(2,f(a,b,c),X) -> X=b)
- sets N th argument of term (
arg(2,f(X,Y,Z),b) -> f(X,b,Z))
functor(Term,Functor,NumberOfArgs)
- gets functor name and number of arguments from the term (functor(f(a,b),F,N) -> F=f,N=2)
- constructs term with given functor and number of free arguments (functor(F,f,2) -> F=f(_,_))
=..
- decomposes the structure of term into list (f(a,b)=..X -> X=[f,a,b])
- constructs term from given list (T=..[f,a,X] -> T=f(a,X))
name(Text,List)
- converts name into list of codes (name(abc,Y) -> Y=[97,98,99])
- constructs name from list of codes (name(X,[97,98,99]) -> X=abc)

If one needs to copy a term (copy has the same structure as the original term but introduces new variables), it is possible to use predicate copy_term/2 which is build-in in most Prolog systems. However, it is straightforward to write a code of copy_term in Prolog using above mentioned predicates.

copy_term(A,B):-cp(A,[],B,_).
   
cp(A,Vars,A,Vars):-
   atomic(A).
cp(V,Vars,NV,NVars):-
   var(V),register_var(V,Vars,NV,NVars).
cp(Term,Vars,NTerm,NVars):-
   compound(Term),
   Term=..[F|Args],    % decompose term
   cp_args(Args,Vars,NArgs,NVars),
   NTerm=..[F|NArgs].  % construct copy term
   
cp_args([H|T],Vars,[NH|NT],NVars):-
   cp(H,Vars,NH,SVars),
   cp_args(T,SVars,NT,NVars).
cp_args([],Vars,[],Vars).

During copying one has to remeber copies of variables which can be used further during copying. Therefore the register of variable copies is maintained.

register_var(V,[X/H|T],N,[X/H|NT]):-
   V\==X,         % different variables
   register_var(V,T,N,NT).
register_var(V,[X/H|T],H,[X/H|T]):-
   V==X.          % same variables
register_var(V,[],N,[V/N]).

Here is an example that clarifies the notion of term copy:

f(X,g(X)) is copy of f(Y,g(Y)) but not of f(U,g(V)).


Unification

Unification is an engine of Prolog. It tries to fing most general substitution of variables in two terms such that after applying this substitution to both terms, the terms became the same. To unify terms A and B, one can easily invoke build-in unification A=B. Try to unify different terms to see what the notion "unification" really means. Again, it is straightworfard to write Prolog code of unification (we use '=' to test equality of two atomic terms or to unify variable with term only).

unify(A,B):-
   atomic(A),atomic(B),A=B.
unify(A,B):-
   var(A),A=B.            % without occurs check
unify(A,B):-
   nonvar(A),var(B),A=B.  % without occurs check
unify(A,B):-
   compound(A),compound(B),
   A=..[F|ArgsA],B=..[F|ArgsB],
   unify_args(ArgsA,ArgsB).
   
unify_args([A|TA],[B|TB]):-
   unify(A,B),
   unify_args(TA,TB).
unify_args([],[]).

Did you find out what is it "occurs check"? OK, try to unify the following terms X and f(X). What happens? Most Prolog systems will fill in the whole memory as they will try to construct infinite term f(f(f(...))) which should be the result of the unification. Such Prolog systems does not incorporate occurs check because of its time consuming nature. So, occurs check tests the occurence of the variable X in the term T (which is not a variable) during unification of X and T.


Operators

Writing terms in the form functor(arg1,arg2,...) is not often appropriate from the human point of view. Just compare the following two transcriptions of the same Prolog clause:

p(X,Z):-q(X,Y),r(Y,Z),s(Z).
   
   ':-'(p(X,Z),(','(q(X,Y),','(r(Y,Z),s(Z))))).

Which one do you prefer?

To simplify the entry of terms, Prolog introduces operators which enable "syntactic sugar", i.e., more natural way of writing terms. Operators are used with unary and binary terms only. They enable to set the location of functor (prefix, infix, postfix), the associative feature and, finally, the priority among operators.

op(Priority,Appearence,Name)
       |        |
       |         -- xfy, yfx, xfx, fx, fy, xf, yf
        -- the higher number the priority has, the lower priority

Instead of explaining the meaning of above definition, look at the following example.

op(400,yfx,'*').  % a*b*c means ((a*b)*c)
op(500,yfx,'+').
op(500,yfx,'-').  % be careful a-b-c means ((a-b)-c)
op(700,xfx,'=')   % it is not possible to write a=b=c
op(900,fy,not).   % one can write not not a and it means not(not(a))
   
not 1=2+3+4*5 is equivalent to:
     not(1=((2+3)+(4*5)))
     not('='(1,'+'('+'(2,3),'*'(4,5)))).

Note, that the numbers indicating priority can be different in miscellaneous implementations of Prolog (the numbers in above example are taken from Open Prolog for Macintosh).

Important!
The definition of operator is not a new program for operator but the "call" of the goal
op. Thus, if you want to define an operator in the program, you write :-op(400,yfx,'*').


Terms make the basics of Prolog.

[terms] [unification] [operators]


See also:
 


Designed and maintained by Roman Barták

Previous | Contents | Next