Prolog Guide - Genealogy

Guide to Prolog Programming

© Roman Barták, 1998

Home
Prolog in Examples
First Steps in Prolog

Previous | Contents | Next

Genealogy Database

A genealogy database seems to be a good introductory to Prolog. In this lesson, we present a simple Prolog program that captures basic family relations. The program demonstrates features of Prolog like using facts, rules, variables or recursion.


Tip: Use Copy&Paste function of the browser to move the code directly into the PROLOG environment.

First, we express the property of being a man or woman by following PROLOG facts:

man(adam).
man(peter).
man(paul).
 
woman(marry).
woman(eve).

Then, we can add relation "parent" which associates parent and child.

parent(adam,peter). % means adam is parent of peter
parent(eve,peter).
parent(adam,paul).
parent(marry,paul).

Till now, we added only facts to our program but the real power of Prolog is in rules. While facts state the relation explicitely, rules define the relation in a more general way. Each rule has its head - name of the defined relation, and its body - a real definition of the relation. The following rules define the relations being a father and being a mother using previously defined relations of being a man or woman and being a parent.

father(F,C):-man(F),parent(F,C).
mother(M,C):-woman(M),parent(M,C).

Note that we use variables (start with capital letter) to express the feature that every man which is a parent of any child is also her or his father. If some parameter of the relation is not important we can use anonymous variable (denoted _ ) like in these definitions:

is_father(F):-father(F,_).
is_mother(M):-mother(M,_).

Before proceeding further one should know how to run the Prolog programs. You run the program by asking questions like this one:

?-father(X,paul).

which expresses: who is father of paul? The answer is X=adam, naturally.

Now extend your facts database and try to define other family relations like being a son, aunt or grandparent. Also, try to ask Prolog system various questions and see what happens. You can compare your program with following rules:

son(S,P):-man(S),parent(P,S).
daughter(D,P):-woman(D),parent(P,D).
 
siblings(A,B):-parent(P,A),parent(P,B),A\=B.
% siblings have at least one common parent
% the test A\=B preserves that siblings are different persons
 
full_siblings(A,B):-
parent(F,A),parent(F,B),
parent(M,A),parent(M,B),
A\=B, F\=M.
% full siblings have common parents (both)
% the test F\=M preserves that full siblings have two different parents (father and mother, naturally)
 
full_siblings2(A,B):-
father(F,A),father(F,B),
mother(M,A),mother(M,B),
A\=B.
% another solution to "full siblings problem" that uses relations father and mother
 
uncle(U,N):-man(U),siblings(U,P),parent(P,N).
aunt(A,N):-woman(A),siblings(A,P),parent(P,N).
 
grand_parent(G,N):-parent(G,X),parent(X,N).

Till now, we use only one rule to express the newly defined relation but we can also define the relation using two and more rules. If we want to express that being a human means being a man or being a woman, we can do it by these two rules:

human(H):-man(H).
human(H):-woman(H).

The body of rule can also use the relation that is just being defined. This features is called recursion and the following rules show its typical usage:

descendent(D,A):-parent(A,D).
descendent(D,A):-parent(P,D),descendent(P,A).

One can use the feature of PROLOG of non-determing the input and output variables and easily define the relation ancestor:

ancestor(A,D):-descendent(D,A).


Nobody can learn programming only by studying programs of others so try to add your own rules to the genealogy program.


Designed and maintained by Roman Barták

Previous | Contents | Next