[comp.lang.prolog] An Eliza-like problem solving assistant

lagache@violet.berkeley.edu (Edouard Lagache) (03/21/88)

    The following program is the mockup of the Eliza-like problem solving
    assistant that was demoed at the March 10 meeting of the PROLOG Forum.
    The program is the result of 3 late night work, and NO claims of
    correctness or efficiency are expressed on implied.  On the contrary,
    suggestions for expansion or improvement are most welcome.  As stated
    earlier, it is hoped to turn this program into a group project, so
    we hope that there is plenty of room for expansion!

    There are some calls to my imfamous PROLOG libraries.  The 'window'
    and 'set_attribute' calls will only work on a Texas Instruments PC,
    so I leave it to you to omit, or port these calls to your system.
    There is one call to the predicate 'nthelem', I have enclosed a copy
    of the predicate at the end of the file.  There may be other calls
    that I have forgotten, if so let me know and I will provide the needed
    code.

    Hack to your hearts delight!

                                                    Edouard Lagache
                                                    lagache@violet.berkeley.edu

================================================================================

/* File: 'consulta.pro' */
/******************************************************************************/
/*                                                                            */
/*                  An A.I. Consultant for PROLOG Programmers                 */
/*                                                                            */
/*       This program is intended to serve as a "intelligent consultant"      */
/*  for PROLOG programs to turn to when encountering some impasse in a        */
/*  programming project.  The program is based on the "Eliza" program, but    */
/*  it designed to provide comments that might foster the user to "solve"     */
/*  his/her own problem.                                                      */
/*                                                                            */
/*               A collaborative project of the PROLOG Forum.                 */
/*    Release - 1.00,  March - 1988,  Copyright(C) 1988, The PROLOG Forum     */
/*                                                                            */
/*  Credits: The concept of an "Eliza" type program to help users with        */
/*           problem solving was first proposed (as far as we know) by        */
/*           Professor Charles Woodson of the School of Education at          */
/*           U.C. Berkeley.  He also built a small system in LISP for the     */
/*           purposes of demonstrating the concept to members of his LISP     */
/*           programming course.                                              */
/*                                                                            */
/******************************************************************************/

/*>> 'gethelp' is the routine that the user can call to get access to the <<*/
/*>> system.  E. Lagache, Ver-1.0, 3/88                                   <<*/
gethelp :- tell('_WINDOWS'), make_window(0,15,14,64), set_attribute(magenta),
           clear_screen, set_attribute(white),
           prtstr("Please describe your problem, type 'quit.' to resume work"),
           nl, converse, close_window, tell(user).

/*>> 'converse' is the main "looping" routine.  It takes a list of words <<*/
/*>> and searches for keywords.  Then it generates a response based on   <<*/
/*>> keywords.  The responses are randomized to make the system more     <<*/
/*>> "humanlike".   E.L.,  Ver-1.0, 3/88                                 <<*/
converse :- set_attribute(white), prtstr("<>-> "), set_attribute('yellow'),
            read_sentence(Request), nl, remove_duplicates(Request,Request1),
            make_reply(Request1,Reply), set_attribute(cyan),
            print_reply(Reply), nl, continue(Request1).

/* continue makes the recursive call to 'converse' if the user doesn't want */
/* quit */
continue(['quit','.']) :- set_attribute(white), pause.
continue(_) :- converse.

/* 'pause' uses the interval function to simply carry out some time consuming */
/* task to make a delay between the exit prompt, and the closing of the       */
/* window.                                                                    */
pause :- interval(1,X,10), fail.
pause.

/* 'print_reply' simply prints out the list of items recursively */
print_reply([]).
print_reply([Item|Rest]) :- print(Item), put(32), print_reply(Rest).


/*>>------------------------------------------------------------------------<<*/
/*>> 'make_reply' generates a response to a keyword in the users input text <<*/
/*>> it keeps a list of keywords and appropriate responses, and chooses one <<*/
/*>> randomly to provide a "natural" appearance.                            <<*/
/*>> E. Lagache,  Ver - 1.0, 3/88                                           <<*/
/* Exit comment */
make_reply(['quit','.'],['Thank','you','I','hope','these','comments','were',
                         'useful.']
          ).

