%%% A test HYPROLOG test program
%%% - integration with an external constraint solver 
%%%
%%% Finding different paths in a graph with constraints.
%%%
%%% (c) Henning Christiansen 2008
%%%
%%% The example is explained in the following reference
%%% as example 3.4
%%%
%%% H. Christiansen.
%%% Executable specifications for hypothesis-based reasoning with
%%% Prolog and Constraint Handling Rules,
%%% Journal of Applied Logic, to appear 2008 or -09.
%%% Preliminary version available at
%%% http://www.ruc.dk/~henning/publications/HypoReason2008_HC.pdf


%%%%%% TESTING ABDUCTION
%%%%%% Finding different paths in a graph
%%%%%% with calculation of costs and requiring
%%%%%% conditions on that cost

%%%%%% The task is to find three different 
%%%%%% paths, that we call the red, green and blue path, and which must be disjoint. 
%%%%%% Furthermore, the collected cost for the red paths must be larger than the one 
%%%%%% for the green path, successively larger than for the blue path. 
%%%%%% Path costs can be calculated incrementally (which is the optimal way), but 
%%%%%% in order to have the external constraint solver do interesting work, we set 
%%%%%% up constraints when generating each path (from the top and downwards), 
%%%%%% so the total and intermediates costs are not known before the path reaches 
%%%%%% node start. However, the program may indirectly compare the costs of paths 
%%%%%% generated from the cost of the edges already involved and the knowledge the 
%%%%%% the unknown costs are positive.


%% For efficiency:
allow_duplicate_abducibles.
no_explicit_negation.


abducible path_edge/4.


:- use_module(library(clpq)).

%% Test by the following  call

problem:- {RedCost > GreenCost, GreenCost > BlueCost},
      path(red,RedCost), path(green,GreenCost), path(blue,BlueCost).

%% .. or use this one for benchmarking:

problemTest:-
  size(H), write(('Problem size '=H)),nl,
  statistics(runtime,_),
  {RedCost > GreenCost, GreenCost > BlueCost},
  %% execute 10 times and remove constraints between each
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  \+ \+ (path(red,RedCost), path(green,GreenCost), path(blue,BlueCost)),
  statistics(runtime,[_,T10]),
  T1 is T10/10,
  write('Used: '),write(T1), write(ms).

%% We let ICs control disjointness and no-loops.


path(Id,Cost):- path(Id,goal,Cost).

path(_,start,StartCost):- {StartCost=0}.

path(Id,N2,C):- edge(N1,N2,C2), {C = C1+C2, C1>=0}, path_edge(Id,N1,N2,C),
   path(Id,N1,C1).


% Integrity constraint: No cycles

path_edge(Id,_,N,_), path_edge(Id,_,N,_) ==> fail.

% nb: in some systems make explicit that startnodes are different

% Integrity constraint: Different paths are disjoint except from
% start end goal

path_edge(Id1,_,N,_), path_edge(Id2,_,N,_) ==>
     Id1 \= Id2, N\=goal | fail.


%%%%%%%%%

:- dynamic dyna_count_abd/1.

reset_count_abd:-
    (retract(dyna_count_abd(_)) -> true; true),
    assert(dyna_count_abd(0)).

count_abd:- 
    retract(dyna_count_abd(N)),
    N1 is N+1,
    assert(dyna_count_abd(N1)).
/************************************

                  goal
         ^  ^     ^  ^    ^   ^  
         /  / ... |  | ... \  \
       
    n1_N------n2_N------ ... -----nN_N
      |         |                   |
      |         |                   |
    n1_N-1----n2_N-1---- ... -----nN_N-1
      |         |                   |
      |         |                   |
      .         .                   .      
      .         .                   .      
      .         .                   .      
      |         |                   |
      |         |                   |
    n1_2------n2_2------ ... -----nN_2
      |         |                   |
      |         |                   |
    n1_1------n2_1------ ... -----nN_1
         ^  ^     ^  ^     ^  ^  
         \  \ ... |  | ... /  /
                 start


All edges, except the very to and very bottom are bidirectional.
A random positive cost is added to each edge and direction.

***************************************/



