Introduction to Prolog

INTRODUCTION TO PROLOG

Prolog was invented in the early seventies by Alain Colmerauer and others at the University of Marseille. Prolog stands for Programmation en Logique (Programming in Logic). Prolog differs from the most common programming languages because it is a declarative langauge. This means that the progammer specifies a goal which is to be achieved and the Prolog interpreter/compiler works out how to achieve it. Traditional programming languages are said to be procedural. This means that the programmer must specify in detail how to solve a problem. In purely declarative languages, the programmer only states what the problem is and leaves the rest to the langauge itself.

Some applications of Prolog are: intelligent data base retrieval, natural language understanding, expert systems, specification language, machine learning, robot planning, graphics, problem solving

Prolog programs specify relationships among objects. When we say, "John owns the book", we are declaring the ownership relationship between two objects: John and the book. When we ask, "Does John own the book?" we are trying to find out about a realtionship.

Relationships can also be described by rules such as the following,

	Two people are sisters if
		are both female and
		they have the same parents.

This is a rule which allows us to find out about a relationship even if the relationship isn't explicitly stated as a fact.

Programming in Prolog consists of:

FACTS

A fact such as, "Jeff lectures in course 611", is written as:
	lectures(jeff, 611).

The names of relationships are in lower case letters. The name of the relationship appears as the first term and the objects appears as arguments to a function. A period "." must end a fact. lectures(jeff, 611) is also called a predicate.

Here is a collection of facts about a hypothetical computer science department:

	lectures(jeff, 611).
	lectures(ken, 621).
	lectures(claude, 641).
	lectures(graham, 642).
	lectures(ken, 643).

	studies(fred, 611).
	studies(jack, 621).
	studies(jill, 641).
	studies(jll, 642).
	studies(henry, 642).
	studies(henry, 643).

	year(fred, 1).
	year(jack, 2).
	year(jill, 2).
	year(henry, 3).

Together, these facts for Prolog's database.

QUESTIONS

Suppose we want to know if Jeff lectures in course 611. We can ask:
	lectures(jeff, 611)?
	** yes			output from Prolog

We will follow the convention that a question is terminated by a question mark, "?". Different Prolog implementations use different conventions. These are discussed in the appendices. To answer this question, Prolog consults its database to see if this is a known fact. Suppose we ask:

	lectures(fred, 611)?
	** no			output from Prolog

Since Prolog is unable to find a fact which matches the question, the answer "no" is printed. This query is said to have failed.

VARIABLES

Suppose we want to ask, "What course does Jeff teach"? This could be written as:
	Is there a subject, X, which Jeff teaches?

Here, X, is a variable which stands for an object which the questioner does not know about yet.

To answer the question, Prolog to find out the value of X, if it exists. As long as we do not know the value of a variable it is said to be unbound or uninstantiated. When a value is found, the variable is said to instantiated or bound to the value. The name of a variable must begin with a capital letter or an underscore character, "_".

To ask Prolog to find the course which Jeff teaches, the following query is entered:

	lectures(jeff, X)?
	X = 611			output from Prolog

To ask which course(s) Ken teaches, a similar question may be asked,

	lectures(ken , X)?
	X = 621
	X = 643

When there is more than one possible answer, Prolog will try to find all of them.

CONJUNCTIONS OF GOALS

How do we ask, "Does Jeff teach Fred"? This can be answered by finding out if Jeff lectures in a subject which fred studies.
	lectures(jeff, Subject), studies(fred, Subject)?

This is like saying, "Jeff lectures in course, Subject and Fred studies (the same) Subject". Subject is a variable. The question consists of two goals. To answer this question, Prolog first finds a course, Subject, for which Jeff is the lecturer and then finds out if Fred studies the Subject which was just found.

A similar query is:

	lectures(ken, Subject), studies(Student, Subject)?
	Subject = 621
	Student = jack

	Subject = 643
	Student = henry

That is: "Which students does Ken teach"? Prolog solves this problem by proceeding left to right and then backtracking. A good way of picturing what happens when Prolog tries to find a solution and backtracks, is to draw tree diagrams like the one on the next page. When given the initial query, Prolog starts by trying to solve

	lectures(ken, Subject)

There are five "lectures" clauses, but only two have "ken" as their first argument. Prolog chooses the first clause containing a reference to ken, i.e. lectures(ken, 621). With Subject = 621, it then tries to satisfy the next goal, viz, studies(Student, 621). After the first solution is found, Prolog retraces its steps up the tree and looks for alternative solutions. It may now go down the branch containing lectures(ken, 643) and then try studies(Student, 643).

RULES

The previous question can be restated as a general rule:
	One person, Teacher, teaches another person, Student if
		X lectures in a subject, Subject and
		Student studies Subject.

In Prolog this is written as:

	teaches(Teacher, Student) :-
		lectures(Teacher, Student),
		studies(Student, Subject).

This is also called a clause. Facts are unit clauses and rules are non-unit clauses. ":-" means "if" or "is implied by". This symbol is often called the neck symbol. The left hand side of the neck is called the head. The right hand side of the neck is called the body. The comma, ",", separating the goals is stands for and.

