How do I check is full binary tree? - prolog

How do I check full binary tree in prolog? I have the 2 base cases
1) if is empty tree, return yes
2) if is just root only, return yes
I'm stuck at the third one and I not sure what should I do with it. We only allow to use 1 arity: full(T).
btree([]).
btree([H|T]):-btree(T).
btree([H|T]):-btree(H),btree(T).
full([]).
full([H]).
full([H|T]):-
anyone can guide me please. My idea is a tree does not have two nonempty tree then it is a full binary tree.
P/S: I am still new to stackoverflow. If I did ask something silly or improper way please do tell me. I want to learn how to use stackoverflow and also make sure of it in proper way.

I would first probably choose a different representation for binary tree. In Prolog, it's generally more conventional and efficient to use a simple atom (such as nil) as a nil node, and something like btree(Value, Left, Right) as the tree term. Outside of that, the solution looks quite like what #pyon suggested.
% full_btree succeeds if `Tree` is a full binary tree
full_btree(Tree) :-
full_btree(Tree, _).
full_btree(nil, 0).
full_btree(b(_, LeftTree, RightTree), Depth) :-
Depth #> 0,
SubDepth #= Depth - 1,
full_btree(LeftTree, SubDepth),
full_btree(RightTree, SubDepth).
The condition Depth #> 0 ensures, regardless of inputs, that the depth will not become negative, and thus helps ensure termination.

I'm going to assume that you represent trees as follows:
A leaf is an empty list.
A non-leaf node is a three-element list, whose last two elements are the subtrees.
Then:
helper([], 0).
helper([_,L,R], H) :- H #= G + 1, helper(L, G), helper(R, G).
/* Old version: helper([_,L,R], H) :- helper(L, G), helper(R, G), H is G + 1.
* The improvement in the new version was suggested by lurker. Thanks!
*/
full(T) :- helper(T, _).
This works because full binary trees can be inductively defined as follows:
A leaf node is a full binary tree of height 0.
An non-leaf node whose children are both full binary trees of height G, is itself a full binary tree of height G + 1.

