8-puzzle has solution in prologue using Manhattan distance

An 8-puzzle will be represented by a list of positions in a 3x3 list, where an empty field will be represented by the value 9, as shown below: [[9,1,3], [5,2,6], [4,7,8]]

Possibility Solution: Only half of the starting positions of the 8-puzzle are allowed. There is a formula that lets you know from the start if you can solve the puzzle. To determine if the 8-puzzle is solvable, for each square containing the value N, the number of numbers less than N after the current cell is calculated. For example, to the initial status:

enter image description here

  • 1 no numbers less then = 0
  • Empty (9) - should subsequently 3,5,2,6,4,7,8 = 7
  • 3 have = 1 to 2
  • 5 subsequently to 2.4 = 2
  • 2 no number under it happen = 0
  • 6 then 4 = 1
  • 4 no numbers less then = 0
  • 7 no minor numbers after = 0
  • 8 no numbers less then = 0

We then calculate the Manhattan distance between the empty position and the position (3.3). In the example above, the blank cell is at position (1.2), so the Manhattan distance is: d = abs (3-1) + abs (3-2) = 3 Finally, add up all the calculated values. If the result is even, it follows that the puzzle is solvable, but it is odd not to be solved. 0 +7 +1 +2 +0 +1 +0 +0 +0 +3 = 14

The solution is designed to create a knowledge base with all possible states of the number on the board, and we will see how many numbers are less than N after the current position.

Here's my code:

%***********************Have Solution*********************************

posA(9,8). posA(8,7). posA(7,6). posA(6,5). posA(5,4). posA(4,3). posA(3,2). posA(2,1). posA(1,0).

posB(9,7). posB(8,7). posB(8,6). posB(7,6). posB(7,5). posB(7,4). 
posB(6,5). posB(6,4). posB(6,3). posB(6,2). posB(5,4). posB(5,3). posB(5,2). posB(5,1).  posB(5,0). 
posB(4,3). posB(4,2). posB(3,2). posB(3,1).  posB(2,1). posB(2,0). posB(1,0).

posC(9,6). posC(8,6). posC(8,5). posC(7,6). posC(7,5). posC(7,4). posC(6,5). posC(6,4). posC(6,3).
posC(5,4). posC(5,3). posC(5,2). posC(4,3). posC(4,2). posC(4,1). posC(4,0).
posC(3,2). posC(3,1). posC(3,0). posC(2,1). posC(1,0).

posD(9,5). posD(8,5). posD(8,4). posD(7,5). posD(7,4). posD(7,3). posD(6,5). posD(6,4). posD(6,3).
posD(6,2). posD(5,4). posD(5,3). posD(5,2). posD(5,1). posD(4,3). posD(4,2). posD(4,1). posD(5,0).
posD(3,2). posD(3,1). posD(3,0). posD(2,1). posD(1,0).

posE(9,4). posE(8,4). posE(8,3). posE(7,4). posE(7,3). posE(7,2). posE(6,4). posE(6,3). posE(6,2). posE(6,1).
posE(5,4). posE(5,3). posE(5,2). posE(5,1). posE(5,0). posE(4,3). posE(4,2). posE(4,1). posE(4,0).
posE(3,2). posE(3,1). posE(3,0). posE(2,1). posE(2,0). posE(1,0).

posF(9,3). posF(8,3). posF(8,2). posF(7,1). posF(7,2). posF(7,3). posF(6,0). posF(6,1). posF(6,2). 
posF(6,3). posF(5,0). posF(5,1). posF(5,2). posF(5,3). posF(4,0). posF(4,1). posF(4,2). posF(4,3).
posF(2,0). posF(2,1). posF(3,0). posF(3,1). posF(3,2). posF(1,0).

posG(9,2). posG(8,0). posG(8,1). posG(8,2).  posG(7,0). posG(7,1). posG(7,2).
posG(6,0). posG(6,1). posG(6,2). posG(5,0).  posG(5,1). posG(5,2). posG(4,0). posG(4,1). posG(4,2).
posG(3,0). posG(3,1). posG(3,2). posG(2,0).  posG(2,1). posG(1,0).

posH(9,1). posH(8,0). posH(8,1). posH(7,0). posH(7,1). posH(6,0). posH(6,1). posH(5,0). posH(5,1). 
posH(4,0). posH(4,1). posH(3,0). posH(3,1). posH(2,0). posH(1,1). posH(1,0).

