I'm trying to solve a CSP where I need to distribute cocktails over bartenders so that each bartender has at most one cocktail and all cocktails are given a bartender. I solved it by creating a list of clpfd variables,first giving them the full domain of all bartenders and then removing all bartenders that don't know how to make that cocktail.
My code works, but there is one problem: it's too slow. If I look in the profiler, remove_domain gets called 2000 times(for the input I'm giving my program), while it's Redo statistic is >100 000.
What do I need to change in one of these functions(or both) so that prolog doesn't need to backtrack?
produce_domains(_,_,[],[]) :- !.
produce_domains(Bartenders,NBartenders,[Cocktail|Cocktails],[Var|Vars]) :-
Var in 1..NBartenders,
remove_domain(Bartenders,NBartenders,Cocktail,Var),!,
produce_domains(Bartenders,NBartenders,Cocktails,Vars),!.
remove_domain([],0,_,_) :- !.
remove_domain([Bartender|Bartenders],NBartenders,Cocktail,Var) :-
(\+ member(Cocktail,Bartender) -> Var #\= NBartenders;!),!,
NNBartenders is NBartenders - 1,
remove_domain(Bartenders,NNBartenders,Cocktail,Var),!.
I have already read this related question, but I am using the latest Windows build of SWI-Prolog(5.10.5), so that shouldn't be the problem here.
You do not need so many !/0: Prolog can often tell that your predicates are deterministic.
Let me first offer the following version of your code. It uses names that are more relational, contains no !/0 and uses higher-order predicates to make the code shorter.
:- use_module(library(clpfd)).
bartenders_cocktails_variables(Bs, Cs, Vs) :-
length(Bs, LBs),
maplist(bartenders_cocktail_variable(Bs, LBs), Cs, Vs).
bartenders_cocktail_variable(Bs, N, C, V) :-
V in 1..N,
foldl(compatible_bartender(C,V), Bs, 1, _).
compatible_bartender(C, V, Cs, N0, N1) :-
( member(C, Cs) -> true
; V #\= N0
),
N1 #= N0 + 1.
Notice that I am counting upwards instead of downwards to enumerate the bartenders (which are just lists of cocktails they are able to mix), since this seems more natural. I was also able to omit a (\+)/1 by simply switching the branches of the if-then-else.
Example query, showing that the predicate is deterministic in this use case:
?- bartenders_cocktails_variables([[a,b],[a,b],[x,y]], [x,a,b], Vars).
Vars = [3, _G1098, _G1101],
_G1098 in 1..2,
_G1101 in 1..2.
We see: Cocktail x must be mixed by the third bartender etc.
I think this part of your program may not be responsible for the slow performance you are describing. Maybe other parts of your program are (unintentionally) not deterministic? Maybe try different labeling strategies or other constraints? We may be able to help you more if you post more context.
Related
Given a number of facts is there a way to count them without using a built in function I have tried doing so with the below code but could no get it work. I hope someone can help me out.
For example the following facts:
stops(jubilee,bondstreet,1).
stops(jubilee,waterloo,2).
stops(jubilee,bakerstreet,3).
The code have got so far is:
findStops(X) :- stops(X,_, N), N1 is N+1, stopsX,_,N1).
I would like to make it so that N1 is the counter of how stops the jubilee line has.
A simple solution would be to count the number of stops/3 facts that have the atom jubilee in the first argument. Assuming all clauses for the stops/3 predicate have a bound first argument, you could write:
?- findall(1, stops(jubilee,_,_), List), length(List, Count).
In this query, findall/3 is a standard Prolog predicate and length/2 is a de facto standard predicate, usually available as a built-in predicate or as a library predicate.
Can you convert this query into a predicate that takes the station as an argument (instead of a hardcoded station as jubilee) and returns the count for that station?
The question isn't totally clear since it hasn't been defined what is allowed in terms of "built in" predicates. Such a problem cannot be solved without using some kind of predefined predicate.
Here are a couple of other ideas.
Using assertz and retract:
count_stops(Count) :-
assertz(num_stops(0)),
count_stops_aux(Count).
count_stops_aux(_) :-
stops(_, _, _),
retract(num_stops(C)),
C1 is C + 1,
assertz(num_stops(C1)),
fail.
count_stops_aux(Count) :-
retract(num_stops(Count)).
You could also probably do something similar with SWI Prolog's b_setval/2 and b_getval/2.
Here's a recursive solution that uses a list to check whether we've counted a particular fact already:
count_stops(Count) :-
count_stops_aux([], 0, Count).
count_stops_aux(L, Count, Total) :-
stops(A, B, C),
\+ member(stops(A,B,C), L),
C is Count + 1,
count_stops_aux([stops(A,B,C)|L], C, Total), !.
count_stops_aux(_, Total, Total).
Or similarly, but using length/2 as well:
count_stops(Count) :-
count_stops_aux([], Facts),
length(Facts, Count).
count_stops_aux(L, Facts) :-
stops(A, B, C),
\+ member(stops(A,B,C), L),
count_stops_aux([stops(A,B,C)|L], Facts), !.
count_stops_aux(Facts, Facts).
The first solution will count redundant facts (if an identical fact exists more than once), and assertz and retract are slow operations. The second and third solutions won't count redundant facts, but are really just clunky, verbose versions of Paulo's solution to avoid using findall. This is all why Prolog has predicates such as findall/3 and bagof/3.
Hey so this is my code so far. I am only a begginer in prolog but i need it for school
firstElement([_|_], [Elem1|List1], [Elem2|List2]):-
Elem1 =< Elem2, merge([Elem1] , List1, [Elem2|List2]);
merge([], [Elem2], List2).
merge([Head|Tail], [Elem1|List1], [Elem2|List2]):-
Elem1 =< Elem2,!, add(Elem1,[Head|Tail],[Head|Tail1]),
merge([Head|Tail1], List1, [Elem2|List2]);
add(Elem2,[Head|Tail],[Head|Tail1]),
merge([Head|Tail1], [Elem1|List1], List2).
merge([Head|Tail], [], [Elem2|List2]):-
add(Elem2,[Head|Tail],[Head|Tail1]).
merge([Head|Tail], [Elem1|List1], []):-
add(Elem1,[Head|Tail],[Head|Tail1]).
merge([Head|Tail], [], []).
add(X,[],[X]).
add(X,[Y|Tail],[Y|Tail1]):-
add(X,Tail,Tail1).
I found out that everytime it gets out of a merge it keeps forgetting the last number so it gets back to nothing in the end.
I think you’ve gotten very mixed up here with your code. A complete solution can be had without helpers and with only a few clauses.
First let us discuss the two base cases involving empty lists:
merge(X, [], X).
merge([], X, X).
You don’t quite have these, but I see some sort of recognition that you need to handle empty lists specially in your second and third clauses, but I think you got confused and overcomplicated them. There’s really three scenarios covered by these two clauses. The case where both lists are empty is a freebie covered by both of them, but since that case would work out to merge([], [], []), it’s covered. The big idea here is that if you exhaust either list, because they were sorted, what you have left in the other list is your result. Think about it.
This leaves the interesting case, which is one where we have some items in both lists. Essentially what you want to do is select the smaller of the two, and then recur on the entire other list and the remainder of the one you selected the smaller value from. This is one clause for that:
merge([L|Ls], [R|Rs], [L|Merged]) :-
L #< R,
merge(Ls, [R|Rs], Merged).
Here’s what you should note:
The “result” has L prepended to the recursively constructed remainder.
The recursive call to merge rebuilds the entire second list, using [R|Rs].
It should be possible to build the other clause by looking at this.
As an intermediate Prolog user, I would be naturally a bit suspicious of using two clauses to do this work, because it’s going to create unnecessary choice points. As a beginner, you will be tempted to erase those choice points using cuts, which will go badly for you. A more intermediate approach would be to subsume both of the necessary clauses into one using a conditional operator:
merge([L|Ls], [R|Rs], [N|Ns]) :-
( L #< R ->
N = L, merge(Ls, [R|Rs], Ns)
; —- other case goes here
).
An expert would probably build it using if_/3 instead:
#<(X,Y,true) :- X #< Y.
#<(X,Y,false) :- X #>= Y.
merge([L|Ls], [R|Rs], [N|Ns]) :-
if_(#<(L,R),
(N = L, merge(Ls, [R|Rs], Ns)),
( -- other case here )).
Anyway, I hope this helps illustrate the situation.
I have a predicate to check if the element is member of list and looks the following:
member(X,[X|_]).
member(X,[_|T]) :- member(X,T).
When I called: ?- member(1,[2,3,1,4])
I get: true.
And now I have to use it to write predicate which will remove all non unique elements from list of lists like the following:
remove([[a,m,t,a],[k,a,w],[i,k,b,b],[z,m,m,c]],X).
X = [[t],[w],[i,b,b],[z,c]]
How can I do that?
Using library(reif) for
SICStus|SWI:
lists_uniques(Xss, Yss) :-
maplist(tfilter(in_unique_t(Xss)), Xss, Yss).
in_unique_t(Xss, E, T) :-
tfilter(memberd_t(E), Xss, [_|Rs]),
=(Rs, [], T).
Remark that while there is no restriction how to name a predicate, a non-relational, imperative name often hides the pure relation behind. remove is a real imperative, but we only want a relation. A relation between a list of lists and a list of lists with only unique elements.
An example usage:
?- lists_uniques([[X,b],[b]], [[X],[]]).
dif(X, b).
So in this case we have left X an uninstantiated variable. Therefore, Prolog computes the most general answer possible, figuring out what X has to look like.
(Note that the answer you have accepted incorrectly fails in this case)
Going by your example and #false's comment, the actual problem seems to be something like removing elements from each sublist that occur in any other sublist. My difficulty conceptualizing this into words has led me to build what I consider a pretty messy and gross piece of code.
So first I want a little helper predicate to sort of move member/2 up to lists of sublists.
in_sublist(X, [Sublist|_]) :- member(X, Sublist).
in_sublist(X, [_|Sublists]) :- in_sublist(X, Sublists).
This is no great piece of work, and in truth I feel like it should be inlined somehow because I just can't see myself ever wanting to use this on its own.
Now, my initial solution wasn't correct and looked like this:
remove([Sub1|Subs], [Res1|Result]) :-
findall(X, (member(X, Sub1), \+ in_sublist(X, Subs)), Res1),
remove(Subs, Result).
remove([], []).
You can see the sort of theme I'm going for here though: let's use findall/3 to enumerate the elements of the sublist in here and then we can filter out the ones that occur in the other lists. This doesn't quite do the trick, the output looks like this.
?- remove([[a,m,t,a],[k,a,w],[i,k,b,b],[z,m,m,c]], R).
R = [[t], [a, w], [i, k, b, b], [z, m, m, c]].
So, it starts off looking OK with [t] but then loses the plot with [a,w] because there is not visibility into the input [a,m,t,a] when we get to the first recursive call. There are several ways we could deal with it; a clever one would probably be to form a sort of zipper, where we have the preceding elements of the list and the succeeding ones together. Another approach would be to remove the elements in this list from all the succeeding lists before the recursive call. I went for a "simpler" solution which is messier and harder to read but took less time. I would strongly recommend you investigate the other options for readability.
remove(In, Out) :- remove(In, Out, []).
remove([Sub1|Subs], [Res1|Result], Seen) :-
findall(X, (member(X, Sub1),
\+ member(X, Seen),
\+ in_sublist(X, Subs)), Res1),
append(Sub1, Seen, Seen1),
remove(Subs, Result, Seen1).
remove([], [], _).
So basically now I'm keeping a "seen" list. Right before the recursive call, I stitch together the stuff I've seen so far and the elements of this list. This is not particularly efficient, but it seems to get the job done:
?- remove([[a,m,t,a],[k,a,w],[i,k,b,b],[z,m,m,c]], R).
R = [[t], [w], [i, b, b], [z, c]].
This strikes me as a pretty nasty problem. I'm surprised how nasty it is, honestly. I'm hoping someone else can come along and find a better solution that reads better.
Another thing to investigate would be DCGs, which can be helpful for doing these kinds of list processing tasks.
Is there a way one can show all solutions and/or find how many there are in SICSTus prolog? For instance, the code below maybe used to solve the map colouring problem.
:- use_module(library(clpfd)).
solve_AUSTRALIA(WA,NT,Q,SA,NSW,V):-
domain([WA,NT,Q,SA,NSW,V], 1, 4),%colours represented by integers from 1 to 4
WA #\= NT,
WA #\= SA,
NT #\= SA,
NT #\= Q,
SA #\= Q,
SA #\= NSW,
SA #\= V,
Q #\= NSW,
NSW #\= V,
labeling([],[WA,NT,Q,SA,NSW,V]).
At the moment,I am typing ; every time to see further solutions till Prolog says no. Is there a way I can tell prolog to show all solutions at once, or better, a way I can find how many there. Like prolog tells me there are five solutions to the problem.
The following is for counting the number of answers. When you ask a query or execute a predicate, what you get back from Prolog are answers. Sometimes these answers are solutions, may contain more than one solution, infinitely many solutions, and sometimes even no solution at all.
The simplest way to go is to say findall(t, Goal_0, Ts), length(Ts, N). The only disadvantage is that this requires space proportional to the number of answers counted.
If you want to go one step further you need some kind of counter. Currently in SICStus 4.3.3 you can do this like so:
:- meta_predicate count_answers(0, ?).
:- meta_predicate count_answers1(0, +, ?). % internal
:- use_module(library(types),[must_be/4]).
:- use_module(library(structs),
[new/2,
dispose/1,
get_contents/3,
put_contents/3]).
count_answers(G_0, N) :-
( nonvar(N)
-> must_be(N, integer, count_answers(G_0, N), 2)
; true
),
new(unsigned_64, Ref),
call_cleanup(count_answers1(G_0, Ref, N), dispose(Ref) ).
count_answers1(G_0, Ref, N) :-
( call(G_0),
get_contents(Ref, contents, N0),
N1 is N0+1,
put_contents(Ref, contents, N1),
fail
; get_contents(Ref, contents, N)
).
See this answer how counters can be implemented in other systems. Example use:
| ?- count_answers(member(_,"abcde"),Ans).
Ans = 5 ? ;
no
Is there a way I can tell Prolog to show all solutions at once
This part of your question is related to the prolog-toplevel. In Prolog IV all answers (not necessarily solutions) were shown by default. The top level loop of a couple of Prolog systems permits to enter a to see all answers at once:
GNU-Prolog (originator)
Trealla-Prolog
Scryer-Prolog
How to implement rule1 that succeeds iff rule2 returns two or more results?
rule1(X) :-
rule2(X, _).
How can I count the results, and then set a minimum for when to succeed?
How can I count the results, and then set a minimum for when it's true?
It is not clear what you mean by results. So I will make some guesses. A result might be:
A solution. For example, the goal member(X,[1,2,1]) has two solutions. Not three. In this case consider using either setof/3 or a similar predicate. In any case, you should first understand setof/3 before addressing the problem you have.
An answer. The goal member(X,[1,2,1]) has three answers. The goal member(X,[Y,Z]) has two answers, but infinitely many solutions.
So if you want to ensure that there are at least a certain number of answers, define:
at_least(Goal, N) :-
\+ \+ call_nth(Goal, N).
with call_nth/2 defined in another SO-answer.
Note that the other SO-answers are not correct: They either do not terminate or produce unexpected instantiations.
you can use library(aggregate) to count solutions
:- use_module(library(aggregate)).
% it's useful to declare this for modularization
:- meta_predicate at_least(0, +).
at_least(Predicate, Minimum) :-
aggregate_all(count, Predicate, N),
N >= Minimum.
example:
?- at_least(member(_,[1,2,3]),3).
true.
?- at_least(member(_,[1,2,3]),4).
false.
edit here is a more efficient way, using SWI-Prolog facilities for global variables
at_least(P, N) :-
nb_setval(at_least, 0),
P,
nb_getval(at_least, C),
S is C + 1,
( S >= N, ! ; nb_setval(at_least, S), fail ).
with this definition, P is called just N times. (I introduce a service predicate m/2 that displays what it returns)
m(X, L) :- member(X, L), writeln(x:X).
?- at_least(m(X,[1,2,3]),2).
x:1
x:2
X = 2.
edit accounting for #false comment, I tried
?- call_nth(m(X,[1,2,3]),2).
x:1
x:2
X = 2 ;
x:3
false.
with call_nth from here.
From the practical point of view, I think nb_setval (vs nb_setarg) suffers the usual tradeoffs between global and local variables. I.e. for some task could be handly to know what's the limit hit to accept the condition. If this is not required, nb_setarg it's more clean.
Bottom line: the better way to do would clearly be using call_nth, with the 'trick' of double negation solving the undue variable instantiation.