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

gimage.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==    chapter 8, image processing utilities                    ==
%  ==               the 'gimage' representation of a pixel image  ==
%  ==                                                             ==
%  ==          Prolog example, Alan Dix, September 1997           ==
%  ==                                                             ==
%  =================================================================

Code

%  Uses:
%      findone/2, findall/3, in_range/3 from file 'meta.p'
%      image_size/3, image_at/4 from file 'image.p'
%  Please:
%      consult('../util/meta.p').
%      consult('../util/list.p').   % used by 'meta.p'
%      consult('image.p').

%  In the image processing examples, several Prolog representations are
%  used for pixel images.

%  This file describes the 'gimage' representation.
%  It is not necessary to understand the details of this file in order
%  to understand the Prolog examples for this chapter.

%  The file 'image.p' has definitons of the simpler list of lists
%  representation and the file 'eximages.p' has the example images
%  from figures in the book.


%  Rather than explicitly constructing an image as a list it is
%  often easier to construct an image using a predicatelife_runage, ... other args, X, Y, Pixel)
%  which returns the filtered pixel at coordinaes X, Y
%  This leads to a second represnetation of an image using such
%  a predicate in a similar fashion to the findall meta-logical predicate.
%  A 'gimage' is a triple:  ((X,Y,P), (W,H), Goal)
%  The first part '(X,Y,P)' is always three variables whoch appear in Goal,
%  the second part '(W,H)' gives the width and height of the image
%  and the third part 'Goal' is a goal which if called when X and Y
%  are bound to values will bind P to the relevant pixel of the image.
%  Don't worry if you don't fully understand this representation,
%  it uses quite complex meta-logical aspects of Prolog, simply follow
%  the pattern of the various filters in the examples for this chapter.

%  Here's an example of a 'gimage' representing an image with a
%  diagonal line of 1s and zeros everywhere else.

gimage_diagonal_at(X,X,1) :- !.
gimage_diagonal_at(X,Y,0).
gimage_diagonal( Size, ((X,Y,P), (Size,Size), gimage_diagonal_at(X,Y,P)) ).
gimage_diagonal10( Diag10 )  :- gimage_diagonal( 10, Diag10).

