1/* Sample example of hierachical probabilistic logic program. inspired from UWCSE dataset from
    2Kok S, Domingos P (2005) Learning the structure of Markov Logic Networks. In:
    3Proceedings of the 22nd international conference on Machine learning, ACM, pp
    4441-448
    5*/

?- inference_hplp(advisedby(harry, ben),ai,Prob). ?- inference_hplp(advisedby(harry, ben),ai,Prob,Circuit). */

   15:- use_module(library(phil)).   16:- if(current_predicate(use_rendering/1)).   17:- use_rendering(c3).   18:- use_rendering(lpad).   19:- endif.   20
   21:- phil.   22
   23:- set_hplp(verbosity, 1).   24% Structure learning settings
   25:- set_hplp(megaex_bottom, 10). % max number of mega examples to considered in the generation of bottoms clauses
   26:- set_hplp(initial_clauses_per_megaex, 1).   27:- set_hplp(rate, 1.0). % defines the probabilityu for going from the first layer to the second layer
   28:- set_hplp(max_layer, -1). % Define the max number of layer: -1 for the maximum depth possible 
   29:- set_hplp(min_probability, 1.0e-5).  % threshold value of the probability under which a clauses is dropped out
   30
   31% Parameter learning settings
   32:- set_hplp(algorithmType, dphil). % parameter learning algorithm dphil or emphil
   33% Maximun iteration and other stop conditions.
   34:- set_hplp(maxIter_phil, 1000).  
   35:- set_hplp(epsilon_deep, 0.0001). 
   36:- set_hplp(epsilon_deep_fraction, 1.0e-5).   37:- set_hplp(useInitParams, yes).   38
   39% regularization parameters 
   40:- set_hplp(regularized, no). % yes to enable regularization and no otherwise 
   41:- set_hplp(regularizationType, 2). % 1 for L1, 2 for L2 and 3 for L3. L3 available only for emphil
   42:- set_hplp(gamma, 10). % regularization strength
   43:- set_hplp(gammaCount, 0). 
   44
   45% Adam parameter for dphil algorithm
   46:- set_hplp(adam_params, [0.1, 0.9, 0.999, 1.0e-8]). % adam(Eta,Beta1,Beta2,Epsilon_adam_hat)
   47% Gradient descent strategy and the corresponding batch size
   48:- set_hplp(batch_strategy, minibatch(50)).   49%:- set_hplp(batch_strategy,stoch_minibatch(10)).
   50%:- set_hplp(batch_strategy,batch).
   51
   52  
   53bg([]).
   54
   55:- begin_in.   56advisedby(A,B):0.3:-
   57    student(A),
   58    professor(B),
   59    project(A,C),
   60    project(A,C),
   61    hidden_1(A,B,C).
   62advisedby(A,B):0.6 :-
   63    student(A),
   64    professor(B),
   65    ta(C,A),
   66    taughtby(C, B).
   67hidden_1(A,B,C):0.2 :-
   68    publication(P, A, C),
   69    publication(P, B, C).
   70:- end_in.   71
   72
   73fold(ai, [ai]).
   74
   75output(advisedby/2).
   76
   77
   78input(student/1).
   79input(professor/1).
   80input(project/2).
   81input(publication/3).
   82input(taughtby/2).
   83input(ta/2).
   84
   85
   86determination(advisedby/2, professor/1).
   87determination(advisedby/2, student/1).
   88determination(advisedby/2, publication/3).
   89determination(advisedby/2, taughtby/2).
   90determination(advisedby/2, ta/2).
   91determination(advisedby/2, project/2).
   92
   93modeh(*, advisedby(+person, +person)).
   94
   95
   96modeb(*, publication(-title, +person, +project)).
   97%modeb(*, publication(+title, -person, +project)).
   98modeb(*, project(+person,-project)).
   99%modeb(*, project(-person, +project)).
  100modeb(*, professor(+person)).
  101modeb(*, student(+person)).
  102modeb(*, taughtby(-course, +person)).
  103%modeb(*, taughtby(+course, -person)).
  104modeb(*, ta(-course, +person)).
  105%modeb(*, ta(-course, +person)).
  106
  107
  108% data
  109advisedby(ai, harry, ben).
  110student(ai, harry).
  111professor(ai, ben).
  112
  113taughtby(ai, c1, ben).
  114taughtby(ai, c2, ben).
  115ta(ai, c1, harry). 
  116ta(ai, c2, harry).
  117
  118project(ai, harry, pr1). 
  119project(ai, harry, pr2).
  120project(ai, ben, pr1). 
  121project(ai, ben, pr2).
  122publication(ai, p1, harry, pr1).
  123publication(ai, p2, harry, pr1).
  124publication(ai, p3, harry, pr2).
  125publication(ai, p4, harry, pr2).
  126publication(ai, p1, ben, pr1).
  127publication(ai, p2, ben, pr1).
  128publication(ai, p3, ben, pr2). 
  129publication(ai, p4, ben, pr2)