Prolog - Lists



In this chapter, we will discuss one of the important concepts in Prolog, The Lists. It is a data structure that can be used in different cases for non-numeric programming. Lists are used to store the atoms as a collection.

In the subsequent sections, we will discuss the following topics −

  • Representation of lists in Prolog

  • Basic operations on prolog such as Insert, delete, update, append.

  • Repositioning operators such as permutation, combination, etc.

  • Set operations like set union, set intersection, etc.

Representation of Lists

The list is a simple data structure that is widely used in non-numeric programming. List consists of any number of items, for example, red, green, blue, white, dark. It will be represented as, [red, green, blue, white, dark]. The list of elements will be enclosed with square brackets.

A list can be either empty or non-empty. In the first case, the list is simply written as a Prolog atom, []. In the second case, the list consists of two things as given below −

  • The first item, called the head of the list;

  • The remaining part of the list, called the tail.

Suppose we have a list like: [red, green, blue, white, dark]. Here the head is red and tail is [green, blue, white, dark]. So the tail is another list.

Now, let us consider we have a list, L = [a, b, c]. If we write Tail = [b, c] then we can also write the list L as L = [ a | Tail]. Here the vertical bar (|) separates the head and tail parts.

So the following list representations are also valid −

  • [a, b, c] = [x | [b, c] ]

  • [a, b, c] = [a, b | [c] ]

  • [a, b, c] = [a, b, c | [ ] ]

For these properties we can define the list as −

A data structure that is either empty or consists of two parts − a head and a tail. The tail itself has to be a list.

Basic Operations on Lists

Following table contains various operations on prolog lists −

Operations Definition
Membership Checking During this operation, we can verify whether a given element is member of specified list or not?
Length Calculation With this operation, we can find the length of a list.
Concatenation Concatenation is an operation which is used to join/add two lists.
Delete Items This operation removes the specified element from a list.
Append Items Append operation adds one list into another (as an item).
Insert Items This operation inserts a given item into a list.

Membership Operation

During this operation, we can check whether a member X is present in list L or not? So how to check this? Well, we have to define one predicate to do so. Suppose the predicate name is list_member(X,L). The goal of this predicate is to check whether X is present in L or not.

To design this predicate, we can follow these observations. X is a member of L if either −

  • X is head of L, or

  • X is a member of the tail of L

Program

list_member(X,[X|_]).
list_member(X,[_|TAIL]) :- list_member(X,TAIL).

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 1 lines read - 467 bytes written, 13 ms

yes
| ?- list_member(b,[a,b,c]).

true ?

yes
| ?- list_member(b,[a,[b,c]]).

no
| ?- list_member([b,c],[a,[b,c]]).

true ?

yes
| ?- list_member(d,[a,b,c]).

no
| ?- list_member(d,[a,b,c]).

Length Calculation

This is used to find the length of list L. We will define one predicate to do this task. Suppose the predicate name is list_length(L,N). This takes L and N as input argument. This will count the elements in a list L and instantiate N to their number. As was the case with our previous relations involving lists, it is useful to consider two cases −

  • If list is empty, then length is 0.

  • If the list is not empty, then L = [Head|Tail], then its length is 1 + length of Tail.

Program

list_length([],0).
list_length([_|TAIL],N) :- list_length(TAIL,N1), N is N1 + 1.

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 4 lines read - 985 bytes written, 23 ms

yes
| ?- list_length([a,b,c,d,e,f,g,h,i,j],Len).

Len = 10

yes
| ?- list_length([],Len).

Len = 0

yes
| ?- list_length([[a,b],[c,d],[e,f]],Len).

Len = 3

yes
| ?-

Concatenation

Concatenation of two lists means adding the list items of the second list after the first one. So if two lists are [a,b,c] and [1,2], then the final list will be [a,b,c,1,2]. So to do this task we will create one predicate called list_concat(), that will take first list L1, second list L2, and the L3 as resultant list. There are two observations here.

  • If the first list is empty, and second list is L, then the resultant list will be L.

  • If the first list is not empty, then write this as [Head|Tail], concatenate Tail with L2 recursively, and store into new list in the form, [Head|New List].