%  Note that this is representing a 10 x 10 image in a few lines of Prolog.
%  The corresponding image starts:
%      [ [ 1,0,0,0,0,0,0,0,0,0 ],
%        [ 0,1,0,0,0,0,0,0,0,0 ]
%        [ 0,0,1,0,0,0,0,0,0,0 ]
%      ... etc.
%  In fact, we can make a 100 x 100 image by simply changing the numbers!

%  Here are corresponding predicates gimage_at/4 and raw_gimage_at/4
%  similar to those for list of list images.

gimage_at( (Loc,(Wid,Ht),Goal), X, Y, 0 ) :-
            nonvar(X), (X<1 ; X>Wid), !.    % out of bounds
gimage_at( (Loc,(Wid,Ht),Goal), X, Y, 0 ) :-
            nonvar(Y), (Y<1 ; Y>Ht), !.     % out of bounds
gimage_at( Gimage, X, Y, Pixel ) :-
            raw_gimage_at( Gimage, X, Y, Pixel ).

%  raw_image_at/4 seems as though it should be simple:
%        raw_image_at( ((X,Y,P),(W,H),Goal), X, Y, P ) :-
%                Goal.
%  However, this would NOT work as it would bind the (X,Y,P) part
%  of the image.  A second call for a different X,Y location would
%  then fail.
%  Instead, we can use findone/2 a meta-logical predicate which
%  runs a goal but only binds required variables.  This then protects
%  the gimage from unwanted bindings.

raw_gimage_at( ((X,Y,P),(W,H),Goal), X1, Y1, Pixel ) :-
            findone( Pixel, ( X=X1, Y=Y1, P=Pixel, Goal ) ).

%  gimage_size/3 is trivial, but included for completeness.

gimage_size( (Loc,(Wid,Ht),Goal), Wid, Ht ).

%  The predicate gimage_to_image/2 converts a 'gimage' to an ordinary,
%  list of lists image.
%  During the conversion it uses a third intermediate represntation
%  as a list of (X,Y,P) triples.

gimage_to_image( ((X,Y,P),(Wid,Ht),G), Image ) :-
            gimage_to_list( ((X,Y,P),(Wid,Ht),G), L ),
            image_size( Image, Wid, Ht ),
            list_to_image(L,Image).

gimage_to_list( ((X,Y,P),(W,H),G), L ) :-
            myfindall( (X,Y,P), (in_range(X,1,W),in_range(Y,1,H),G), L ).

list_to_image([], Image).
list_to_image([(X,Y,P)|L],Image) :-
            image_at(Image,X,Y,P), !,  % cut to allow tail recursion
            list_to_image(L,Image).

%  The predicate image_to_gimage/2 does the inverss job.
%  Calling 'image_to_gimage(Image,Gimage)' creates a gimage with
%  the equivalent content to the original image.
%  As you see, it is somewhat simplter than image_to_gimage!!

image_to_gimage( Image, ((X,Y,P), (W,H), image_at(Image,X,Y,P) ) ) :-
            image_size( Image, W, H ).

%  The (X,Y,P) list is intended primarily as an intermediate representation
%  but could be used for inputing spares images.  That is images with very
%  few non-zero pixels.
%  For example, here is code to construct an image with a single 1
%  in each corner:
%      sparse_image( The_Image ) :-
%          image_size( The_Image , 100, 100 ),
%          list_to_image( [ (1,1,1), (1,100,1), (100,1,1), (100,100,1) ]
%                         The_Image ),
%          default_to_zero( The_Image ).
%  This is clearly a lot smaller than the corresponding list of list
%  image and slightly more concise than the equivalent gimage.

%  The predicate default_image_to_zero/1 simply binds every undefined
%  (free variable) pixel of an image to zero.

default_image_to_zero( [] ).
default_image_to_zero( [Line|Image] ) :-
        default_row_to_zero( Line ),
        default_image_to_zero( Image ).

default_row_to_zero( [] ).
default_row_to_zero( [0|Line ] ) :-
        !, default_row_to_zero( Line ).
default_row_to_zero( [X|Line ] ) :-
        default_row_to_zero( Line ).

Running this Code

%  RUNNING THIS CODE
%
%  Try the gimage_at predicate in the diagonal image:
%>      gimage_diagonal10( Diag ),
%+      raw_gimage_at(Diag,3,3,P1),
%+      gimage_at(Diag,2,7,P2),
%+      gimage_at(Diag,15,-3,P3).    % default to zero
%
%  Now convert it to a list of lists image:
%>      gimage_diagonal( 5, Diag ),
%+      gimage_to_image(Diag,Image).
%  Doing 5x5 diagonal matrix as the 10x10 takes a long time!
%
%  To convince yourself, try converting an image back and forth:
%>      image_to_gimage( [[4,5,6],[7,8,9]], Gimage ),
%+      gimage_to_image(Gimage ,Image).
%
%  Did it come out right?
%
%  You can also try the example of the list, but do use a smaller
%  image for the sake of your screen phosphor!
%>      image_size( The_Image , 5, 5 ),
%+      list_to_image( [ (1,1,1), (1,5,1), (5,1,1), (5,5,1) ], The_Image ),
%+      default_image_to_zero( The_Image ).

Examples

%  EXAMPLES
%
%>   gimage_diagonal10( Diag ),
%+   raw_gimage_at(Diag,3,3,P1),
%+   gimage_at(Diag,2,7,P2),
%+   gimage_at(Diag,15,-3,P3).    % default to zero
%
%>   gimage_diagonal( 5, Diag ),
%+   gimage_to_image(Diag,Image).
%
%>   image_to_gimage( [[4,5,6],[7,8,9]], Gimage ),
%+   gimage_to_image(Gimage ,Image).
%
%>   image_size( The_Image , 5, 5 ),
%+   list_to_image( [ (1,1,1), (1,5,1), (5,1,1), (5,5,1) ], The_Image ),
%+   default_image_to_zero( The_Image ).


Query

Response