% a simple hill climging search

% works in SWI-Prolog.  
% Written by Tim Finin, http://umbc.edu/~finin/, finin@Umbc.edu


:- ensure_loaded(showPath).
:-ensure_loaded(dbug).

% hill climbing search.

hc :- 
  hc(Path), 
  showPath(Path).

hc(Path) :- 
  start(S), 
  hc(S,Path).

hc(S,[S]) :- goal(S), !.

hc(S,[S|Path]) :-
  h(S,H),
  findall(HSS-SS,
         (arc(S,SS), h(SS,HSS)), L),
  keysort(L,[BestH-BestSS|_]),
  H>BestH -> hc(BestSS,Path)
             ; (dbug("Local max at ~p.~n",[S]), fail).


	