Program

list_concat([],L,L).
list_concat([X1|L1],L2,[X1|L3]) :- list_concat(L1,L2,L3).

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 7 lines read - 1367 bytes written, 19 ms

yes
| ?- list_concat([1,2],[a,b,c],NewList).

NewList = [1,2,a,b,c]

yes
| ?- list_concat([],[a,b,c],NewList).

NewList = [a,b,c]

yes
| ?- list_concat([[1,2,3],[p,q,r]],[a,b,c],NewList).

NewList = [[1,2,3],[p,q,r],a,b,c]

yes
| ?-

Delete from List

Suppose we have a list L and an element X, we have to delete X from L. So there are three cases −

  • If X is the only element, then after deleting it, it will return empty list.

  • If X is head of L, the resultant list will be the Tail part.

  • If X is present in the Tail part, then delete from there recursively.

Program

list_delete(X, [X], []).
list_delete(X,[X|L1], L1).
list_delete(X, [Y|L2], [Y|L1]) :- list_delete(X,L2,L1).

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 11 lines read - 1923 bytes written, 25 ms

yes
| ?- list_delete(a,[a,e,i,o,u],NewList).

NewList = [e,i,o,u] ?

yes
| ?- list_delete(a,[a],NewList).

NewList = [] ?

yes
| ?- list_delete(X,[a,e,i,o,u],[a,e,o,u]).

X = i ? ;

no
| ?-

Append into List

Appending two lists means adding two lists together, or adding one list as an item. Now if the item is present in the list, then the append function will not work. So we will create one predicate namely, list_append(L1, L2, L3). The following are some observations −

  • Let A is an element, L1 is a list, the output will be L1 also, when L1 has A already.

  • Otherwise new list will be L2 = [A|L1].

Program

list_member(X,[X|_]).
list_member(X,[_|TAIL]) :- list_member(X,TAIL).

list_append(A,T,T) :- list_member(A,T),!.
list_append(A,T,[A|T]).

In this case, we have used (!) symbol, that is known as cut. So when the first line is executed successfully, then we cut it, so it will not execute the next operation.

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 14 lines read - 2334 bytes written, 25 ms

(16 ms) yes
| ?- list_append(a,[e,i,o,u],NewList).

NewList = [a,e,i,o,u]

yes
| ?- list_append(e,[e,i,o,u],NewList).

NewList = [e,i,o,u]

yes
| ?- list_append([a,b],[e,i,o,u],NewList).

NewList = [[a,b],e,i,o,u]

yes
| ?-

Insert into List

This method is used to insert an item X into list L, and the resultant list will be R. So the predicate will be in this form list_insert(X, L, R). So this can insert X into L in all possible positions. If we see closer, then there are some observations.

  • If we perform list_insert(X,L,R), we can use list_delete(X,R,L), so delete X from R and make new list L.

Program

list_delete(X, [X], []).
list_delete(X,[X|L1], L1).
list_delete(X, [Y|L2], [Y|L1]) :- list_delete(X,L2,L1).

list_insert(X,L,R) :- list_delete(X,R,L).

Output

| ?- [list_basics].
compiling D:/TP Prolog/Sample_Codes/list_basics.pl for byte code...
D:/TP Prolog/Sample_Codes/list_basics.pl compiled, 16 lines read - 2558 bytes written, 22 ms

(16 ms) yes
| ?- list_insert(a,[e,i,o,u],NewList).

NewList = [a,e,i,o,u] ? a

NewList = [e,a,i,o,u]

NewList = [e,i,a,o,u]

NewList = [e,i,o,a,u]

NewList = [e,i,o,u,a]

NewList = [e,i,o,u,a]

(15 ms) no
| ?-

Repositioning operations of list items

Following are repositioning operations −

Repositioning Operations Definition
Permutation This operation will change the list item positions and generate all possible outcomes.
Reverse Items This operation arranges the items of a list in reverse order.
Shift Items This operation will shift one element of a list to the left rotationally.
Order Items This operation verifies whether the given list is ordered or not.

Permutation Operation