Ok, since there is already an answer that doesn't answer the question at face value, here is mine. It doesn't add much anything to the answer by #lurker, it just offers details and explanations that were too much for comments. It also avoids CLP(FD) completely, which is why I felt it should be a separate answer.
You can start (as #lurker has) by using a more conventional binary tree representation. The empty tree is nil, and the non-empty tree is bt(Value, Left, Right) where Value is the value at this node and Left and Right are the left and right sub-trees. This is the conventional representation because it is at the very least more memory efficient. A "leaf" (a tree without sub-trees) is, in your original representation:
.(Value, .([], .([], [])))
instead of:
bt(Value, nil, nil)
The amount of memory needed to represent the two would be different between different Prolog implementations, but I don't know how to make the first smaller than the second.
Then: as #false commented above, a list is usually a collection of Things which conventionally has the following properties:
There can be no Things, or any number of Things in the collection;
The order of Things matters;
All the Things are somehow the same.
Using a list like you do breaks the last convention: the first argument is a value, while the second and third arguments are trees.
This doesn't exclude using list for representing a binary tree but it is unfamiliar.
With this out of the way: successor arithmetic is a silly way of doing actual arithmetic, but it is very convenient if you want to use pattern matching for non-negative integers. You cannot do it with the built-in integer type of Prolog, like 0 or -23 or whatever. Successor arithmetic gives you:
a zero which is structurally different from all positive integers: 0 vs s(_)
adding and subtracting is done by pattern matching, and both are done with the same operation: X + 1 is s(X).
negative numbers are not possible
So, you could define your "full tree" like this:
full_btree(T) :-
full_btree(T, _).
full_btree(nil, 0).
full_btree(bt(_, L, R), s(D)) :-
full_btree(L, D),
full_btree(R, D).
The s(D) and the two Ds state that the tree in your first argument is one deeper than the sub-trees, and that both sub-trees are the same depth. The empty tree nil has a depth of 0 (as defined in the first clause of full_btree/2).
This works as follows:
?- full_btree(nil).
true.
?- full_btree(bt(x, nil, nil)).
true.
?- full_btree(bt(x, bt(y, nil, nil), nil)).
false.
?- full_btree(bt(x, bt(y, nil, nil), bt(z, nil, nil))).
true.
?- full_btree(T), numbervars(T).
T = nil ;
T = bt(A, nil, nil) ;
T = bt(A, bt(B, nil, nil), bt(C, nil, nil)) ;
T = bt(A, bt(B, bt(C, nil, nil), bt(D, nil, nil)), bt(E, bt(F, nil, nil), bt(G, nil, nil))) . % and so on
One more thing: to close the circle, you can do successor arithmetic with lists, too. Just use [] instead of 0 and [_|X] for s(X). With this, you would have:
full_tree(nil, []).
full_tree(bt(_, L, R), [_|D]) :-
full_tree(L, D),
full_tree(R, D).
This is slightly less memory efficient, instead of s(s(s(0))) you would have .(_, .(_, ,(_, []))). However! it is now much easier to make actual integers out of the successor-notation integers, and the other way round: just use length/2. Writing a predicate that converts between s(s(...)) and an integer that works both ways in pure Prolog is not as trivial. I think it is possible to search Stackoverflow for such questions.

Related

Prolog- what causes the out of local stack error in this case?

I have a very simple program where a relation is defined between an AVL tree and a list of elements. I get correct results but after some semicolons I will receive an out of memory error, even for small inputs.
The code is not perfect as I am just trying at first to get to know the language, so it is not efficient but my question is where is the infinite loop or something similar hiding.
Only the last rule causes this problem, I tested the previous ones earlier and they worked fine.
:- use_module(library(clpfd)).
% Stuff
max(X,Y,X):- X#>=Y.
max(X,Y,Y):- Y#>X.
sub(X,Y,Z):- Z is X-Y.
append([],Ys,Ys).
append([X|Xs],Ys,[X|Zs]):-append(Xs,Ys,Zs).
% Checking "tree-ness" of a term
% is_tree(Tree)
is_tree(tree(_,Left,Right)) :-
Left=nil, Right=nil;
Left=nil, is_tree(Right);
Right=nil, is_tree(Left);
is_tree(Left), is_tree(Right).
% Computing tree height
% tree_height(Tree, Height)
tree_height(nil,0).
tree_height(tree(_,L,R),H) :-
tree_height(L,H1),
tree_height(R,H2),
H1#>=H2,
H is H1+1.
tree_height(tree(_,L,R),H) :-
tree_height(L,H1),
tree_height(R,H2),
H2#>H1,
H is H2+1.
% Checking "AVL tree-ness" of a term
% is_avl_tree(Tree, Height)
is_avl_tree_help(nil,0).
is_avl_tree_help(tree(_,L,R),H) :-
is_avl_tree_help(L,H1),
is_avl_tree_help(R,H2),
sub(H1,H2,D),
D in -1 .. 1,
max(H1,H2,H3),
H is H3+1.
is_avl_tree(Tree,H) :-
is_tree(Tree),
is_avl_tree_help(Tree,H).
% Define relation between a Tree and a List
tree_elements_help(nil,[]).
tree_elements_help(tree(X,Le,Ri),L) :-
tree_elements_help(Le,L1),
tree_elements_help(Ri,L2),
append(L1,[X|L2],L).
tree_elements(Tree,L) :-
is_tree(Tree),
tree_elements_help(Tree,L).
avl_tree_planter(Tree,L) :-
is_avl_tree(Tree,H),
tree_elements(Tree,L2),
permutation(L2,L).
The problem is that predicates like tree_elements/2 and avl_tree_planter/2 are not reversible. I assume you noticed the issue after calling avl_tree_planter/2 with its first argument uninstantiated. For example, the following queries do not terminate:
?- tree_elements(Tree,[]).
?- avl_tree_planter(Tree,[]).
I will focus on the simpler case of writing a reversible predicate inorder/2 that generates every binary tree having a given inorder traversal. The following implementation does not terminate when its first argument is uninstantiated:
inorder(leaf,[]).
inorder(node(X,L,R),L3) :-
inorder(L,L1),
inorder(R,L2),
append(L1,[X|L2],L3).
If you trace the query ?- inorder(Tree,[]) you will find that the first recursive call to inorder/2 causes the problem. In order to prove inorder(Tree,[]) it is necessary to prove infinitely many goals of the form inorder(X,[]). In general, the first recursive call to inorder/2 prevents the construction of the left subtree. This is analogous to the problem of left recursion in parsing.
Here is one solution. We introduce two arguments that track the state of the traversal. The first argument represents the input state and tracks the unprocessed elements. The second represents the output state and tracks the remaining elements. Their difference corresponds to the elements processed during a recursive call. It follows that inorder(Tree,List) should succeed with input state List and output state []. Here is one possible implementation:
inorder(Tree,List) :-
inorder(Tree,List,List,[]).
inorder(leaf,[],State,State).
inorder(node(X,L,R),List,[_|State1],State3) :-
inorder(L,Left,State1,State2),
inorder(R,Right,State2,State3),
append(Left,[X|Right],List).
For example:
?- inorder(leaf,List).
List = [].
?- inorder(node(1,leaf,leaf),List).
List = [1].
?- inorder(node(1,node(2,leaf,leaf),leaf),List).
List = [2, 1].
?- findall(Tree,inorder(Tree,[]),Trees).
Trees = [leaf].
?- findall(Tree,inorder(Tree,[1]),Trees).
Trees = [node(1, leaf, leaf)].
?- findall(Tree,inorder(Tree,[1,2]),Trees).
Trees = [node(1, leaf, node(2, leaf, leaf)), node(2, node(1, leaf, leaf), leaf)].
If this implementation reminds you of parsing, that's because it implements roughly the same functionality as the following definite clause grammar (DCG). The following code and a discussion of the relationship between nontermination and left recursion can be found at Markus Triska's DCG tutorial, which I suggest reading. Using DCG's for list processing is considered idiomatic Prolog.
:- use_module(library(dcg/basics)).
inorder(Tree,List) :-
phrase(inorder(Tree,List,_),List).
inorder(leaf,S,S) -->
[].
inorder(node(X,L,R),[_|S1],S3) -->
inorder(L,S1,S2),
[X],
inorder(R,S2,S3).
How to solve your original problem? In order to adapt these techniques to the setting of AVL trees, you need to place additional restrictions on which trees are generated (i.e., only succeed with binary search trees satisfying the AVL property). This should not be difficult. I hope you found this explanation helpful.

How to convert tree to list in Prolog?

Implement the predicate treeToList(X,List), where X is a given ordered non-empty binary tree, and List is an ordered list of elements in nodes of the tree.
4
/ \
2 6
/ \ / \
1 3 5 7
is an ordered tree given as an input to predicate "treeToList".
Your program must compute the list [1,2,3,4,5,6,7].
Here is the codes I had so far:
treeToList(X,List) :- binaryTree(X), convert(X,List).
convert( tree(Element,void,void), List) :- List=[Element].
The helping predicate convert(X,List) is true if X is a given non-empty tree, and List is a representation of this tree as an ordered list.
But I have no idea how to write the recursive part of this question
convert( tree(Root,Left,Right), List) :-
Can someone help me with this part?
You never explicitly said what your data structure looks like in Prolog, but I can infer that you have basically two kinds of tree node:
tree(Element, Left, Right)
void
To handle any recursive data structure, you write a recursive predicate. Usually (but not always) you want clauses for each kind of element. In Haskell, this is a bit more clear because you have to define your types and their constructors, but you can apply the same reasoning here. So your convert/2 predicate is going to have a clause for each of your kinds of element:
convert(void, ...) :- ...
convert(tree(Element, Left, Right), ...) :- ...
You can see right away that the first clause is going to be pretty simple:
convert(void, []).
The second clause is where things get a bit more interesting. The key is to recursively apply convert/2 to the subtrees on the left and right, and then you need to do something with the element you have:
convert(tree(Element, Left, Right), Rest) :-
convert(Left, LeftList),
convert(Right, RightList),
append(LeftList, [Element|RightList], Rest).
Note that I'm prepending the current element to the right list before appending. This is to insert the element in its proper place in the list for an in-order traversal, to get you the result you want:
?- convert(tree(4, tree(2, tree(1, void, void), tree(3, void, void)),
tree(6, tree(5, void, void), tree(7, void, void))),
List).
List = [1, 2, 3, 4, 5, 6, 7].
This gives you an in-order traversal. If you wanted a pre-order or a post-order traversal you would instead place the element in another position, such as at the start of the result or the end of the result.
Your tree has, based on the question, two "families" of data:
the constant void; and
a compound term with a tree/3 with as arguments the value and the left and right subtree.
We can implement a predicate like #DanielLyons demonstrated. We can slightly optimize this by defining a predicate convert/3 where we the first parameter is the tree to convert, the second parameter is the head of the list, and the third parameter is the tail of the list.
We can thus define our predicate as:
convert(void, L, L).
convert(tree(V, L, R), H, T2) :-
convert(L, H, [V|T1]),
convert(R, T1, T2).
If we thus encounter a void, then the start and the end of the list remain the same. If we encounter a tree(V, L, R), we will first recursively call convert(L, H, [V|T1]). By writing [V|T1] as tail, we thus force Prolog to yield the V value in the result. The tail T1 is then the start of the convert/3 of the second subtree.
We then can define convert/2 in terms of convert/3:
convert(T, L) :-
convert(T, L, []).

Prolog predicate single node in tree

Code a predicate that finds all nodes in the tree with exactly one single child node.
Given the tree
treeEx(X) :-
X = t(73,t(31,t(5,nil,nil),nil),t(101,t(83,nil,t(97,nil,nil)),nil)).
73
/ \
31 101
/ /
5 83
/
97
It should return L = [31, 101, 83]
I have tried the following, but it returns all nodes. I do not know how to list only the single child nodes.
single(nil,[]).
single(t(X,L,R),[X|S]) :-
append(SL,SR,S), single(L,SL), single(R,SR).
[..] a predicate that finds all nodes in the tree with exactly one single child node.
First think about which cases You're interested in:
t(V,nil,R) := a node with value V and a single (right) child R.
t(V,L,nil) := a node with value V and a single (left) child L.
Then think about the other cases, which You're not interested in (in as general terms as possible):
t(V,nil,nil) := a node with value V and no children.
t(V,L,R) := a node with value V and both a left (L) and right (R) child.
Next think about what You want to "do": Collect the values of the cases You're interested in in a list. Thus, when You have a case You're interested in, then You'd need to add the value V to a list with Your results:
[V|RestResults] % whatever RestResults is, not important atm
With that, You can write Your predicate: You know it has one "input" parameter (the tree) and one "output" parameter (the list). First the cases You're interested in:
single(t(V, nil, R), [V|Vr]) :- single(R, Vr).
single(t(V, L, nil), [V|Vl]) :- single(L, Vl).
You add the value V to the results (list of values) You get from the single child branch.
Next the cases You're not interested in. First the easy one:
single(t(_,nil,nil), []).
That's a leaf node (no children). Its value isn't interesting, and there are no results that might come from its children, so the result list is the empty list.
Finally, the most complex case:
single(t(_, L, R), X) :- single(L, Vl), single(R, Vr), append(Vl, Vr, X).
Two children; the value isn't interesting in this case, but the children are: You need to gather their result lists and append them to create the result list of this node.
Now, the order in which You write these rules is normally important in Prolog, but in this case the order doesn't matter (when Prolog uses the "wrong" rule for a node, e.g. the last one - two children - for a t(_,nil,nil), then it quickly arrives in a situation - single(nil, _) - where no rule matches, and backtracks to the "correct" rule). Nonetheless I'd sort the rules according to how "specific" their pattern is: First the rule for no children, then the two for one child, and finally the one for two children.
(Live on ideone)

Understanding this bubble sort solution in Prolog

How does this bubble sort solution work in Prolog?
bubblesort([], []).
bubblesort([H], [H]).
bubblesort([H|D], R) :-
bubblesort(D, E),
[B|G] = E,
( (H =< B, R = [H|E])
; (H > B, bubblesort([B,H|G], R))
).
Here is an example trace: https://pastebin.com/T0DLsmAV
I understand the the line bubblesort(D,E), is responsible for sorting it down to one element, but I don't understand how this works. I understand the basics of lists in prolog, but still cannot work out how this solution operates.
The main difficulty with this code is that bad variable names were chosen and are making the logic harder to follow than it needs to be.
The first two cases are obviously base cases. The first says "the empty list is already sorted" and the second says "a singleton list is already sorted." This should make sense. The third case is where things get interesting.
Let's examine the first part.
bubblesort([H|D], R) :-
bubblesort(D, E),
All that's happened so far is we've named our result R and broken our inputs into a first element H and a tail D. From there, we have said, let's bubblesort the tail of our input and call that E. Maybe this would be a little easier to follow?
bubblesort([H|T], Result) :-
bubblesort(T, TSorted),
Next up,
[B|G] = E,
Again, bad names, but what the author is intending to do here is straightforward: take apart the result of sorting the tail so we can talk about whether the next item in the sorted tail is the right element for that position, or if it needs to switch places with the head of our input. Let's rename:
[HeadOfTSorted|RestOfTSorted] = TSorted,
Now we have a condition. Think of it in terms of prepending onto a sorted list. Say you have some element, like 3, and I hand you a sorted list. You want to determine if your 3 goes at the front or somewhere else. Well, suppose I gave you a sorted list that looked like [5,7,19,23,...]. You'd know that your 3 is right where it needs to be, and you'd hand back [3,5,7,19,23,...]. That's exactly the first case of the condition:
( (H =< HeadOfTSorted, Result = [H|TSorted])
Now consider another case, where I hand you a list that starts with [1,2,...]. You know you can't just put the three at the start and give me back [3,1,2,...]. But you don't really know where the 3 goes; it just doesn't go at the start. So what you have to do is resort the rest of the list with the 3 at the start, after the 1: [1 | resorted([3,2,...])]. That's effectively the other branch of the condition:
; (H > HeadOfTSorted, bubblesort([HeadOfTSorted,H|RestOfTSorted], R))
).
Hope this helps!
note: the key to recursive problem solving is exactly not to think about the minutiae of our code's operations. Imagine you already have the solution, then just use it to solve a smaller subproblem, thus arriving at the full problem's solution.
Your code, with more suggestive variable names so I could follow it, reads:
bubblesort([], []). % empty list is already sorted
bubblesort([H], [H]). % singleton list is already sorted
bubblesort([H|T], S) :- % `[H|T]` sorted is `S`, *if*
bubblesort(T, [M|R]), % `T` sorted is `[M|R]`, *and*
( % *either*,
H =< M, % in case `H` is not greater than `M`,
S = [H,M|R] % `S` is `[H,M|R]`,
; % *or*
H > M, % in case `H` is greater than `M`,
bubblesort([M,H|R], S) % `S` is `[M,H|R]` sorted by the same algorithm
).
(H is for "head", T is for "tail", S is "sorted", R "rest" and M is "minimum" -- see below for that).
We prove its correctness by structural induction. The induction hypothesis (IH) is that this definition is correct for shorter lists. We need to prove it is then also correct for a longer list. Indeed T is one-element shorter than [H|T]. Thus IH says [M|R] is sorted. This means M is the minimum element in T. It also means T is non-empty (sorting doesn't change the number of elements), so the clauses are indeed mutually-exclusive.
If H is not larger than the minimum element in T, [H,M|R] is obviously sorted.
Otherwise, we sort [M,H|R]. M is the minimum element and thus guaranteed to be the first in the result. What's actually sorted is [H|R], which is one element shorter, thus by IH sorting it works. QED.
If the last step sounds fishy to you, consider replacing the second alternative with the equivalent
; H > M, % in case `H` is greater then `M`,
bubblesort([H|R], S1), % `S1` is `[H|R]` sorted by the same algorithm
S = [M|S1]
).
where the applicability of the induction step is even clearer.
I'm not so sure it's a bubble sort though.
update: Indeed, measuring the empirical orders of growth, its number of inferences grows as ~ n3 (or slower), but true bubble sort clocked at ~ n2.1 (close enough to the theoretical ~ n2), where n is the list's length:
tbs([], []). % 'true' bubble sort
tbs([H],[H]).
tbs(L,S):- bubble(L,B),
( L==B -> S=L ; tbs(B,S) ).
bubble([],[]).
bubble([A],[A]).
bubble([A,B|C],R):-
( A =< B -> bubble([B|C],X), R=[A|X]
; bubble([A|C],X), R=[B|X] ).

How can I verify if a coordinate is in a list

I'm generating random coordinates and adding on my list, but first I need verify if that coordinate already exists. I'm trying to use member but when I was debugging I saw that isn't working:
My code is basically this:
% L is a list and Q is a count that define the number of coordinate
% X and Y are the coordinate members
% check if the coordniate already exists
% if exists, R is 0 and if not, R is 1
createCoordinates(L,Q) :-
random(1,10,X),
random(1,10,Y),
convertNumber(X,Z),
checkCoordinate([Z,Y],L,R),
(R is 0 -> print('member'), createCoordinates(L,Q); print('not member'),createCoordinates(L,Q-1).
checkCoordinate(C,L,R) :-
(member(C,L) -> R is 0; R is 1).
% transforms the number N in a letter L
convertNumber(N,L) :-
N is 1, L = 'A';
N is 2, L = 'B';
...
N is 10, L = 'J'.
%call createCoordinates
createCoordinates(L,20).
When I was debugging this was the output:
In this picture I'm in the firts interation and L is empty, so R should be 1 but always is 0, the coordinate always is part of the list.
I have the impression that the member clause is adding the coordinate at my list and does'nt make sense
First off, I would recommend breaking your problem down into smaller pieces. You should have a procedure for making a random coordinate:
random_coordinate([X,Y]) :-
random(1, 10, XN), convertNumber(XN, X),
random(1, 10, Y).
Second, your checkCoordinate/3 is converting Prolog's success/failure into an integer, which is just busy work for Prolog and not really improving life for you. memberchk/2 is completely sufficient to your task (member/2 would work too but is more powerful than necessary). The real problem here is not that member/2 didn't work, it's that you are trying to build up this list parameter on the way out, but you need it to exist on the way in to examine it.
We usually solve this kind of problem in Prolog by adding a third parameter and prepending values to the list on the way through. The base case then equates that list with the outbound list and we protect the whole thing with a lower-arity procedure. In other words, we do this:
random_coordinates(N, Coordinates) :- random_coordinates(N, [], Coordinates).
random_coordinates(0, Result, Result).
random_coordinates(N, CoordinatesSoFar, FinalResult) :- ...
Now that we have two things, memberchk/2 should work the way we need it to:
random_coordinates(N, CoordinatesSoFar, FinalResult) :-
N > 0, succ(N0, N), % count down, will need for recursive call
random_coordinate(Coord),
(memberchk(Coord, CoordinatesSoFar) ->
random_coordinates(N, CoordinatesSoFar, FinalResult)
;
random_coordinates(N0, [Coord|CoordinatesSoFar], FinalResult)
).
And this seems to do what we want:
?- random_coordinates(10, L), write(L), nl.
[[G,7],[G,3],[H,9],[H,8],[A,4],[G,1],[I,9],[H,6],[E,5],[G,8]]
?- random_coordinates(10, L), write(L), nl.
[[F,1],[I,8],[H,4],[I,1],[D,3],[I,6],[E,9],[D,1],[C,5],[F,8]]
Finally, I note you continue to use this syntax: N is 1, .... I caution you that this looks like an error to me because there is no distinction between this and N = 1, and your predicate could be stated somewhat tiresomely just with this:
convertNumber(1, 'A').
convertNumber(2, 'B').
...
My inclination would be to do it computationally with char_code/2 but this construction is actually probably better.
Another hint that you are doing something wrong is that the parameter L to createCoordinates/2 gets passed along in all cases and is not examined in any of them. In Prolog, we often have variables that appear to just be passed around meaninglessly, but they usually change positions or are used multiple times, as in random_coordinates(0, Result, Result); while nothing appears to be happening there, what's actually happening is plumbing: the built-up parameter becomes the result value. Nothing interesting is happening to the variable directly there, but it is being plumbed around. But nothing is happening at all to L in your code, except it is supposedly being checked for a new coordinate. But you're never actually appending anything to it, so there's no reason to expect that anything would wind up in L.
Edit Notice that #lambda.xy.x solves the problem in their answer by prepending the new coordinate in the head of the clause and examining the list only after the recursive call in the body, obviating the need for the second list parameter.
Edit 2 Also take a look at #lambda.xy.x's other solution as it has better time complexity as N approaches 100.
Since i had already written it, here is an alternative solution: The building block is gen_coord_notin/2 which guarantees a fresh solution C with regard to an exclusion list Excl.
gen_coord_notin(C, Excl) :-
random(1,10,X),
random(1,10,Y),
( memberchk(X-Y, Excl) ->
gen_coord_notin(C, Excl)
;
C = X-Y
).
The trick is that we only unify C with the new result, if it is fresh.
Then we only have to fold the generations into N iterations:
gen_coords([], 0).
gen_coords([X|Xs], N) :-
N > 0,
M is N - 1,
gen_coords(Xs, M),
gen_coord_notin(X, Xs).
Remark 1: since coordinates are always 2-tuples, a list representation invites unwanted errors (e.g. writing [X|Y] instead of [X,Y]). Traditionally, an infix operator like - is used to seperate tuples, but it's not any different than using coord(X,Y).
Remark 2: this predicate is inherently non-logical (i.e. calling gen_coords(X, 20) twice will result in different substitutions for X). You might use the meta-level predicates var/1, nonvar/1, ground/1, integer, etc. to guard against non-sensical calls like gen_coord(1-2, [1-1]).
Remark 3: it is also important that the conditional does not have multiple solutions (compare member(X,[A,B]) and memberchk(X,[A,B])). In general, this can be achieved by calling once/1 but there is a specialized predicate memberchk/2 which I used here.
I just realized that the performance of my other solutions is very bad for N close to 100. The reason is that with diminishing possible coordinates, the generate and test approach will take longer and longer. There's an alternative solution which generates all coordinates and picks N random ones:
all_pairs(Ls) :-
findall(X-Y, (between(1,10,X), between(1,10,Y)), Ls).
remove_index(X,[X|Xs],Xs,0).
remove_index(I,[X|Xs],[X|Rest],N) :-
N > 0,
M is N - 1,
remove_index(I,Xs,Rest,M).
n_from_pool(_Pool, [], 0).
n_from_pool(Pool, [C|Cs], N) :-
N > 0,
M is N - 1,
length(Pool, L),
random(0,L,R),
remove_index(C,Pool,NPool,R),
n_from_pool(NPool, Cs, M).
gen_coords2(Xs, N) :-
all_pairs(Pool),
n_from_pool(Pool, Xs, N).
Now the query
?- gen_coords2(Xs, 100).
Xs = [4-6, 5-6, 5-8, 9-6, 3-1, 1-3, 9-4, 6-1, ... - ...|...] ;
false.
succeeds as expected. The error message
?- gen_coords2(Xs, 101).
ERROR: random/1: Domain error: not_less_than_one' expected, found0'
when we try to generate more distinct elements than possible is not nice, but better than non-termination.

Resources