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

certf.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==         chapter 2, pages 37-38:  certainty factors          ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

mb(foggy,'air is moist',0.5).
md(foggy,'air is moist',0.1).
mb(foggy,'poor visibility',0.7).
md(foggy,'poor visibility',0.0).

%  The predicate cf(H,E,CF) calculates the certainty factor of 
%  an hypothesis H given a single evidence E

cf(H,E,CF) :- 
            mb(H,E,MB),
            md(H,E,MD),
            CF is MB-MD.

%  There are two versions of the predicates.
%  The first version of each mb0 and md0 uses the formulae
%  to calculate the combined measure of belief/disbelief
%  The second version of each mb and md, adds in the extra
%  rule which says that each is 0 if the other is 1.
%  If we coded this with a single predicate, then 

mb0(H,E1,E2,MB) :-
            mb(H,E1,MB1),
            mb(H,E2,MB2),
            MB is MB1 + MB2*(1-MB1).
md0(H,E1,E2,MD) :-
            md(H,E1,MD1),
            md(H,E2,MD2),
            MD is MD1 + MD2*(1-MD1).

mb(H,E1,E2,0)  :-  md0(H,E1,E2,1).
mb(H,E1,E2,MB) :-  \+ md0(H,E1,E2,1), mb0(H,E1,E2,MB).

md(H,E1,E2,0)  :-  mb0(H,E1,E2,1).
md(H,E1,E2,MD) :-  \+ mb0(H,E1,E2,1), md0(H,E1,E2,MD).

%  Note the trick here, mb/3 are the facts and mb/4 is
%  the calculation.  We are usingh the same predicate name
%  with different numbers of arguments.

%  the certainty factor calculations are identical to cf/3

cf(H,E1,E2,CF) :- 
            mb(H,E1,E2,MB),
            md(H,E1,E2,MD),
            CF is MB-MD.

Running this Code

%  RUNNING THIS CODE
%
%  First of all check the certainty factor calculations for
%  single evidences:
%>      cf(foggy,'air is moist',CF).
%>      cf(foggy,'poor visibility',CF).
%  then try to combine evidence:
%      cf(foggy,'air is moist','poor visibility',CF).
%
%  You can also examine the calculated measures of belief and
%  disbelief given the combined evidence:
%>      mb(foggy,'air is moist','poor visibility',MB).
%>      md(foggy,'air is moist','poor visibility',MD).
%

%  MORE EVIDENCE
%
%  We can do the same for a whole list of evidences
%  Obviously more types of evidence would need to be included
%  In the database for this to be useful!

mb0_list(H,[],0).
mb0_list(H,[E|Rest],MB) :-
            mb(H,E,MBe),
            mb_list(H,Rest,MBrest),
            MB is MBe + MBrest*(1-MBe).
md0_list(H,[],0).
md0_list(H,[E|Rest],MD) :-
            md(H,E,MDe),
            md_list(H,Rest,MDrest),
            MD is MDe + MDrest*(1-MDe).

mb_list(H,Elist,0)  :-  md0_list(H,Elist,1).
mb_list(H,Elist,MB) :-  \+ md0_list(H,Elist,1), mb0_list(H,Elist,MB).

md_list(H,Elist,0)  :-  mb0_list(H,Elist,1).
md_list(H,Elist,MD) :-  \+ mb0_list(H,Elist,1), md0_list(H,Elist,MD).

cf_list(H,Elist,CF) :- 
            mb_list(H,Elist,MB),
            md_list(H,Elist,MD),
            CF is MB-MD.

%
%  check with a few examples that 'cf_list(H,[E1,E2],MB)' gives the same
%  answer as 'cf(H,E1,H2,MB)'


Examples

%  EXAMPLES
%
%>   cf(foggy,'air is moist',CF).
%
%>   cf(foggy,'poor visibility',CF).
% 
%>   cf(foggy,'air is moist','poor visibility',CF).
%
%>   mb(foggy,'air is moist','poor visibility',MB).
%
%>   md(foggy,'air is moist','poor visibility',MD).

Query

Response