CS 3723
 Programming Languages 
   Geneology in Prolog  


Sample Data.

For this discussion, data (or ``raw'' data) is computer data without any concern for its meaning. Information is data with a meaning, data that means something. A data base is a collection of information that allows one to extract meaningful data in many different ways. A knowledge base, as represented by the prolog program below, has even more: in addition to the information (called facts in prolog), and the ability to extract information, there is also the ability to deduce new facts using prolog rules.

Here are some facts for a simple prolog knowledge base. It gives facts about a small family tree, with parts of four generations, but also with a lot missing. Below is a graphical representation of the family tree. The two parents are above the children, and a line connects parents, while a circle and line descends to each child. Males are given in all capitol letters. (The graph is given to help orient you to the example, but it is not needed in the remainder, since all aspects of this diagram are implicit in the facts and rules given later.)

GEN 1:   ALBERTUS   lydia       ALBERT     may
            |         |            |        |
            +--o------+            +----o---+
               |                        |
GEN 2:       RALPH                   alberta    JOHN                   cleo
               |                        |        |                      |
               +---o--------o-------o---+        +--o-------o--------o--+
                   |        |       |               |       |        |
GEN 3:    joan   WAYNE    martha   NEAL           debbie  elizabeth SEAN      kathy
            |     |                 |               |                |          |
            +-0---+                 +-o----o-----o--+                +-o-----o--+
              |                       |    |     |                     |     |
GEN 4:       amy                    NATE  IAN  bethany                KYLE  DANIEL


Prolog's View of the Same Data.

In the example below, a fact like "male(neal)." means that some object "neal" has property "male". (In fact, we mean that the person "neal" is a male individual.) Similarly, "parent(neal, nate)." means that "neal" is the parent of "nate". (Together, we know that these two facts mean that "neal" is the father of "nate", but that will come later.) There are also facts stating that persons are female, and that some people are married to others. The names male, female, parent and married are deliberately chosen to represent relationships in the real world, but the system presented below is completely abstract, and stands alone as a consistent logical system without reference to the real world.

Here is a complete list of facts corresponding to the family tree above:

Prolog Facts:
male(albertus).
male(albert).
male(ralph).
male(neal).
male(wayne).
male(nate).
male(ian).
male(john).
male(sean).
male(kyle).
male(daniel).
male(shane).
female(lydia).
female(may).
female(alberta).
female(joan).
female(amy).
female(bethany).
female(debbie).
female(cleo).
female(elizabeth).
female(kathy).
female(martha).
parent(albertus, ralph).
parent(albert, alberta).
parent(ralph, neal).
parent(ralph, wayne).
parent(ralph, martha).
parent(wayne, amy).
parent(neal, nate).
parent(neal, ian).
parent(neal, bethany).
parent(john, debbie).
parent(john, sean).
parent(john, elizabeth).
parent(sean, kyle).
parent(sean, daniel).
parent(lydia, ralph).
parent(may, alberta).
parent(alberta, neal).
parent(alberta, wayne).
parent(alberta, martha).
parent(debbie, nate).
parent(debbie, ian).
parent(debbie, bethany).
parent(cleo, debbie).
parent(cleo, sean).
parent(cleo, elizabeth).
parent(kathy, kyle).
parent(kathy, daniel).
parent(joan, amy).
married(neal, debbie).
married(ralph, alberta).
married(albertus, lydia).
married(albert, may).
married(sean, kathy).
married(john, cleo).
married(debbie,neal).
married(alberta, ralph).
married(lydia, albertus).
married(may, albert).
married(kathy, sean).
married(cleo, john).

After the facts above come rules related to the facts. These rules give logical ways to deduce new facts from the available ones. In the rules below, the symbol ":-" can be read as "is true if", or "holds, provided that" or "in case". The comma (,) means "and", and the period ends each rule, as it ends each fact above. Constant entities use a name starting with a lower-case letter, while variables, that is, entities that might stand for a number of specific entities, start with an upper-case letter. The rules below involve variables such as X, Y, Z, and W which stand for any person, but any name starting with a capital letter could serve as a variable.

