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

forback.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==  chapter 2, pages 33-34:  forwards and backwards reasoning  ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

%  ** uses set predicates:  member/2, subset/2
%  ** see list.p for definitions if not available on your Prolog

%  Prolog has its own reasoning engine.  It uses a form of backwards
%  reasoning.
%
%  For example, suppose Prolog has the following rules:
%      A :- B, C
%      C :- D
%      B :- D, E
%  You then ask it to deduce A from the given facts D,E.  It proceeds
%  as follows:
%        1.  in order to prove A both B and C must be true
%        2.  look at B first
%          2.1.  in order to prove B both D and E must be true
%          2.2.  look at D first - it is true!
%          2.3.  now look at E - it is true!
%          2.4   D and E are true so B is true too
%        3.  now look at C
%          2.1.  in order to prove C, D must be true
%          2.2.  D is true!
%          2.3.  so C is true too
%        4.  both B and C are true so A must be true
%
%  See how this works backwards from what you want to prove (A) towards
%  what you know to be true (D and E).
%
%  Because this is built in to the way Prolog works it is quite hard to
%  actually be aware of this reasoning, and harder still to make Prolog
%  think the other way round and do forwards reasoning.
%
%  In order to demonstrate both forms of reasoning, the following example
%  makes the deduction mechanism explicit.
%  Things that are true are stored as a list of facts and rules stored
%  in the form:  rule( thing to be proved, [ list of conditions ] ).
%  So, the above example is coded:

rule(a,[b,c]).
rule(c,[d]).
rule(b,[d,e]).

%  There are two reasoning predicates:
%      forward([list of premises],conc).
%      backward([list of premises],conc).
%  Both succeed if it is possible to conclude 'conc' from the premises

%  Forward uses a cut (!) to force Prolog to operate in a sequential
%  manner.  This is because we do not want Prolog to use its normal
%  reasoning mechanism.

% ---------
%  FORWARD
% ---------

forward(P,C) :- member(C,P).
forward(P,C) :- \+ member(C,P), extend(P,Q), !, forward(Q,C).

extend(P,[A|P]) :- rule(A,L), \+ member(A,P), subset(L,P),
                   log_extend(A,L,P).
        %  'extend' finds a rule the conclusion of which is not already
        %  in the list of known facts (P) and the premises of which
        %  are all already known to be true.  The conclusion of the rule
        %  is then added to P to give the new set of known facts

log_extend(A,L,P) :- write(['given: ', P, 'using the rule: ', A, ' :- ', L, 'deduce: ', A]), nl.
        %  redefine log_extend to reduce or remove the trace of deductions

% ----------
%  BACKWARD
% ----------

backward(P,C) :- back1(0,P,C).

back1(N,P,C) :- member(C,P),
                log_back1_premise(N,C).
back1(N,P,C) :- \+ member(C,P), 
                rule(C,L), log_back1_rule(N,C,L),
                N2 is N+1, back2(N2,P,L), log_back1_proved(N,C).
back1(N,P,C) :- member(C,P),
                log_back1_false(N,C).

back2(N,P,[]) :- log_back2_done(N).
back2(N,P,[C|R]) :-
                 log_back2_next(N,C),
                 N2 is N+1, back1(N2,P,C),
                 back2(N,P,R).

%  again, redefine these logging predicates to reduce the amount
%  of tracing.

log_back1_premise(N,C) :-  tab(N), write([C,' is a premise']), nl.
log_back1_rule(N,A,L)  :-  tab(N), write(['using the rule: ',A,' :- ',L]), nl.
log_back1_proved(N,C)  :-  tab(N), write([C,' is proven!']), nl.
log_back1_false(N,C)   :-  tab(N), write([C,' is false']), nl.

log_back2_done(N)    :-  tab(N), write('all proved'), nl.
log_back2_next(N,C)  :-  tab(N), write(['proving ',C]), nl.

tab(0).
tab(N) :- N > 0, write('  '), N2 is N-1, tab(N2).

Running this Code

%  RUNNING THIS CODE
%
%  use:  'forward([d,e],a).'  and 'backward([d,e],a).'
%  to see a successful chain of deduction.
%  try:  'forward([d,f],a).'  and 'backward([d,f],a).'
%  to see what happens when they fail.
%
%  Try defining your own rules and see how forward and backward behave.
%  You can use variables in the rules as in ordinary Prolog:
%  For example:    rule(sibling(Y,Z),[parent(X,Y),parent(X,Z)]).
%
%  To see Prolog's own backwards reasoning at work use your Prolog
%  interpreter's trace facility.
%

%  META-INTERPRETERS
%
%  'forward' and 'backward' are examples of meta-interpreters.
%  They are interpreters for a logic programming language written
%  in Prolog - an interpreted logic programming language.
%  These versions do not accpet all of Prolog (e.g. no cuts within
%  the rules).  However, it is possible to write more extensive
%  meta-interpreters which can execute all of Prolog.
%  You may wonder why this is useful.  In fcat the above examples
%  show you.  Researchers in AI and logic programming often want to
%  experiment with different sorts of reasoning mechanisms.  It would be
%  possible to write an interpreter in another language, such as C, but
%  Prolog givres you a lot for free, including:
%    *  backtracking: trying different things when the first thing
%                     doesn't work
%    *  unification:  matching partially defined terms
%    *  database:     flexibly accessed using unification
%    *  structures:   using terms including reading and writing
%  Of course, sometimes the things that come for free get in the
%  way, and one has to do nasty things to get round them.
%  But even given that, the above forward reasoning system would not
%  have been as short or as quick to program in a language such as
%  C or Pascal.
%


Examples

%  EXAMPLES
%
%> forward([d,e],a).
%
%>  backward([d,e],a).
%  
%>  forward([d,f],a).
%
%>  backward([d,f],a).

Query

Response