1% =======================================================
    2/* 
    3%
    4%= predicates to examine the state of pfc 
    5% interactively exploring Pfc justifications.
    6%
    7% Logicmoo Project PrologMUD: A MUD server written in Prolog
    8% Maintainer: Douglas Miles
    9% Dec 13, 2035
   10%
   11*/
   12% =======================================================
   13% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/mpred/mpred_list_triggers.pl
   14:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )).   15mpred_listing_module:- nop( module(mpred_listing,
   16          [ draw_line/0,
   17            loop_check_just/1,
   18            pinfo/1,
   19            pp_items/2,
   20            pp_item/2,
   21            pp_filtered/1,
   22            pp_facts/2,
   23            pp_facts/1,
   24            pp_facts/0,
   25            mpred_list_triggers_types/1,
   26            mpred_list_triggers_nlc/1,
   27            mpred_list_triggers_1/1,
   28            mpred_list_triggers_0/1,
   29            mpred_list_triggers/1,
   30            mpred_contains_term/2,
   31            mpred_classify_facts/4,
   32            lqu/0,
   33            get_clause_vars_for_print/2,
   34            %mpred_whyBrouse/2,
   35            %mpred_why1/1,
   36            %mpred_why/1,
   37            %mpred_why/0,
   38            pp_rules/0,
   39            pp_supports/0,
   40            pp_triggers/0,            
   41            print_db_items/1,
   42            print_db_items/2,
   43            print_db_items/3,
   44            print_db_items/4,
   45            print_db_items_and_neg/3,
   46            show_pred_info/1,
   47            show_pred_info_0/1,
   48            mpred_listing_file/0
   49          ])).
   50
   51:- include('mpred_header.pi').   52
   53:- endif.   54
   55% :- use_module(logicmoo(util/logicmoo_util_preddefs)).
   56
   57
   58
   59:- multifile((
   60              user:portray/1,
   61  	user:prolog_list_goal/1,
   62  	user:prolog_predicate_name/2,
   63  	user:prolog_clause_name/2)).   64
   65:- dynamic
   66  	user:portray/1.   67
   68% :- dynamic(whybuffer/2).
   69
   70
   71
   72%= 	 	 
 lqu is semidet
Lqu.
   78lqu :- listing(que/2).
   79
   80
   81 
   82
   83%= 	 	 
 pp_facts is semidet
Pretty Print Facts.
   89pp_facts :- pp_facts(_,true).
   90
   91
   92%= 	 	 
 pp_facts(?Pattern) is semidet
Pretty Print Facts.
   98pp_facts(Pattern) :- pp_facts(Pattern,true).
   99
  100
  101%= 	 	 
 pp_facts(?P, ?C) is semidet
Pretty Print Facts.
  107pp_facts(P,C) :-
  108  mpred_facts(P,C,L),
  109  mpred_classify_facts(L,User,Pfc,_Rule),
  110  draw_line,
  111  fmt("User added facts:",[]),
  112  pp_items(user,User),
  113  draw_line,
  114  draw_line,
  115  fmt("Pfc added facts:",[]),
  116  pp_items(system,Pfc),
  117  draw_line.
  118
  119
  120
  121%= 	 	 
 pp_items(?Type, :TermH) is semidet
Pretty Print Items.
  127pp_items(_Type,[]):-!.
  128pp_items(Type,[H|T]) :-
  129  ignore(pp_item(Type,H)),!,
  130  pp_items(Type,T).
  131pp_items(Type,H) :- ignore(pp_item(Type,H)).
  132
  133:- thread_local(t_l:print_mode/1).  134
  135%= 	 	 
 pp_item(?MM, :TermH) is semidet