For example, the rule

    father(X, Y) :- male(X), parent(X, Y).

means that X is the father of Y in case it is both true that X is male and that X is the parent of Y.

Some rules are very simple, such as

    child(Y, X) :- parent(X, Y).

which says that Y is the child of X in case X is the parent of Y. Other rules get complicated, like the rule for sibling(X, Y), where X and Y are siblings if the have the same father Z and the same mother W, and are not the same person. Without the last, a person would be a sibling of themselves. See the rules below for the formal definition of sibling.

Another kind of complicated rule is the rule for ancestor(X,Y). Here there are two parts: X is the ancestor of Y in case X is the parent of Y, and in another way, X is the ancestor of Y in case X is the parent of someone Z, and Z is the ancestor of Y.

When there are two rules like this, you could connect them with the "or" operator, which is a ';', but it is better for now to express "or" just as two rules with the same left hand side.

Finally the rule for auntoruncle(X, W) is complicated because an uncle (or an aunt) can be a blood relative, or can be an uncle or aunt through a marriage.

The rules listed below are not the only way to write such rules, and these have not been thoroughly "debugged", so that there may be logical problems with them.

Prolog Rules:
spouse(X, Y)             :-  married(X, Y).
husband(X, Y)            :-  male(X),       married(X, Y).
wife(X, Y)               :-  female(X),     married(X, Y).
father(X, Y)             :-  male(X),       parent(X, Y).
mother(X, Y)             :-  female(X),     parent(X, Y).
sibling(X, Y)            :-  father(Z, X),  father(Z, Y),
                             mother(W, X),  mother(W, Y),  not(X = Y).
brother(X, Y)            :-  male(X),       sibling(X, Y).
sister(X, Y)             :-  female(X),     sibling(X, Y).
grandparent(X, Z)        :-  parent(X, Y),  parent(Y, Z).
grandfather(X, Z)        :-  male(X),       grandparent(X, Z).
grandmother(X, Z)        :-  female(X),     grandparent(X, Z).
grandchild(X, Z)         :-  grandparent(Z, X).
grandson(X, Z)           :-  male(X),       grandchild(X, Z).
granddaughter(X, Z)      :-  female(X),     grandchild(X, Z).
ancestor(X,Y)            :-  parent(X,Y).
ancestor(X, Y)           :-  parent(X, Z),  ancestor(Z, Y).
child(Y, X)              :-  parent(X, Y).
son(Y, X)                :-  male(Y),       child(Y, X).
daughter(Y, X)           :-  female(Y),     child(Y, X).
descendant(Y, X)         :-  ancestor(X, Y).
auntoruncle(X, W)        :-  sibling(X, Y), parent(Y, W).
auntoruncle(X, Z)        :-  married(X,Y),  sibling(Y,W), parent(W,Z).
uncle(X, W)              :-  male(X),       auntoruncle(X, W).
aunt(X, W)               :-  female(X),     auntoruncle(X, W).
cousin(X, Y)             :-  parent(Z, X),  auntoruncle(Z, Y).
nieceornephew(X, Y)      :-  parent(Z, X),  sibling(Z, Y).
nephew(X, Y)             :-  male(X),       nieceornephew(X, Y).
niece(X, Y)              :-  female(X),     nieceornephew(X, Y).
greatgrandparent(X, Z)   :-  parent(X, Y),  grandparent(Y, Z).
greatgrandfather(X, Z)   :-  male(X),       greatgrandparent(X, Z).
greatgrandmother(X, Z)   :-  female(X),     greatgrandparent(X, Z).
greatgrandchild(X, Z)    :-  child(X, Y),   grandchild(Y, Z).
greatgrandson(X, Z)      :-  male(X),       greatgrandchild(X, Z).
greatgranddaughter(X, Z) :-  female(X),     greatgrandchild(X, Z).
parentinlaw(X, Y)        :-  married(Y, Z), parent(X, Z).
fatherinlaw(X, Y)        :-  male(X),       parentinlaw(X, Y).
motherinlaw(X, Y)        :-  female(X),     parentinlaw(X, Y).
siblinginlaw(X, Y)       :-  married(Y, Z), sibling(X, Z).
brotherinlaw(X, Y)       :-  male(X),       siblinginlaw(X, Y).
sisterinlaw(X, Y)        :-  female(X),     siblinginlaw(X, Y).
childinlaw(X, Y)         :-  married(X, Z), child(Z, Y).
soninlaw(X, Y)           :-  male(X),       childinlaw(X, Y).
daughterinlaw(X, Y)      :-  female(X),     childinlaw(X, Y).