This operation will change the list item positions and generate all possible outcomes. So we will create one predicate as list_perm(L1,L2), This will generate all permutation of L1, and store them into L2. To do this we need list_delete() clause to help.

To design this predicate, we can follow few observations as given below −

X is member of L if either −

  • If the first list is empty, then the second list must also be empty.

  • If the first list is not empty then it has the form [X | L], and a permutation of such a list can be constructed as, first permute L obtaining L1 and then insert X at any position into L1.

Program

list_delete(X,[X|L1], L1).
list_delete(X, [Y|L2], [Y|L1]) :- list_delete(X,L2,L1).

list_perm([],[]).
list_perm(L,[X|P]) :- list_delete(X,L,L1),list_perm(L1,P).

Output

| ?- [list_repos].
compiling D:/TP Prolog/Sample_Codes/list_repos.pl for byte code...
D:/TP Prolog/Sample_Codes/list_repos.pl compiled, 4 lines read - 1060 bytes written, 17 ms

(15 ms) yes
| ?- list_perm([a,b,c,d],X).

X = [a,b,c,d] ? a

X = [a,b,d,c]

X = [a,c,b,d]

X = [a,c,d,b]

X = [a,d,b,c]

X = [a,d,c,b]

X = [b,a,c,d]

X = [b,a,d,c]

X = [b,c,a,d]

X = [b,c,d,a]

X = [b,d,a,c]

X = [b,d,c,a]

X = [c,a,b,d]

X = [c,a,d,b]

X = [c,b,a,d]

X = [c,b,d,a]

X = [c,d,a,b]

X = [c,d,b,a]

X = [d,a,b,c]

X = [d,a,c,b]

X = [d,b,a,c]

X = [d,b,c,a]

X = [d,c,a,b]

X = [d,c,b,a]

(31 ms) no
| ?-

Reverse Operation

Suppose we have a list L = [a,b,c,d,e], and we want to reverse the elements, so the output will be [e,d,c,b,a]. To do this, we will create a clause, list_reverse(List, ReversedList). Following are some observations −

  • If the list is empty, then the resultant list will also be empty.

  • Otherwise put the list items namely, [Head|Tail], and reverse the Tail items recursively, and concatenate with the Head.

  • Otherwise put the list items namely, [Head|Tail], and reverse the Tail items recursively, and concatenate with the Head.

Program

list_concat([],L,L).
list_concat([X1|L1],L2,[X1|L3]) :- list_concat(L1,L2,L3).

list_rev([],[]).
list_rev([Head|Tail],Reversed) :-
   list_rev(Tail, RevTail),list_concat(RevTail, [Head],Reversed).

Output

| ?- [list_repos].
compiling D:/TP Prolog/Sample_Codes/list_repos.pl for byte code...
D:/TP Prolog/Sample_Codes/list_repos.pl compiled, 10 lines read - 1977 bytes written, 19 ms

yes
| ?- list_rev([a,b,c,d,e],NewList).

NewList = [e,d,c,b,a]

yes
| ?- list_rev([a,b,c,d,e],[e,d,c,b,a]).

yes
| ?-

Shift Operation

Using Shift operation, we can shift one element of a list to the left rotationally. So if the list items are [a,b,c,d], then after shifting, it will be [b,c,d,a]. So we will make a clause list_shift(L1, L2).

  • We will express the list as [Head|Tail], then recursively concatenate Head after the Tail, so as a result we can feel that the elements are shifted.

  • This can also be used to check whether the two lists are shifted at one position or not.

Program

list_concat([],L,L).
list_concat([X1|L1],L2,[X1|L3]) :- list_concat(L1,L2,L3).

list_shift([Head|Tail],Shifted) :- list_concat(Tail, [Head],Shifted).

Output

| ?- [list_repos].
compiling D:/TP Prolog/Sample_Codes/list_repos.pl for byte code...
D:/TP Prolog/Sample_Codes/list_repos.pl compiled, 12 lines read - 2287 bytes written, 10 ms

yes
| ?- list_shift([a,b,c,d,e],L2).

L2 = [b,c,d,e,a]

