%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%                                                           %
% You are a train driver. Your train is represented by      %
% a list of the form [c_1, c_2, ..., c_n] where c_i are the %
% cars. The locomotive is supposed to be on the left of     %
% the car c_1 but is not explicitly represented.            %
% You are in a marshalling yard and your task is to         %
% rearrange the cars in a specific order.                   %
% The marshalling yard has two sorting tracks where you can %
% push or remove cars.                                      %
%                                                           %
%                    /====== RailTrack2                     %
%  RailTrack1 ======|                                       %
%                    \====== RailTrack3                     %
%                                                           %
%  -> [RailTrack1, RailTrack2, RailTrack3]                  %
%                                                           %
%                                                           %
% ?- train([a, b, c], [b, c, a], Sol).                      %
%                                                           %
%    Sol = [[[a, b, c], [], []],                            %
%           [[a], [b, c], []],                              %
%           [[], [b, c], [a]],                              %
%           [[b, c], [], [a]],                              %
%           [[b, c, a], [], []]].                           %
%                                                           %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%


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

:- use_module(search).

:- dynamic(goal/1). % Because we use assert & retract for the goal



train(Start, Goal, Sol) :-
    retractall(goal(_)), % Just in case !
    assert(goal([Goal, [], []])),
    solve([Start, [], []], Sol), !,
    retract(goal([Goal, [], []])).
	
solve(A, B) :-
    df_id(A, B).



s([W1, W2, W3], [W4, W5, W3]) :-
    append(W4, [B|Bs], W1),
    append([B|Bs], W2, W5).

s([W1, W2, W3], [W4, W2, W6]) :-
    append(W4, [B|Bs], W1),
    append([B|Bs], W3, W6).

s([W1, W2, W3], [W4, W5, W3]) :-
    append([A|As], W5, W2),
    append(W1, [A|As], W4).

s([W1, W2, W3], [W4, W2, W6]) :-
    append([A|As], W6, W3),
    append(W1, [A|As], W4).