/* Main test, select some set of keywords, test if they match, if so succeed */
/* otherwise fail and look at another possibility.                           */
make_reply(Sentence,Reply) :- word_class(Keywords,Responses),
                              intersection(Keywords,Sentence,List),
                              List \== [], !, length(Responses,Top),
                              irandom(1,Top,Number),
                              nthelem(Responses,Number,Reply).

/* if no keywords are found, then use default responses */
make_reply(_,Reply) :- default_responses(Responses), length(Responses,Top),
                       irandom(1,Top,Number), nthelem(Responses,Number,Reply).

/* 'remove_duplicates' returns a list that contains only one of each item.  */
/* This is necessary for the 'intersection' predicate, and makes the search */
/* less time consuming.  E.L. 3/88                                          */
remove_duplicates([],[]).
                             /* First case, don't copy duplicate items */
remove_duplicates([Item|Rest],NewRest) :- member(Item,Rest), !,
                                          remove_duplicates(Rest,NewRest).
                             /* If not duplicated, then copy */
remove_duplicates([Item|Rest],[Item|NewRest]):- remove_duplicates(Rest,NewRest).

/* 'intersection' return true if one of the keywords was found among the */
/* words typed in.  From C&M page 154 */
intersection([],X,[]).
intersection([X|R],Y,[X|Z]) :- member(X,Y), !, intersection(R,Y,Z).
intersection([X|R],Y,Z) :- intersection(R,Y,Z).

/*>> 'irandom' returns a integer in the range specified by the first two <<*/
/*>> arguments to the predicate, E. Lagache, Ver-1.0, 3/88               <<*/
/*>> Values for computation taken from the first edition of "Oh Pascal"  <<*/
/*>> By Clancy and Cooper (page-227).                                    <<*/
irandom(Lower,Upper,Number) :- get_seed(Seed),
                               Start is (25173*Seed + 13849) mod 65536,
                               Number is (Start mod (Upper - Lower)) + Lower.

/* 'get_seed' will in general be an implementation specific predicate.     */
/* For ADA PROLOG, 'get_seed' will return the number of logical inferences */
/* so far made, using the ADA specific 'licount' predicate                 */
get_seed(Seed) :- licount(Seed).



/*>>---------------------------------------------------------------------<<*/
/*>> 'read_sentence' is a routine to take user input and make a list of  <<*/
/*>> atoms out of it.  It is slightly modified from Clocksin & Mellish   <<*/
/*>> page 104.                                                           <<*/
read_sentence([W|Wa]) :- get0(C), readword(C,W,C1), restsent(W,C1,Wa).

/* Given a word and the character after it, read in the rest of the sentence */
restsent(W,_,[]) :- lastword(W),!.

restsent(W,C,[W1|Wa]) :- readword(C,W1,C1), restsent(W1,C1,Wa).

/* Read in a single word, given initial character, and remembering what */
/* character came after that word.                                      */
readword(C,W,C1) :- single_character(C), !, name(W,[C]), get0(C1).

readword(C,W,C2) :- in_word(C,NewC), !, get0(C1), restword(C1,Cs,C2),
                    name(W,[NewC|Cs]).

readword(C,W,C2) :- get0(C1), readword(C1,W,C2).

/* continue process of stringing characters of the same word together */
restword(C,[NewC|Cs],C2) :- in_word(C,NewC), !, get0(C1), restword(C1,Cs,C2).

restword(C,[],C).

/*  These characters form words on their own */
single_character(44).        /* , */
single_character(59).        /* ; */
single_character(58).        /* : */
single_character(63).        /* ? */
single_character(33).        /* ! */
single_character(46).        /* . */

/* These characters can appear within a word */
/* the second in_word clause converts letters to lower case */
in_word(C,C) :- C>96, C<123.                /* 'a' to 'z' */
in_word(C,L) :- C>64, C<91, L is C+32.      /* 'a' to 'z' */
in_word(C,C) :- C>47, C<58.                 /* '0' to '9' */
in_word(39,39).                             /* '\'' */
in_word(45,45).                             /* '-' */