(16 ms) yes
| ?- list_shift([a,b,c,d,e],[b,c,d,e,a]).

yes
| ?-

Order Operation

Here we will define a predicate list_order(L) which checks whether L is ordered or not. So if L = [1,2,3,4,5,6], then the result will be true.

  • If there is only one element, that is already ordered.

  • Otherwise take first two elements X and Y as Head, and rest as Tail. If X =< Y, then call the clause again with the parameter [Y|Tail], so this will recursively check from the next element.

Program

list_order([X, Y | Tail]) :- X =< Y, list_order([Y|Tail]).
list_order([X]).

Output

| ?- [list_repos].
compiling D:/TP Prolog/Sample_Codes/list_repos.pl for byte code...
D:/TP Prolog/Sample_Codes/list_repos.pl:15: warning: singleton variables [X] for list_order/1
D:/TP Prolog/Sample_Codes/list_repos.pl compiled, 15 lines read - 2805 bytes written, 18 ms

yes
| ?- list_order([1,2,3,4,5,6,6,7,7,8]).

true ?

yes
| ?- list_order([1,4,2,3,6,5]).

no
| ?-

Set operations on lists

We will try to write a clause that will get all possible subsets of a given set. So if the set is [a,b], then the result will be [], [a], [b], [a,b]. To do so, we will create one clause, list_subset(L, X). It will take L and return each subsets into X. So we will proceed in the following way −

  • If list is empty, the subset is also empty.

  • Find the subset recursively by retaining the Head, and

  • Make another recursive call where we will remove Head.

Program

list_subset([],[]).
list_subset([Head|Tail],[Head|Subset]) :- list_subset(Tail,Subset).
list_subset([Head|Tail],Subset) :- list_subset(Tail,Subset).

Output

| ?- [list_set].
compiling D:/TP Prolog/Sample_Codes/list_set.pl for byte code...
D:/TP Prolog/Sample_Codes/list_set.pl:3: warning: singleton variables [Head] for list_subset/2
D:/TP Prolog/Sample_Codes/list_set.pl compiled, 2 lines read - 653 bytes written, 7 ms

yes
| ?- list_subset([a,b],X).

X = [a,b] ? ;

X = [a] ? ;

X = [b] ? ;

X = []

(15 ms) yes
| ?- list_subset([x,y,z],X).

X = [x,y,z] ? a

X = [x,y]

X = [x,z]

X = [x]

X = [y,z]

X = [y]

X = [z]

X = []

yes
| ?-

Union Operation

Let us define a clause called list_union(L1,L2,L3), So this will take L1 and L2, and perform Union on them, and store the result into L3. As you know if two lists have the same element twice, then after union, there will be only one. So we need another helper clause to check the membership.

Program

list_member(X,[X|_]).
list_member(X,[_|TAIL]) :- list_member(X,TAIL).

list_union([X|Y],Z,W) :- list_member(X,Z),list_union(Y,Z,W).
list_union([X|Y],Z,[X|W]) :- \+ list_member(X,Z), list_union(Y,Z,W).
list_union([],Z,Z).

Note − In the program, we have used (\+) operator, this operator is used for NOT.

Output

| ?- [list_set].
compiling D:/TP Prolog/Sample_Codes/list_set.pl for byte code...
D:/TP Prolog/Sample_Codes/list_set.pl:6: warning: singleton variables [Head] for list_subset/2
D:/TP Prolog/Sample_Codes/list_set.pl compiled, 9 lines read - 2004 bytes written, 18 ms

yes
| ?- list_union([a,b,c,d,e],[a,e,i,o,u],L3).

L3 = [b,c,d,a,e,i,o,u] ?

(16 ms) yes

| ?- list_union([a,b,c,d,e],[1,2],L3).

L3 = [a,b,c,d,e,1,2]

yes

Intersection Operation

Let us define a clause called list_intersection(L1,L2,L3), So this will take L1 and L2, and perform Intersection operation, and store the result into L3. Intersection will return those elements that are present in both lists. So L1 = [a,b,c,d,e], L2 = [a,e,i,o,u], then L3 = [a,e]. Here, we will use the list_member() clause to check if one element is present in a list or not.

