Sliding tile puzzle with varying tile size using logic programming - prolog

So I am trying to solve this Booth arrangement problem given here. It is basically a sliding tile puzzle where one (booth)tile has to reach a target spot and in the end all other (booths)tiles should be in their original location. Each tile/booth has a dimension and following are the input fact and relation descriptions:
One fact of the form room(W,H), which specifies the width W and
height H of the room (3 ≤ W, H ≤ 20).
One fact booths(B), which
specifies the number of booths (1 ≤ B ≤ 20).
A relation that consists
of facts of the form dimension(B, W, H), which specifies the width W
and height H of booth B.
A relation consisting of facts of the form
position(B, W, H), specifying the initial position (W, H) of booth B.
One fact target(B, W, H), specifying the destination (W, H) of the
target booth B.
An additional fact horizon(H) gives an upper bound on
the number of moves to be performed.
The program is supposed to read input facts from a file but I am just trying to do the solving so I have just copy pasted one possible input for now, and I have written some basic clauses:
room(3, 3).
booths(3).
dimension(1, 2, 1).
dimension(2, 2, 1).
dimension(3, 1, 1).
position(1, 0, 1).
position(2, 1, 2).
position(3, 0, 0).
target(3, 0, 2).
horizon(10).
xlim(X) :- room(X,_).
ylim(X) :- room(_,X).
sum(X,Y,Z) :- Z is X+Y .
do(position(B,X,Y),movedown,position(B,X,Z)) :- Y > 0 , sum(Y,-1,Z) .
do(position(B,X,Y),moveup,position(B,X,Z)) :- ylim(L), Y < L , sum(Y,1,Z) .
do(position(B,X,Y),moveleft,position(B,Z,Y)) :- X > 0 , sum(X,-1,Z) .
do(position(B,X,Y),moveright,position(B,Z,Y)) :- xlim(L), X < L, sum(X,1,Z) .
noverlap(B1,B2) :-
position(B1,X1,Y1),
position(B2,X2,Y2),
ends(Xe1,Ye1,B1),
ends(Xe2,Ye2,B2),
( Xe1 < X2 ;
Xe2 < X1 ;
Ye1 < Y2 ;
Ye2 < Y1 ).
ends(Xe,Ye,B) :-
dimension(B,W,H),
position(B,X,Y),
Xe is X+W-1,
Ye is Y+H-1.
between(X,Y,Z) :-
X > Y ,
X < Z .
validMove(M,B) :- do(position(B,X,Y),M,position(B,Xn,Yn)) .
I am new to Prolog and I am stuck on how to go from here, I have the no_overlap rule so I can test if a move is valid or not but I am not sure how with the current clauses that I have. My current clauses for moves do/3 probably needs some modification. Any pointers?.

You need to express the task in terms of relations between states of the puzzle. Your current clauses determine the validity of a single move, and can also generate possible moves.
However, that is not sufficient: You need to express more than just a single move and its effect on a single tile. You need to encode, in some way, the state of the whole puzzle, and also encode how a single move changes the state of the whole task.
For a start, I recommend you think about a relation like:
world0_move_world(W0, M, W) :- ...
and express the relation between a given "world" W0, a possible move M, and the resulting world W. This relation should be so general as to generate, on backtracking, each move M that is possible in W0. Ideally, it should even work if W0 is a free variable, and for this you may find clpfd useful: Constraints allow you to express arithmetic relations in a much more general way than you are currently using.
Once you have such a relation, the whole task is to find a sequence Ms of moves such that any initial world W0 is transformed to a desired state W.
Assuming you have implemented world0_move_world/3 as a building block, you can easily lift this to lists of moves as follows (using dcg):
moves(W0) --> { desired_world(W0) }.
moves(W0) --> [M], { world0_move_world(W0, M, W) }, moves(W).
You can then use iterative deepening to find a shortest sequence of moves that solves the puzzle:
?- length(Ms, _), initial_world(W0), phrase(moves(W0), Ms).

Related

Fold over a partial list