/* These words terminate a sentence */
lastword('.').
lastword('!').
lastword('?').

/*>>-----------------------------------------------------------------------<<*/

/*>> 'word_class' and 'default_responses' contain the text that will be    <<*/
/*>> presented to the user.  'word_class' also contains the list of        <<*/
/*>> keywords, that will be used to decide if this type of response is     <<*/
/*>> appropriate.                                                          <<*/

/* --------------------- Programming specific keywords -------------------- */
/* Words related to failure to get the file to consult properly */
word_class([consult,consulting,compile,compiling,load,loads,loading],
           [
              ['Do',you,know,at,what,location,the,problem,'is?'],
              ['Could',the,problem,be,at,a,different,place,from,where,the,
               error,message,is,'reported?'
              ],
              ['What',sort,of,diagnostic,message,did,the,system,'give?'],
              ['What',sort,of,problems,could,have,caused,this,'situation?'],
              ['Is',there,another,way,you,could,arrange,your,file,that,might,
               make,it,easier,to,find,the,'problem?'],
           ]
          ).

/* Problems with incorrect output */
word_class([output,print,prints,printing,write,writes,writing,printout],
           [
              ['What',sort,of,output,were,you,'expecting?'],
              ['What',kind,of,output,did,you,actually,get,'(if','anything)?'],
              ['How',could,you,modify,your,program,to,get,more,information,
               about,this,'i/o','problem?'
              ],
              ['Can',you,see,where,in,the,program,the,bug,must,be,'located?'],
              ['How',could,you,further,localize,the,source,of,the,incorrect,
               'output?'
              ]
           ]
          ).

/* Input problems */
word_class([input,read,reads,reading],
           [
              ['How',do,you,that,the,problem,is,caused,by,incorrect,input,
               'routines?'
              ],
              ['How',could,you,modify,your,program,to,get,more,information,
               about,this,'i/o','problem?'
              ],
              ['How',could,you,further,localize,the,source,of,the,incorrect,
               input,'behavior?'
              ],
              ['How',could,you,test,these,input,routines,in,'isolation?'],
           ]
          ).

/* flow of control problems */
word_class([infinite,loop,recursion,stepping,trace,tracing],
           [
              ['Where',is,the,last,place,that,you,know,your,program,was,running,
               'correctly?'
              ],
              ['How',do,you,know,that,the,program,is,not,behaving,as,it,
               'should?'
              ],
              ['Which',predicates,could,have,caused,this,'phenomenon?'],
              ['Is',there,any,way,that,you,could,isolate,the,predicates,that,
               are,at,'fault?'
              ],
           ]
         ).
/* Error word */
word_class([error,warning,failure,diagnostics],
           [
              ['Can',you,isolate,the,error,to,one,'place?'],
              ['Can',you,find,a,reasonable,interpretation,for,these,
               diagnostics
              ],
              ['Have',you,encountered,similar,sorts,of,messages,in,the,
               'past?'
              ],
              ['What',sort,of,information,would,allow,you,to,deal,with,this,
               'message?'
              ],
           ]
          ).

/* Logical errors */
word_class([infer,inference,deduce,deduction,entails,entailment],
           [
              ['What',should,have,the,system,'deduced?'],
              ['What',was,the,last,inference,that,you,know,was,'correct?'],
              ['How',do,you,know,that,the,inference,was,in,fact,incorrect,
               '(given',the,systems,actual,'configuration)?'
              ],
              ['What',sort,of,database,condition,could,have,caused,the,
               observed,'deductions?'
              ]
           ]
          ).

/* Bug talk */
word_class([bug,malfunction,wrong,incorrect,incomplete,unexpected],
           [
              ['How',do,you,know,you,have,a,'bug?'],
              ['Where',is,the,last,place,that,you,know,your,program,was,
               functioning,'correctly?'
              ],
              ['What',program,behavior,where,you,'expecting?'],
              ['What',indicates,that,something,is,'wrong?'],
              ['What',occurred,that,was,not,'expected?'],
              ['What',information,would,you,need,to,isolate,the,'bug?'],
              ['what',would,you,need,to,know,to,locate,the,'malfunction?'],
              ['What',tests,could,you,perform,to,get,at,the,'problem?'],
           ]
          ).

