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

bayes.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==            chapter 2, page 36:  Baysian inference           ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

%  The code uses the fact p(H,P) to record the initial probability 
%  of a hypothesis H, and p_eh(E,H,P) to record the probability of
%  the evidence E if H is true.
%
%  The predicate p_he(H,E,P) uses these to calculate the probability
%  of the hypthesis H if we observe the evidence E.
%  This in turn uses p_e_and_h(E,H,P) which calculates the probability
%  that both the evidence E is observed and that the hypothesis H is
%  true.

p(cold,0.2).
p(meningitis,0.000001).

p_eh(headache,cold,0.8).
p_eh(headache,meningitis,0.9).

p_he(H,E,P) :-
            p_e_and_h(E,H,Peh),
            sumall( Px, p_e_and_h(E,Hi,Px), Pe ),
            fdiv(Peh,Pe,P).
%            P is Peh/Pe.  % some Prologs bad at floating division

p_e_and_h(E,H,P) :- p(H,P1), p_eh(E,H,P2), P is P1*P2.

Running this Code

%  RUNNING THIS CODE
%
%  to calculate the probability of the patient having a cold
%  given the patient has a headache type:
%    p_he(cold,headache,P).
%  this should give the same answer as in the book!
%  The only other thing you can really do is work out the probability
%  of meningitis:
%    p_he(meningitis,headache,P).
%
%  To make things more interesting add the following facts:
%    hypothesis(h3,measles).
%    evidence(e1,headache).
%    evidence(e2,spots).
%    evidence(e3,'fear of light').
%    p(measles,0.01).
%    p_eh(headache,measles,0.9).
%    p_eh(spots,cold,0.0000001).      %  only happens for some other reason
%    p_eh(spots,meningitis,0.0000001). % ditto
%    p_eh(spots,measles,1.0).
%    p_eh('fear of light',cold,0.0000001).    %  as for spots
%    p_eh('fear of light',meningitis,0.7).
%    p_eh('fear of light',measles,0.0000001).
%
%  These are also in the file 'bayes2.p'
%
%  Now you can retry the goal 'p_he(cold,headache,P)'
%  The answer is different!
%  This is because we now know of another potential cause of headaches,
%  measles, so are less likely to attribute a headache to a cold,
%  although it is still the most likely cause.
%  However, if you look at 'p_he(meningitis,'fear of light',P)'
%  you will see that meningitis becomes very likely.
%  In fact, the only reason for putting a non-zero value in for colds
%  is that you may just happen to have someone with a cold who also
%  just happens to be sensitive to light.
%  If we instead set 'p_eh('fear of light',cold,0)' and
%  'p_eh('fear of light',measles,0)', then we would find that the
%  Baysian probability of meningitis would be 1.0 - certainty.
%  This would be because we would be saying that meningitis was the
%  ONLY possible cause of 'fear of light'.  So if we see anyone exhibiting
%  this symptom, they must have meningitis.


Examples

%  EXAMPLES
%
%>  p_he(cold,headache,P).
%  
%>  p_he(meningitis,headache,P).
%
%>  p_he(meningitis,'fear of light',P).

Query

Response