This is a question provoked by an already deleted answer to this question. The issue could be summarized as follows:
Is it possible to fold over a list, with the tail of the list generated while folding?
Here is what I mean. Say I want to calculate the factorial (this is a silly example but it is just for demonstration), and decide to do it like this:
fac_a(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; numlist(2, N, [H|T]),
foldl(multiplication, T, H, F)
).
multiplication(X, Y, Z) :-
Z is Y * X.
Here, I need to generate the list that I give to foldl. However, I could do the same in constant memory (without generating the list and without using foldl):
fac_b(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; fac_b_1(2, N, 2, F)
).
fac_b_1(X, N, Acc, F) :-
( X < N
-> succ(X, X1),
Acc1 is X1 * Acc,
fac_b_1(X1, N, Acc1, F)
; Acc = F
).
The point here is that unlike the solution that uses foldl, this uses constant memory: no need for generating a list with all values!
Calculating a factorial is not the best example, but it is easier to follow for the stupidity that comes next.
Let's say that I am really afraid of loops (and recursion), and insist on calculating the factorial using a fold. I still would need a list, though. So here is what I might try:
fac_c(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; foldl(fac_foldl(N), [2|Back], 2-Back, F-[])
).
fac_foldl(N, X, Acc-Back, F-Rest) :-
( X < N
-> succ(X, X1),
F is Acc * X1,
Back = [X1|Rest]
; Acc = F,
Back = []
).
To my surprise, this works as intended. I can "seed" the fold with an initial value at the head of a partial list, and keep on adding the next element as I consume the current head. The definition of fac_foldl/4 is almost identical to the definition of fac_b_1/4 above: the only difference is that the state is maintained differently. My assumption here is that this should use constant memory: is that assumption wrong?
I know this is silly, but it could however be useful for folding over a list that cannot be known when the fold starts. In the original question we had to find a connected region, given a list of x-y coordinates. It is not enough to fold over the list of x-y coordinates once (you can however do it in two passes; note that there is at least one better way to do it, referenced in the same Wikipedia article, but this also uses multiple passes; altogether, the multiple-pass algorithms assume constant-time access to neighboring pixels!).
My own solution to the original "regions" question looks something like this:
set_region_rest([A|As], Region, Rest) :-
sort([A|As], [B|Bs]),
open_set_closed_rest([B], Bs, Region0, Rest),
sort(Region0, Region).
open_set_closed_rest([], Rest, [], Rest).
open_set_closed_rest([X-Y|As], Set, [X-Y|Closed0], Rest) :-
X0 is X-1, X1 is X + 1,
Y0 is Y-1, Y1 is Y + 1,
ord_intersection([X0-Y,X-Y0,X-Y1,X1-Y], Set, New, Set0),
append(New, As, Open),
open_set_closed_rest(Open, Set0, Closed0, Rest).
Using the same "technique" as above, we can twist this into a fold:
set_region_rest_foldl([A|As], Region, Rest) :-
sort([A|As], [B|Bs]),
foldl(region_foldl, [B|Back],
closed_rest(Region0, Bs)-Back,
closed_rest([], Rest)-[]),
!,
sort(Region0, Region).
region_foldl(X-Y,
closed_rest([X-Y|Closed0], Set)-Back,
closed_rest(Closed0, Set0)-Back0) :-
X0 is X-1, X1 is X + 1,
Y0 is Y-1, Y1 is Y + 1,
ord_intersection([X0-Y,X-Y0,X-Y1,X1-Y], Set, New, Set0),
append(New, Back0, Back).
This also "works". The fold leaves behind a choice point, because I haven't articulated the end condition as in fac_foldl/4 above, so I need a cut right after it (ugly).
The Questions
Is there a clean way of closing the list and removing the cut? In the factorial example, we know when to stop because we have additional information; however, in the second example, how do we notice that the back of the list should be the empty list?
Is there a hidden problem I am missing?
This looks like its somehow similar to the Implicit State with DCGs, but I have to admit I never quite got how that works; are these connected?
You are touching on several extremely interesting aspects of Prolog, each well worth several separate questions on its own. I will provide a high-level answer to your actual questions, and hope that you post follow-up questions on the points that are most interesting to you.
First, I will trim down the fragment to its essence:
essence(N) :-
foldl(essence_(N), [2|Back], Back, _).
essence_(N, X0, Back, Rest) :-
( X0 #< N ->
X1 #= X0 + 1,
Back = [X1|Rest]
; Back = []
).
Note that this prevents the creation of extremely large integers, so that we can really study the memory behaviour of this pattern.
To your first question: Yes, this runs in O(1) space (assuming constant space for arising integers).
Why? Because although you continuously create lists in Back = [X1|Rest], these lists can all be readily garbage collected because you are not referencing them anywhere.
To test memory aspects of your program, consider for example the following query, and limit the global stack of your Prolog system so that you can quickly detect growing memory by running out of (global) stack:
?- length(_, E),
N #= 2^E,
portray_clause(N),
essence(N),
false.
This yields:
1.
2.
...
8388608.
16777216.
etc.
It would be completely different if you referenced the list somewhere. For example:
essence(N) :-
foldl(essence_(N), [2|Back], Back, _),
Back = [].
With this very small change, the above query yields:
?- length(_, E),
N #= 2^E,
portray_clause(N),
essence(N),
false.
1.
2.
...
1048576.
ERROR: Out of global stack
Thus, whether a term is referenced somewhere can significantly influence the memory requirements of your program. This sounds quite frightening, but really is hardly an issue in practice: You either need the term, in which case you need to represent it in memory anyway, or you don't need the term, in which case it is simply no longer referenced in your program and becomes amenable to garbage collection. In fact, the amazing thing is rather that GC works so well in Prolog also for quite complex programs that not much needs to be said about it in many situations.
On to your second question: Clearly, using (->)/2 is almost always highly problematic in that it limits you to a particular direction of use, destroying the generality we expect from logical relations.
There are several solutions for this. If your CLP(FD) system supports zcompare/3 or a similar feature, you can write essence_/3 as follows:
essence_(N, X0, Back, Rest) :-
zcompare(C, X0, N),
closing(C, X0, Back, Rest).
closing(<, X0, [X1|Rest], Rest) :- X1 #= X0 + 1.
closing(=, _, [], _).
Another very nice meta-predicate called if_/3 was recently introduced in Indexing dif/2 by Ulrich Neumerkel and Stefan Kral. I leave implementing this with if_/3 as a very worthwhile and instructive exercise. Discussing this is well worth its own question!
On to the third question: How do states with DCGs relate to this? DCG notation is definitely useful if you want to pass around a global state to several predicates, where only a few of them need to access or modify the state, and most of them simply pass the state through. This is completely analogous to monads in Haskell.
The "normal" Prolog solution would be to extend each predicate with 2 arguments to describe the relation between the state before the call of the predicate, and the state after it. DCG notation lets you avoid this hassle.
Importantly, using DCG notation, you can copy imperative algorithms almost verbatim to Prolog, without the hassle of introducing many auxiliary arguments, even if you need global states. As an example for this, consider a fragment of Tarjan's strongly connected components algorithm in imperative terms:
function strongconnect(v)
// Set the depth index for v to the smallest unused index
v.index := index
v.lowlink := index
index := index + 1
S.push(v)
This clearly makes use of a global stack and index, which ordinarily would become new arguments that you need to pass around in all your predicates. Not so with DCG notation! For the moment, assume that the global entities are simply easily accessible, and so you can code the whole fragment in Prolog as:
scc_(V) -->
vindex_is_index(V),
vlowlink_is_index(V),
index_plus_one,
s_push(V),
This is a very good candidate for its own question, so consider this a teaser.
At last, I have a general remark: In my view, we are only at the beginning of finding a series of very powerful and general meta-predicates, and the solution space is still largely unexplored. call/N, maplist/[3,4], foldl/4 and other meta-predicates are definitely a good start. if_/3 has the potential to combine good performance with the generality we expect from Prolog predicates.
If your Prolog implementation supports freeze/2 or similar predicate (e.g. Swi-Prolog), then you can use following approach:
fac_list(L, N, Max) :-
(N >= Max, L = [Max], !)
;
freeze(L, (
L = [N|Rest],
N2 is N + 1,
fac_list(Rest, N2, Max)
)).
multiplication(X, Y, Z) :-
Z is Y * X.
factorial(N, Factorial) :-
fac_list(L, 1, N),
foldl(multiplication, L, 1, Factorial).
Example above first defines a predicate (fac_list) which creates a "lazy" list of increasing integer values starting from N up to maximum value (Max), where next list element is generated only after previous one was "accessed" (more on that below). Then, factorial just folds multiplication over lazy list, resulting in constant memory usage.
The key to understanding how this example works is remembering that Prolog lists are, in fact, just terms of arity 2 with name '.' (actually, in Swi-Prolog 7 the name was changed, but this is not important for this discussion), where first element represents list item and the second element represents tail (or terminating element - empty list, []). For example. [1, 2, 3] can be represented as:
.(1, .(2, .(3, [])))
Then, freeze is defined as follows:
freeze(+Var, :Goal)
Delay the execution of Goal until Var is bound
This means if we call:
freeze(L, L=[1|Tail]), L = [A|Rest].
then following steps will happen:
freeze(L, L=[1|Tail]) is called
Prolog "remembers" that when L will be unified with "anything", it needs to call L=[1|Tail]
L = [A|Rest] is called
Prolog unifies L with .(A, Rest)
This unification triggers execution of L=[1|Tail]
This, obviously, unifies L, which at this point is bound to .(A, Rest), with .(1, Tail)
As a result, A gets unified with 1.
We can extend this example as follows:
freeze(L1, L1=[1|L2]),
freeze(L2, L2=[2|L3]),
freeze(L3, L3=[3]),
L1 = [A|R2], % L1=[1|L2] is called at this point
R2 = [B|R3], % L2=[2|L3] is called at this point
R3 = [C]. % L3=[3] is called at this point
This works exactly like the previous example, except that it gradually generates 3 elements, instead of 1.
As per Boris's request, the second example implemented using freeze. Honestly, I'm not quite sure whether this answers the question, as the code (and, IMO, the problem) is rather contrived, but here it is. At least I hope this will give other people the idea what freeze might be useful for. For simplicity, I am using 1D problem instead of 2D, but changing the code to use 2 coordinates should be rather trivial.
The general idea is to have (1) function that generates new Open/Closed/Rest/etc. state based on previous one, (2) "infinite" list generator which can be told to "stop" generating new elements from the "outside", and (3) fold_step function which folds over "infinite" list, generating new state on each list item and, if that state is considered to be the last one, tells generator to halt.
It is worth to note that list's elements are used for no other reason but to inform generator to stop. All calculation state is stored inside accumulator.
Boris, please clarify whether this gives a solution to your problem. More precisely, what kind of data you were trying to pass to fold step handler (Item, Accumulator, Next Accumulator)?
adjacent(X, Y) :-
succ(X, Y) ;
succ(Y, X).
state_seq(State, L) :-
(State == halt -> L = [], !)
;
freeze(L, (
L = [H|T],
freeze(H, state_seq(H, T))
)).
fold_step(Item, Acc, NewAcc) :-
next_state(Acc, NewAcc),
NewAcc = _:_:_:NewRest,
(var(NewRest) ->
Item = next ;
Item = halt
).
next_state(Open:Set:Region:_Rest, NewOpen:NewSet:NewRegion:NewRest) :-
Open = [],
NewOpen = Open,
NewSet = Set,
NewRegion = Region,
NewRest = Set.
next_state(Open:Set:Region:Rest, NewOpen:NewSet:NewRegion:NewRest) :-
Open = [H|T],
partition(adjacent(H), Set, Adjacent, NotAdjacent),
append(Adjacent, T, NewOpen),
NewSet = NotAdjacent,
NewRegion = [H|Region],
NewRest = Rest.
set_region_rest(Ns, Region, Rest) :-
Ns = [H|T],
state_seq(next, L),
foldl(fold_step, L, [H]:T:[]:_, _:_:Region:Rest).
One fine improvement to the code above would be making fold_step a higher order function, passing it next_state as the first argument.

