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

life.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==       chapter 10, pages 240-241:  Conways game of Life      ==
%  ==                                                             ==
%  ==          Prolog example, Alan Dix, September 1997           ==
%  ==                                                             ==
%  =================================================================

Code

%  Uses:
%      filter_at/5     -  from file 'filter.p'
%  Please:
%      consult('../ch8/filter.p').
%      consult('../util/math.p').  % \
%      consult('../util/meta.p').  %  \
%      consult('../util/list.p').  %   > -  used by 'filter.p'
%      consult('../ch8/image.p').  %  / 
%      consult('../ch8/gimage.p'). % /

%  The code for Life uses the image processing predicates
%  developed for chapter 8
%  The code is similar to that in the file 'threshold.p'
%  except that it has a more complicated thresholding function
%  (either 3 or 4 rather than over a given value) and also
%  pre-filters each pixel using a 3x3 filter:
%      [ [ 1, 1, 1 ],
%        [ 1, 0, 1 ],
%        [ 1, 1, 1 ] ]
%  This filter effectively counts the population of the neighbouring cells

life_threshold( Pixel, 0 ) :- Pixel < 3, !.
life_threshold( Pixel, 0 ) :- Pixel > 4, !.
life_threshold( Pixel, 1 ).

life_at( Input, X, Y, Out_Pix ) :-
            X1 is X-1, Y1 is Y-1,
            filter_at( Input, [[1,1,1],[1,0,1],[1,1,1]], X1, Y1, In_Pix ),
            life_threshold( In_Pix, Out_Pix ).

life_step( Input, Wid, Ht, Output ) :-
            gimage_to_image( ( (X,Y,P), (Wid,Ht),
                               life_at(Input,X, Y, P) ),
                             Output ).

draw_life( [] ).
draw_life( [Col|Rest] ) :-
        draw_life_col( Col ), nl,
        draw_life( Rest ).

draw_life_col( Col ) :- write(Col).



run_life( Input, Wid, Ht, Nos_steps, Output ) :-
        Nos_steps > 0, !,
        draw_life( Input ), nl,
        write('time left:'), write(Nos_steps), nl, nl,
        life_step( Input, Wid, Ht, One_step ),
        N1 is Nos_steps-1, !,
        run_life( One_step, Wid, Ht, N1, Output ).

run_life( Input, _, _, Nos_steps, Input) :-
        Nos_steps =< 0,
        draw_life( Input ), nl,
        write('finished!'), nl, nl.


%  Initial state in figure 10.2

example_life( 'figure 10.2', [ [ 0, 0, 0, 0, 0 ],
                               [ 0, 0, 1, 1, 0 ],
                               [ 0, 1, 1, 1, 0 ],
                               [ 0, 1, 0, 0, 0 ],
                               [ 0, 0, 0, 0, 0 ] ] ).

Running this Code

%  RUNNING THIS CODE
%
%  To reproduce the example in figure 10.2 type:
%
%>     example_life( _, Initial ),
%+     run_life( Initial, 5, 5, 7, Final ).
%
%  Notice how it reaches a pair of alternating states.


Query

Response