Pretty Print Item.
  141pp_item(_M,H):-pp_filtered(H),!.
  142pp_item(MM,(H:-B)):- B ==true,pp_item(MM,H).
  143pp_item(MM,H):- flag(show_asserions_offered,X,X+1),find_and_call(get_print_mode(html)), ( \+ \+ if_defined(pp_item_html(MM,H))),!.
  144
  145
  146pp_item(MM,spft(W0,U,ax)):- W = (_KB:W0),!,pp_item(MM,U:W).
  147pp_item(MM,spft(W0,F,U)):- W = (_KB:W0),atom(U),!,    fmt('~N%~n',[]),pp_item(MM,U:W), fmt('rule: ~p~n~n', [F]),!.
  148pp_item(MM,spft(W0,F,U)):- W = (_KB:W0),         !,   fmt('~w~nd:       ~p~nformat:    ~p~n', [MM,W,F]),pp_item(MM,U).
  149pp_item(MM,nt(Trigger0,Test,Body)) :- Trigger = (_KB:Trigger0), !, fmt('~w n-trigger: ~p~ntest: ~p~nbody: ~p~n', [MM,Trigger,Test,Body]).
  150pp_item(MM,pt(F0,Body)):- F = (_KB:F0),             !,fmt('~w p-trigger:~n', [MM]), pp_item('',(F:-Body)).
  151pp_item(MM,bt(F0,Body)):- F = (_KB:F0),             !,fmt('~w b-trigger:~n', [MM]), pp_item('',(F:-Body)).
  152
  153
  154pp_item(MM,U:W):- !,sformat(S,'~w  ~w:',[MM,U]),!, pp_item(S,W).
  155pp_item(MM,H):- \+ \+ (( get_clause_vars_for_print(H,HH),fmt("~w ~p~N",[MM,HH]))).
  156
  157
  158%= 	 	 
 get_clause_vars_for_print(?HB, ?HB) is semidet
Get Clause Variables For Print.
  164get_clause_vars_for_print(HB,HB):- ground(HB),!.
  165get_clause_vars_for_print(I,I):- is_listing_hidden(skipVarnames),!.
  166get_clause_vars_for_print(H0,MHB):- get_clause_vars_copy(H0,MHB),!.
  167get_clause_vars_for_print(HB,HB).
  168
  169%= 	 	 
 mpred_classify_facts(:TermH, ?User, :TermPfc, ?H) is semidet
Managed Predicate Classify Facts.
  175mpred_classify_facts([],[],[],[]).
  176
  177mpred_classify_facts([H|T],User,Pfc,[H|Rule]) :-
  178  mpred_db_type(H,rule),
  179  !,
  180  mpred_classify_facts(T,User,Pfc,Rule).
  181
  182mpred_classify_facts([H|T],[H|User],Pfc,Rule) :-
  183  mpred_get_support(H,(mfl4(_VarNameZ,_,_,_),ax)),
  184  !,
  185  mpred_classify_facts(T,User,Pfc,Rule).
  186
  187mpred_classify_facts([H|T],User,[H|Pfc],Rule) :-
  188  mpred_classify_facts(T,User,Pfc,Rule).
  189
  190
  191
  192%= 	 	 
 print_db_items(?T, ?I) is semidet
Print Database Items.
  198print_db_items(T, I):- 
  199    draw_line, 
  200    fmt("~N~w ...~n",[T]),
  201    print_db_items(I),
  202    draw_line,!.
  203
  204
  205%= 	 	 
 print_db_items(?I) is semidet
Print Database Items.
  211print_db_items(F/A):-number(A),!,safe_functor(P,F,A),!,print_db_items(P).
  212print_db_items(H):- bagof(H,clause_u(H,true),R1),pp_items((:),R1),R1\==[],!.
  213print_db_items(H):- \+ current_predicate(_,H),!. 
  214print_db_items(H):- catch( ('$find_predicate'(H,_),call_u(listing(H))),_,true),!,nl,nl.
  215
  216
  217%= 	 	 
  218
  219%% pp_rules is semidet.
  220%
  221% Pretty Print Rules.
  222%
  223pp_rules :-
  224   print_db_items("Forward Rules",(_ ==> _)),
  225   print_db_items("Bidirectional Rules",(_ <==> _)), 
  226   print_db_items("Implication Rules",(_ => _)),
  227   print_db_items("Bi-conditional Rules",(_ <=> _)),
  228   print_db_items("Backchaining Rules",(_ <- _)),
  229   print_db_items("Positive Facts",(==>(_))),
  230   print_db_items("Negative Facts",(~(_))).
  231
  232
  233%= 	 	 
 pp_triggers is semidet
