Prolog
lists
Lists
In Prolog, a list is a sequence of any number of terms, separated by commas and enclosed in square brackets:
[1, 2, 3]
[a, b, c, d]
[a, [1, 2, 3], tom, 15, date(1, may, 1995)]
In fact, a list is actually a pair of a head and a tail (which is a list itself):
[Head | Tail]
[A, B, C] = [A | [B | [C | []]]] = [A, B | [C]]
Kind of like SML lists.
Built-in list predicates
length/2
length(L, N) is satisfied when L is a list of length N.
?- length([a, b, [c, d], e], N).
?- length(L, 4).
length/2
length/2 is implemented as follows:
length([], 0).
length([_|Tail], N) :-
length(Tail, N1),
N is 1 + N1.
is_list/1
is_list(X) is satisfied when X is a list.
?- is_list(17).
?- is_list([1, 2, 3]).
How would you implement this predicate?
...
is_list/1
is_list([]).
is_list([X|Xs]) :- is_list(Xs).
member/2
member(X, L) is satisfied when X is a member of L.
?- member(X, [17, 13, 2, 5]).
How would you implement this predicate?
...
member/2
member(X, [X|Xs]).
member(X, [Y|Ys]) :- member(X, Ys).
prefix/2
prefix(X, L) is satisfied when X is a prefix of L.
?- prefix(X, [a, b, c, d]).
How would you implement this predicate?
...
prefix/2
prefix([], L).
prefix([X|Xs], [X|Ys]) :- prefix(Xs, Ys).
suffix/2
suffix(X, L) is satisfied when X is a suffix of L.
?- suffix(X, [1, 2, 3]).
How would you implement this predicate?
...
suffix/2
suffix(Xs, Xs).
suffix(Xs, [Y|Ys]) :- suffix(Xs, Ys).
nth0/3 and nth1/3
nth0(I, L, E) is satisfied when E is the I‘th element of L starting with index 0.
?- nth0(1, [1, 2, 3], X).
nth1/3is the same asnth0/3but starts with index 1.
max_list/2 and min_list/2
max_list(L, M) is satisfied when M is the maximum element of L.
?- max_list([1, 2, 3], X).
min_list/2is the same asmax_list/2but for the minimum element.
flatten/2
flatten(L, F) is satisfied when F is the (recursively) flattened version of L.
?- flatten([1, [2, [3, 4], 5], 6], X).
List Exercises
Implement the following (non built-in) predicates.
del/3
del(X, L, R) is satisfied when R is L without one of the occurrences of X.
...
?- del(2, [1, 2, 3, 2, 3, 2], X).
del/3
del(X, [X|Xs], Xs).
del(X, [Y|Ys], [Y|Zs]) :- del(X, Ys, Zs).
?- del(2, [1, 2, 3, 2, 3, 2], X).
insert/3
Insert(X, L, R) is satisfied when R is L with an additional occurrence of X.
...
?- insert(3, [1, 2, 3], X).
insert/3
insert(X, L, R) :- del(X, R, L).
?- insert(3, [1, 2, 3], X).
append/3
append(X, Y, Z) is satisfied when Z is the concatenation of X and Y (in that order).
...
?- append([1, 2], [3, 4, 5], X).
append/3
append([], Ys, Ys).
append([X|Xs], Ys, [X|Zs]) :- append(Xs, Ys, Zs).
?- append([1, 2], [3, 4, 5], X).
define member/2 using append/3
...
member(X, Xs) :- append(_, [X|_], Xs).
sublist/2
sublist(X, Y) is satisfied when X is a sublist of Y.
...
sublist/2
sublist(Xs, Ys) :-
append(As, Bs, Ys),
append(Xs, Cs, Bs).
prefix(Xs, Ys) :- append(Xs, _, Ys).
suffix(Xs, Ys) :- append(_, Xs, Ys).
sublist(Xs, Ys) :-
prefix(Ps, Ys),
suffix(Xs, Ps).
permutation/2
permutation(X, Y) is satisfied when X is a permutation of Y.
...
?- permutation([1, 2, 3], X).
permutation/2
permutation([], []).
permutation([X|L], P) :-
permutation(L, L1),
insert(X, L1, P).
?- permutation([1, 2, 3], X).