Program

list_member(X,[X|_]).
list_member(X,[_|TAIL]) :- list_member(X,TAIL).

list_intersect([X|Y],Z,[X|W]) :-
   list_member(X,Z), list_intersect(Y,Z,W).
list_intersect([X|Y],Z,W) :-
   \+ list_member(X,Z), list_intersect(Y,Z,W).
list_intersect([],Z,[]).

Output

| ?- [list_set].
compiling D:/TP Prolog/Sample_Codes/list_set.pl for byte code...
D:/TP Prolog/Sample_Codes/list_set.pl compiled, 13 lines read - 3054 bytes written, 9 ms

(15 ms) yes
| ?- list_intersect([a,b,c,d,e],[a,e,i,o,u],L3).

L3 = [a,e] ?

yes
| ?- list_intersect([a,b,c,d,e],[],L3).

L3 = []

yes
| ?-

Misc Operations on Lists

Following are some miscellaneous operations that can be performed on lists −

Misc Operations Definition
Even and Odd Length Finding Verifies whether the list has odd number or even number of elements.
Divide Divides a list into two lists, and these lists are of approximately same length.
Max Retrieves the element with maximum value from the given list.
Sum Returns the sum of elements of the given list.
Merge Sort Arranges the elements of a given list in order (using Merge Sort algorithm).

Even and Odd Length Operation

In this example, we will see two operations using which we can check whether the list has odd number of elements or the even number of elements. We will define predicates namely, list_even_len(L) and list_odd_len(L).

  • If the list has no elements, then that is even length list.

  • Otherwise we take it as [Head|Tail], then if Tail is of odd length, then the total list is even length string.

  • Similarly, if the list has only one element, then that is odd length list.

  • By taking it as [Head|Tail] and Tail is even length string, then entire list is odd length list.

Program

list_even_len([]).
list_even_len([Head|Tail]) :- list_odd_len(Tail).

list_odd_len([_]).
list_odd_len([Head|Tail]) :- list_even_len(Tail).

Output

| ?- [list_misc].
compiling D:/TP Prolog/Sample_Codes/list_misc.pl for byte code...
D:/TP Prolog/Sample_Codes/list_misc.pl:2: warning: singleton variables [Head] for list_even_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl:5: warning: singleton variables [Head] for list_odd_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl compiled, 4 lines read - 726 bytes written, 20 ms

yes
| ?- list_odd_len([a,2,b,3,c]).

true ?

yes
| ?- list_odd_len([a,2,b,3]).

no
| ?- list_even_len([a,2,b,3]).

true ?

yes
| ?- list_even_len([a,2,b,3,c]).

no
| ?-

Divide List Operation

This operation divides a list into two lists, and these lists are of approximately same length. So if the given list is [a,b,c,d,e], then the result will be [a,c,e],[b,d]. This will place all of the odd placed elements into one list, and all even placed elements into another list. We will define a predicate, list_divide(L1,L2,L3) to solve this task.

  • If given list is empty, then it will return empty lists.

  • If there is only one element, then the first list will be a list with that element, and the second list will be empty.

  • Suppose X,Y are two elements from head, and rest are Tail, So make two lists [X|List1], [Y|List2], these List1 and List2 are separated by dividing Tail.

Program

list_divide([],[],[]).
list_divide([X],[X],[]).
list_divide([X,Y|Tail], [X|List1],[Y|List2]) :-
   list_divide(Tail,List1,List2).

Output

| ?- [list_misc].
compiling D:/TP Prolog/Sample_Codes/list_misc.pl for byte code...
D:/TP Prolog/Sample_Codes/list_misc.pl:2: warning: singleton variables [Head] for list_even_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl:5: warning: singleton variables [Head] for list_odd_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl compiled, 8 lines read - 1432 bytes written, 8 ms

yes
| ?- list_divide([a,1,b,2,c,3,d,5,e],L1,L2).

L1 = [a,b,c,d,e]
L2 = [1,2,3,5] ?

yes
| ?- list_divide([a,b,c,d],L1,L2).

