An introduction to Artificial Intelligence. Finlay and Dix. 1st Edition.

prod.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==          chapter 1, pages 19-20:  production rules          ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

%  To some extent production rules look quite like logical rules.
%  However, the underlying model in a production rule system is a
%  'state' which is being updated, very different form the declarative
%  model of pure Prolog.
%  This program therefore make liberal use of 'assert' and 'retract'
%  to store the state of the production rule system in Prolog's
%  database of facts.
%  It is possible to make the effect of a changing state in Prolog
%  using more pure Prolog code, but it is less clear.

fact(X,Y) :- clause(prod_memory(X,Y),_).  % use clause to avoid predicate existence errors if there is no matching term

unknown(X) :- \+ fact(X,Y).   %   \+ means 'not provable', ir in this case 

prod_set(X,Y) :- assertz(prod_memory(X,Y)).

prod_forget(X) :- retract(prod_memory(X,Y)).

show_memory :- fact(X,Y), write(fact(X,Y)).
show_memory.

init .

clear_database :-
           retract(prod_memory(X,Y)), fail.
clear_database.

finish:-   assertz(finished).
is_finished:-   clause(finished,_).  % like prod_fact, use clause to prevent predicate existence error

ask(X) :-  write(X), nl.

say(X) :-  write(X), nl.
say(X,Y) :- write(X), write(Y), nl.

%  The coding of production system rules in Prolog is quite easy.
%  However, it looks rather strange as both the IF and THEN parts are
%  coded similarly.  Given a Prolog clause of the form 'A :- B' is often
%  interpretted as saying 'if B then A', we might have exepected the THEN
%  part of the production rule to have sat on the left hand side of the
%  Prolog clauses.  The reason for this paradox is that the 'then' in
%  pure logical interpretation of Prolog clauses is logical entailment
%  whereas the THEN part of a production rule is action based: 'IF this
%  is true THEN do that'.  This sequencing is captured by the two things
%  in the Prolog:
%  *  First, the IF part precedes the THEN part and because the right
%     hand side of the Prolog clause is tested term by term, the THEN
%     part is never executed unless the IF part is true.
%  *  Second, the sort of things that sit in the IF and THEN parts are
%     different.  The terms in the IF part are pure test of the state of
%     the system, which may fail to be true, but never change the state.
%     In contrast, the terms in the THEN part always succeed exactly once
%     and have side effects.
%  
%  With ruleset only one of the rules ever has an IF part true at any time.
%  With different rules, the order in which rules are executed might vary
%  but with production rules, one should not expect any particular order 
%  of rule firing amongst those where the IF part is true.

rule(1) :- unknown(client_working),              % IF part
           % ------------------------
           ask('Are you working?'),              % THEN part
           read(WORKING),
           prod_set(client_working,WORKING).


rule(2) :- fact(client_working,yes), unknown(salary),     % IF part
           % ------------------------
           ask('What is your salary?'),                   % THEN part
           read(SALARY),
           prod_set(salary,SALARY).

rule(3) :- fact(client_working,yes), fact(salary,SALARY),    % IF part
           fact(request,AMOUNT), SALARY >= (5*AMOUNT),
           % ------------------------
           say('grant loan of ',AMOUNT),                     % THEN part
           clear_database,
           finish.

rule(4) :- fact(client_working,yes), fact(salary,SALARY),    % IF part
           fact(request,AMOUNT), SALARY < (5*AMOUNT),
           % ------------------------
           GRANTED is (SALARY/5),                            % THEN part
           say('grant loan of ',GRANTED),
           clear_database,
           finish.

rule(5) :- fact(client_working,no), unknown(client_student),   % IF part
           % ------------------------
           ask('Are you a student?'),                          % THEN part
           read(STUDENT),
           prod_set(client_student,STUDENT).

rule(6) :- fact(client_working,no), fact(client_student,yes),  % IF part
           % ------------------------
           say('We need to discuss a student loan'),           % THEN part
           clear_database,
           finish.

rule(7) :- fact(client_working,no), fact(client_student,no),   % IF part
           % ------------------------
           say('Your request for a loan is refused'),          % THEN part
           clear_database,
           finish.


r_rules :- rule(R), is_finished.  %  Keeps on executing rules until either
                                  %  finished is true, or no further rule
                                  %  can execute
r_rules :- write('r_rules done').

run_rules :- r_rules.
run_rules :- is_finished, retract(finished), !.  % cut to prevent next clause from running
run_rules :- say('I do not know what to do!').
                               %  Last clause should never be executed as
                               %  the production rules should always lead
                               %  to a finished state.


clean_up :- clear_database, retract(finished).
clean_up.                      %  ensure that things start with
                               %  a clean slate.

execute :-  clean_up,
           init,
           ask('How much do you want to loan?'),
           read(Amount),
           prod_set(request,Amount),
           run_rules.

Running this Code

%  RUNNING THIS CODE
%
%  This is an interactive program.
%  To start it simply type 'execute.'
%
%  You are asked to input various information.
%  Answer 'yes.' or 'no.' to yes/no questions (such as 'Are you working?')
%  and a number followed by a full stop (e.g. '1500.') to amount questions.
%
%  Input is read using Prolog's in-built 'read' predicate.  This reads a
%  Prolog term which is why you need a full stop after everything.  It also
%  means that you can't read in multi-word answers unless there is a full
%  stop between each word, or the whole thing is quoted!
%  The 'get' and 'get0' predicate allow more control over input, but only
%  work a character at a time, so need more code around them to read
%  numbers etc.
%  Your Prolog system may have a fuller set of input/output primatives
%  possibly including window-based interfaces.
%

Examples

%  EXAMPLES
%
%>  execute.

Query

Response