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

filter.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==           chapter 8, pages 169-172:  digital filters        ==
%  ==                      pages 174-175:  gradient filters       ==
%  ==                                                             ==
%  ==          Prolog example, Alan Dix, September 1997           ==
%  ==                                                             ==
%  =================================================================

Code

%  The files 'image.p' and 'gimage.p' describe the image representations
%  used in this file and predicates to manipulate them..

%  Uses:
%      min/3, round/2    -  from file 'math.p'
%      sumall/3          -  from file 'meta.p'
%      image_at/4, image_size/3 -  from file 'image.p'
%      gimage_at/4, gimage_size/3,            - from file 'gimage.p'
%      image_to_gimage/2, gimage_to_image/2       "    "      "
%  Please:
%      consult('../util/math.p').
%      consult('../util/meta.p').
%      consult('../util/list.p').   % used by 'meta.p'
%      consult('image.p').
%      consult('gimage.p').

sub_image_at(Image,Xpos,Ypos,X,Y,Pixel) :-
        X1 is Xpos-1+X, Y1 is Ypos-1+Y,
        image_at(Image,X1,Y1,Pixel).
sub_image(Image,Xpos,Ypos,W,H,Gimage) :-
        Gimage = ( (X,Y,P), (W,H), sub_image_at(Image,Xpos,Ypos,X,Y,P) ).

multiply_gimages_at( A, B, X, Y, Res) :-
        gimage_at(A,X,Y,Pa),
        gimage_at(B,X,Y,Pb),
        Res is Pa * Pb.

multiply_gimages( A, B, Res) :-
        gimage_size(A,Wa,Ha),
        gimage_size(B,Wb,Hb),
        min(Wa,Wb,W),  min(Hb,Hb,H),
        sumall( V, ( in_range(X,1,W),in_range(Y,1,H),
                     multiply_gimages_at(A,B,X,Y,V) ),  Res ).

filter_at( Input, Filter, X, Y, Out_Pix ) :-
            image_size(Filter,Wf,Hf),
            sub_image( Input, X, Y, Wf, Hf, Window),
            image_to_gimage( Filter, Gfilter ),
            multiply_gimages( Gfilter, Window, Out_Pix ).

filter_image( Input, Filter, Wid, Ht, Output ) :-
            image_size(Filter,Wf,Hf),
            W is Wid+1-Wf,  H is Ht+1-Hf,
            gimage_to_image( ( (X,Y,P), (W,H),
                               filter_at(Input,Filter,X, Y, P) ),
                             Output ).

scale_image( [], Scale, [] ).
scale_image( [Row|Image], Scale, [Scaled_Row|Scaled_Image] ) :-
            scale_row( Row, Scale, Scaled_Row ),
            scale_image( Image, Scale, Scaled_Image ).

scale_row( [], Scale, [] ).
scale_row( [Pixel|Row], Scale, [Scaled_Pixel|Scaled_Row] ) :-
            X is Pixel * Scale,
            round(X,Scaled_Pixel),
            scale_row( Row, Scale, Scaled_Row ).

Running this Code

%  RUNNING THIS CODE
%
%  The file 'eximages.p' contains example images from all the figures
%  in chapter 9.  In particular, it has the pixel images used in the
%  filtering examples in figure 8.5, 8.6, 8.7, 8.9 and 8.10.
%  Consult this file:
%        consult('eximages.p').
%
%
%  Figure 8.5 - applying a digital filter
%>        image('figure 8.5', Wid, Ht, Image),
%+        Filter = [[0,1,0],[1,-4,1],[0,1,0]],
%+        filter_image( Image, Filter, Wid, Ht, Output ).
%
%  N.B.  you may notice a discrepency between the Prolog output
%        and figure 8.5 in the book.  The last value of the third
%        row is -6 in the book and -4 in the poutput here.
%        The figure in the book was hand calculated.
%        The Prolog is right.
%
%
%  Figure 8.6 - applying a 2x2 smoothing filter
%>        image('figure 8.6', Wid, Ht, Image),
%+        Filter = [[1,1],[1,1]],
%+        filter_image( Image, Filter, Wid, Ht, Output ),
%+        scale_image(Output,0.25,Scaled).
%
%  N.B.  again a discrepency - the 2nd row 4th value should
%        be 4 not 0 as in figure 8.6 in the book.
%
%
%  Figure 8.9 - applying gradient filters
%  N.B.  in both the below there are small differences due to rounding.
%        In the hand calculations the ones became zeros - oops!
%
%  horizontal filter:
%>        image('figure 8.9', Wid, Ht, Image),
%+        Horizontal = [[-1,0,1],[-2,0,2],[-1,0,1]],
%+        filter_image( Image, Horizontal, Wid, Ht, Output ),
%+        scale_image(Output,0.125,Scaled).
%
%
%  vertical filter:
%>        image('figure 8.9', Wid, Ht, Image),
%+        Vertical = [[-1,-2,-1],[0,0,0],[1,2,1]],
%+        filter_image( Image, Vertical , Wid, Ht, Output ),
%+        scale_image(Output,0.125,Scaled).
%
%
%  Figure 8.10 - gradient filter on a diagonal edge
%>        image('figure 8.10', Wid, Ht, Image),
%+        Horizontal = [[-1,0,1],[-2,0,2],[-1,0,1]],
%+        filter_image( Image, Horizontal, Wid, Ht, Output ),
%+        scale_image(Output,0.125,Scaled).
%


Query

Response