%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%                            %
% 15 puzzle (sliding puzzle) %
%                            %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%


:- set_prolog_flag(toplevel_print_options,
                   [quoted(true), portray(true), max_depth(0)]).

:- use_module(search).


% pretty print the first sol
sliding2(Start) :-
    solve(Start, Path), !,
    printPath(Path).

printPath([]) :- nl.
printPath([[T, _, _]|Ps]) :- nl, printTab(T), printPath(Ps).

printTab([]).
printTab([L|Ls]) :- writeln(L), printTab(Ls).


% set0(+I, +E, +Ls, -Zs)
% true if Zs = Ls and the element at pos I is replaced by E.
set0(0, E, [_|Ls], [E|Ls]) :- !.
set0(N, E, [L|Ls], [L|Zs]) :- N1 is N-1, set0(N1, E, Ls, Zs).



sliding(Start, Path) :-
    solve(Start, Path).

solve(A, B) :-
    df_id(A, B).




goal([[[1, 2, 3, 4], [5, 6, 7, 8], [9, 10, 11, 12], [13, 14, 15, x]], 3, 3]).



s([Tab1, N, M], [Tab2, N2, M2]) :-
    move(N, M, N2, M2),
    nth0(N2, Tab1, L1),
    nth0(M2, L1, E),
    set0(M2, x, L1, L2),
    set0(N2, L2, Tab1, Tab3),
    nth0(N, Tab3, L3),
    set0(M, E, L3, L4),
    set0(N, L4, Tab3, Tab2).


move(N, M, N2, M) :- N > 0, N2 is N - 1.
move(N, M, N2, M) :- N < 3, N2 is N + 1.
move(N, M, N, M2) :- M > 0, M2 is M - 1.
move(N, M, N, M2) :- M < 3, M2 is M + 1.