posI(9,0). posI(8,0). posI(7,0). posI(6,0). posI(5,0). posI(4,0). posI(3,0). posI(2,0). posI(1,0).  

haveSolution([[A,B,C],[D,E,F],[G,H,I]]):- distManhattan([A,B,C,D,E,F,G,H,I], Z),
                                         posA(A,Pa), posB(B,Pb), posC(C,Pc),
                                         posD(D,Pd), posE(E,Pe), posF(F,Pf),
                                         posG(G,Pg), posH(H,Ph), posI(I,Pi),
                                         P is Pa+Pb+Pc+Pd+Pe+Pf+Pg+Ph+Pg+Pi+Z, 0 is P mod 2,
                                         write('The 8-puzzle have solution').

%%*************************Manhattan distance***********************
distManhattan([A,B,C,D,E,F,G,H,I], Dist):-  A=9, Dist is abs(3-1)+abs(3-1), !;
                                            B=9, Dist is abs(3-1)+abs(3-2), !;
                                            C=9, Dist is abs(3-1)+abs(3-3), !;
                                            D=9, Dist is abs(3-2)+abs(3-1), !;
                                            E=9, Dist is abs(3-2)+abs(3-2), !;
                                            F=9, Dist is abs(3-2)+abs(3-3), !;
                                            G=9, Dist is abs(3-3)+abs(3-1), !;
                                            H=9, Dist is abs(3-3)+abs(3-2), !;
                                            I=9, Dist is abs(3-3)+abs(3-3).

      

The problem is that I am wrong, because there are situations where I may have several alternatives, for example>:

|  1 |  9 | 3  |
|  5 |  2 | 6  |
|  4 |  7 | 8  |    


posA(1,0)+posB(9,7)+posC(3,1)+posD(5,2)+posE(2,0)+posF(6,1)+posG(4,0)+posH(7,0)+posI(8,0).

      

The correct solution for posC (C, Pc) is posC (3,1), which is 1; but there are other branches that sometimes cause wrong exits ... what am I doing wrong in my code and how can I change it?

+3


source to share


2 answers


This answer looks at the problem from a different perspective:

  • Single board configurations are represented using a stacked one board/9

    .
  • The configurations that are equal to the sliding of one piece are related by the ratio m/2

    .

So let's define m/2

!

m (board ( '' , B, C, D , E, F, G, H, I), board ( D , B, C, '' , E, F, G, H, I)).
m (board ( '' , B , C, D, E, F, G, H, I), board ( B , '' , C, D, E, F, G, H, I)).

enter image description hereenter image description here
enter image description hereenter image description here


m (board ( A , '' , C, D, E, F, G, H, I), board ( '' , A , C, D, E, F, G, H, I)).
m (board (A, '' , C , D, E, F, G, H, I), board (A, C , '' , D, E, F, G, H, I)).
m (board (A, '' , C, D, E , F, G, H, I), board (A, E , C, D, '' , F, G, H, I)).

enter image description hereenter image description hereenter image description here
enter image description hereenter image description hereenter image description here


m (board (A, B , '' , D, E, F, G, H, I), board (A, '' , B , D, E, F, G, H, I)).
m (board (A, B, '' , D, E, F , G, H, I), board (A, B, F , D, E, '' , G, H, I)).

enter image description hereenter image description here
enter image description hereenter image description here


m (board ( A , B, C, '' , E, F, G, H, I), board ( '' , B, C, A , E, F, G, H, I)).
m (board (A, B, C, '' , E , F, G, H, I), board (A, B, C, E , '' , F, G, H, I)).
m (board (A, B, C, '' , E, F, G , H, I), board (A, B, C, G , E, F, '' , H, I)).

enter image description hereenter image description hereenter image description here
enter image description hereenter image description hereenter image description here


m (board (A, B, C, D , '' , F, G, H, I), board (A, B, C, '' , D , F, G, H, I)).
m (board (A, B , C, D, '' , F, G, H, I), board (A, '' , C, D, B , F, G, H, I)).
m (board (A, B, C, D, '' , F , G, H, I), board (A, B, C, D, F , '' , G, H, I)).
m (board (A, B, C, D, '' , F, G, H , I), board (A, B, C, D, H , F, G, '' , I)).

enter image description hereenter image description hereenter image description hereenter image description here
enter image description hereenter image description hereenter image description hereenter image description here