How to maximize the goal in prolog?

I am trying to solve the knapsack problem in prolog. Following is my implementation.
% 'ks' is compound term which has 4 argumets
% 1 - List of items to be chosen from.
% 2 - Maximum weight a knapsack can carry.
% 3 - Selected items which sum of weights is less than or equal to knapsack capacity.
% 4 - The gain after choosing the selected item.
% base conditions where input list contains only one items and
% it is either selected or excluded.
ks([item(W1, V1)], W, [item(W1, V1)], V1):- W1 =< W.
ks([item(W1, _)], W, [], 0):- W1 > W.
% An item from the input list is chosen in the knapsack.
% In that case, we recurse with smaller list with reduced weight constraint.
ks(ItemList, MaxWeight, SelectItems, Gain) :-
append(Prefix, [item(W1, V1)|Suffix], ItemList),
append(Prefix, Suffix, RemList),
NewWeight is MaxWeight - W1,
W1 =< MaxWeight,
append([item(W1, V1)], SelectItems1, SelectItems),
ks(RemList, NewWeight, SelectItems1, Gain1),
Gain is V1 + Gain1.
% An item from the input list is not chosen in the knapsack.
% In that case, we recurse with smaller list but with the same weight constraint.
ks(ItemList, MaxWeight, SelectItems, Gain) :-
append([P1|Prefix], [item(W1, V1)|Suffix], ItemList),
append([P1|Prefix], Suffix, RemList),
not(member(item(W1, V1), SelectItems)),
ks(RemList, MaxWeight, SelectItems, Gain).
The input to the program will be list of items as below. in term item(W, V) W is weight of the item while V is value of the item. Goal to maximize the value for the given weight constraint.
ks([item(2,3), item(3,4), item(4,5), item(5,8), item(9,10)], 20, List, Gain).
List = [item(2, 3), item(3, 4), item(4, 5), item(5, 8)],
Gain = 20 ;
While I am able to generate all the combinations of items with above program, I am not able to code to find out the maximum gain only.
Could any one please point me the right direction?
Thanks.
I think that to find reusable abstractions it's an important point of studying programming. If we have a subset_set/2 that yields on backtracking all subsets, ks/4 becomes really simple:
subset_set([], _).
subset_set([H|T], Set) :-
append(_, [H|Rest], Set),
subset_set(T, Rest).
ks(Set, Limit, Choice, Gain) :-
subset_set(Choice, Set),
aggregate((sum(W), sum(G)), member(item(W, G), Choice), (TotWeight, Gain)),
TotWeight =< Limit.
and then
ks_max(Items, Limit, Sel, WMax) :-
aggregate(max(W,I), ks(Items,Limit,I,W), max(WMax,Sel)).
despite its simplicity, subset_set/2 is not really easy to code, and library available alternatives (subset/2, ord_subset/2) don't enumerate, but only check for the relation.
There are at least two things you can do, depending on how you want to approach this.
You could simply collect all solutions and find the maximum. Something along the lines of:
?- Items = [item(2,3), item(3,4), item(4,5), item(5,8), item(9,10)],
findall(Gain-List, ks(Items, 20, List, Gain), Solutions),
sort(Solutions, Sorted),
reverse(Sorted, [MaxGain-MaxList|_]).
% ...
MaxGain = 26,
MaxList = [item(9, 10), item(5, 8), item(4, 5), item(2, 3)].
So you find all solutions, sort them by Gain, and take the last. This is just one way to do it: if you don't mind collecting all solutions, it is up to you how you want to pick out the solution you need from the list. You might also want to find all maximum solutions: see this question and answers for ideas how to do that.
The cleaner approach would be to use constraints. As the comment to your questions points out, it is not very clear what you are actually doing, but the way to go would be to use a library like CLP(FD). With it, you could simply tell labeling/2 to look for the maximum Gain first (once you have expressed your problem in terms of constraints).
greedy Approximation algorithm :
pw((P,W),Res) :- PW is P/W, Res=(PW,P,W).
pws(Ps_Ws,PWs) :- maplist(pw,Ps_Ws,PWs).
sort_desc(List,Desc_list) :-
sort(List,Slist),
reverse(Slist,Desc_list).
ransack_([],_,_,[]).
ransack_([(_,P,W)|PWs],Const,Sum,Res) :-
Sum1 is W+Sum,
Sum1 < Const ->
Res=[(P,W)|Res1],
ransack_(PWs,Const,Sum1,Res1)
;ransack_(PWs,Const,Sum,Res).
% ransack(+[(P,W)|..],+W,,Res)
ransack(L_PWs,W,Res) :-
pws(L_PWs,Aux),
sort_desc(Aux,PWs),
ransack_(PWs,W,0,Res).
Test
item(W, V)-->(V,W)
| ?- ransack([(3,2),(4,3),(5,4),(8,5),(10,9)],20,Res).
Res = [(8,5),(3,2),(4,3),(5,4)] ? ;
no

