%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%                                  %
% Basic Problem-Solving Strategies %
%                                  %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

:- module(search, [depthfirst/2, depthfirst2/2, depthfirst3/3, depthfirst4/3,
                   df_id/2, df_id2/3, breadthfirst/2, breadthfirst2/2]).


% depth-first
% depthfirst(+Start, -Solution)
depthfirst(Node, [Node]) :-
    goal(Node), !.

depthfirst(Node, [Node|Sol1]) :-
    s(Node, NextNode),
    depthfirst(NextNode, Sol1).




% depth-first acyclic
% depthfirst2(+Start, -Solution)
depthfirst2(Start, Sol) :-
    depthfirst2([Start], Start, RevSol),
    reverse(RevSol, Sol).

% depthfirst2(+Path, +Node, -Solution)
% When we add a new node in path, check if it is not already member of the path!
depthfirst2(Sol, Node, Sol) :-
    goal(Node), !.

depthfirst2(Path, Node, Sol) :-
    s(Node, NextNode),
    \+ member(NextNode, Path),
    depthfirst2([NextNode|Path], NextNode, Sol).




% depth-first depth-limited
% depthfirst3(+Start, -Solution, +Maxdepth)
depthfirst3(Node, [Node], _) :-
    goal(Node), !.

depthfirst3(Node, [Node|Sol1], Max) :-
    Max > 0,
    s(Node, NextNode),
    Max1 is Max - 1,
    depthfirst3(NextNode, Sol1, Max1).




% depth-first acyclic depth-limited
% depthfirst4(+Start, -Solution, +Maxdepth)
depthfirst4(Start, Sol, Max) :-
    depthfirst4([Start], Start, RevSol, Max),
    reverse(RevSol, Sol).

% depthfirst4(+Path, +Node, -Solution, +Maxdepth)
% When we add a new node in path, check if it is not already member of the path!
depthfirst4(Sol, Node, Sol, _) :-
    goal(Node), !.

depthfirst4(Path, Node, Sol, Max) :-
    Max > 0,
    s(Node, NextNode),
    \+ member(NextNode, Path),
    Max1 is Max - 1,
    depthfirst4([NextNode|Path], NextNode, Sol, Max1).





% depth-first iterative deepening
% (using classical depth-first acyclic depth-limited)
% and incrementing the limit starting with 1.
% df_id2(+Start, -Solution, +Maxdepth)
df_id2(N, Sol, Max) :-
    df_id2(N, Sol, 0, Max).

df_id2(N, Sol, I, _) :-
    depthfirst4(N, Sol, I),
    length(Sol, L), % add this to have only solutions of size I+1
    L =:= I + 1.    % and avoid to have several times the same solution

df_id2(N, Sol, I, Max) :-
    I =< Max,
    I1 is I + 1,
    df_id2(N, Sol, I1, Max).





% depth-first iterative deepening (more efficient)
% Warning, don't stop after finding the last solution
% In general it is not a problem beacause we are only interested
% in the first solution
% df_id(+Start, -Solution)
df_id(N, Sol) :-
    goal(Goal),
    path(N, Goal, Sol2),
    reverse(Sol2, Sol).

% path(N1, N2, Path)
% Generate path from N1 to N2 of increasing length
path(N, N, [N]).

path(N1, N2, [N2|Path]) :-
    path(N1, N3, Path),
    s(N3, N2),
    \+ member(N2, Path).





% breadth-first
breadthfirst2(Start, Sol) :-
    breadthfirst2_aux([[Start]], Sol2),
    reverse(Sol2, Sol).

% breadthfirst2_aux([Path1,Path2,...], Sol)
% Sol is an extension to a goal of one of paths
breadthfirst2_aux([[Node|Path]|_], [Node|Path]) :-
    goal(Node).

breadthfirst2_aux([Path|Paths], Sol) :-
    extend(Path, NewPaths),
    append(Paths, NewPaths, Paths1),
    breadthfirst2_aux(Paths1, Sol).


extend([Node|Path], NewPaths) :-
    findall([NewNode, Node | Path],
            (s(Node, NewNode), \+ member(NewNode, [Node|Path])),
            NewPaths).





% breadth-first (with lists difference notation -> more efficient !!!)
% breadthfirst(+Start, -Solution)
breadthfirst(Start, Sol) :-
    breadthfirst_aux([[Start]|Z] - Z, Sol2),
    reverse(Sol2, Sol).

breadthfirst_aux([[Node|Path]|_] - _, [Node|Path]) :-
    goal(Node).

breadthfirst_aux([Path|Paths] - Z, Sol) :-
    extend(Path, NewPaths),
    append(NewPaths, Z1, Z),
    Paths \== Z1, % To stop if there is no more path
    breadthfirst_aux(Paths - Z1, Sol).