m (board (A, B, C , D, E, '' , G, H, I), board (A, B, '' , D, E, C , G, H, I)).
m (board (A, B, C, D, E , '' , G, H, I), board (A, B, C, D, '' , E , G, H, I)).
m (board (A, B, C, D, E, '' , G, H, I ), board (A, B, C, D, E, I , G, H, '' )).

enter image description hereenter image description hereenter image description here
enter image description hereenter image description hereenter image description here


m (board (A, B, C, D , E, F, '' , H, I), board (A, B, C, '' , E, F, D , H, I)).
m (board (A, B, C, D, E, F, '' , H , I), board (A, B, C, D, E, F, H , '' , I)).

enter image description hereenter image description here
enter image description hereenter image description here


m (board (A, B, C, D, E , F, G, '' , I), board (A, B, C, D, '' , F, G, E , I)).
m (board (A, B, C, D, E, F, G , '' , I), board (A, B, C, D, E, F, '' , G , I)).
m (board (A, B, C, D, E, F, G, '' , I ), board (A, B, C, D, E, F, G, I , '' )).

enter image description hereenter image description hereenter image description here
enter image description hereenter image description hereenter image description here


m (board (A, B, C, D, E, F , G, H, '' ), board (A, B, C, D, E, '' , G, H, F )).
m (board (A, B, C, D, E, F, G, H , '' ), board (A, B, C, D, E, F, G, '' , H )).

enter image description hereenter image description here
enter image description hereenter image description here


Almost done! To connect the steps, we use the path [4]together with length/2

to perform iterative deepening.

The following problem examples are taken from @ CapelliC's answer:

?- length(Path,N), path(m,Path,/* from */ board(1,' ',3,5,2,6,4,7, 8 ),
                               /*  to  */ board(1, 2 ,3,4,5,6,7,8,' ')).
N =  6, Path = [board(1,' ',3,5,2,6,4,7,8), board(1,2,3,5,' ',6,4,7,8),
                board(1,2,3,' ',5,6,4,7,8), board(1,2,3,4,5,6,' ',7,8),
                board(1,2,3,4,5,6,7,' ',8), board(1,2,3,4,5,6,7,8,' ')] ? ;
N = 12, Path = [board(1,' ',3,5,2,6,4,7,8), board(1,2,3,5,' ',6,4,7,8),
                board(1,2,3,5,7,6,4,' ',8), board(1,2,3,5,7,6,' ',4,8),
                board(1,2,3,' ',7,6,5,4,8), board(1,2,3,7,' ',6,5,4,8),
                board(1,2,3,7,4,6,5,' ',8), board(1,2,3,7,4,6,' ',5,8),
                board(1,2,3,' ',4,6,7,5,8), board(1,2,3,4,' ',6,7,5,8),
                board(1,2,3,4,5,6,7,' ',8), board(1,2,3,4,5,6,7,8,' ')] ? ;
...

?- length(Path,N), path(m,Path,/* from */ board(8,7,4,6,' ',5,3,2, 1 ),
                               /*  to  */ board(1,2,3,4, 5 ,6,7,8,' ')).
N = 27, Path = [board(8,7,4,6,' ',5,3,2,1), board(8,7,4,6,5,' ',3,2,1),
                board(8,7,4,6,5,1,3,2,' '), board(8,7,4,6,5,1,3,' ',2),
                board(8,7,4,6,5,1,' ',3,2), board(8,7,4,' ',5,1,6,3,2),
                board(' ',7,4,8,5,1,6,3,2), board(7,' ',4,8,5,1,6,3,2),
                board(7,4,' ',8,5,1,6,3,2), board(7,4,1,8,5,' ',6,3,2),
                board(7,4,1,8,5,2,6,3,' '), board(7,4,1,8,5,2,6,' ',3),
                board(7,4,1,8,5,2,' ',6,3), board(7,4,1,' ',5,2,8,6,3),
                board(' ',4,1,7,5,2,8,6,3), board(4,' ',1,7,5,2,8,6,3),
                board(4,1,' ',7,5,2,8,6,3), board(4,1,2,7,5,' ',8,6,3),
                board(4,1,2,7,5,3,8,6,' '), board(4,1,2,7,5,3,8,' ',6),
                board(4,1,2,7,5,3,' ',8,6), board(4,1,2,' ',5,3,7,8,6),
                board(' ',1,2,4,5,3,7,8,6), board(1,' ',2,4,5,3,7,8,6),
                board(1,2,' ',4,5,3,7,8,6), board(1,2,3,4,5,' ',7,8,6),
                board(1,2,3,4,5,6,7,8,' ')] ? ;