Pretty Print Triggers.
  239pp_triggers :-
  240     print_db_items("Positive triggers", pt(_,_,_)),
  241     print_db_items("Negative triggers", nt(_,_,_,_)),
  242     print_db_items("Goal triggers",bt(_,_,_)).
  243
  244
  245%= 	 	 
 pp_supports is semidet
Pretty Print Supports.
  251pp_supports :-
  252  % temporary hack.
  253  draw_line,
  254  fmt("Supports ...~n",[]), 
  255  setof((P =< S), (mpred_get_support(P,S), \+ pp_filtered(P)),L),
  256  pp_items('Support',L),
  257  draw_line,!.
  258
  259
  260pp_filtered(P):-var(P),!,fail.
  261pp_filtered(_:P):- !, pp_filtered(P).
  262pp_filtered(P):- safe_functor(P,F,A),F\==(/),!,pp_filtered(F/A).
  263pp_filtered(F/_):-F==mpred_prop.
 draw_line is semidet
Draw Line.
  271draw_line:- \+ thread_self_main,!.
  272draw_line:- (t_l:print_mode(H)->true;H=unknown),fmt("~N%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%~n",[]),H=H.
  273
  274 :- meta_predicate loop_check_just(0).  275
  276%= 	 	 
 loop_check_just(:GoalG) is semidet
Loop Check Justification.
  282loop_check_just(G):-loop_check(G,ignore(arg(1,G,[]))).
  283
  284
  285%= 	 	 
 show_pred_info(?F) is semidet
Show Predicate Info.
  291show_pred_info(PI):-
  292   ((
  293       pi_to_head_l(PI,Head),      
  294       % doall(show_call(why,call_u(isa(Head,_)))),
  295        safe_functor(Head,F,_),
  296        doall(show_call(why,call_u(isa(F,_)))),
  297       ((current_predicate(_,M:Head), (\+ predicate_property(M:Head,imported_from(_))))
  298          -> show_pred_info_0(M:Head); 
  299             wdmsg_pretty(cannot_show_pred_info(Head))))),!.
  300
  301
  302%= 	 	 
 show_pred_info_0(?Head) is semidet
show Predicate info Primary Helper.
  308show_pred_info_0(Head):- 
  309        doall(show_call(why,predicate_property(Head,_))),
  310        (has_cl(Head)->doall((show_call(why,clause(Head,_))));quietly((listing(Head)))),!.
  311
  312
  313% ===================================================
  314% Pretty Print Formula
  315% ===================================================
  316
  317
  318
  319%= 	 	 
 print_db_items(?Title, ?Mask, ?What) is semidet
Print Database Items.
  325print_db_items(Title,Mask,What):-print_db_items(Title,Mask,Mask,What).
  326
  327%= 	 	 
 print_db_items(?Title, ?Mask, ?SHOW, ?What0) is semidet
Print Database Items.
  333print_db_items(Title,Mask,SHOW,What0):-
  334     get_pi(Mask,H),get_pi(What0,What),
  335     format(atom(Showing),'~p for ~p...',[Title,What]),
  336     statistics(cputime,Now),Max is Now + 2,!,
  337       gripe_time(1.0,
  338         doall((once(statistics(cputime,NewNow)),NewNow<Max,clause_or_call(H,B),
  339             quietly(mpred_contains_term(What,(H:-B))),
  340             flag(print_db_items,LI,LI+1),
  341             ignore(quietly(pp_item(Showing,SHOW)))))),
  342     ignore(pp_item(Showing,done)),!.
  343
  344
  345%= 	 	 
 mpred_contains_term(?What, ?VALUE2) is semidet
