1% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/util/logicmoo_util_prolog_frames.pl
    2:- module(frames,
    3          [ current_frames/4,
    4            current_next_frames/4,
    5            in_pengines/0,
    6            find_parent_frame_attribute/5,
    7            parent_goal/2,
    8            prolog_frame_match/3,
    9            relative_frame/3,
   10            stack_check/0,
   11            stack_check/1,
   12            stack_check/2,
   13            stack_check_else/2,
   14            stack_depth/1
   15          ]).   16:- module_transparent
   17        current_frames/4,
   18        current_next_frames/4,
   19        in_pengines/0,
   20        find_parent_frame_attribute/5,
   21        parent_goal/2,
   22        prolog_frame_match/3,
   23        relative_frame/3,
   24        stack_check/0,
   25        stack_check/1,
   26        stack_check/2,
   27        stack_check_else/2,
   28        stack_depth/1.   29
   30:- set_module(class(library)).   31
   32  
   33
   34/*
   35:- mpred_trace_nochilds(stack_depth/1).
   36:- mpred_trace_nochilds(stack_check/0).
   37:- mpred_trace_nochilds(stack_check/1).
   38:- mpred_trace_nochilds(stack_check/2).
   39*/
   40
   41%= 	 	 
 stack_depth(?Level) is semidet
Stack Depth.
   47stack_depth(Level):-quietly((prolog_current_frame(Frame),prolog_frame_attribute(Frame,level,Level))).
   48
   49
   50:-  module_transparent stack_check/0.   51:-  module_transparent stack_check/1.
 stack_check is semidet
Stack Check.
   57stack_check:- sanity(stack_check(6606)).
   58
   59%= 	 	 
 stack_check(?BreakIfOver) is semidet
Stack Check.
   65stack_check(BreakIfOver):- stack_check_else(BreakIfOver, trace_or_throw(stack_check(BreakIfOver))).
   66
   67%= 	 	 
 stack_check(?BreakIfOver, ?Error) is semidet
Stack Check.
   73stack_check(BreakIfOver,Error):- stack_check_else(BreakIfOver, trace_or_throw(stack_check(BreakIfOver,Error))).
   74
   75%= 	 	 
 stack_check_else(?BreakIfOver, ?Call) is semidet
Stack Check Else.
   81stack_check_else(BreakIfOver,Call):- stack_depth(Level) ,  ( Level < BreakIfOver -> true ; (dbgsubst(Call,stack_lvl,Level,NewCall),NewCall)).
   82
   83
   84
   85%= 	 	 
 in_pengines is semidet
In Pengines.
   91in_pengines:- zotrace(relative_frame(context_module,pengines,_)).
   92
   93% ?- relative_frame(context_module,X,Y).
   94:- export(relative_frame/3).   95
   96%= 	 	 
 relative_frame(?Attrib, ?Term, ?Nth) is semidet
Relative Frame.
  102relative_frame(Attrib,Term,Nth):- find_parent_frame_attribute(Attrib,Term,Nth,_RealNth,_FrameNum).
  103
  104:- export(parent_goal/2).  105
  106%= 	 	 
 parent_goal(?Goal) is semidet
Parent Goal.
  112parent_goal(Goal):- nonvar(Goal), quietly((prolog_current_frame(Frame),prolog_frame_attribute(Frame,parent,PFrame),
  113  prolog_frame_attribute(PFrame,parent_goal,Goal))).
  114parent_goal(Goal):- !, quietly((prolog_current_frame(Frame),prolog_frame_attribute(Frame,parent,PFrame0),
  115  prolog_frame_attribute(PFrame0,parent,PFrame),
  116  goals_above(PFrame,Goal))).
  117
  118goals_above(Frame,Goal):- prolog_frame_attribute(Frame,goal,Term),unify_goals(Goal,Term).
  119goals_above(Frame,Goal):- prolog_frame_attribute(Frame,parent,PFrame), goals_above(PFrame,Goal).
  120
  121unify_goals(Goal,Term):- (var(Goal);var(Term)),!,Term=Goal.
  122unify_goals(M:Goal,N:Term):-!, unify_goals0(Goal,Term),M=N.
  123unify_goals(Goal,_:Term):-!, unify_goals0(Goal,Term).
  124unify_goals(_:Goal,Term):-!, unify_goals0(Goal,Term).
  125
  126unify_goals0(X,X).
  127
  128%= 	 	 
 parent_goal(?Goal, ?Nth) is semidet