Try this rule out:

	more_advanced(Student1, Student2) :-
		year(Student1, Year1),
		year(Student2, Year2),
		Year1 > Year2.

Note the use of the predefined predicate ">".

STRUCTURES (or Pattern Matching as a Way of Life)

Functional terms can be used to construct complex datastructures. For example, if we want to say that John owns the book The Hitchhicker's Guide to the Galaxy, this may be expressed as:
 
	owns(john, "The Hitchhicker's Guide to the Galaxy").

This statement tells us very little about the book. Often we ascribe to objects a number of attributes. In this case, we would like to represent a book as having a title and an author. A structured object such a book can be represented by a functional term as follows:

owns(john, book("The Hitchhicker's Guide to the Galaxy", adams)).

Now the second argument to the predicate shows us more detail. Adams is avery common name, so to be more accurate we should give the author's family and given names.

	owns(john, book("The Hitchhicker's Guide to the Galaxy",
					author(adams,douglas))).

How do we ask, "What books does John own which were written by someone called "Adams"?

	owns(john, book(Title, author(adams, GivenName))?
	Title = " The Hitchhicker's Guide to the Galaxy "
	GivenName = douglas

Notice that in order to find a fact in the database which would answer the question, Prolog performed a quite complex matching operation between the structures in the query and those in the clause head.

Here is a more complicated example of the use of structures in Prolog. It is also out first moderately useful set of prolog programs. A database of books in a library contains facts of the form

	book(CatalogNumber, Title, author(FamilyName, GivenName)).
	member(MemberNumber, name(FamilyName, GivenName), Address).
	loan(CatalogNumber, MemberNumber, BorrowDate, DueDate).

A member of the library may borrow a book. When this is done, a "loan" is entered into the database recording the catalogue number of the book which was borrowed and the number of the member who borrowed it. The date at which the book was borrowed and the due date are also recorded. Dates are stored as structures of the form date(Year, Month, Day). For example date(86, 6, 16) represents 16 June 1986. Names and address are all stored as character strings (i.e. atoms).

The first program we write tells us which books a member has borrowed:

	has_borrowed(MemberFamilyName, Title, CatalogNumber) : -
		member(MemberNumber, name(MemberFamilyName, _), _),
		loan(CatalogNumber, MemberNumber, _, _),
		book(CatalogNumber, Title, _).

Next we would like to know which books are overdue but before we can get started on this program we first have to work out how to compare dates. The following predicate tells us when the first date comes after the second.

	later(date(Year, Month, Day1), date(Year, Month, Day2)) :- !,
		Day1 > Day2.
	later(date(Year, Month1, _), date(Year, Month2, _)) :- !,
		Month1 > Month2.
	later(date(Year1, _, _), date(Year2, _, _)) :-
		Year1 > Year2.

Note that the cuts indicate that if Prolog has found a clause head which matches the goal then there is no need to consider the following clauses. Also notice that the program uses comparison operators. These operators can be thought of predicates that have been predefined in the Prolog system.

	overdue(DateToday, Title, CatalogNumber, MemberFamilyName) :-
		loan(CatalogNumber, MemberNumber, _, DueDate),
		later(DueDate, DateToday),
		book(CatalogNumber, Title, _),
		member(MemberNumber, name(MemberFamilyName, _), _).

For the final program in this example, let's write a rule which will help us to determine that date on which a book is due.

	due_date(date(Year, Month1, Day), date(Year, Month2, Day)) :-
		Month2 is Month1 + 1.

This rule illustrates the use of another arithmetic predefined predicate, namely, the is operator. Is accepts two arguments. The right hand argument must be a term which can be treated as an arithmetic expression. This term is evaluated and then unified with the left hand argument.

RECURSIVE PROGRAMS

In the library database example we saw how terms in Prolog can be used to represent objects such as books, library members, loans records, etc. Some complex terms contained other terms, for example, book contained name. The following term also contains another term , this time it is one similar to itself:
	tree(tree(_, jack, _), jim, tree(_, jill, _))

The '_' symbol may be replaced by any other term, we don't care what it is. A structure like this could be used to represent a binary tree that looks like:

A term which contains another term which has the same principal functor is said to be recursive.

The definition of a binary tree is that it is a structure which is either empty or it contains a left and right subtree. A non-empty tree may also contain some data. In Prolog we would express this definition as:

	is_tree(empty).
	is_tree(tree(Left, Data, Right)) :-
		is_tree(Left),
		some_data(Data),
		is_tree(Right).

The empty tree is represented by the word empty. This is not some special word known to Prolog, it is just an arbitrary word that we choose to use by convention. A non-empty tree is represented by a 3-arity term. Two of the arguments are the left and right sub-trees which are also binary trees. The Data field is any data which we care to put in the tree. Now let us define the size of tree:

	tree_size(empty, 0).
	tree_size(tree(Left, _, Right), Total_Size) :-
		tree_size(Left, Left_Size),
		tree_size(Right, Right_Size),
		Total_Size is Left_Size + Right_Size + 1.

That is, the size of an empty tree is zero and the size of a non-empty tree is the size of the left sub-tree plus the sise of the right sub-tree plus one for the current tree node. The data does not contribute to the total size of the tree.

Notice that when there is a recursive relationship between terms ,we write recursive programs to describe these relationships. A recursive program is one which refers to itself, thus, tree_size contains goals which call tree_size recursively.

LISTS

A very important type of recursive term is the list. The recursive definition of a list is: a list may be nil or it may be a term which has a head, which can be any term, and a tail which is another list. Using standard Prolog notation, we could define the list as:
	is_list(nil).
	is_list(list(Head, Tail)) :-
		list(Tail).

A list of numbers [1, 2, 3] would look like:

	list(1, list(2, list(3, nil)))

Although this notation is consistent with the way Prolog treats all other data structures, it can be rather clumsy at times. Because lists are used so often, most Prolog implementations use the alternative, more convenient notation, [1, 2, 3]. Internally, Prolog still stores the list as if it were entered in the prefix form.

To get some idea of how the compact list notation works look at the following queries to Prolog and the answers the system returns:

	[X, Y, Z] = [1, 2, 3]?
	X = 1
	Y = 2
	Z = 3

This query asks Prolog to match (or unify) the two terms on either side of the equals sign. If a variable appears in a position corresponding to an element in the second list then that variable is unified with the element.

	[X | Y] = [1, 2, 3]?
	X = 1
	Y = [2, 3]

The most common procedure for processing a list is to find the first element, that is the head of the list, perform an operation on it and then repeat the process for all the elements remaining in the tail. The head and tail may be separated by using the vertical bar '|' to indicate that the term following the bar should unify with the tail of the list. Remember that the tail is usually also a list.

	[X | Y] = [1]?
	X = 1
	Y = []

An empty list is written as '[]'. The end of a list is indicated by an empty tail. That is, the tail is []. If necessary, several elements from the front of the list can be selected before matching the tail.

	[X, Y | Z] = [fred, jim, jill, mary]?
	X = fred
	Y = jim
	Z = [jill, mary]

In this example there must be at least two elements in the list on the right in order for the goal to succeed. List elements can be as complex as desired.

	[X | Y] = [[a, f(e)], [n, m, [2]]]?
	X = [ a, f(e)]
	Y = [[n, m, [2]]]

This example shows how to put lists inside lists. The right hand list has two elements:

	[a, f(e)]       [n, m, [2]]

Notice that Y is shown with an extra pair of brackets. That is because Y is the tail of the entire list, [n, m, [2] is just one element.

A term is a member of a list if the term is the same as the term which is the head of the list, or the term is a member of the tail of the list. In Prolog , this is expressed as:

	member(X, [X | _]).
	member(X, [_ | Y]) :- member(X, Y).

This simple example illustrates a few rules about writing programs which deal with recursive data structures:

Only deal with one element at a time!

Given the problem of specifying that a term is a member of a list, it might be tempting to think of the list as one single structure. This leads you to try and examine groups of elements. Always remember that lists and all other structures in Prolog are made of of smaller things. First write programs to deals with the smaller things and then worry about putting them together. In that spirit, the member program checks that head of the list before proceeding down the tail.

Believe that the recursive program you are writting has already been written!

The definition of member says that a term is a member of a list if the term is the same as the head or it is a member of the tail of the list. In the definition we are already assuming that we know how to find a member in the tail. This is one of the hardest concepts to get used to in writting recursive programs. If you work out how to deal with just one element then you can leave the rest to recursion if you pretend that the program is already complete.

Write definitions not programs!

If you are used to writing programs for conventions languages, the you are used to giving instructions on how to peform certain operations. In Prolog, you define relationships between objects and let the system do its best to construct object which satisfy the given relationship.

CONTROLLING EXECUTION

You are about the read something that contradicts the last statement! If we were using full predicate logic as a programming language then it would be true that you need only provide a logical specification and the system would do the rest. However, for reasons of efficiency, Prolog implementations introduce simplifications which make it less than deal as a logic programming language. While improvements to the langauge are sought, we have to learn to live with some of its non-logical features.

On page 5 we drew a proof tree, which showed how Prolog searched for the answer to a simple query. The search method is called depth first because the system attempts to follow one path down as far as it can before backtracking and trying another one. Unless told otherwise, Prolog always backtracks when a failure occurs. Sometimes it is undesirable to attempt some alternatives.

Suppose we wanted only the students of one of the courses which Ken teaches:

	lectures(ken, Subject), !, studies(Student, Subject)?

The '!' is called the cut. The affect of the cut is limit the alternatives that Prolog can select. In the proof tree this looks like branches on the right hand side of the tree have been cut off. If the goals to the right of the cut fail then the entire clause fails and the the goal which caused this clause to be invoked also fails. That is, if the clause which failed has alternatives, these are not attempted.

CONCLUSION

We have introduced a lot of new ideas in this introductory chapter. How all these new concepts fit together will, hopefully, become clear as we start to examine some Prolog applications.