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

fuzzy.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==          chapter 2, pages 39-40:  fuzzy set theory          ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

%  fuzzy_and/fuzzy_or/fuzzy_not do the fuzzy logic
%  equivalents of and/or/not

fuzzy_and(P,Q,PandQ) :-  min(P,Q,PandQ).
fuzzy_or(P,Q,PorQ)   :-  max(P,Q,PorQ).
fuzzy_not(P,NotP)    :-  NotP is 1-P.


%  fuzzy sets are encoded similar ordinary sets (that is as lists)
%  except the list contains (value,degree) pairs.

fuzzy_member(X,S,Degree) :-
            member((X,Degree),S).
fuzzy_member(X,S,0) :-
            \+ member((X,Degree),S).

%  the support of a fuzzy set is the (ordinary) set of all 
%  values which have a non-zero degree of membership

fuzzy_support([],[]).
fuzzy_support([(X,0)|Fs],Ss) :-
            fuzzy_support(Fs,Ss).
fuzzy_support([(X,Degree)|Fs],[X|Ss]) :-
            Degree \= 0,
            fuzzy_support(Fs,Ss).

%  The fuzzy union of two fuzzy sets F1 and F2 is the fuzzy sets
%  whose support is the union of the supports of F1 and F2
%  and the degree of membership of each element is the
%  fuzzy 'or' of the degree of membership of F1 and F2
%  This corresponds to ordinary logic where X is a member
%  of the union of S1 and S2 if it is a member of S1 *or*
%  it is also a member of S2.  In fuzzy logic this Boolean
%  or is replaced by its fuzzy equivalent.

fuzzy_union(F1,F2,F) :-
            fuzzy_support(F1,S1),
            fuzzy_support(F2,S2),
            union(S1,S2,Ss),
            do_union(F1,F2,Ss,F).

do_union(F1,F2,[],[]).
do_union(F1,F2,[X|Ss],[(X,Degree)|F]):-
            fuzzy_member(X,F1,D1),
            fuzzy_member(X,F2,D2),
            fuzzy_or(D1,D2,Degree ),
            do_union(F1,F2,Ss,F).

%  fuzzy intersection of F1 and F2 is similar except that its support
%  is the intersection of their supports, and the degree of membership
%  is the fuzzy and of the degree of membership of F1 and F2

fuzzy_intersect(F1,F2,F) :-
            fuzzy_support(F1,S1),
            fuzzy_support(F2,S2),
            intersect(S1,S2,Ss),
            do_intersect(F1,F2,Ss,F).

do_intersect(F1,F2,[],[]).
do_intersect(F1,F2,[X|Ss],[(X,Degree)|F]):-
            fuzzy_member(X,F1,D1),
            fuzzy_member(X,F2,D2),
            fuzzy_and(D1,D2,Degree),
            do_intersect(S1,S2,Ss,F).

Running this Code

%  RUNNING THIS CODE
%
%  Use the example in the book:
%>    fuzzy_and(0.9,0.6,Degree).
%
%  Try:
%>    fuzzy_support(
%+        [(porsche944,0.9),(bmw316,0.5),(vauxhallNova12,0.1)],  % FastCar
%+        Supp ).
%
%  and:
%>    fuzzy_intersect(
%+        [(porsche944,0.9),(bmw316,0.5),(vauxhallNova12,0.1)],  % Fast Car
%+        [(porsche944,0.6),(rollsRoyce,0.8)],            % Pretentious Car
%+        Result ).
%

Examples

%  EXAMPLES
%
%>  fuzzy_and(0.9,0.6,Degree).
%
%>  fuzzy_support(
%+        [(porsche944,0.9),(bmw316,0.5),(vauxhallNova12,0.1)],  % FastCar
%+        Supp ).
%
%>  fuzzy_intersect(
%+        [(porsche944,0.9),(bmw316,0.5),(vauxhallNova12,0.1)],  % Fast Car
%+        [(porsche944,0.6),(rollsRoyce,0.8)],            % Pretentious Car
%+        Result ).

Query

Response