Managed Predicate Contains Term.
  351mpred_contains_term(What,_):-is_ftVar(What),!.
  352mpred_contains_term(What,Inside):- compound(What),!,(\+ \+ ((copy_term_nat(Inside,Inside0),snumbervars(Inside0),contains_term(What,Inside0)))),!.
  353mpred_contains_term(What,Inside):- (\+ \+ once((subst(Inside,What,foundZadooksy,Diff),Diff \=@= Inside ))),!.
  354
  355
  356
  357%= 	 	 
 hook_mpred_listing(?What) is semidet
Hook To [hook_mpred_listing/1] For Module Mpred_listing. Hook Managed Predicate Listing.
  364baseKB:hook_mpred_listing(What):- on_x_debug(mpred_list_triggers(What)).
  365
  366:- thread_local t_l:mpred_list_triggers_disabled.  367% listing(L):-locally(t_l:mpred_list_triggers_disabled,listing(L)).
  368
  369
  370%= 	 	 
 mpred_list_triggers(?What) is semidet
Managed Predicate List Triggers.
  376mpred_list_triggers(_):-t_l:mpred_list_triggers_disabled,!.
  377mpred_list_triggers(What):-loop_check(mpred_list_triggers_nlc(What)).
  378
  379:- meta_predicate(mpred_list_triggers_nlc(?)).  380
  381
  382%= 	 	 
 mpred_list_triggers_nlc(?What) is semidet
Managed Predicate List Triggers Nlc.
  388mpred_list_triggers_nlc(MM:What):-atom(MM),!,MM:mpred_list_triggers(What).
  389mpred_list_triggers_nlc(What):-loop_check(mpred_list_triggers_0(What),true).
  390
  391
  392%= 	 	 
 mpred_list_triggers_0(?What) is semidet
Managed Predicate list triggers Primary Helper.
  398mpred_list_triggers_0(What):-get_pi(What,PI),PI\=@=What,mpred_list_triggers(PI).
  399mpred_list_triggers_0(What):-nonvar(What),What= ~(Then),!, \+ \+ mpred_list_triggers_1(Then), \+ \+ mpred_list_triggers_1(What).
  400mpred_list_triggers_0(What):- \+ \+  mpred_list_triggers_1(~(What)), \+ \+ mpred_list_triggers_1(What).
  401
  402
  403%= 	 	 
 mpred_list_triggers_types(?VALUE1) is semidet
Managed Predicate list triggers Types.
  409mpred_list_triggers_types('Triggers').
  410mpred_list_triggers_types('Instances').
  411mpred_list_triggers_types('Subclasses').
  412mpred_list_triggers_types('ArgTypes').
  413mpred_list_triggers_types('Arity').
  414mpred_list_triggers_types('Forward').
  415mpred_list_triggers_types('Bidirectional').
  416mpred_list_triggers_types('Backchaining').
  417mpred_list_triggers_types('Negative').
  418mpred_list_triggers_types('Sources').
  419mpred_list_triggers_types('Supports').
  420mpred_list_triggers_types('Edits').
  421
  422% print_db_items_and_neg(Title,Fact,What):-nonvar(Fact),Fact= ~(_),!,fail.
  423
  424%= 	 	 
 print_db_items_and_neg(?Title, ?Fact, ?What) is semidet
Print Database Items And Negated.
  430print_db_items_and_neg(Title,Fact,What):-print_db_items(Title,Fact,What).
  431print_db_items_and_neg(Title,Fact,What):-print_db_items(Title,~(Fact),What).
  432
  433
  434%= 	 	 
 mpred_list_triggers_1(?What) is semidet
