1:-[nnet].    2
    3
    4dnn_heuristic(Nnet,G,SList,method(_,input(TreeBreadth,TreeDepth),_),Res):-
    5  pred_to_vec(G,SList,TreeBreadth,TreeDepth,InVec),
    6  nnet_forward(Nnet,[InVec],[OutVec]),
    7  label_vec(OutVec,1,OVL),
    8  sort(OVL,OVLS),
    9  reverse(OVLS,Res),
   10  !.
   11
   12
   13comp_indim(TreeBreadth,TreeDepth,NumWord,Dim):-
   14  get_partial_tree(a,TreeBreadth,TreeDepth,T),
   15  flatten(T,FT),
   16  length(FT,P),
   17  Dim is P * NumWord,
   18  !.
   19
   20
   21pred_to_vec(Pred,[SList,MaxN],TreeBreadth,TreeDepth,Vec):-
   22  copy_term(Pred,GT),
   23  vble_fill(GT,GTF),
   24  get_partial_tree(GTF,TreeBreadth,TreeDepth,PT),
   25  flatten(PT,PTF),
   26  symlist_to_numlist(PTF,SList,NL),
   27  numlist_to_vec(NL,MaxN,Vec),
   28  !.
   29
   30label_vec([],_,[]):-!.
   31label_vec([Elem|L],Num,[[Elem,Num]|LT]):-
   32  N1 is Num + 1,
   33  label_vec(L,N1,LT),
   34  !.
   35  
   36
   37dnn_train(Nnet,G,SList,AxNum,method(learning(NumEpoch,LRate),input(TreeBreadth,TreeDepth),output(OutDim))):-
   38  pred_to_vec(G,SList,TreeBreadth,TreeDepth,InVec),
   39  axnum_to_vec(AxNum,OutDim,TgtVec),
   40  nnet_train(Nnet,[InVec],[TgtVec],NumEpoch,LRate),
   41  !.
   42
   43axnum_to_vec(AxNum,Dim,Vec):-
   44  AxNum > Dim,
   45  print(['Warning: AxNum is bigger than Dim: ',AxNum,Dim]),nl,
   46  copy_n_times(0,Dim,Vec),
   47  !.
   48
   49axnum_to_vec(AxNum,Dim,Vec):-
   50  D1 is AxNum - 1,
   51  copy_n_times(0,D1,Vec1),
   52  D2 is Dim - AxNum,
   53  copy_n_times(0,D2,Vec2),
   54  append(Vec1,[1|Vec2],Vec),
   55  !.
   56
   57
   58:- dynamic search_time/1.   59init_search_time:-
   60  retractall(search_time(_)),
   61  assert(search_time(0)).
   62add_search_time:-
   63  search_time(N),
   64  retractall(search_time(_)),
   65  N1 is N + 1,
   66  assert(search_time(N1)),
   67  !.
   68
   69dnn_sl_resolution(A,B,C,D,E,F,G):-
   70  dnn_sl_resolution(A,B,C,standard,D,E,F,G).
   71
   72dnn_sl_resolution([],_,_,_,_,_,_,[]).
   73dnn_sl_resolution(GList,[AList,NumA],SList,StatModName,Nnet,Mtd,Depth,Path):-
   74  Depth > 0,
   75  D1 is Depth - 1,
   76  GList = [-OrgG|GLT],
   77  copy_term(GList,PreGList),
   78  static_module(StatModName,OrgG,G),
   79  copy_term(G,GTemp),
   80  dnn_heuristic(Nnet,G,SList,Mtd,SAL),
   81  %SAL = AList,
   82  member([_,AxNum],SAL),
   83  member([AxNum,AxName,AxRule],AList),
   84add_search_time,
   85  copy_term(AxRule,Ax),
   86  %Ax = [+G|GN],
   87  append(GN,[+G],Ax),
   88  append(GN,GLT,GListNew),
   89  dnn_sl_resolution(GListNew,[AList,NumA],SList,StatModName,Nnet,Mtd,D1,PathNew),
   90  Path = [[PreGList,AxName]|PathNew],
   91  (
   92    Mtd = method(learning(_,_),_,_),
   93    dnn_train(Nnet,GTemp,SList,AxNum,Mtd)
   94    ;
   95    Mtd = method(reasoning,_,_)
   96  ).
   97
   98print_by_line([]).
   99print_by_line([X|L]):-
  100  print(X),nl,
  101  print_by_line(L).
  102
  103
  104
  105:- dynamic num_vble/1.  106:- retractall(num_vble(_)).  107:- assert(num_vble(0)).  108
  109vble_fill(X,X):-
  110  ground(X),
  111  !.
  112vble_fill(X,X):-
  113  var(X),
  114  num_vble(N1),
  115  N is N1 + 1,
  116  retractall(num_vble(_)),
  117  assert(num_vble(N)),
  118  X = vble(N),
  119  !.
  120vble_fill([],[]):-!.
  121vble_fill([X|L],[XT|LT]):-
  122  vble_fill(X,XT),
  123  vble_fill(L,LT),
  124  !.
  125 
  126
  127copy_n_times(_,0,[]):-!.
  128copy_n_times(X,N,[X|L]):-
  129  N > 0,
  130  N1 is N - 1,
  131  copy_n_times(X,N1,L),
  132  !.
  133
  134produce_empty_tree(_,0,novalue):-!.
  135produce_empty_tree(B,D,[novalue|L]):-
  136  D > 0,
  137  D1 is D - 1,
  138  produce_empty_tree(B,D1,Res1),
  139  copy_n_times(Res1,B,L),
  140  !.
  141
  142get_partial_tree([X|_],_,0,X):-!.
  143get_partial_tree(X,_,0,X):-
  144  \+is_list(X),
  145  !.
  146get_partial_tree([X|L],Breadth,Depth,[X|LT]):-
  147  Depth > 0,
  148  D1 is Depth - 1,
  149  get_partial_tree2(L,Breadth,D1,LT),
  150  !.
  151get_partial_tree(X,Breadth,Depth,[X|LT]):-
  152  \+is_list(X),
  153  Depth > 0,
  154  D1 is Depth - 1,
  155  get_partial_tree2([],Breadth,D1,LT),
  156  !.
  157
  158get_partial_tree2(L,Breadth,Depth,Res):-
  159  findall(XT,(member(X,L),get_partial_tree(X,Breadth,Depth,XT)),Res1),
  160  length(L,LenL),
  161  length(XT,LenL), % Check if the lengths agree.
  162  N1 is Breadth - LenL,
  163  (
  164    N1 >= 0,
  165    produce_empty_tree(Breadth,Depth,TEmpty),
  166    copy_n_times(TEmpty,N1,Res2),
  167    append(Res1,Res2,Res)
  168    ;
  169    N1 < 0,
  170    get_first_element(Res1,Breadth,Res)
  171  ),
  172  !.
  173
  174get_first_element(_,0,[]).
  175get_first_element([],N,[norule|Res1]):-
  176  N > 0,
  177  N1 is N - 1,
  178  get_first_element([],N1,Res1).
  179get_first_element([X|L],N,[X|Res1]):-
  180  N > 0,
  181  N1 is N - 1,
  182  get_first_element(L,N1,Res1).
  183
  184symlist_to_numlist([],_,[]):-!.
  185symlist_to_numlist([X|L],SList,[XT|LT]):-
  186  (
  187    X = vble(_),
  188    XT = 1
  189    ;
  190    X = novalue,
  191    XT = -1
  192    ;
  193    member([XT,X],SList)
  194  ),
  195  symlist_to_numlist(L,SList,LT),
  196  !.
  197
  198num_to_vec(-1,Dim,Vec):-
  199  copy_n_times(0,Dim,Vec),
  200  !.
  201num_to_vec(Num,Dim,Vec):-
  202  Num > Dim,
  203  print(['Warning: Num is bigger than Dim: ',Num,Dim]),nl,
  204  copy_n_times(0,Dim,Vec),
  205  !.
  206
  207num_to_vec(Num,Dim,Vec):-
  208  D1 is Num - 1,
  209  copy_n_times(0,D1,Vec1),
  210  D2 is Dim - Num,
  211  copy_n_times(0,D2,Vec2),
  212  append(Vec1,[1|Vec2],Vec),
  213  !.
  214
  215
  216
  217numlist_to_vec([],_,[]):-!.
  218numlist_to_vec([X|L],Dim,Res):-
  219  num_to_vec(X,Dim,XT),
  220  numlist_to_vec(L,Dim,LT),
  221  append(XT,LT,Res),
  222  !.
  223
  224for(K,P,Q):-
  225  P =< Q,
  226  K = P.
  227for(K,P,Q):-
  228  P < Q,
  229  P1 is P + 1,
  230  for(K,P1,Q).
  231
  232static_module(standard,G,G)