bsort(From, [From|Config]) :- sorting_moves(0, From, Config). sorting_moves(N, From, Config) :- length(Config, N), moves(From, Config), last(Config, Last), sorted(Last). sorting_moves(N, From, Config) :- N1 is N + 1, sorting_moves(N1, From, Config). moves(_From, []). moves(From, [To|Cs]) :- move(From, To), moves(To, Cs). move(From, To) :- length(From, Len), length(To, Len), % pick two adjacent pegs nth0(N, From, P1), peg(P1), N1 is N + 1, nth0(N1, From, P2), peg(P2), % find two adjacent empty holes nth0(M, From, empty), M1 is M + 1, nth0(M1, From, empty), \+ (nth0(Nin, From, empty), Nin > min(N1,M1), Nin < max(N,M)), % put them in nth0(N, To, empty), nth0(N1, To, empty), nth0(M, To, P1), nth0(M1, To, P2), unify_free(From, To). sorted(Ps) :- adjacent(Ps), left_right(Ps). adjacent(Ps) :- forall(nth0(N, Ps, empty), outsider(N, Ps)). left_right(Ps) :- \+ (nth0(N, Ps, black), nth0(M1, Ps, white), nth0(M2, Ps, white), M1 < N, M2 > N), \+ (nth0(N, Ps, white), nth0(M1, Ps, black), nth0(M2, Ps, black), M1 < N, M2 > N). outsider(N, Ps) :- \+ (nth0(M, Ps, P), peg(P), M > N). outsider(N, Ps) :- \+ (nth0(M, Ps, P), peg(P), M < N). peg(black). peg(white). unify_free([], []). unify_free([X|Xs], [Y|Ys]) :- var(Y), X = Y, unify_free(Xs, Ys). unify_free([_X|Xs], [Y|Ys]) :- \+ var(Y), unify_free(Xs, Ys).