Managed Predicate list triggers Secondary Helper.
  440mpred_list_triggers_1(~(What)):-var(What),!.
  441mpred_list_triggers_1(~(_What)):-!.
  442mpred_list_triggers_1(What):-var(What),!.
  443mpred_list_triggers_1(What):- 
  444   print_db_items('Supports User',spft_precanonical(P,mfl4(VarNameZ,_,_,_),ax),spft(P,mfl4(VarNameZ,_,_,_),ax),What),
  445   print_db_items('Forward Facts',(nesc(F)),F,What),
  446   print_db_items('Forward Rules',(_==>_),What),
  447 ignore((What\= ~(_),safe_functor(What,IWhat,_),
  448   print_db_items_and_neg('Instance Of',isa(IWhat,_),IWhat),
  449   print_db_items_and_neg('Instances: ',isa(_,IWhat),IWhat),
  450   print_db_items_and_neg('Subclass Of',genls(IWhat,_),IWhat),
  451   print_db_items_and_neg('Subclasses: ',genls(_,IWhat),IWhat))),
  452   forall(suggest_m(M),print_db_items('PFC Watches', mpred_prop(M,_,_,_),What)),
  453   print_db_items('Triggers Negative', nt(_,_,_,_),What),
  454   print_db_items('Triggers Goal',bt(_,_,_),What),
  455   print_db_items('Triggers Positive',pt(_,_,_),What),
  456   print_db_items('Bidirectional Rules',(_<==>_),What), 
  457   dif(A,B),print_db_items('Supports Deduced',spft_precanonical(P,A,B),spft(P,A,B),What),
  458   dif(G,ax),print_db_items('Supports Nonuser',spft_precanonical(P,G,G),spft(P,G,G),What),
  459   print_db_items('Backchaining Rules',(_<-_),What),
  460   % print_db_items('Edits',is_disabled_clause(_),What),
  461   print_db_items('Edits',is_edited_clause(_,_,_),What),
  462   print_db_items('Instances',isa(_,_),What),
  463   print_db_items('Subclasses',genls(_,_),What),
  464   print_db_items('Negative Facts',~(_),What),
  465
  466   print_db_items('ArgTypes',argGenls(_,_,_),What),
  467   print_db_items('ArgTypes',argIsa(_,_,_),What),
  468   print_db_items('ArgTypes',argQuotedIsa(_,_,_),What),
  469   print_db_items('ArgTypes',meta_argtypes(_),What),
  470   print_db_items('ArgTypes',predicate_property(G,meta_predicate(G)),What),
  471   print_db_items('ArgTypes',resultGenls(_,_),What),
  472   print_db_items('ArgTypes',resultIsa(_,_),What),
  473   print_db_items('Arity',arity(_,_),What),
  474   print_db_items('Arity',current_predicate(_),What),
  475   print_db_items('MetaFacts Predicate',predicate_property(_,_),What),
  476   print_db_items('Sources',module_property(_,_),What),
  477   print_db_items('Sources',predicateConventionMt(_,_),What),
  478   print_db_items('Sources',source_file(_,_),What),
  479   print_db_items('Sources',_:man_index(_,_,_,_,_),What),
  480   print_db_items('Sources',_:'$pldoc'(_,_,_,_),What),
  481   print_db_items('Sources',_:'$pred_option'(_,_,_,_),What),
  482   print_db_items('Sources',_:'$mode'(_,_),What),
  483   !.     
  484
  485
  486pinfo(F/A):- listing(F/A),safe_functor(P,F,A),findall(Prop,predicate_property(P,Prop),List),wdmsg_pretty(pinfo(F/A)==List),!.
 pp_DB is semidet
Pretty Print All.

