What does member[H|T] mean? - prolog

I am just learning Prolog and stumbled across following question: Prolog - Seeing if the same element occurs in two lists.
This question includes following line: =(member(X,[H|T]), member[Z|Q])).
I know about member(?Elem, ?List), but I do not understand the member[Z|Q] part. What does this mean? And isn't there a closing paranthesis too much?

Summary:
Do not worry about this at all.
Here are several reasons:
Syntax error
First of all, this is invalid syntax. When you consult the program you link to, you get:
ERROR: file.pl:5:28: Syntax error: Operator expected
indicating exactly the line containing:
=(member(X,[H|T]), member[Z|Q])),
Dubious meaning
Second, even if we somehow fix the problematic syntax, and write this line for example as:
=(member(X,[H|T]), member_whatever),
Then it would still be highly dubious that this is what the author meant to express.
The predicate that is used in this case is (=)/2, and you can write this equivalently using infix notation as:
member(X,[H|T]) = member_whatever,
And from this, it is already clear that this cannot succeed because (=)/2 does not even hold for the much more general case
member(_,_) = member_whatever,
So, it definitely fails of course also in the more specific case above!
Fundamental issues
When programming in Prolog, focus on a clear description of what holds.
For example, to state that "the same elements occurs in two lists" is straight-forward:
element_in_both(E, As, Bs) :-
member(E, As),
member(E, Bs).
That's it! You can read it as follows: If E is a member of As and E is a member of Bs then E is a member of both As and Bs.
It works quite generally, for example:
?- length(Cs, _),
append(As, Bs, Cs),
element_in_both(E, As, Bs).
Cs = [E, E],
As = Bs, Bs = [E] ;
Cs = [E, E, _2946],
As = [E],
Bs = [E, _2946] ;
Cs = [E, _2940, E],
As = [E],
Bs = [_2940, E] .
You can use this predicate to generate lists where this relation holds, to test whether it holds for a specific instance, to complete partial lists such that they satisfy this predicate etc.
All of this follows from a clear declarative description of the conditions that make this relation hold.
In Prolog courses, there is a tendency to needlessly complicate this rather simple fundamental principle of declarative programming. Do not fall into this trap. If your predicate becomes convoluted, your are often overlooking something simpler.

Related

CLPFD ins operator yields not sufficiently instantiated error