L1 = [a,c]
L2 = [b,d]

yes
| ?-

Max Item Operation

This operation is used to find the maximum element from a list. We will define a predicate, list_max_elem(List, Max), then this will find Max element from the list and return.

  • If there is only one element, then it will be the max element.

  • Divide the list as [X,Y|Tail]. Now recursively find max of [Y|Tail] and store it into MaxRest, and store maximum of X and MaxRest, then store it to Max.

Program

max_of_two(X,Y,X) :- X >= Y.
max_of_two(X,Y,Y) :- X < Y.
list_max_elem([X],X).
list_max_elem([X,Y|Rest],Max) :-
   list_max_elem([Y|Rest],MaxRest),
   max_of_two(X,MaxRest,Max).

Output

| ?- [list_misc].
compiling D:/TP Prolog/Sample_Codes/list_misc.pl for byte code...
D:/TP Prolog/Sample_Codes/list_misc.pl:2: warning: singleton variables [Head] for list_even_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl:5: warning: singleton variables [Head] for list_odd_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl compiled, 16 lines read - 2385 bytes written, 16 ms

yes
| ?- list_max_elem([8,5,3,4,7,9,6,1],Max).

Max = 9 ?

yes
| ?- list_max_elem([5,12,69,112,48,4],Max).

Max = 112 ?

yes
| ?-

List Sum Operation

In this example, we will define a clause, list_sum(List, Sum), this will return the sum of the elements of the list.

  • If the list is empty, then sum will be 0.

  • Represent list as [Head|Tail], find sum of tail recursively and store them into SumTemp, then set Sum = Head + SumTemp.

Program

list_sum([],0).
list_sum([Head|Tail], Sum) :-
   list_sum(Tail,SumTemp),
   Sum is Head + SumTemp.

Output

yes
| ?- [list_misc].
compiling D:/TP Prolog/Sample_Codes/list_misc.pl for byte code...
D:/TP Prolog/Sample_Codes/list_misc.pl:2: warning: singleton variables [Head] for list_even_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl:5: warning: singleton variables [Head] for list_odd_len/1
D:/TP Prolog/Sample_Codes/list_misc.pl compiled, 21 lines read - 2897 bytes written, 21 ms

(32 ms) yes
| ?- list_sum([5,12,69,112,48,4],Sum).

Sum = 250

yes
| ?- list_sum([8,5,3,4,7,9,6,1],Sum).

Sum = 43

yes
| ?-

Merge Sort on a List

If the list is [4,5,3,7,8,1,2], then the result will be [1,2,3,4,5,7,8]. The steps of performing merge sort are shown below −

  • Take the list and split them into two sub-lists. This split will be performed recursively.

  • Merge each split in sorted order.

  • Thus the entire list will be sorted.

We will define a predicate called mergesort(L, SL), it will take L and return result into SL.

Program

mergesort([],[]).    /* covers special case */
mergesort([A],[A]).
mergesort([A,B|R],S) :-
   split([A,B|R],L1,L2),
   mergesort(L1,S1),
   mergesort(L2,S2),
   merge(S1,S2,S).
   
split([],[],[]).
split([A],[A],[]).
split([A,B|R],[A|Ra],[B|Rb]) :-
   split(R,Ra,Rb).
merge(A,[],A).
merge([],B,B).
merge([A|Ra],[B|Rb],[A|M]) :-
   A =< B, merge(Ra,[B|Rb],M).
merge([A|Ra],[B|Rb],[B|M]) :-
   A > B, merge([A|Ra],Rb,M).

Output

| ?- [merge_sort].
compiling D:/TP Prolog/Sample_Codes/merge_sort.pl for byte code...
D:/TP Prolog/Sample_Codes/merge_sort.pl compiled, 17 lines read - 3048 bytes written, 19 ms

yes
| ?- mergesort([4,5,3,7,8,1,2],L).

L = [1,2,3,4,5,7,8] ?

yes
| ?- mergesort([8,5,3,4,7,9,6,1],L).

L = [1,3,4,5,6,7,8,9] ?

yes
| ?-
Advertisements