8-puzzle has a solution in prolog using manhattan distance

后端 未结 2 689
臣服心动
臣服心动 2020-12-15 15:02

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

P

相关标签:
2条回答
  • 2020-12-15 15:19

    Here is a solver, not an answer to the original question. Joel76 already addressed the problem in comments, and thus he will get the deserved reputation when he will answer.

    But the 8-puzzle was interesting to solve, and pose some efficiency problem. Here is my best effort, where I used library(nb_set) in attempt to achieve reasonable efficiency on full solutions enumeration.

    Note: nb_set is required to keep track of visited also on failed paths. The alternative is a :- dynamic visited/1. but that turned out to be too much 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 Stack Overflow 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 that Joel76 posed to show the bug in my first effort:

    ?- 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 讨论(0)
  • 2020-12-15 15:28

    This answer looks at the problem from a different point of view:

    • Single board configurations are represented using the compound structure board/9.
    • Configurations that are equal up to sliding a single piece are connected by relation 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 here enter image description here
    enter image description here enter 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 here enter image description here enter image description here
    enter image description here enter image description here enter 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 here enter image description here
    enter image description here enter 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 here enter image description here enter image description here
    enter image description here enter image description here enter 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 here enter image description here enter image description here enter image description here
    enter image description here enter image description here enter image description here enter 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 here enter image description here enter image description here
    enter image description here enter image description here enter 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 here enter image description here
    enter image description here enter 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 here enter image description here enter image description here
    enter image description here enter image description here enter 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 here enter image description here
    enter image description here enter image description here


    Almost done! To connect the steps, we use the meta-predicate path/4 together with length/2 for performing iterative deepening.

    The following problem instances are 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 = [...] ? ;
    ...
    
    0 讨论(0)
提交回复
热议问题