New Facts From Facts and Rules.

Finally, one can deduce new specific facts from the given collection of facts and rules. For this reason the system is called a knowledge base.

Suppose the facts and rules above are contained in a file: family.pl. To get started (on the systems in the Linux lab), first enter pl to invoke prolog. You get the interactive prolog prompt ?-. Now type consult(family). to get the prolog system to "absorb" the given facts and rules.

Now one can continue at the prompt: ?- , entering prolog queries to see what matches the system can achieve. (Below, boldface shows what you type.) For example:

     % prolog  # in the Linux lab
     Welcome to SWI-Prolog (blah ... blah)

     ?- consult(family).
     % family compiled 0.01 sec, 14,500 bytes

     ?- daughter(X,Y).

     X = alberta
     Y = albert ; % try for another answer with semicolon

     X = alberta
     Y = may ;

     X = amy
     Y = wayne ;

     X = amy
     Y = joan
       (plus many more daughters)
In this way, one has many new facts, such as:
     daughter(alberta,albert).
     daughter(alberta,may).
     daughter(amy,wayne).
     daughter(amy,joan).
       (plus many more specific daughter facts)
Similarly, albert has two greatgranddaughters, as is shown by
     ?- greatgranddaughter(X, albert).

     X = amy ;

     X = bethany ;

     false.
Here the "false." means that albert has no more greatgranddaughters (in this restricted family tree). Thus we see that the following facts are true:
     greatgranddaughter(amy, albert).
     greatgranddaughter(bethany, albert).
Here are two more queries and their results:
     ?- soninlaw(X,Y).

     X = ralph
     Y = albert ;

     X = ralph
     Y = may ;

     X = neal
     Y = john ;
     
     X = neal
     Y = cleo ;

     false.

     ?- aunt(debbie, X).

     X = kyle ;

     X = daniel ;

     X = amy ;

     false.
Let's try out the recursive rules for ancestor that were mentioned before:
     ancestor(X,Y)            :-  parent(X,Y).
     ancestor(X, Y)           :-  parent(X, Z),  ancestor(Z, Y).
Here they are used:
     ?- ancestor(X, neal).

     X = ralph ;
     X = alberta ;
     X = albertus ;
     X = albert ;
     X = lydia ;
     X = may ;
     false.

     ?- halt. % back to Linux
     %
Now make up a little printing rule and put it into family.pl:
     print_ancestors_neal(_) :-  ancestor(X, neal), write(X), write(', '), fail.
Then the result it:
     ?- print_ancestors_neal(_).
     ralph, alberta, albertus, albert, lydia, may, 

     false.


Conclusions.

This example gives one view of a small portion of Prolog. The example makes Prolog look as if it would only be good for a toy system and not scalable to large, real-world applications, but this is not the case. The example above, in addition to only involving a few people, has nothing weird about it: no sex changes, no gay marriages, not even divorces. All such complexities could easily be built in. Perhaps more importantly, the example doesn't have full names, but this could also easily be provided as shown below. In the same way dates (for marriages, births, deaths) could be included without much trouble, as well as any other information a family tree might need.

See the example related to CS courses as UTSA for many of the additions needed in real applications.


Revision date: 2013-11-07. (Please use ISO 8601, the International Standard Date and Time Notation.)