Basic prolog rule syntax

Rules provide mechanisms for the prolog engine to combine facts and variables to attempt to deduce whether a query is true, and follow the general logic:
property(a, b, c, ...) is true if X, Y, and Z are all true.

Here X, Y, and Z are all new subgoals (queries) which must be solved by the prolog engine before it can decide whether this rule is sufficient to answer the query.

The syntax for this is to use the :- symbol for if, and to list the subgoals on the right side as a comma-seperated list.

For example, suppose we wanted to add the following rule:
X is between Y and Z if Y < X and X < Z.
The syntax for this might look like:
between(X, Y, Z) :- Y < X, X < Z.
If we were to later ask the query between(5, 3, 7). the prolog engine could answer YES.

(The , is used for logical AND whereas the ; is used for logical OR.)

There are limits to the prolog engine's effectiveness in combining facts and rules however. If we were to ask between(X, 3, 7). it would respond with NO, since we haven't given it a way to come up with a specific numeric value for X that would make the query true.

We can introduce new (local) variables on the right side of a rule, and perform basic computation to try to answer queries, e.g. suppose we want to ask questions about a polynomial aX2+bX+c:

% compute the value of AX^2 + BX + C, and try to match that with Result
evalquad(A,B,C,X,Result) :- R is A*X*X + B*X + C, R = Result.  
If we try query evalquad(1,2,3,0.5,N). it will come up with the result N = 4.25.
If we try query evalquad(1,1,1,1,3). it will respond with true.
If we try query evalquad(1,1,1,1,0). it will respond with false.
If we try the query with non-numeric values it will crash (more error checking is needed, we'll get to that in later sections).

Suppose we wished to use two properties, parent and male, to determine if someone was a father. We might use a fact/rule set like:

% list the known parents
parent(marge, bart).
parent(homer, maggie).

% list the known males
male(bart).
male(homer).

% have a rule specify the requirements for fatherhood,
%    specifying that you must be male and a parent of someone
father(X) :- male(X), parent(X, Y).
Note that in this case the value of the variable Y doesn't really matter to us, and as such it can be replaced with an anonymous variable:
father(X) :- male(X), parent(X, _).

As another example, suppose we wanted to consider the siblings Bart, Lisa, and Maggie. We could try the following:

; start with a couple of basic facts:
sibling(Bart, Lisa).
sibling(Maggie, Bart).

; then add some rules for making further deductions:

; X is Y's sibling if Y is X's sibling,
sibling(X, Y) :- sibling(Y, X).

; or possibly with an additional rule specifying that X and Y
;    cannot be the same entity (X \= Y)
sibling(X, Y) :- X \= Y, sibling(Y, X).

; if X and Y are siblings, and Y and Z are siblings,
;    then X and Z are siblings
sibling(X, Y) :- sibling(X, Z), sibling(Z, Y).