1% MODULE environment EXPORTS
    2
    3:- module(environment,
    4        [ oracle/1, 
    5          oracle/2, 
    6          oracle/3,
    7          satisfiable/1,
    8          ask_for/1,
    9          ask_for_ex/1,
   10          confirm/2, 
   11          get_ci/2]).   12
   13
   14% IMPORTS
   15:- use_module(home(kb),
   16              [get_clause/5,delete_clause/1,store_clause/4,
   17               interpretable_predicate/1,get_example/3,store_ex/3,
   18               rename/3,delete_all/1]).   19:- use_module(home(show_utils),
   20              [show_clauses/1,show_names/0]).   21:- use_module_if_exists(library(prompt),
   22              [prompt/1]).   23:- use_module_if_exists(library(ask),
   24              [yesno/1,yesno/2,ask_chars/4]).   25:- use_module_if_exists(library(sets),
   26              [union/3]).   27:- use_module_if_exists(library(subsumes),
   28              [subsumes_chk/2]).   29
   30% METAPREDICATES
   31% none
   32
   33
   34%***********************************************************************
   35%*	
   36%* module: envirnonment.pl        					
   37%*									
   38%* author: B.Jung, M.Mueller, I.Stahl, B.Tausend              date:12/92	
   39%*									
   40%* changed:								
   41%*									
   42%*									
   43%* description: procedures for oracle interaction
   44%*      1. membership queries - oracle/1
   45%*	2. existential queries - oracle/2
   46%*	3. subset queries - oracle/2							
   47%*	4. name queries - oracle/2							
   48%*	5. general questions with default answers - oracle/3
   49%*									
   50%* see also:								
   51%*									
   52%*									
   53%***********************************************************************
   54
   55%***********************************************************************
   56%*									
   57%* predicate:	satisfiable/1							
   58%*									
   59%* syntax: satisfiable(+SG_list)
   60%*									
   61%* args: SG_list ... list of subgoals [...,[ID,Subgoal,Proof],...]
   62%*									
   63%* description:	each Subgoal in SG_list	is tested on satisfiability.
   64%*     The oracle is used if the satisfiability of Subgoal can not be
   65%*     decided on the available knowledge
   66%*									
   67%* example:								
   68%*									
   69%* peculiarities:	none						
   70%*									
   71%* see also:								
   72%*									
   73%***********************************************************************
   74
   75satisfiable([]).
   76satisfiable([[_,H,_]|R]):-
   77   ask_for(H),
   78   satisfiable(R).
   79
   80
   81
   82%***********************************************************************
   83%*									
   84%* predicate:	ask_for/1							
   85%*									
   86%* syntax: ask_for(+Goal)								
   87%*									
   88%* args: Goal is a ground atom								
   89%*									
   90%* description: succeds if Goal is valid in the kb, or declared to be
   91%*      valid by the oracle
   92%*									
   93%* example:								
   94%*									
   95%* peculiarities:	none						
   96%*									
   97%* see also:								
   98%*									
   99%***********************************************************************
  100
  101ask_for(Lit):-
  102   (   interpretable_predicate(Lit) ->
  103        (   (get_clause(_,Lit,true,_,_); get_example(_,Lit,'+')) ->
  104            true
  105        ;   (   get_example(_,Lit,'-') ->
  106                fail
  107            ;   (   ground(Lit) ->
  108                    (   oracle(Lit) ->
  109                        store_ex(Lit,'+',_)
  110                     ;  store_ex(Lit,'-',_), fail
  111                    )
  112                ;   fail
  113                )
  114            )
  115        )
  116   ;   Lit
  117   ).
  118
  119
  120
  121%***********************************************************************
  122%*									
  123%* predicate:	ask_for_ex/1							
  124%*									
  125%* syntax: ask_for(+Goal)								
  126%*									
  127%* args: Goal is an atom								
  128%*									
  129%* description: succeds if Goal is valid in the kb, or declared to be
  130%*      valid by the oracle
  131%*									
  132%* example:								
  133%*									
  134%* peculiarities:	none						
  135%*									
  136%* see also:								
  137%*									
  138%***********************************************************************
  139
  140ask_for_ex(Lit):-
  141   (   interpretable_predicate(Lit) ->
  142        (   (get_clause(_,Lit,true,_,_); get_example(_,Lit,'+')) ->
  143            true
  144        ;   (   get_example(_,Lit,'-') ->
  145                fail
  146            ;   (   oracle(Lit,Lit) ->
  147                    store_ex(Lit,'+',_)
  148                ;   fail
  149                )
  150            )
  151        )
  152   ;   Lit
  153   ).
  154
  155
  156%***********************************************************************
  157%*									
  158%* predicate:	term_help/0							
  159%*									
  160%* syntax:								
  161%*									
  162%* args:								
  163%*									
  164%* description:	prompts a help line							
  165%*									
  166%* example:								
  167%*									
  168%* peculiarities:							
  169%*									
  170%* see also:								
  171%*									
  172%***********************************************************************
  173
  174
  175term_help :-
  176 prompt('Please enter a proper PROLOG-term followed by a full-stop and RETURN').
  177
  178
  179%***********************************************************************
  180%*									
  181%* predicate:	 oracle/1							
  182%*									
  183%* syntax:	 oracle( + Literal)							
  184%*									
  185%* args:								
  186%*									
  187%* description: membership queries:
  188%*    "Is the following literal always true?" -> succeeds iff oracle answers yes
  189%*									
  190%* example:								
  191%*									
  192%* peculiarities:							
  193%*									
  194%* see also:								
  195%*									
  196%***********************************************************************
  197%%%oracle(mappend(A,B,C)):- !,append(A,B,C).
  198oracle(Lit) :- 
  199        nl, prompt('Is the following literal always true:'),
  200        nl, nl, portray_clause(Lit), nl, !,
  201        yesno('> (y/n) ').
  202
  203
  204%***********************************************************************
  205%*									
  206%* predicate: oracle/2							
  207%*									
  208%* syntax: oracle( + List_of_Clause_Ids, - Example_Id)
  209%*									
  210%* args:								
  211%*									
  212%* description:	subset queries
  213%*    "Are the following clauses always true?"
  214%*    If not, the user might supply a counter example.
  215%*									
  216%* example:								
  217%*									
  218%* peculiarities: fails only if the oracle answers "no" AND does not 
  219%*      supply a counter example
  220%*									
  221%* see also:								
  222%*									
  223%***********************************************************************
  224
  225oracle([Id1|Rest], NegexId) :-
  226        nl, prompt('Are the following clauses always true:'),
  227	nl, show_clauses([Id1|Rest]), !,
  228	(yesno('> (y/n) ') -> true ;
  229	    yesno('> Would You like to give a counter-example','no') ->
  230	    repeat,
  231	    prompt('> Please enter negative example as Prolog-term: '),
  232	    read(Ex),
  233	    (Ex = h ->
  234		term_help, fail ;
  235		store_ex(Ex,'-',NegexId), !)
  236	    ).
  237           
  238
  239%***********************************************************************
  240%*									
  241%* predicate:	oracle/2					
  242%*									
  243%* syntax:	oracle( + PnameAtom, - NewNameAtom)
  244%*									
  245%* args:								
  246%*									
  247%*									
  248%* description:	name queries
  249%*    "How would you like to call predicate pXYZ", where pXYZ is a new predicate.
  250%*    The oracle may use every atom as answer. However, the atom "list" 
  251%*    causes the system to show every known predicate symbol within the knowledge base
  252%*									
  253%* example:								
  254%*									
  255%* peculiarities: the predicate returns the new predicate name, but does not
  256%*         replace the old name by the new one within the kb.  
  257%*
  258%* see also:								
  259%*									
  260%***********************************************************************
  261
  262oracle(Pname, Newname) :-
  263	functor(Pname,_,0),
  264	nl, prompt('How would You like to call predicate '), write(Pname), write(' ?'),
  265	!, repeat,
  266	ask_chars('> Please enter a name or "list" followed by RETURN',1,40,A1),
  267	atom_chars(A2,A1),
  268	(A2 == 'list'  ->
  269	prompt('So far the following predicates have been defined in the knowledge-base:'),
  270	    nl, show_names, fail ;
  271	    Newname = A2, !).
  272
  273
  274%***********************************************************************
  275%*									
  276%* predicate:	oracle/2							
  277%*									
  278%* syntax:	oracle(+Lit, -InstLit)							
  279%*									
  280%* args:								
  281%*									
  282%* description:	existential queries
  283%*    "Is there a correct instance of the following literal?"
  284%*    If yes, the oracle supplies an instance -> InstLit
  285%*    Else, the predicate fails
  286%*									
  287%* example:								
  288%*									
  289%* peculiarities:							
  290%*									
  291%* see also:								
  292%*									
  293%***********************************************************************
  294
  295oracle(Lit, InstLit) :- 
  296        nl, prompt('Is there a correct instance of the following literal:'),
  297        nl, nl, portray_clause(Lit), nl, !,
  298        yesno('> (y/n) '),
  299        repeat,
  300           prompt('> Please enter an instance: '),
  301           read(InstLit),
  302           (InstLit = h ->
  303           term_help, fail
  304           ;  subsumes_chk(Lit, InstLit) -> !
  305              ;  prompt('This is no instantiation of the literal!'), fail          
  306           ).
  307
  308
  309%***********************************************************************
  310%*									
  311%* predicate:	oracle/3							
  312%*									
  313%* syntax:	oracle( + QuestionAtom, ? DefaultAtom, - AnswerAtom)
  314%*									
  315%* args:								
  316%*									
  317%* description:	general questions with default answers
  318%*      If no default is necessary, use '_' as second argument
  319%*									
  320%* example:								
  321%*									
  322%* peculiarities:							
  323%*									
  324%* see also:								
  325%*									
  326%***********************************************************************
  327
  328oracle(Question, Default, Answer) :-
  329	atom_chars(Question,Qlist),
  330	append([62,32],Qlist,P1list),
  331	(var(Default) -> atom_chars(Prompt,P1list) ;
  332	    atom_chars(Default,Dlist),
  333	    append(Dlist,[93],D1list),
  334	    append(P1list,[32,91|D1list],P2list),
  335	    atom_chars(Prompt,P2list)),
  336	nl, ask_chars(Prompt,0,255,Alist),
  337	(Alist == [], nonvar(Default) -> 
  338	    Answer = Default ;
  339	    atom_chars(Answer,Alist)
  340	).
  341
  342
  343%***********************************************************************
  344%*									
  345%* predicate: confirm/2	
  346%*									
  347%* syntax: confirm(+Clause_IDs,+Oldterm)	
  348%*									
  349%* args: Clause_IDs .. list of clauseIDs, 
  350%*       Oldterm.. term of the predicate to be replaced	
  351%*									
  352%* description:	confirm new clauses and rename the new predicate (using the oracle)
  353%*              if oracle refuses the new clauses, delete 'em.
  354%*              if they are accepted, delete the old ones (see g2_op).
  355%*									
  356%* example:								
  357%*									
  358%* peculiarities:							
  359%*									
  360%* see also:								
  361%*									
  362%***********************************************************************
  363
  364confirm( Clause_ids, L) :-
  365	oracle(Clause_ids, Ex),
  366	var(Ex),
  367	functor(L, Oldname, _),
  368	oracle(Oldname, Newname),
  369	rename(Clause_ids , Oldname, Newname), !.
  370
  371confirm( Clause_ids, _) :-
  372	delete_all(Clause_ids),
  373	nl, write('New clauses deleted.'),
  374	fail.
  375
  376
  377
  378%************************************************************************
  379%*
  380%* predicate: get_ci/2
  381%*
  382%* syntax: get_ci(+L,-L)
  383%*
  384%* args: L ... list of clauseIDs
  385%*
  386%* description: reads the IDs of the Ci used for the g2-operator one
  387%*              by one
  388%*
  389%* example:
  390%*
  391%* peculiarities:
  392%*
  393%* see also:
  394%*
  395%************************************************************************
  396
  397get_ci(Sofar, CC) :- 
  398	oracle('Please enter a resolvent ID followed by RETURN','stop',Answer),
  399	Answer \== 'stop',
  400	atom_chars(Answer,Idc),
  401	( number_chars(Id,Idc),
  402	  union(Sofar,[Id],Sofarnew) ->
  403	  true;
  404	  Sofarnew = Sofar
  405	),!,
  406	get_ci(Sofarnew, CC).
  407get_ci(CC, CC) :- !