pp_DB:- defaultAssertMt(M),clause_b(mtHybrid(M)),!,pp_DB(M). pp_DB:- forall(clause_b(mtHybrid(M)),pp_DB(M)).

  497pp_DB:- defaultAssertMt(M),pp_DB(M).
  498 
  499
  500pp_DB(M):-
  501 with_exact_kb(M,
  502 M:must_det_l((
  503  pp_db_facts,
  504  pp_db_rules,
  505  pp_db_triggers,
  506  pp_db_supports))).
  507
  508pp_db_facts:- context_module(M), pp_db_facts(M).
  509pp_db_rules:- context_module(M), pp_db_rules(M).
  510pp_db_triggers:- context_module(M), pp_db_triggers(M).
  511pp_db_supports:- context_module(M), pp_db_supports(M).
  512
  513
  514:- system:import(pp_DB/0).  515:- system:export(pp_DB/0).  516
  517%  pp_db_facts ...
  518
  519pp_db_facts(MM):- ignore(pp_db_facts(MM,_,true)).
  520
  521pp_db_facts(MM,Pattern):- pp_db_facts(MM,Pattern,true).
  522
  523pp_db_facts(MM,P,C):-
  524  mpred_facts_in_kb(MM,P,C,L),
  525  mpred_classifyFacts(L,User,Pfc,_ZRule),
  526  length(User,UserSize),length(Pfc,PfcSize),
  527  format("~N~nUser added facts in [~w]: ~w",[MM,UserSize]),
  528  pp_db_items(User),
  529  format("~N~nSystem added facts in [~w]: ~w",[MM,PfcSize]),
  530  pp_db_items(Pfc).
  531
  532%  printitems clobbers it''s arguments - beware!
  533
  534
  535pp_db_items(Var):-var(Var),!,format("~N  ~p",[Var]).
  536pp_db_items([]):-!.
  537pp_db_items([H|T]):- !,
  538  % numbervars(H,0,_),
  539  format("~N  ~p",[H]),
  540  nonvar(T),pp_db_items(T).
  541
  542pp_db_items((P >= FT)):- is_hidden_pft(P,FT),!.
  543  
  544pp_db_items(Var):-
  545  format("~N  ~p",[Var]).
  546
  547
  548is_hidden_pft(_,(mfl4(_VarNameZ,baseKB,_,_),ax)).
  549is_hidden_pft(_,(why_marked(_),ax)).
  550
  551
  552pp_mask(Type,MM,Mask):-   
  553  bagof_or_nil(Mask,lookup_kb(MM,Mask),Nts),
  554  list_to_set_variant(Nts,NtsSet),!,
  555  pp_mask_list(Type,MM,NtsSet).
  556
  557pp_mask_list(Type,MM,[]):- !,
  558  format("~N~nNo ~ws in [~w]...~n",[Type,MM]).
  559pp_mask_list(Type,MM,NtsSet):- length(NtsSet,Size), !,
  560  format("~N~n~ws (~w) in [~w]...~n",[Type,Size,MM]),
  561  pp_db_items(NtsSet).
  562
  563mpred_classifyFacts([],[],[],[]).
  564
  565mpred_classifyFacts([H|T],User,Pfc,[H|Rule]):-
  566  mpred_db_type(H,rule(_)),
  567  !,
  568  mpred_classifyFacts(T,User,Pfc,Rule).
  569
  570mpred_classifyFacts([H|T],[H|User],Pfc,Rule):-
  571  % get_source_uu(UU),
  572  get_first_user_reason(H,_UU),
  573  !,
  574  mpred_classifyFacts(T,User,Pfc,Rule).
  575
  576mpred_classifyFacts([H|T],User,[H|Pfc],Rule):-
  577  mpred_classifyFacts(T,User,Pfc,Rule).
  578
  579
  580pp_db_rules(MM):- 
  581 pp_mask("Forward Rule",MM,==>(_,_)),
  582 pp_mask("Bi-conditional Rule",MM,<==>(_,_)),
  583 pp_mask("Backward Rule",MM,<-(_,_)),
  584 % pp_mask("Prolog Rule",MM,:-(_,_)),
  585 !.
  586
  587
  588pp_db_triggers(MM):- 
  589 pp_mask("Positive trigger",MM,pt(_,_)),
  590 pp_mask("Negative trigger",MM,nt(_,_,_)),
  591 pp_mask("Goal trigger",MM,bt(_,_)),!.
  592
  593pp_db_supports(MM):-
  594  % temporary hack.
  595  format("~N~nSupports in [~w]...~n",[MM]),
  596  with_exact_kb(MM, bagof_or_nil((P >= S), mpred_get_support(P,S),L)),
  597  list_to_set_variant(L,LS),
  598  pp_db_items(LS),!.
  599
  600
  601
  602:- fixup_exports.  603
  604mpred_listing_file