/* -----------------  Problem solving keywords  ------------------------- */
/* Alternatives */
word_class([option,options,alternatives,possible,possibilities],
           [
              ['What',alternatives,have,you,already,'tried?'],
              ['Are',there,other,possibilities,that,you,might,'consider?'],
              ['Which',options,have,you,already,'tried?'],
              ['Might','I',suggest,that,you,take,a,new,look,at,your,
               'alternatives.'
              ],
           ]
          ).
/* Reflection, on previous work */
word_class([tried,attempted,thought],
           [
              ['What',have,you,done,in,the,past,in,such,'situations?'],
              ['Tell',me,which,approaches,you,have,already,'tried?'],
              ['What',have,you,attempted,'previously?'],
              ['What',have,you,done,here,that,you,might,want,to,do,differently,
               in,the,'future?'
              ]
           ]
          ).

/* Strategic problem solving, evaluating plans */
word_class([try,attempt,do,complete,investigate,think,thinking],
           [
              ['How',will,trying,this,help,you,out,of,your,'impasse?'],
              ['What',can,you,learn,from,doing,'this?'],
              ['Are',you,sure,that,there,is,not,a,more,productive,investigation,
               that,you,could,'make?'
              ],
              ['Are',there,better,ways,to,get,the,information,you,need,to,solve,
               this,'problem?'
              ],
           ]
          ).

/* -------------------------- Human Psychology words ----------------------- */
/* stuck words */
word_class([stuck,stopped,impasse],
           [
              ['Perhaps',you,should,reflect,back,on,the,various,'possibilities.'
              ],
              ['There',must,be,alternatives,that,you,have,not,'considered.'],
              ['I',suggest,that,you,step,back,from,the,problem,and,review,
               what,you,have,'tried.'
              ],
           ]
          ).
/* "down" words */
word_class([depress,depressing,depressed,frustrating,frustrated,mad,annoy,
            annoyed,annoying
           ],
           [
              ['It',is,not,a,good,idea,to,get,worked,up,about,a,'program.'],
              ['One',should,not,take,this,too,'seriously,',after,all,it,is,
               only,a,'program.'
              ],
              ['If',this,task,is,getting,to,you,perhaps,you,should,take,a,break,
               and,come,back,to,it,'later.'
              ],
              ['Perhaps',you,have,been,working,too,long,on,this,one,'problem,',
               maybe,you,should,take,a,'break.'
              ],
              ['Do',you,tell,me,that,this,program,is,getting,to,'you!'],
              ['Well',nobody,said,that,programming,was,'easy.'],
              ['Do',not,get,worked,up,over,'this,','after,all,',no,program,that,
               is,interesting,is,easy,to,'write.'
              ]
           ]
         ).

/* "Bad" words (should this sort of thing be censored!?!) */
word_class([fuck,fucking,shit,shitty,damn,screw,screwed,hell],
           [
              ['Well','I',hope,that,relieves,your,'aggressions;',now,can,
               we,get,back,to,'work?'
              ],
              ['I',am,glad,you,know,'profanity;',unfortunately,this,system,
               only,understands,'PROLOG!'
              ],
              ['Yes,','yes,',profanity,is,the,language,that,all,programmers,
               know,'best!'
              ],
              ['If',you,can,not,say,anything,more,'constructive,',perhaps,
               you,should,take,a,break,and,come,back,to,this,'problem.'
              ],
              ['Sorry',that,language,is,not,in,my,'vocabulary!'],
           ]
         ).