N = 29, Path = [...] ? ;
...

      

+2


source


Here is a solver, not an answer to the original question. Joel76 has already addressed the issue in the comments and so he will get a well-deserved reputation when he answers.

But puzzle 8 was interesting to solve and posed an efficiency problem. Here are my best efforts as I used the ( nb_set ) library in an attempt to achieve reasonable efficiency when listing a complete solution.

Note. nb_set is required to track visits also on unsuccessful paths. The alternative is :- dynamic visited/1.

, but it turned out to be too slow.



/*  File:    8-puzzle.pl
    Author:  Carlo,,,
    Created: Feb  4 2013
    Purpose: solve 8-puzzle
*/

:- module(eight_puzzle,
      [eight_puzzle/3
      ]).

:- use_module(library(nb_set)).

% test cases from Qaru thread with Joel76
test0(R) :- eight_puzzle([1,2,3,4,5,6,7,8,0], [1,0,3, 5,2,6, 4,7,8], R).
test1(R) :- eight_puzzle([1,2,3,4,5,6,7,8,0], [8,7,4, 6,0,5, 3,2,1], R).

%%  eight_puzzle(+Target, +Start, -Moves) is ndet
%
%   public interface to solver
%
eight_puzzle(Target, Start, Moves) :-
    empty_nb_set(E),
    eight_p(E, Target, Start, Moves).

%%  -- private here --

eight_p(_, Target, Target, []) :-
    !.
eight_p(S, Target, Current, [Move|Ms]) :-
    add_to_seen(S, Current),
    setof(Dist-M-Update,
          (  get_move(Current, P, M),
         apply_move(Current, P, M, Update),
         distance(Target, Update, Dist)
          ), Moves),
    member(_-Move-U, Moves),
    eight_p(S, Target, U, Ms).

%%  get_move(+Board, +P, -Q) is semidet
%
%   based only on coords, get next empty cell
%
get_move(Board, P, Q) :-
    nth0(P, Board, 0),
    coord(P, R, C),
    (   R < 2, Q is P + 3
    ;   R > 0, Q is P - 3
    ;   C < 2, Q is P + 1
    ;   C > 0, Q is P - 1
    ).

%%  apply_move(+Current, +P, +M, -Update)
%
%   swap elements at position P and M
%
apply_move(Current, P, M, Update) :-
    assertion(nth0(P, Current, 0)), % constrain to this application usage
    ( P > M -> (F,S) = (M,P) ; (F,S) = (P,M) ),
    nth0(S, Current, Sv, A),
    nth0(F, A, Fv, B),
    nth0(F, C, Sv, B),
    nth0(S, Update, Fv, C).

%%  coord(+P, -R, -C)
%
%   from linear index to row, col
%   size fixed to 3*3
%
coord(P, R, C) :-
    R is P // 3,
    C is P mod 3.

%%  distance(+Current, +Target, -Dist)
%
%   compute Manatthan distance between equals values
%
distance(Current, Target, Dist) :-
    aggregate_all(sum(D),
              (   nth0(P, Current, N), coord(P, Rp, Cp),
              nth0(Q, Target, N), coord(Q, Rq, Cq),
              D is abs(Rp - Rq) + abs(Cp - Cq)
              ), Dist).

%%  add_to_seen(+S, +Current)
%
%   fail if already in, else store
%
add_to_seen(S, [A,B,C,D,E,F,G,H,I]) :-
    Sig is
    A*100000000+
    B*10000000+
    C*1000000+
    D*100000+
    E*10000+
    F*1000+
    G*100+
    H*10+
    I,
    add_nb_set(Sig, S, true)

      

Test case Joel76 delivered to show the error in my first efforts:

?- time(eight_puzzle:test1(R)).
% 25,791 inferences, 0,012 CPU in 0,012 seconds (100% CPU, 2137659 Lips)
R = [5, 8, 7, 6, 3, 0, 1, 2, 5|...] ;
% 108,017 inferences, 0,055 CPU in 0,055 seconds (100% CPU, 1967037 Lips)
R = [5, 8, 7, 6, 3, 0, 1, 2, 5|...] ;
% 187,817,057 inferences, 93,761 CPU in 93,867 seconds (100% CPU, 2003139 Lips)
false.

      

0


source







All Articles