1% search(M,F) is true if there is a path from F to a goal node.
    2%  M is the search method. It is one of {depth,breadth,heuristic_depth,best}
    3
    4% To seach from a node o103, issue the query:
    5% ? search(depth,[o103]).
    6% ? search(breadth,[o103]).
    7% or to see paths, issue these commands (note the extra [])
    8% ? psearch(depth, [[o103]], P).
    9% ? psearch(breadth, [[o103]], P).
   10
   11search(M,F) <-
   12   choose(M,N,F,_)&
   13   is_goal(N).
   14search(M,F) <-
   15   choose(M,N,F,F1) &
   16   neighbours(N,NN) &
   17   add_to_frontier(M,NN,F1,F2) &
   18   search(M,F2).
   19
   20% choose(M,E,F,NF) is true if E is an element of frontier F and NF is
   21%   the remaining frontier after E is removed. M is the search method used.
   22% In each of these the frontier is the list of elements in order they
   23%   are to be chosen.
   24
   25choose(_,N,[N|F],F).
   26
   27% add_to_frontier(M,N,F1,F2) is true if when using search method M, when
   28%   nodes N are added to frontier F1, the resulting frontier is list F2.
   29
   30add_to_frontier(depth,N,F1,F2) <- 
   31   append(N,F1,F2).
   32
   33add_to_frontier(breadth,N,F1,F2) <- 
   34   append(F1,N,F2).
   35
   36add_to_frontier(heuristic_depth,N,F1,F2) <- 
   37   mergeinto1(N,[],NF) &
   38   append(NF,F1,F2).
   39
   40add_to_frontier(best,N,F1,F2) <-
   41   mergeinto1(N,F1,F2).
   42
   43% mergeinto1(NL,F1,F2) is true if when NL is added to F1, the result is F2,
   44%   assuming F1 is in sorted order of h, F2 will be in order of h.
   45mergeinto1([],L,L).
   46mergeinto1([H|T],L1,L3) <-
   47   insertinto1(H,L1,L2) &
   48   mergeinto1(T,L2,L3).
   49
   50% insertinto1(N,F1,F2) is true if F2 contains the elements of F1 with
   51%   node N inserted into the position determined by the heuristic value of N
   52insertinto1(E,[],[E]).
   53insertinto1(N,[N1|R],[N,N1|R]) <-
   54   h(N,NC) &
   55   h(N1,NC1) &
   56   NC =< NC1.
   57insertinto1(N,[N1|R],[N1|R1]) <-
   58   h(N,NC) &
   59   h(N1,NC1) &
   60   NC > NC1 &
   61   insertinto1(N,R,R1).
   62
   63% **************************************************
   64% psearch is like search, but elements of the frontier are paths in reverse 
   65%   order. 
   66% psearch(M,F,S) means method M from frontier F results in path S to goal.
   67%   This only works for methods in {breadth,depth}. Exercise: fix it.
   68
   69% To seach from a node s, issue the query:
   70% ? psearch(depth,[[s]],P).
   71
   72psearch(M,F,[N|P]) <-
   73   choose(M,[N|P],F,_) &
   74   is_goal(N).
   75psearch(M,F,S) <-
   76   choose(M,[N|P],F,F1) &
   77   neighbours(N,NN) &
   78   add_paths(NN,[N|P],NN2) &
   79   add_to_frontier(M,NN2,F1,F2) &
   80   psearch(M,F2,S).
   81
   82add_paths([],_,[]).
   83add_paths([M|R],P,[[M|P]|PR]) <-
   84   add_paths(R,P,PR).
   85
   86% **************************************************
   87% Auxiliary definitions
   88
   89% append(A,B,R) is true if R is the list containing the elements of A
   90% followed by the elements of B
   91append([],R,R).
   92append([H|T],L,[H|R])