/*  Help words */
word_class([help,assistance,explain,explanation],
           [
              ['In',what,area,do,you,need,some,'assistance?'],
              ['Can',you,be,more,specific,about,what,sort,of,help,you,'need?'],
              ['Exactly',what,sort,of,information,do,you,'seek?'],
              ['In',what,way,may,'I',be,of,'assistance?'],
              ['What',kind,of,advice,do,you,'need?'],
              ['Exactly',in,what,area,do,you,need,an,'explanation?'],
              ['Please',tell,me,background,about,your,'problem?'],
              ['Could',you,further,elaborate,on,the,type,of,problem,you,are,
               'having? '
              ]
           ]
          ).

default_responses([
                   ['Please','continue.'],
                   ['Could','you','say','more','about','your','problem.'],
                   ['I','would','like','to','hear','some','more','specifics.'],
                   ['Could','you','please','elaborate','on','one','aspect',
                    'of','your','problem.'
                   ],
                   ['Is',there,anything,else,that,you,know,about,this,
                    'problem?'
                   ],
                   ['I',do,not,quite,understand,the,'situation;',could,you,
                    elaborate,it,for,'me?'
                   ]
                  ]
                 ).

/* * * * * * * * * * * * * * * * * * * * * * * */
/*  'nthelem' returns the element in the       */
/*  'Index' place of the list.                 */
/*                                             */
/*     E. Lagache,  Vers. - 1.00, Dec - 86     */
/* * * * * * * * * * * * * * * * * * * * * * * */
nthelem([],_,error):- !, fail.  /* fail if list is smaller than index */
nthelem([Item|_],1,Item):- !.   /* return item */
nthelem([X|Rest],NewIndex,Item):- Index is NewIndex-1,nthelem(Rest,Index,Item).

/* end file consulta.pro */

ok@quintus.UUCP (Richard A. O'Keefe) (03/24/88)

In article <7845@agate.BERKELEY.EDU>,
lagache@violet.berkeley.edu (Edouard Lagache) distributed
an "Eliza-like problem solving assistant".

(1) In the tables at the end of the program, the pattern
	word_class([...],
	    [
		[...],
		...
		[...],
*--------------------^
	    ]).
    occurs quite often.  While C allows extra commas in initialisers,
    many Prolog systems will be unhappy about that extra comma.

(2) In order to test whether any of a given list of Keywords occurs in
    a given Sentence, the program does

	intersection(Keywords, Sentence, List),
	List \== [],

    This is correct, but there isn't a lot of point in constructing List.
    A more efficient approach (effiency is not a concern in this program)
    would be to call

	intersect(Keywords, Sentence)

    where for example

	intersect(Set1, Set2) :-
		member(X, Set1),
		member(X, Set2),
		!.

(3) I thought I'd try the program.  This is what I got:
Please describe your problem.  Type 'quit.' to resume work.
e> My nematodes have been eaten by the peripatus.
Could you say more about your problem. 
e> Yes.
Could you please elaborate on one aspect of your problem. 
e> Well, the peripatus crawled out of its box last night, and it got into
e> another box on the same bench, where we keep nematodes, and well, it
e> ate the lot of them.
Is there anything else that you know about this problem? 
e> I suppose there are two problems, really.  One problem is how do I
e> stop this sort of thing in the future, and the other is where do I
e> get some more nematodes right now.  I want your help with the second
e> part of the problem.
What can you learn from doing this? 
e> From doing WHAT?
Could you say more about your problem. 
e> I just told you everything there was to say.
Could you say more about your problem. 
e> You're getting a bit repetitious, aren't you?
I do not quite understand the situation; could you elaborate it for me? 
e> Gods below, what is there to understand?  I need some nematodes, I
e> had some nematodes, but Hodgkins' wretched peripatus ate them.
Is there anything else that you know about this problem? 
e> Oh forget it.
Could you say more about your problem. 
e> quit.

    In case you were wondering, the e> lines do make sense.

(4) Part of the reason for the frustrating and unhelpful nature of the
    conversation shown is that the program is not Eliza-like.  One of
    the things that Eliza would do is pick up phrases of yours and
    throw them back at you.  For example, after my third input, an
    Eliza-like program might say
	Tell me more about the box.
    			   ^^^^^^^----- copied from input
    or after the last input but two,
	Why did Hodgkins' wretched peripatus eat them?
		^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ transformed input