So, my goal is to make a map colourer in Prolog. Here's the map I'm using:
And this are my colouring constraints:
colouring([A,B,C,D,E,F]) :-
maplist( #\=(A), [B,C,D,E] ),
maplist( #\=(B), [C,D,F]),
C #\= D,
maplist( #\=(D), [E,F]),
E #\= F.
Where [A,B,C,D,E,F] is a list of numbers(colors) from 1 to n.
So I want my solver to, given a List of 6 colors and a natural number N, determine the colors and N constraints both ways, in a way that even the most general query could yield results:
regions_ncolors(L,N) :- colouring(L), L ins 1..N, label(L).
Where the most general query is regions_ncolors(L,N).
However, the operator ins doesn't seem to accept a variable N, it instead yields an argument not sufficiently instantiated error. I've tried using this solution instead:
int_cset_(N,Acc,Acc) :- N #= 0.
int_cset_(N,Acc,Cs) :- N_1 #= N-1, int_cset_(N_1,[N|Acc],Cs).
int_cset(N,Cs) :- int_cset_(N,[],Cs).
% most general solver
regions_ncolors(L,N) :- colouring(L), int_cset(N,Cs), subset(L,Cs), label(L).
Where the arguments in int_cset(N,Cs) is a natural number(N) and the counting set Sn = {1,2,...,N}
But this solution is buggy as regions_ncolors(L,N). only returns the same(one) solution for all N, and when I try to add a constraint to N, it goes in an infinite loop.
So what can I do to make the most general query work both ways(for not-instantiated variables)?
Thanks in advance!
Btw, I added a swi-prolog tag in my last post although it was removed by moderation. I don't know if this question is specific to swi-prolog which is why I'm keeping the tag, just in case :)
Your colouring is too specific, you encode the topology of your map into it. Not a problem as is, but it defeats of the purpose of then having a "most general query" solution for just any list.
If you want to avoid the problem of having a free variable instead of a list, you could first instantiate the list with length/2. Compare:
?- L ins 1..3.
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR: [16] throw(error(instantiation_error,_86828))
ERROR: [10] clpfd:(_86858 ins 1..3) ...
Is that the same problem as you see?
If you first make a list and a corresponding set:
?- length(L, N), L ins 1..N.
L = [],
N = 0 ;
L = [1],
N = 1 ;
L = [_A, _B],
N = 2,
_A in 1..2,
_B in 1..2 ;
L = [_A, _B, _C],
N = 3,
_A in 1..3,
_B in 1..3,
_C in 1..3 .
If you use length/2 like this you will enumerate the possible lists and integer sets completely outside of the CLP(FD) labeling. You can then add more constraints on the variables on the list and if necessary, use labeling.
Does that help you get any further with your problem? I am not sure how it helps for the colouring problem. You would need a different representation of the map topology so that you don't have to manually define it within a predicate like your colouring/1 you have in your question.
There are several issues in your program.
subset/2 is impure
SWI's (by default) built-in predicate subset/2 is not the pure relation you are hoping for. Instead, it expects that both arguments are already sufficiently instantiated. And if not, it takes a guess and sticks to it:
?- colouring(L), subset(L,[1,2,3,4,5]).
L = [1,2,3,4,2,1].
?- colouring(L), subset(L,[1,2,3,4,5]), L = [2|_].
false.
?- L = [2|_], colouring(L), subset(L,[1,2,3,4,5]), L = [2|_].
L = [2,1,3,4,1,2].
With a pure definition it is impossible that adding a further goal as L = [2|_] in the third query makes a failing query succeed.
In general it is a good idea to not interfere with labeling/2 except for the order of variables and the options argument. The internal implementation is often much faster than manual instantiations.
Also, your map is far too simple to expose subset/2s weakness. Not sure what the minimal failing graph is, but here is one such example from
R. Janczewski et al. The smallest hard-to-color graph for algorithm DSATUR, Discrete Mathematics 236 (2001) p.164.
colouring_m13([K1,K2,K3,K6,K5,K7,K4]):-
maplist(#\=(K1), [K2,K3,K4,K7]),
maplist(#\=(K2), [K3,K5,K6]),
maplist(#\=(K3), [K4,K5]),
maplist(#\=(K4), [K5,K7]),
maplist(#\=(K5), [K6,K7]),
maplist(#\=(K6), [K7]).
?- colouring_m13(L), subset(L,[1,2,3,4]).
false. % incomplete
?- L = [3|_], colouring_m13(L), subset(L,[1,2,3,4]).
L = [3,1,2,2,3,1,4].
int_cset/2 never terminates
... (except for some error cases like int_cset(non_integer, _).). As an example consider:
?- int_cset(1,Cs).
Cs = [1]
; loops.
And don't get fooled by the fact that an actual solution was found! It still does not terminate.
#Luis: But how come? I'm getting baffled by this, the same thing is happening on ...
To see this, you need the notion of a failure-slice which helps to identify the responsible part in your program. With some falsework consisting of goals false the responsible part is exposed.
All unnecessary parts have been removed by false. What remains has to be changed somehow.
int_cset_(N,Acc,Acc) :- false, N #= 0.
int_cset_(N,Acc,Cs) :- N1 #= N-1, int_cset_(N1,[N|Acc],Cs), false.
int_cset(N,Cs) :- int_cset_(N,[],Cs), false.
?- int_cset(1, Cs), false.
loops.
Adding the redundant goal N1 #> 0
will avoid unnecessary non-termination.
This alone will not solve your problem since if N is not given, you will still encounter non-termination due to the following failure slice:
regions_ncolors(L,N) :-
colouring(L),
int_cset(N,Cs), false,
subset(L,Cs),
label(L).
In int_cset(N,Cs), Cs occurs for the first time and thus cannot influence termination (there is another reason too, its definition would ignore it as well..) and therefore only N has a chance to induce termination.
The actual solution has been already suggested by #TA_intern using length/2 which liberates one of such mode-infested chores.

Prolog order of clauses causes pathfinding to fail

I am developing a path finding algorithm in Prolog, giving all nodes accessible by a path from a starting node. To avoid duplicate paths, visited nodes are kept in a list.
Nodes and neighbors are defined as below:
node(a).
node(b).
node(c).
node(d).
node(e).
edge(a,b).
edge(b,c).
edge(c,d).
edge(b,d).
neighbor(X,Y) :- edge(X,Y).
neighbor(X,Y) :- edge(Y,X).
The original algorithm below works fine:
path2(X,Y) :-
pathHelper(X,Y,[X]).
pathHelper(X,Y,L) :-
neighbor(X,Y),
\+ member(Y,L).
pathHelper(X,Y,H) :-
neighbor(X,Z),
\+ member(Z,H),
pathHelper(Z,Y,[Z|H]).
This works fine
[debug] ?- path2(a,X).
X = b ;
X = c ;
X = d ;
X = d ;
X = c ;
false.
however, when changing the order of the two clauses in the second definition, such as below
pathHelper(X,Y,L) :-
\+ member(Y,L),
neighbor(X,Y).
When trying the same here, swipl returns the following:
[debug] ?- path2(a,X).
false.
The query doesn't work anymore, and only returns false. I have tried to understand this through the tracecommand, but still can't make sense of what exactly is wrong.
In other words, I am failing to understand why the order of neighbor(X,Y)and \+ member(Y,L)is crucial here. It makes sense to have neighbor(X,Y) first in terms of efficiency, but not in terms of correctness to me.
You are now encountering the not so clean-cut borders of pure Prolog and its illogical surroundings. Welcome to the real world.
Or rather, not welcome! Instead, let's try to improve your definition. The key problem is
\+ member(Y, [a]), Y = b.
which fails while
Y = b, \+ member(Y,[a]).
succeeds. There is no logic to justify this. It's just the operational mechanism of Prolog's built-in (\+)/1.
Happily, we can improve upon this. Enter non_member/2.
non_member(_X, []).
non_member(X, [E|Es]) :-
dif(X, E),
non_member(X, Es).
Now,
?- non_member(Y, [a]).
dif(Y,a).
Mark this answer, it says: Yes, Y is not an element of [a], provided Y is different from a. Think of the many solutions this answer includes, like Y = 42, or Y = b and infinitely many more such solutions that are not a. Infinitely many solutions captured in nine characters!
Now, both non_member(Y, [a]), Y = b and Y = b, non_member(Y, [a]) succeed. So exchanging them has only influence on runtime and space consumption. If we are at it, note that you check for non-memberness in two clauses. You can factor this out. For a generic solution to this, see closure/3. With it, you simply say: closure(neighbor, A,B).
Also consider the case where you have only edge(a,a). Your definition fails here for path2(a,X). But shouldn't this rather succeed?
And the name path2/2 is not that fitting, rather reserve this word for an actual path.
The doubt you have is related to how prolog handle negation. Prolog uses negation as failure. This means that, if prolog has to negate a goal g (indicate it with not(g)), it tries to prove g by executing it and then, if the g fails, not(g) (or \+ g, i.e. the negation of g) succeeds and viceversa.
Keep in mind also that, after the execution of not(g), if the goal has variables, they will not be instantiated. This because prolog should instantiate the variables with all the terms that makes g fail, and this is likely an infinite set (for example for a list, not(member(A,[a]) should instantiate the variable A with all the elements that are not in the list).
Let's see an example. Consider this simple program:
test:-
L = [a,b,c],
\+member(A,L),
writeln(A).
and run it with ?- trace, test. First of all you get a Singleton variable in \+: A warning for the reason i explained before, but let's ignore it and see what happens.
Call:test
Call:_5204=[a, b]
Exit:[a, b]=[a, b]
Call:lists:member(_5204, [a, b])
Exit:lists:member(a, [a, b]) % <-----
Fail:test
false
You see at the highlighted line that the variable A is instantiated to a and so member/2 succeeds and so \+ member(A,L) is false.
So, in your code, if you write pathHelper(X,Y,L) :- \+ member(Y,L), neighbor(X,Y)., this clause will always fail because Y is not sufficiently instantiated. If you swap the two terms, Y will be ground and so member/2 can fail (and \+member succeeds).

Easier way to get "unique" bindings?

Sorry if my terminology is off. Long term (40 years? ouch...) imperative programmer, dabbled in functional, spending some time this morning trying to be a bit more serious about declarative. Going through a learning site, and decided to try the "crossword" in exercise 2.4 here: http://www.learnprolognow.org/lpnpage.php?pagetype=html&pageid=lpn-htmlse7
I've got it, but it feels ridiculously clunky. Here's my newbie solution:
word(astante, a,s,t,a,n,t,e).
word(astoria, a,s,t,o,r,i,a).
word(baratto, b,a,r,a,t,t,o).
word(cobalto, c,o,b,a,l,t,o).
word(pistola, p,i,s,t,o,l,a).
word(statale, s,t,a,t,a,l,e).
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,V1a,V1b,V1c,V1d,V1e,V1f,V1g),
word(V2,V2a,V2b,V2c,V2d,V2e,V2f,V2g),
word(V3,V3a,V3b,V3c,V3d,V3e,V3f,V3g),
word(H1,H1a,H1b,H1c,H1d,H1e,H1f,H1g),
word(H2,H2a,H2b,H2c,H2d,H2e,H2f,H2g),
word(H3,H3a,H3b,H3c,H3d,H3e,H3f,H3g),
V1b = H1b,
V1d = H2b,
V1f = H3b,
V2b = H1d,
V2d = H2d,
V2f = H3d,
V3b = H1f,
V3d = H2f,
V3f = H3f,
not(V1 = V2),
not(V1 = V3),
not(V1 = H1),
not(V1 = H2),
not(V1 = H3),
not(V2 = V3),
not(V2 = H1),
not(V2 = H2),
not(V2 = H3),
not(V3 = H1),
not(V3 = H2),
not(V3 = H3),
not(H1 = H2),
not(H1 = H3),
not(H2 = H3).
It works. crossword will give me the two possible layouts (puzzle is symmetric, after all). But yeesh...
Some of the clunkiness is just because I've only started, so I don't have any feel for how to mark bindings as "don't care" (the 1st, 3rd, 5th, and 7th letters of the words are completely irrelevant, for instance). But what is really chafing me right now is having to put in the triangular matrix of "don't duplicate any bindings" there at the end. This issue keeps coming up (an earlier toy problem involved loves(A,B) and jealous(X,Y) and if you allow X=Y then everybody leading off a loves relationship is claimed to be jealous of themselves (which I see someone else was fighting with a few years ago:Get unique results with Prolog)), but this tutorial doesn't address it. It hasn't even told me about 'not' yet -- I had to dig around elsewhere to get that, which led into completely valid questions of "well, what kind of 'not equal' did you want?", which I am currently unprepared to answer. But I digress...
It is inconceivable to me that this is the way this actually gets done in real code. Combinatorially, it's ridiculous. And it seems like it violates (or at least bends) the principal of least astonishment. Without the uniqueness restrictions, there are a huge number of solutions that just set V1=H1, V2=H2, V3=H3. I guess I could have only disallowed those, but the real solution needs to do the full restriction.
Yes, I completely understand that logically and mathematically there is no reason not to bind the same value into multiple parameters, and also that there are many situations where such a multiple binding is not just helpful but required to handle the issues at hand. I'm not arguing with the default behavior at all, just looking for a better way to express uniqueness constraints when I need them.
I'd love to know a better way to handle this, because honestly I don't think I can dig much deeper into these tutorials if they're all going to require this much fluff to do something so seemingly obvious.
Thanks in advance!
In my opinion, the exercise is setting you up for failure.
First, because it uses a knowledge representation that is unsuitable for processing similar elements in a uniform fashion.
Second, because you do not have the necessary prerequisites at this point in the book to do so, even if the knowledge representation would make it easier.
I can assure you: What you are doing is of course not necessary when programming in Prolog.
So, don't let a single book detract you from the language.
At this point, I would like to show you how you could solve this task if you had more experience with the language, and used more suitable language features. You may enjoy going back to this later, when you have read other material.
The key change I would like to make is to let you reason about the available words more explicitly, as data structures that are available within your program, instead of "only" as facts:
words(Ws) :-
Ws = [[a,s,t,a,n,t,e],
[a,s,t,o,r,i,a],
[b,a,r,a,t,t,o],
[c,o,b,a,l,t,o],
[p,i,s,t,o,l,a],
[s,t,a,t,a,l,e]].
You can of course easily obtain such an explicit (sometimes called spatial) representation automatically, using all-solutions predicates such as findall/3.
The key predicate I now introduce lets us relate a word in this representation to its every second letter:
word_evens([_,A,_,B,_,C,_], [A,B,C]).
Note how easily this relation can be expressed if you can reason explicitly about the list of letters that constitute a word.
Now, the whole solution, using the predicates permutation/2 and transpose/2, which you can either find as library predicates in your Prolog system, or also implement easily yourself:
solution(Ls) :-
Ls = [V1,V2,V3,H1,H2,H3],
words(Ws),
Ws = [First|_],
maplist(same_length(First), Ls),
maplist(word_evens, [H1,H2,H3], Ess),
transpose(Ess, TEss),
maplist(word_evens, [V1,V2,V3], TEss),
permutation(Ws, Ls).
Sample query and the two solutions:
?- solution(Ls).
Ls = [[a, s, t, a, n, t, e], [c, o, b, a, l, t, o], [p, i, s, t, o, l|...], [a, s, t, o, r|...], [b, a, r, a|...], [s, t, a|...]] ;
Ls = [[a, s, t, o, r, i, a], [b, a, r, a, t, t, o], [s, t, a, t, a, l|...], [a, s, t, a, n|...], [c, o, b, a|...], [p, i, s|...]] ;
false.
At least maplist/2 should be available in your Prolog, and same_length/2 is easy to define if your system does not provide it.
If you really want to express disequality of terms, use prolog-dif.
But what is really chafing me right now is having to put in the triangular matrix of "don't duplicate any bindings" there at the end.
We can get a better solution with the all_dif/1 predicate from here: https://stackoverflow.com/a/47294595/4391743
all_dif([]).
all_dif([E|Es]) :-
maplist(dif(E), Es),
all_dif(Es).
This predicate accepts a list of elements that are all different from each other. Don't worry about not understanding it just yet, you can treat it as a black box for now.
You can use this to replace the big block of not goals at the end of your predicate definition:
crossword(V1,V2,V3,H1,H2,H3):-
... % unchanged code here
all_dif([V1, V2, V3, H1, H2, H3]).
With this you get back to only the two solutions in which all the words are used.
I don't have any feel for how to mark bindings as "don't care" (the 1st, 3rd, 5th, and 7th letters of the words are completely irrelevant, for instance).
This is indeed a very important issue! And Prolog should warn you about variables you only use once (called "singletons"), because they are a frequent source of bugs:
Singleton variables: [V1a,V1c,V1e,V1g,V2a,V2c,V2e,V2g,V3a,V3c,V3e,V3g,H1a,H1c,H1e,H1g,H2a,H2c,H2e,H2g,H3a,H3c,H3e,H3g]
You explicitly mark a variable as "don't care" by giving it a name that starts with the underscore character _, or just naming it _ altogether. Different occurrences of _ mark different "don't care" variables. So we get:
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,_,V1b,_,V1d,_,V1f,_),
word(V2,_,V2b,_,V2d,_,V2f,_),
word(V3,_,V3b,_,V3d,_,V3f,_),
word(H1,_,H1b,_,H1d,_,H1f,_),
word(H2,_,H2b,_,H2d,_,H2f,_),
word(H3,_,H3b,_,H3d,_,H3f,_),
V1b = H1b,
V1d = H2b,
V1f = H3b,
V2b = H1d,
V2d = H2d,
V2f = H3d,
V3b = H1f,
V3d = H2f,
V3f = H3f,
all_dif([V1, V2, V3, H1, H2, H3]).
The warnings are gone and we the program is easier to read because the underscores leave "holes" in uninteresting places, and we see more clearly which variables matter.
That leaves us with the task of removing all those equations. General Prolog tip: Except maybe sometimes for reasons of clarity, there is never any need to write an equation of the form Var1 = Var2 where both sides are variables. Just use the same name for both variables in the whole clause, and you get the same result!
So let's replace V1b and H1b by the same variable named A, V1d and H2b by the same variable B, etc.:
crossword(V1,V2,V3,H1,H2,H3):-
word(V1,_,A,_,B,_,C,_),
word(V2,_,D,_,E,_,F,_),
word(V3,_,G,_,H,_,I,_),
word(H1,_,A,_,D,_,G,_),
word(H2,_,B,_,E,_,H,_),
word(H3,_,C,_,F,_,I,_),
all_dif([V1, V2, V3, H1, H2, H3]).
This is equivalent to your initial solution and, I hope, fairly beginner-friendly.
Hopefully this convices you that Prolog programs can be a bit less clunky than your first attempt. Please stick around, we're here to help if you get stuck, and hopefully you will have some less frustrating experiences and see the magic of Prolog.

Collect all "minimum" solutions from a predicate

Given the following facts in a database:
foo(a, 3).
foo(b, 2).
foo(c, 4).
foo(d, 3).
foo(e, 2).
foo(f, 6).
foo(g, 3).
foo(h, 2).
I want to collect all first arguments that have the smallest second argument, plus the value of the second argument. First try:
find_min_1(Min, As) :-
setof(B-A, foo(A, B), [Min-_|_]),
findall(A, foo(A, Min), As).
?- find_min_1(Min, As).
Min = 2,
As = [b, e, h].
Instead of setof/3, I could use aggregate/3:
find_min_2(Min, As) :-
aggregate(min(B), A^foo(A, B), Min),
findall(A, foo(A, Min), As).
?- find_min_2(Min, As).
Min = 2,
As = [b, e, h].
NB
This only gives the same results if I am looking for the minimum of a number. If an arithmetic expression in involved, the results might be different. If a non-number is involved, aggregate(min(...), ...) will throw an error!
Or, instead, I can use the full key-sorted list:
find_min_3(Min, As) :-
setof(B-A, foo(A, B), [Min-First|Rest]),
min_prefix([Min-First|Rest], Min, As).
min_prefix([Min-First|Rest], Min, [First|As]) :-
!,
min_prefix(Rest, Min, As).
min_prefix(_, _, []).
?- find_min_3(Min, As).
Min = 2,
As = [b, e, h].
Finally, to the question(s):
Can I do this directly with library(aggregate)? It feels like it should be possible....
Or is there a predicate like std::partition_point from the C++ standard library?
Or is there some easier way to do this?
EDIT:
To be more descriptive. Say there was a (library) predicate partition_point/4:
partition_point(Pred_1, List, Before, After) :-
partition_point_1(List, Pred_1, Before, After).
partition_point_1([], _, [], []).
partition_point_1([H|T], Pred_1, Before, After) :-
( call(Pred_1, H)
-> Before = [H|B],
partition_point_1(T, Pred_1, B, After)
; Before = [],
After = [H|T]
).
(I don't like the name but we can live with it for now)
Then:
find_min_4(Min, As) :-
setof(B-A, foo(A, B), [Min-X|Rest]),
partition_point(is_min(Min), [Min-X|Rest], Min_pairs, _),
pairs_values(Min_pairs, As).
is_min(Min, Min-_).
?- find_min_4(Min, As).
Min = 2,
As = [b, e, h].
What is the idiomatic approach to this class of problems?
Is there a way to simplify the problem?
Many of the following remarks could be added to many programs here on SO.
Imperative names
Every time, you write an imperative name for something that is a relation you will reduce your understanding of relations. Not much, just a little bit. Many common Prolog idioms like append/3 do not set a good example. Think of append(As,As,AsAs). The first argument of find_min(Min, As) is the minimum. So minimum_with_nodes/2 might be a better name.
findall/3
Do not use findall/3 unless the uses are rigorously checked, essentially everything must be ground. In your case it happens to work. But once you generalize foo/2 a bit, you will lose. And that is frequently a problem: You write a tiny program ; and it seems to work.
Once you move to bigger ones, the same approach no longer works. findall/3 is (compared to setof/3) like a bull in a china shop smashing the fine fabric of shared variables and quantification. Another problem is that accidental failure does not lead to failure of findall/3 which often leads to bizarre, hard to imagine corner cases.
Untestable, too specific program
Another problem is somewhat related to findall/3, too. Your program is so specific, that it is quite improbable that you will ever test it. And marginal changes will invalidate your tests. So you will soon give up to perform testing. Let's see what is specific: Primarily the foo/2 relation. Yes, only an example. Think of how to set up a test configuration where foo/2 may change. After each change (writing a new file) you will have to reload the program. This is so complex, chances are you will never do it. I presume you do not have a test harness for that. Plunit for one, does not cover such testing.
As a rule of thumb: If you cannot test a predicate on the top level you never will. Consider instead
minimum_with(Rel_2, Min, Els)
With such a relation, you can now have a generalized xfoo/3 with an additional parameter, say:
xfoo(o, A,B) :-
foo(A,B).
xfoo(n, A,B) :-
newfoo(A,B).
and you most naturally get two answers for minimum_with(xfoo(X), Min, Els). Would you have used findall/3 instead of setof/3 you already would have serious problems. Or just in general: minmum_with(\A^B^member(A-B, [x-10,y-20]), Min, Els). So you can play around on the top level and produce lots of interesting test cases.
Unchecked border cases
Your version 3 is clearly my preferred approach, however there are still some parts that can be improved. In particular, if there are answers that contain variables as a minimum. These should be checked.
And certainly, also setof/3 has its limits. And ideally you would test them. Answers should not contain constraints, in particular not in the relevant variables. This shows how setof/3 itself has certain limits. After the pioneering phase, SICStus produced many errors for constraints in such cases (mid 1990s), later changed to consequently ignoring constraints in built-ins that cannot handle them. SWI on the other hand does entirely undefined things here. Sometimes things are copied, sometimes not. As an example take:
setof(A, ( A in 1..3 ; A in 3..5 ), _) and setof(t, ( A in 1..3 ; A in 3.. 5 ), _).
By wrapping the goal this can be avoided.
call_unconstrained(Goal_0) :-
call_residue_vars(Goal_0, Vs),
( Vs = [] -> true ; throw(error(representation_error(constraint),_)) ).
Beware, however, that SWI has spurious constraints:
?- call_residue_vars(all_different([]), Xs).
Xs = [_A].
Not clear if this is a feature in the meantime. It has been there since the introduction of call_residue_vars/2 about 5 years ago.
I don't think that library(aggregate) covers your use case. aggregate(min) allows for one witness:
min(Expr, Witness)
A term min(Min, Witness), where Min is the minimal version of Expr over all solutions, and Witness is any other template applied to solutions that produced Min. If multiple solutions provide the same minimum, Witness corresponds to the first solution.
Some time ago, I wrote a small 'library', lag.pl, with predicates to aggregate with low overhead - hence the name (LAG = Linear AGgregate). I've added a snippet, that handles your use case:
integrate(min_list_associated, Goal, Min-Ws) :-
State = term(_, [], _),
forall(call(Goal, V, W), % W stands for witness
( arg(1, State, C), % C is current min
arg(2, State, CW), % CW are current min witnesses
( ( var(C) ; V #< C )
-> U = V, Ws = [W]
; U = C,
( C == V
-> Ws = [W|CW]
; Ws = CW
)
),
nb_setarg(1, State, U),
nb_setarg(2, State, Ws)
)),
arg(1, State, Min), arg(2, State, Ws).
It's a simple minded extension of integrate(min)...
The comparison method it's surely questionable (it uses less general operator for equality), could be worth to adopt instead a conventional call like that adopted for predsort/3. Efficiency wise, still better would be to encode the comparison method as option in the 'function selector' (min_list_associated in this case)
edit thanks #false and #Boris for correcting the bug relative to the state representation. Calling nb_setarg(2, State, Ws) actually changes the term' shape, when State = (_,[],_) was used. Will update the github repo accordingly...
Using library(pairs) and [sort/4], this can be simply written as:
?- bagof(B-A, foo(A, B), Ps),
sort(1, #=<, Ps, Ss), % or keysort(Ps, Ss)
group_pairs_by_key(Ss, [Min-As|_]).
Min = 2,
As = [b, e, h].
This call to sort/4 can be replaced with keysort/2, but with sort/4 one can also find for example the first arguments associated with the largest second argument: just use #>= as the second argument.
This solution is probably not as time and space efficient as the other ones, but may be easier to grok.
But there is another way to do it altogether:
?- bagof(A, ( foo(A, Min), \+ ( foo(_, Y), Y #< Min ) ), As).
Min = 2,
As = [b, e, h].

Number of occurrences of X in the List L in prolog

I am trying to find the number of occurrences of X in the List L
For eg :-
occurrences(a, [b, a, b, c, a, d, a], N ).
N =3
My code not working .Here is my code.
occ(K,L,N) :- N1=0, occ1(K,L,N1,N).
occ1(K,[],N1,N) :- N=N1.
occ1(K,L,N1,N) :-
L=[X|L1],
( K=X -> N1 is N1+1, occ1(K,L1,N1,N) ; occ1(K,L1,N1,N) ).
Can anybody tell me what's wrong in the code.
While the answer given by #Kay is spot-on as far as fixing the bug is concerned, it completely circumvents a much bigger issue: The code of occ1/4 is logically impure.
This may not appear very important to you right now,
but using impure code has several negative consequences:
Impure code cannot be read declaratively, only procedurally.
Debugging impure code is often tedious and pain-staking.
Impure predicates are less "relational" than their pure counterparts.
Logical impurity hampers code re-use.
Because it is non-monotone, impure code is prone to lead to logically unsound answers, particularly when working with non-ground terms.
To show that these problems persisted in your code after having been "fixed" as suggested #Kay, let us consider the "corrected" code and some queries. First, here's the corrected code:
occ(K,L,N) :- N1=0, occ1(K,L,N1,N).
occ1(_,[],N1,N) :- N=N1.
occ1(K,L,N1,N) :-
L=[X|L1],
( K=X -> N2 is N1+1, occ1(K,L1,N2,N) ; occ1(K,L1,N1,N) ).
Here's the query you gave in your question:
?- occ(a,[b,a,b,c,a,d,a],N).
N = 3 ;
false.
Okay! What if we write the query differently?
?- A=a,B=b,C=c,D=d, occ(a,[B,A,B,C,A,D,A],N).
A = a, B = b, C = c, D = d, N = 3 ;
false.
Okay! What if we reorder goals? Logical conjunction should be commutative...
?- occ(a,[B,A,B,C,A,D,A],N), A=a,B=b,C=c,D=d.
false.
Fail! It seemed that occ1/4 is fine, but now we get an answer that is logically unsound.
This can be avoided by using logically pure code:
Look at the pure and monotone code I gave in my answer to the related question "Prolog - count repititions in list (sic)".
The problem is
N1 is N1+1
Variables cannot be "overwritten" in Prolog. You need to just a new variable, e.g.
N2 is N1+1, occ1(K,L1,N2,N)
To your question "Can we replace a particular list element. If yes, what is the syntax?":
You can only build a new list:
replace(_, _, [], []).
replace(Old, New, [H0|T0], [H1|T1]) :-
(H0 = Old -> H1 = New; H1 = H0),
replace(Old, New, T0, T1).

Resources