Trouble displaying constraint values - SICStus clpfd

I am trying to solve a problem for a class that consists of this:
Fill the white cells on the each barrels side with different digits from 1 to 6. Digits cannot
repeat in every horizontal and vertical directions. Each number on the barrels top must
be equal to the sum or product of the four different digits in the barrel. All top numbers
are different and less than 91.
I can achieve the results fine, but I need to display the barrel's results and when I run my base case it shows this:
[_24087,18,60,17,_24343,72,_24471,_24535,14]
[1,2,3,4,5,6,3,4,5,6,1,2,2,5,1,3,6,4,4,6,2,5,3,1,5,1,6,2,4,3,6,3,4,1,2,5]
Result achieved in 0.015 sec.
Resumptions: 6197
Entailments: 1306
Prunings: 3520
Backtracks: 62
Constraints created: 107
The 1st list is the barrels and the 2nd list the Matrix calculated with labeling.
In order to calculate the barrels I use this on a rule:
getlist(Matrix,CounterX,CounterY,InnerSize,Value), % gets the barrel sublist
all_distinct(Value),
sum(Value, #=, SSet), % sum
prod(Value, VSet), % product
Set #= SSet #\/ Set #= VSet, % chooses one
Set #=< MaxValue,
insertinto(Set, List, NewList), % inserts into the barrel list
Since SICStus doesn't have a product calculation rule, I created this one:
prod([H|T], R) :-
prod(T, H, R).
prod([], R, R).
prod([H|T], V, R) :-
NV #= H * V,
prod(T, NV, R).
I don't understand where the problem actually lies.
In my prod rule -> It seems to unify correctly but seems not to when 1 is in the sublist.
How I unify the sum or prod -> Maybe that barrel can be a sum or prod and can't unify with Set correctly.

How to add polynoms in Prolog?

I have the following task:
Write a method that will add two polynoms. I.e 0+2*x^3 and 0+1*x^3+2*x^4 will give 0+3*x^3+2*x^4.
I also wrote the following code:
add_poly(+A1*x^B1+P1,+A2*x^B2+P2,+A3*x^B3+P3):-
(
B1=B2,
B3 = B2,
A3 is A1+A2,
add_poly(P1,P2,P3)
;
B1<B2,
B3=B1,
A3=A1,
add_poly(P1,+A2*x^B2+P2,P3)
;
B1>B2,
B3=B2,
A3=A2,
add_poly(+A1*x^B1+P1,P2,P3)
).
add_poly(X+P1,Y+P2,Z+P3):-
Z is X+Y,
add_poly(P1,P2,P3).
My problem is that I don't know how to stop. I would like to stop when one the arguments is null and than to append the second argument to the third one. But how can I check that they are null?
Thanks.
Several remarks:
Try to avoid disjunctions (;)/2 in the beginning. They need special indentation to be readable. And they make reading a single rule more complex — think of all the extra (=)/2 goals you have to write and keep track of.
Then, I am not sure what you can assume about your polynomials. Can you assume they are written in canonical form?
And for your program: Consider the head of your first rule:
add_poly(+A1*x^B1+P1,+A2*x^B2+P2,+A3*x^B3+P3):-
I will generalize away some of the arguments:
add_poly(+A1*x^B1+P1,_,_):-
and some of the subterms:
add_poly(+_+_,_,_):-
This corresponds to:
add_poly(+(+(_),_),_,_) :-
Not sure you like this.
So this rule applies only to terms starting with a prefix + followed by an infix +. At least your sample data did not contain a prefix +.
Also, please remark that the +-operator is left associative. That means that 1+2+3+4 associates to the left:
?- write_canonical(1+2+3+4).
+(+(+(1,2),3),4)
So if you have a term 0+3*x^3+2*x^4 the first thing you "see" is _+2*x^4. The terms on the left are nested deeper.
For your actual question (how to stop) - you will have to test explicitly that the leftmost subterm is an integer, use integer/1 - or maybe a term (*)/2 (that depends on your assumptions).
I assume that polynomials you are speaking of are in 1 variable and with integer exponents.
Here a procedure working on normal polynomial form: a polynomial can be represented as a list (a sum) of factors, where the (integer) exponent is implicitly represented by the position.
:- [library(clpfd)].
add_poly(P1, P2, Sum) :-
normalize(P1, N1),
normalize(P2, N2),
append(N1, N2, Nt),
aggregate_all(max(L), (member(M, Nt), length(M, L)), LMax),
maplist(rpad(LMax), Nt, Nn),
clpfd:transpose(Nn, Tn),
maplist(sumlist, Tn, NSum),
denormalize(NSum, Sum).
rpad(LMax, List, ListN) :-
length(List, L),
D is LMax - L,
zeros(D, Z),
append(List, Z, ListN).
% the hardest part is of course normalization: here a draft
normalize(Ts + T, [N|Ns]) :-
normalize_fact(T, N),
normalize(Ts, Ns).
normalize(T, [N]) :-
normalize_fact(T, N).
% build a list with 0s left before position E
normalize_fact(T, Normal) :-
fact_exp(T, F, E),
zeros(E, Zeros),
nth0(E, Normal, F, Zeros).
zeros(E, Zeros) :-
length(Zeros, E),
maplist(copy_term(0), Zeros).
fact_exp(F * x ^ E, F, E).
fact_exp(x ^ E, 1, E).
fact_exp(F * x, F, 1).
fact_exp(F, F, 0).
% TBD...
denormalize(NSum, NSum).
test:
?- add_poly(0+2*x^3, 0+1*x^3+2*x^4, P).
P = [0, 0, 0, 3, 2]
the answer is still in normal form, denormalize/2 should be written...

Solve Cannibals/Missionaries using breadth-first search (BFS) in Prolog?

I am working on solving the classic Missionaries(M) and Cannibals(C) problem, the start state is 3 M and 3 C on the left bank and the goal state is 3M, 3C on the right bank. I have complete the basic function in my program and I need to implemet the search-strategy such as BFS and DFS.
Basically my code is learn from the Internet. So far I can successfuly run the program with DFS method, but I try to run with BFS it always return false. This is my very first SWI-Prolog program, I can not find where is the problem of my code.
Here is part of my code, hope you can help me find the problem of it
solve2 :-
bfs([[[3,3,left]]],[0,0,right],[[3,3,left]],Solution),
printSolution(Solution).
bfs([[[A,B,C]]],[A,B,C],_,[]).
bfs([[[A,B,C]|Visisted]|RestPaths],[D,E,F],Visisted,Moves) :-
findall([[I,J,K],[A,B,C]|Visited]),
(
move([A,B,C],[I,J,K],Description),
safe([I,J,K]),
not(member([I,J,K],Visited)
),
NewPaths
),
append(RestPaths,NewPaths,CurrentPaths),
bfs(CurrentPaths,[D,E,F],[[I,J,K]|Visisted],MoreMoves),
Moves = [ [[A,B,C],[I,J,K],Description] | MoreMoves ].
move([A,B,left],[A1,B,right],'One missionary cross river') :-
A > 0, A1 is A - 1.
% Go this state if left M > 0. New left M is M-1
.
.
.
.
.
safe([A,B,_]) :-
(B =< A ; A = 0),
A1 is 3-A, B1 is 3-B,
(B1 =< A1; A1 =0).
I use findall to find all possible path before go to next level. Only the one pass the safe() will be consider as possible next state. The state will not use if it already exist. Since my program can run with DFS so I think there is nothing wrong with move() and safe() predicate. My BFS predicate is changing base on my DFS code, but its not work.
There is a very simple way to turn a depth-first search program into a breadth-first one, provided the depth-first search is directly mapped to Prolog's search. This technique is called iterative deepening.
Simply add an additional argument to ensure that the search will only go N steps deep.
So a dfs-version:
dfs(State) :-
final(State).
dfs(State1) :-
state_transition(State1, State2),
dfs(State2).
Is transformed into a bfs by adding an argument for the depth. E.g. by using successor-arithmetics:
bfs(State, _) :-
final(State).
bfs(State1, s(X)) :-
state_transition(State1, State2),
bfs(State2, X).
A goal bfs(State,s(s(s(0)))) will now find all derivations requiring 3 or less steps. You still can perform dfs! Simply use bfs(State,X).
To find all derivations use natural_number(X), bfs(State,X).
Often it is useful to use a list instead of the s(X)-number. This list might contain all intermediary states or the particular transitions performed.
You might hesitate to use this technique, because it seems to recompute a lot of intermediary states ("repeatedly expanded states"). After all, first it searches all paths with one step, then, at most two steps, then, at most three steps... However, if your problem is a search problem, the branching factor here hidden within state_transition/2 will mitigate that overhead. To see this, consider a branching factor of 2: We only will have an overhead of a factor of two! Often, there are easy ways to regain that factor of two: E.g., by speeding up state_transition/2 or final/1.
But the biggest advantage is that it does not consume a lot of space - in contrast to naive dfs.
The Logtalk distribution includes an example, "searching", which implements a framework for state space searching:
https://github.com/LogtalkDotOrg/logtalk3/tree/master/examples/searching
The "classical" problems are included (farmer, missionaries and cannibals, puzzle 8, bridge, water jugs, etc). Some of the search algorithms are adapted (with permission) from Ivan Bratko's book "Prolog programming for artificial intelligence". The example also includes a performance monitor that can give you some basic stats on the performance of a search method (e.g. branching factors and number of state transitions). The framework is easy to extend, both for new problems and new search methods.
If anyone still interested in this for a python solution please find the following.
For the simplification, count of Missionaries and Cannibals on left is only taken to the consideration.
This is the solution tree.
#M #missionaries in left
#C #cannibals in left
# B=1left
# B=0right
def is_valid(state):
if(state[0]>3 or state[1]>3 or state[2]>1 or state[0]<0 or state[1]<0 or state[2]<0 or (0<state[0]<state[1]) or (0<(3-state[0])<(3-state[1]))):
return False
else:
return True
def generate_next_states(M,C,B):
moves = [[1, 0, 1], [0, 1, 1], [2, 0, 1], [0, 2, 1], [1, 1, 1]]
valid_states = []
for each in moves:
if(B==1):next_state = [x1 - x2 for (x1, x2) in zip([M, C, B], each)]
else:next_state = [x1 + x2 for (x1, x2) in zip([M, C, B], each)]
if (is_valid(next_state)):
# print(next_state)
valid_states.append(next_state)
return valid_states
solutions = []
def find_sol(M,C,B,visited):
if([M,C,B]==[0,0,0]):#everyne crossed successfully
# print("Solution reached, steps: ",visited+[[0,0,0]])
solutions.append(visited+[[0,0,0]])
return True
elif([M,C,B] in visited):#prevent looping
return False
else:
visited.append([M,C,B])
if(B==1):#boat is in left
for each_s in generate_next_states(M,C,B):
find_sol(each_s[0],each_s[1],each_s[2],visited[:])
else:#boat in in right
for each_s in generate_next_states(M,C,B):
find_sol(each_s[0],each_s[1],each_s[2],visited[:])
find_sol(3,3,1,[])
solutions.sort()
for each_sol in solutions:
print(each_sol)
Please refer to this gist to see a possible solution, maybe helpful to your problem.
Gist: solve Missionaries and cannibals in Prolog
I've solved with depth-first and then with breadth-first, attempting to clearly separate the reusable part from the state search algorithm:
miss_cann_dfs :-
initial(I),
solve_dfs(I, [I], Path),
maplist(writeln, Path), nl.
solve_dfs(S, RPath, Path) :-
final(S),
reverse(RPath, Path).
solve_dfs(S, SoFar, Path) :-
move(S, T),
\+ memberchk(T, SoFar),
solve_dfs(T, [T|SoFar], Path).
miss_cann_bfs :-
initial(I),
solve_bfs([[I]], Path),
maplist(writeln, Path), nl.
solve_bfs(Paths, Path) :-
extend(Paths, Extended),
( member(RPath, Extended),
RPath = [H|_],
final(H),
reverse(RPath, Path)
; solve_bfs(Extended, Path)
).
extend(Paths, Extended) :-
findall([Q,H|R],
( member([H|R], Paths),
move(H, Q),
\+ member(Q, R)
), Extended),
Extended \= [].
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% problem representation
% independent from search method
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
initial((3,3, >, 0,0)).
final((0,0, <, 3,3)).
% apply a *valid* move
move((M1i,C1i, Bi, M2i,C2i), (M1f,C1f, Bf, M2f,C2f)) :-
direction(Bi, F1, F2, Bf),
who_move(MM, CM),
M1f is M1i + MM * F1, M1f >= 0,
C1f is C1i + CM * F1, C1f >= 0,
( M1f >= C1f ; M1f == 0 ),
M2f is M2i + MM * F2, M2f >= 0,
C2f is C2i + CM * F2, C2f >= 0,
( M2f >= C2f ; M2f == 0 ).
direction(>, -1, +1, <).
direction(<, +1, -1, >).
% valid placements on boat
who_move(M, C) :-
M = 2, C = 0 ;
M = 1, C = 0 ;
M = 1, C = 1 ;
M = 0, C = 2 ;
M = 0, C = 1 .
I suggest you to structure your code in a similar way, with a predicate similar to extend/2, that make clear when to stop the search.
If your Prolog system has a forward chainer you can also solve
the problem by modelling it via forward chaining rules. Here
is an example how to solve a water jug problem in Jekejeke Minlog.
The state is represented by a predicate state/2.
You first give a rule that filters duplicates as follows. The
rule says that an incoming state/2 fact should be removed,
if it is already in the forward store:
% avoid duplicate state
unit &:- &- state(X,Y) && state(X,Y), !.
Then you give rules that state that search need not be continued
when a final state is reached. In the present example we check
that one of the vessels contains 1 liter of water:
% halt for final states
unit &:- state(_,1), !.
unit &:- state(1,_), !.
As a next step one models the state transitions as forward chaining
rules. This is straight forward. We model emptying, filling and pouring
of vessels:
% emptying a vessel
state(0,X) &:- state(_,X).
state(X,0) &:- state(X,_).
% filling a vessel
state(5,X) &:- state(_,X).
state(X,7) &:- state(X,_).
% pouring water from one vessel to the other vessel
state(Z,T) &:- state(X,Y), Z is min(5,X+Y), T is max(0,X+Y-5).
state(T,Z) &:- state(X,Y), Z is min(7,X+Y), T is max(0,X+Y-7).
We can now use the forward chaining engine to do the job for us. It
will not do iterative deeping and it will also not do breadth first.
It will just do unit resolution by a strategy that is greedy for the
given fact and the process only completes, since the state space
is finite. Here is the result:
?- post(state(0,0)), posted.
state(0, 0).
state(5, 0).
state(5, 7).
state(0, 7).
Etc..
The approach will tell you whether there is a solution, but not explain
the solution. One approach to make it explainable is to use a fact
state/4 instead of a fact state/2. The last two arguments are used for
a list of actions and for the length of the list.
The rule that avoids duplicates is then changed for a rule that picks
the smallest solution. It reads as follows:
% choose shorter path
unit &:- &- state(X,Y,_,N) && state(X,Y,_,M), M<N, !.
unit &:- state(X,Y,_,N) && &- state(X,Y,_,M), N<M.
We then get:
?- post(state(0,0,[],0)), posted.
state(0, 0, [], 0).
state(5, 0, [fl], 1).
state(5, 7, [fr,fl], 2).
state(0, 5, [plr,fl], 2).
Etc..
With a little helper predicate we can force an explanation of
the actions that lead to a path:
?- post(state(0,0,[],0)), state(1,7,L,_), explain(L).
0-0
fill left vessel
5-0
pour left vessel into right vessel
0-5
fill left vessel
5-5
pour left vessel into right vessel
3-7
empty right vessel
3-0
pour left vessel into right vessel
0-3
fill left vessel
5-3
pour left vessel into right vessel
1-7
Bye
Source Code: Water Jug State
http://www.xlog.ch/jekejeke/forward/jugs3.p
Source Code: Water Jug State and Path
http://www.xlog.ch/jekejeke/forward/jugs3path.p

Resources