1% MODULE show_utils EXPORTS
    2:- module( show_utils, 
    3	 [ show_kb/0,                   % Show all clauses
    4           show_ex/0,                   % Show all examples
    5	   show_clause/1,               % Show one clause
    6           show_kb_clause/4,
    7	   show_clauses/1,
    8	   show_names/0,                % Show all names of predicates
    9	   show_kb_part/2,              % Show some clauses
   10           show_kb_types/0,             % displays all available types
   11           show_type_restrictions/0,
   12	   print_kb/1,                  % Print all clauses to UNIX-file
   13           show_heads /0,
   14           show_bodies/0,
   15           pp_clause/1,
   16	   write_list/1]).   17
   18
   19% IMPORTS
   20:- use_module(home(bu_basics),
   21              [head/3, body/3]).   22:- use_module(home(div_utils),
   23                  [make_unique/2,mysetof/3]).   24:- use_module(home(kb),
   25              [get_clause/5,get_example/3]).   26:- use_module(home(argument_types),
   27                  [type_restriction/2]).   28:- use_module_if_exists(library(basics),
   29              [nonmember/2,member/2]).   30% METAPREDICATES
   31% none
   32
   33
   34%***********************************************************************
   35%*	
   36%* module: show_utils.pl        					
   37%*									
   38%* author: B.Jung, M.Mueller, I.Stahl, B.Tausend              date:12/92	
   39%*									
   40%* changed:								
   41%*									
   42%* description:	various diplays predicates
   43%*		
   44%* see also:								
   45%*									
   46%***********************************************************************
   47
   48
   49
   50%***********************************************************************
   51%*									
   52%* predicate:	show_kb/0							
   53%*									
   54%* syntax:	-							
   55%*									
   56%* args:	none							
   57%*									
   58%* description:	displays all clauses in kb asserted by known
   59%*
   60%***********************************************************************
   61
   62show_kb :- get_clause(I,H,B,_,O),      
   63           show_kb_clause(I,H,B,O),
   64           fail.
   65show_kb :- !.
   66
   67
   68%***********************************************************************
   69%*									
   70%* predicate:	 print_kb/1
   71%*									
   72%* syntax:	 print_kb(+ File)						
   73%*									
   74%* args: File: name of a file							
   75%*									
   76%* description:	prints kb to a file	
   77%*
   78%***********************************************************************
   79
   80print_kb(Filename) :- tell(Filename),
   81                      show_kb,
   82                      told.
   83
   84
   85
   86%***********************************************************************
   87%*									
   88%* predicate:	 show_clause/1
   89%*									
   90%* syntax:	show_clause(+ ID)							
   91%*									
   92%* args:	ID: the ID of a clause							
   93%*									
   94%* description:	displays the clause stored with ID
   95%*									
   96%***********************************************************************
   97
   98show_clause(I) :- get_clause(I,H,B,_,O),
   99                  write(I),write(': '),
  100                  write('(by '),write(O),write(')'),
  101                  portray_clause((H:-B)),!.
  102
  103
  104%***********************************************************************
  105%*									
  106%* predicate: 	show_clauses/1							
  107%*									
  108%* syntax:      show_clauses(+List_of_clauseIDs)
  109%*									
  110%* args:	+List_of_clauseIDs: a list of clause IDs
  111%*									
  112%* description:	displays each clause with ID in List_of_clauseIDs
  113%*									
  114%***********************************************************************
  115
  116show_clauses([]) :- !.
  117show_clauses([Id1|Rest]) :- show_clause(Id1), nl, show_clauses(Rest).
  118
  119
  120%************************************************************************
  121%*
  122%* predicate:    show_kb_clause/4
  123%*
  124%* syntax:       show_kb_clause(+I,+H,+B,+O)
  125%*
  126%* args:         I: an ID in KB
  127%*               H: the head of a clause
  128%*               B: the body of a clause
  129%*               O: the label of a clause
  130%*
  131%* description: displays a clause H:-B, used for xm 
  132%*
  133%************************************************************************
  134
  135show_kb_clause(I,H,B,O):-
  136	  format('~N~n% Clause ~w (label ~w)~n',[I, O]),
  137          \+ \+ ((guess_varnames((H:-B)),
  138                  implode_varnames((H:-B)),
  139                  portray_clause((H:-B)))), !.
  140
  141
  142%***********************************************************************
  143%*									
  144%* predicate:show_names/0								
  145%*									
  146%* syntax:								
  147%*									
  148%* args:	none							
  149%*									
  150%* description:	lists all predicate names available in the kb
  151%*									
  152%***********************************************************************
  153
  154show_names :- show_names([]).
  155show_names(Accu) :-
  156	get_clause(_,H,_,_,_),
  157	functor(H,Name,_),
  158	nonmember(Name,Accu),
  159	format("~10|~a~n",Name), !,
  160	show_names([Name|Accu]).
  161show_names(_) :- !.
  162
  163%************************************************************************
  164%*
  165%* predicate: show_kb_part/2
  166%*
  167%* syntax:    show_kb_part(+From,+To) 
  168%*
  169%* args:      From: the min ID of KB entries to be shown
  170%*            To:   the max ID of KB entries to  be shown
  171%*
  172%* description: shows all clauses with From <= ID <= To
  173%*									
  174%************************************************************************
  175
  176show_kb_part(From,To) :- 
  177   mysetof(I,H^B^S^O^(get_clause(I,H,B,S,O),
  178                      From =< I,To >= I),IDL),
  179   show_clauses(IDL).
  180
  181
  182%***********************************************************************
  183%*									
  184%* predicate:	show_ex/0
  185%*									
  186%* syntax:								
  187%*									
  188%* args:	none							
  189%*									
  190%* description: displays all examples in kb
  191%*									
  192%***********************************************************************
  193
  194show_ex :- get_example(I,F,C),
  195           write('Example '),write(I),write(': '),
  196           write(F), write(' -> '), write(C),nl,
  197           fail.
  198show_ex :- !.
  199
  200
  201%***********************************************************************
  202%*									
  203%* predicate:  show_heads/0, show_bodies/0						
  204%*									
  205%* syntax:								
  206%*									
  207%* args:								
  208%*									
  209%* description:	displays all intermediate heads/bodies stored by absorption,
  210%*		saturation,... in the kb
  211%*									
  212%* example:								
  213%*									
  214%* peculiarities:	none				
  215%*									
  216%* see also:								
  217%*									
  218%***********************************************************************
  219
  220show_heads:- head(L,Flag,C), write( head(L,Flag,C)), nl, fail.
  221show_heads.
  222
  223show_bodies:- body(L,Flag,C), write( body(L,Flag,C)), nl, fail.
  224show_bodies. 
  225
  226
  227%***********************************************************************
  228%*									
  229%* predicate:	pp_clause/1							
  230%*									
  231%* syntax: pp_clause(+CL)								
  232%*							
  233%* args: CL .. clause in list notation
  234%*									
  235%* description: displays clause in list notation
  236%*									
  237%* example:								
  238%*									
  239%* peculiarities:	none				
  240%*									
  241%* see also:								
  242%*									
  243%***********************************************************************
  244
  245pp_clause([]).
  246pp_clause([H:S|Rest]):- write(H:S),nl,pp_clause(Rest).
  247
  248
  249%***********************************************************************
  250%*									
  251%* predicate:	write_list/1							
  252%*									
  253%* syntax:	write_list(+List)							
  254%*									
  255%* args:	List: a list
  256%*									
  257%* description:	displays copy of a  list after instantiating all terms 
  258%               within the copy by $Var(N)
  259%*									
  260%* peculiarities:	none						
  261%*									
  262%* see also:								
  263%*									
  264%***********************************************************************
  265
  266write_list([]).
  267write_list([X0|R]):-  
  268   copy_term(X0,X),      
  269   numbervars(X,0,_),write(X),nl,write_list(R).
  270write_list(PS:_:_):- write_list(PS).
  271
  272
  273%***********************************************************************
  274%*									
  275%* predicate:   show_kb_types/0
  276%*									
  277%* syntax:	
  278%*									
  279%* args:	
  280%*									
  281%* description:	displays definitions of all types in the kb
  282%*									
  283%* example:								
  284%*									
  285%* peculiarities:	none				
  286%*									
  287%***********************************************************************
  288
  289show_kb_types:-
  290   findall(T:Def,(get_clause(_,H,_,_,type),H =.. [T|_],
  291                  findall((H1:-B1),(get_clause(_,H1,B1,_,type),H1 =.. [T|_]),Def)),
  292                 Tlist0),
  293   make_unique(Tlist0,Tlist),
  294   nl, write('The following types are defined in the knowledge base:'),nl,
  295   show_kb_types([atom:[],number:[],atomic:[]|Tlist]).
  296
  297show_kb_types([]).
  298show_kb_types([T:Def|R]):-
  299   nl, write(T),write(':'),nl,
  300   show_kb_t(Def),
  301   show_kb_types(R).
  302
  303show_kb_t([]).
  304show_kb_t([C|R]):-
  305   numbervars(C,0,_),
  306   write(C),
  307   nl,
  308   show_kb_t(R).
  309
  310
  311%***********************************************************************
  312%*									
  313%* predicate:   show_type_restrictions/0
  314%*									
  315%* syntax:	
  316%*									
  317%* args:	
  318%*									
  319%* description:	displays all type restrictions in the kb
  320%*									
  321%* example:								
  322%*									
  323%* peculiarities:	none				
  324%*									
  325%* see also:								
  326%*									
  327%***********************************************************************
  328
  329show_type_restrictions:-
  330   type_restriction(M,A),
  331   numbervars((M,A),0,_),
  332   nl,write('type_restriction( '),write(M), write(', '), write(A), write(' )'),
  333   fail.
  334show_type_restrictions