Parent Goal.
  134parent_goal(Goal,Nth):-  number(Nth),!, prolog_current_frame(Frame),prolog_frame_attribute(Frame,parent,PFrame),nth_parent_goal(PFrame,Goal,Nth).
  135parent_goal(Goal,Nth):-  find_parent_frame_attribute(goal,Goal,Nth,_RealNth,_FrameNum).
  136
  137
  138%= 	 	 
 nth_parent_goal(?Frame, ?Goal, ?Nth) is semidet
Nth Parent Goal.
  144nth_parent_goal(Frame,Goal,Nth):- Nth>0, Nth2 is Nth-1, prolog_frame_attribute(Frame,parent,PFrame),!,zotrace((nth_parent_goal(PFrame,Goal,Nth2))).
  145nth_parent_goal(Frame,Goal,_):- zotrace((prolog_frame_attribute(Frame,goal,Goal))),!.
  146
  147:- export(find_parent_frame_attribute/5).  148
  149%= 	 	 
 find_parent_frame_attribute(?Attrib, ?Term, ?Nth, ?RealNth, ?FrameNum) is semidet
Find Parent Frame Attribute.
  155find_parent_frame_attribute(Attrib,Term,Nth,RealNth,FrameNum):-quietly((ignore(Attrib=goal),prolog_current_frame(Frame),
  156                  current_frames(Frame,Attrib,5,NextList))),!,                 
  157                  catch(nth1(Nth,NextList,Out),E,(wdmsg(E),trace,nth1(Nth,NextList,Out))),
  158                  Out = RealNth-FrameNum-Term.
  159
  160
  161
  162%= 	 	 
 prolog_frame_match(?Frame, :TermAttrib, :TermTerm) is semidet
Prolog Frame Match.
  168prolog_frame_match(Frame,goal,Term):-!,prolog_frame_attribute(Frame,goal,TermO),!,Term=TermO.
  169prolog_frame_match(Frame,parent_goal,Term):-nonvar(Term),!,prolog_frame_attribute(Frame,parent_goal,Term).
  170prolog_frame_match(Frame,not(Attrib),Term):-!,nonvar(Attrib),not(prolog_frame_attribute(Frame,Attrib,Term)).
  171prolog_frame_match(_,[],X):-!,X=[].
  172prolog_frame_match(Frame,[I|IL],[O|OL]):-!,prolog_frame_match(Frame,I,O),!,prolog_frame_match(Frame,IL,OL),!.
  173prolog_frame_match(Frame,Attrib,Term):-prolog_frame_attribute(Frame,Attrib,Term).
  174
  175
  176%= 	 	 
 current_frames(?Frame, ?Attrib, :GoalN, ?NextList) is semidet
Current Frames.
  182current_frames(Frame,Attrib,N,NextList):- notrace(current_frames0(Frame,Attrib,N,NextList)).
  183current_frames0(Frame,Attrib,N,NextList):- N>0, N2 is N-1,prolog_frame_attribute(Frame,parent,ParentFrame),!,current_frames0(ParentFrame,Attrib,N2,NextList).
  184current_frames0(Frame,Attrib,0,NextList):- current_next_frames(Attrib,1,Frame,NextList).
  185
  186
  187%= 	 	 
 current_next_frames(?Attrib, ?Nth, ?Frame, ?NextList) is semidet
Current Next Frames.
  193current_next_frames(Attrib,Nth,Frame,[Nth-Frame-Term|NextList]):- zotrace((prolog_frame_match(Frame,Attrib,Term))), !,
  194   (prolog_frame_attribute(Frame,parent,ParentFrame) -> 
  195    ( Nth2 is Nth+1, current_next_frames(Attrib,Nth2, ParentFrame,NextList));
  196         NextList=[]).
  197current_next_frames(Attrib,Nth,Frame,NextList):- 
  198   (prolog_frame_attribute(Frame,parent,ParentFrame) -> 
  199    ( Nth2 is Nth+1, current_next_frames(Attrib,Nth2, ParentFrame,NextList));
  200         NextList=[]).
  201current_next_frames(_,_,_,[]).
  202
  203
  204
  205:- ignore((source_location(S,_),prolog_load_context(module,M),module_property(M,class(library)),
  206 forall(source_file(M:H,S),
  207 ignore((functor(H,F,A),
  208  ignore(((\+ atom_concat('$',_,F),(export(F/A) , current_predicate(system:F/A)->true; system:import(M:F/A))))),
  209  ignore(((\+ predicate_property(M:H,transparent), module_transparent(M:F/A), \+ atom_concat('__aux',_,F),debug(modules,'~N:- module_transparent((~q)/~q).~n',[F,A]))))))))).