size(5).

node(start).

edge(start,n1_1,53).
edge(start,n2_1,19).
edge(start,n3_1,7).
edge(start,n4_1,45).
edge(start,n5_1,7).

node(n1_1).
edge(n1_1,n2_1,18).
edge(n2_1,n1_1,57).
edge(n1_1,n1_2,89).
edge(n1_2,n1_1,83).
node(n2_1).
edge(n2_1,n3_1,67).
edge(n3_1,n2_1,97).
edge(n2_1,n2_2,73).
edge(n2_2,n2_1,87).
node(n3_1).
edge(n3_1,n4_1,23).
edge(n4_1,n3_1,75).
edge(n3_1,n3_2,6).
edge(n3_2,n3_1,83).
node(n4_1).
edge(n4_1,n5_1,9).
edge(n5_1,n4_1,81).
edge(n4_1,n4_2,20).
edge(n4_2,n4_1,69).
node(n5_1).
edge(n5_1,n5_2,42).
edge(n5_2,n5_1,46).

node(n1_2).
edge(n1_2,n2_2,44).
edge(n2_2,n1_2,81).
edge(n1_2,n1_3,14).
edge(n1_3,n1_2,22).
node(n2_2).
edge(n2_2,n3_2,17).
edge(n3_2,n2_2,18).
edge(n2_2,n2_3,66).
edge(n2_3,n2_2,95).
node(n3_2).
edge(n3_2,n4_2,89).
edge(n4_2,n3_2,62).
edge(n3_2,n3_3,84).
edge(n3_3,n3_2,98).
node(n4_2).
edge(n4_2,n5_2,69).
edge(n5_2,n4_2,54).
edge(n4_2,n4_3,43).
edge(n4_3,n4_2,67).
node(n5_2).
edge(n5_2,n5_3,67).
edge(n5_3,n5_2,13).

node(n1_3).
edge(n1_3,n2_3,10).
edge(n2_3,n1_3,40).
edge(n1_3,n1_4,47).
edge(n1_4,n1_3,76).
node(n2_3).
edge(n2_3,n3_3,20).
edge(n3_3,n2_3,76).
edge(n2_3,n2_4,19).
edge(n2_4,n2_3,52).
node(n3_3).
edge(n3_3,n4_3,91).
edge(n4_3,n3_3,70).
edge(n3_3,n3_4,20).
edge(n3_4,n3_3,54).
node(n4_3).
edge(n4_3,n5_3,42).
edge(n5_3,n4_3,18).
edge(n4_3,n4_4,20).
edge(n4_4,n4_3,37).
node(n5_3).
edge(n5_3,n5_4,61).
edge(n5_4,n5_3,98).

node(n1_4).
edge(n1_4,n2_4,88).
edge(n2_4,n1_4,62).
edge(n1_4,n1_5,2).
edge(n1_5,n1_4,46).
node(n2_4).
edge(n2_4,n3_4,57).
edge(n3_4,n2_4,6).
edge(n2_4,n2_5,77).
edge(n2_5,n2_4,17).
node(n3_4).
edge(n3_4,n4_4,16).
edge(n4_4,n3_4,72).
edge(n3_4,n3_5,58).
edge(n3_5,n3_4,27).
node(n4_4).
edge(n4_4,n5_4,76).
edge(n5_4,n4_4,50).
edge(n4_4,n4_5,93).
edge(n4_5,n4_4,43).
node(n5_4).
edge(n5_4,n5_5,46).
edge(n5_5,n5_4,2).

node(n1_5).
edge(n1_5,n2_5,9).
edge(n2_5,n1_5,39).
edge(n1_5,goal,82).
node(n2_5).
edge(n2_5,n3_5,26).
edge(n3_5,n2_5,42).
edge(n2_5,goal,71).
node(n3_5).
edge(n3_5,n4_5,75).
edge(n4_5,n3_5,40).
edge(n3_5,goal,38).
node(n4_5).
edge(n4_5,n5_5,42).
edge(n5_5,n4_5,7).
edge(n4_5,goal,9).
node(n5_5).
edge(n5_5,goal,16).

node(goal).