Week 3: Notes

Here is a summary of the Prolog elements we discussed:

operator syntax

Prolog recognizes binary infix operators such as + and *. An expression containing these operators is an ordinary Prolog structure.

Prolog understands operator precedence, so 1 + 2 * 3 is the same as 1 + (2 * 3) and represents the structure +(1, *(2, 3)).

arithmetic expressions

An arithmetic expression is a number, a variable, or a compound expression built using these elements:

Note that unlike most languages, Prolog does not automatically evaluate arithmetic expressions:

?- 2 + 3 = 3 + 2.
false
The goal above is false bceause the structures +(2, 3) and +(3, 2) are not identical.
We can ask Prolog to evaluate an arithmetic expression using the 'is' operator:
?- X is 2 + 3.
X = 5.

?- X is cos(pi).
X = -1.0.

In classic Prolog, 'is' was the only way to perform arithmetic. Unfortunately, 'is' requires its right side to be a fully instantiated term, i.e. one with no variables:

?- 2 + 3 is X.
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR:    [8] 2+3 is _6562
ERROR:    [7] <user>
?- X is Y + 1.
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR:    [8] _7580 is _7586+1
ERROR:    [7] <user>

This means that 'is' is not part of the pure logical core of Prolog. Any predicate using 'is' is unlikely to work in multiple directions.

integer constraints

Modern Prolog includes integer constraints, which allow us to perfom arithmetic bidirectionally. In this course we will generally use integer constraints rather than 'is'.

To use these constraints in SWI-Prolog, you must import the clpfd module:

?- use_module(library(clpfd)).

I recommend putting the preceding command into your SWI-Prolog initialization file so that it will automatically run at the beginning of each session.

Relational operators for integer constraints begin with the '#' character, We have #= (equals), #\= (not equals), #< (less than), #=< (less than or equal), #> (greater than) and #>= (greater than or equal). Note carefully the unusual symbol ordering in the less than or equals operator #=<. If you write the syntax #<= that you might expect, you will get a syntax error.

Prolog can combine integer constraints, and solve simple equations and systems of equations involving constraints:

?- X + 2 #= 3.
X = 1

?- X * X #= Y + 1, Y - 4 #= 20.
Y = 24,
X in -5\/5

?- X #\= 10.
X in inf..9\/11..sup

Above, '-5\/5' means 'either -5 or 5'. The \/ operator forms the union of two domains. Each domain is a single integer, or a range of integers. inf ("inferior") means -∞ and sup ("superior") means +∞, so inf..9\/11..sup means any value in the set (-∞, 9] ∪ [10, +∞), i.e. any integer x such that x ≤ 9 or 11 ≤ x.

The in operator states that a variable belongs to a domain:

?- X in 1..10.
X in 1..10

I recommend that you use this domain notation only when you have a fixed numeric range, since Prolog requires that the lower and upper bounds be known. The following will fail if Y is not yet known:

?- X in 1 .. Y.
ERROR: Arguments are not sufficiently instantiated

In this situation, here is a better alternative:

?- X #>= 1, X #=< Y.
X in 1..sup,
Y#>=X,
Y in 1..sup.

The ins operator is similar in in, but works for multiple variables at once:

?- [X, Y] ins 5..sup.
X in 5..sup,
Y in 5..sup

?- [X, Y] ins 0..2, Z #= X + Y, Z #= 0.
X = Y, Y = Z, Z = 0

Sometimes Prolog's constraint propagation alone can find unique solutions for integer variables, as in the examples above. But sometimes it cannot:

?- X + Y #= 10, X - Y #= 2.
2+Y#=X,
X+Y#=10

This system has a unique solution, but the constraint propagator cannot find it (it is not smart enough to solve a linear system). In this case and in more complicated examples, we will need to ask the constraint system to search for a solution. We can do this using the label predicate, which finds solutions for one or more variables. Note that in the above example, calling label alone is not enough:

?- X + Y #= 10, X - Y #= 2, label([X, Y]).
ERROR: Arguments are not sufficiently instantiated

Every variable to label must belong to some domain that is bounded on at least one side, i.e. is not (-∞, ∞). If we add constraints stating that X and Y are positive, Prolog can find a solution:

?- X + Y #= 10, X - Y #= 2, X #> 0, Y #> 0, label([X, Y]).
X = 6,
Y = 4

Also note the useful predicate all_distinct that states that a set of variables have distinct integer values:

?- [X, Y, Z] ins 1..3, X = 2, Y = 3, all_distinct([X, Y, Z]).
X = 2,
Y = 3,
Z = 1

real constraints

Modern Prolog also features real constraints, which let us write predicates that use real (i.e. floating-point) numbers and work bidirectionally. To use these constraints, you must import the clpr module:

?- use_module(library(clpr)).

I recommend putting the preceding command into your SWI-Prolog initialization file (as described in the previous section).

Real constraints use a completely different syntax than integer constraints. To specify real constraints, write an expression in curly braces and use ordinary arithmetic operators (=, =\=, <, =<, >, or >=). Multiple constraints are separated by commas. For example:

?- {X + 2 = 3}.
X = 1.0

?- {X * X = Y + 1, Y - 4 = 20}.
X = 5.0,
Y = 24.0 ;
X = -5.0,
Y = 24.0

Note the real constraint solver can solve linear systems:

?- { X + Y = 10, X - Y = 2}.
X = 6.0,
Y = 4.0

examples

sum of a list

sum([], 0).
sum([I | L], J) :- sum(L, J1), I + J1 #= J.

?- sum([3, 4, 5], X).
X = 12

?- sum([3, X, 5], 12).
X = 4

?- sum([X, X, X], 12), X #> 0, label([X]).
X = 4

length of a list

len([], 0).
len([_ | L], N) :- N #> 0, N #= K + 1, len(L, K).

?- len([a, b, c], N).
N = 3.

?- len(L, 3).
L = [_5424, _5610, _5796]

This predicate works and terminates in both directions. Here is some general advice for writing predicates that will terminate bidirectionally:

  1. Constrain the arguments. In the above predicate, N #> 0 states that N must be positive. When in doubt, it is often better to add constraints, since redundant constraints will not affect the results and are not especially expensive.

  2. Make the recursive call last. This may seem counterintuitive: in the len predicate above, don't we want Prolog to first recursively compute the length of the sublist, and only afterward add 1 to produce the output value N? Prolog can remember constraints that you specify before a recursive call and combine them with other information later. Moving the constraints before a recursive call can only help termination.

adding times

Suppose the we represent a time of day using a structure such as time(11, 26, 13), representing the time 11:26:13. We'd like to write a predicate add(T1, N, T2), which says that time T2 is N seconds after T1. Here is an implementation:

% Convert a time to a number of seconds after midnight.
convert(time(H, M, S), N) :-
    H in 0 .. 23, [M, S] ins 0 .. 59, N #= 3600 * H + 60 * M + S.

% Add time T1 plus N seconds to form time T2.
add(T1, N, T2) :-
    convert(T1, N1), convert(T2, N2), N1 + N #= N2.

Remarkably, add will work in every direction:

?- add(time(11, 30, 0), 75, T).
T = time(11, 31, 15).

?- add(time(11, 30, 0), N, time(11, 31, 15)).
N = 75.

?- add(T, 75, time(11, 31, 15)).
T = time(11, 30, 0).