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

hanint.p

download

Header

%  =================================================================
%  ==                                                             ==
%  ==          An Introduction to ARTIFICIAL INTELLIGENCE         ==
%  ==                  Janet Finlay and Alan Dix                  ==
%  ==                       UCL Press, 1996                       ==
%  ==                                                             ==
%  =================================================================
%  ==                                                             ==
%  ==        chapter 3, pages 52-53:  hanoi search graph 2        ==
%  ==                                                             ==
%  ==            Prolog example, Alan Dix, August 1996            ==
%  ==                                                             ==
%  =================================================================

Code

%  In this example and hanext.pl we look at two representations
%  of the search graph for the Towers of Hanoi problem.

%  In this file, we will look at an intensional (that is rule
%  based) representation, whereas hanext.pl has an extensional
%  representation (listing all cases).

%  In both cases the state of the problem is be represented
%  by a list of lists of numbers, where each number stands for a ring,
%  a ring - the larger the number, the bigger the ring.
%  For example, the list:  [[1,3],[],[2]]
%  will represent the problem state:
%
%              |      |      |
%             ===     |      |
%           =======   |    =====
%        ------+------+------+------
%
%  Moves will be of the form move(From,To), where From and To
%  are numbers representing the towers.
%  For example,  move(1,3), will mean that the top ring from
%  the 1st tower is moved to the 3rd tower.
%  As only the top-most ring can move there is no reason to
%  say which ring on the tower we mean.

%  If you look at the extensional representation in hanext.pl
%  you will see that there are 24 moves stored for the
%  Towers of Hanoi problem with just TWO rings.
%  Listing such moves is tedious and error prone.
%  Imagine listing all moves for three rings or even four!

%  This listing of all cases is called an extensional
%  definition.  It is clearly impractical for large
%  problems.  In fact, in the magic squares examples
%  there is no list of all possible magic squares,
%  instead rules are given which generate them.
%  This is called an intensional definition.

%  The predicate hanoi_int gives just such a definition
%  for the Towers of Hanoi.
%  It works by extracting the relevant towers and then
%  using predicate 'move_tower' which looks at two
%  'disembodied' towers and says whether a move is legal.

hanoi_int(move(From,To),H1,H2) :-
        get_tower(From,H1,F1),
        get_tower(To,H1,T1),
        get_tower(Other,H1,U),
        From \= To,           %  stop degenerate moves, strictly not
        Other \= To,          %  necessary as move_tower would also
        From \= Other,        %  reject such moves
        get_tower(From,H2,F2),
        get_tower(To,H2,T2),
        get_tower(Other,H2,U),   %  untouched tower
        move_tower(F1,T1,F2,T2).

%  The get_tower predicate simply selects the relevant
%  tower from a problem state:

get_tower(1,[Tower,_,_],Tower).
get_tower(2,[_,Tower,_],Tower).
get_tower(3,[_,_,Tower],Tower).

%  This is a simple definition.
%  A more elegant solution would be something like
%    get_tower(1,[Tower|Rest],Tower).
%    get_tower(N,[Top|Rest],Tower) :-
%            N > 2,  N1 is N-1,
%            get_tower(N1,Rest,Tower).
%

%  The move_tower predicate says whether you can move between
%  two towers.
%  move_tower(Before1,Before2,After1,After2) says:
%  1. before the move between the towers:
%         1.1  Before1 is the state of the rings on one tower
%       and
%         1.2  Before2 is the state of the rings on the second tower
%  2. the move is legal (not moving on top of a smaller ring)
%  3. after the move:
%         3.1  After1 is the state of the rings on the first tower
%       and
%         3.2  After2 is the state of the rings on the second tower
%
%  The Prolog description is quite short, just two rules.
%  However, you may need to think through some examples to convince
%  yourself that they work!

%  the first rule says you can always move to an empty tower

move_tower([Ring|Rest],[],Rest,[Ring]).

%  the second rule says if the second tower is occupied, its top-most
%  ring must be bigger than the ring being moved

move_tower([Ring|Rest1],[Bigger|Rest2],Rest1,[Ring,Bigger|Rest2]) :-
        Ring < Bigger.


Running this Code

%  RUNNING THIS CODE
%
%  We can use hanoi_int to ask Prolog to generate possible moves for us.
%  If you simply enter:
%            hanoi_int(Move,State1,State2).
%  Prolog will have some problems (see what happens).
%  This is because hanoi_int works for all 3 tower Hanoi problems,
%  not just the 2 ring version.
%  Prolog doesn't know how many rings you want!

%  To make this clear you need an extra predicate: hanoi_state(N,State)
%  which will be true if State is a valid N rings Hanoi state

hanoi_state(N,[A,B,C]) :-
        up_to_n(N,List),
        split_list(List,A,B,C),
        ordered_tower(A),
        ordered_tower(B),
        ordered_tower(C).

%  up_to_n(N,List) generates the list [1,2, ... N]
%  It is easy to write a recursive predicate which
%  generates the list [N, ... ,3,2,1]
%  But to get them ending in N, one really wants to add
%  to the end of a list.  An efficient way to do this is
%  to use an extra parameter which represents then end of
%  the list you are building up. 
%  For this reason, the predicate up_to_n2(N,List,End)
%  is defined which is true if List is [1,2,3, ...,N|End]

up_to_n(N,L) :- up_to_n2(N,L,[]).

up_to_n2(0,L,L).
up_to_n2(N,L,End) :-
        N > 0, N1 is N-1,
        up_to_n2(N1,L,[N|End]).

%  split_list divides the elements of the first list amongst
%  the rest, keeping the order.

split_list([],[],[],[]).
split_list([F|L],[F|A],B,C) :- split_list(L,A,B,C).
split_list([F|L],A,[F|B],C) :- split_list(L,A,B,C).
split_list([F|L],A,B,[F|C]) :- split_list(L,A,B,C).

%  ordered_tower checks that the tower is correctly ordered with the
%  biggest ring on the bottom down to th smallest on the top.

ordered_tower([]).
ordered_tower([X]).
ordered_tower([X,Y|T]) :- X < Y,  ordered_tower([Y|T]).

%
%  With these definitions you can go ahead and enter:
%>            hanoi_state(2,State1),
%+            hanoi_int(Move,State1,State2).
%
%  Prolog should give you a list very like the one in the definition
%  of hanoi_ext in hanext.pl
%  (I should have got Prolog to do the work for me shouldn't I!)
%
%  Furthermore, because the definition of hanoi_state is general you
%  can also do:
%>            hanoi_state(3,State1),
%+            hanoi_int(Move,State1,State2).
%
%  Which will give you an even longer list!
%
%  In real problems you don't generate all the possible moves, but instead
%  simply generate moves and states as needed.


%  EXERCISE
%
%  Try writing a 4 tower version of hanoi_state.
%  If you also use the 'elegant' version of get_tower
%  you will be able to get Prolog to tell you about
%  moves on 4 towers!


Examples

%  EXAMPLES
% 
%>  hanoi_state(2,State1),
%+  hanoi_int(Move,State1,State2).
%
%>  hanoi_state(3,State1),
%+  hanoi_int(Move,State1,State2).
%



Query

Response