:- ensure_loaded(dbug). % This file sets up the eight puzzle for various prolog % search procedures (e.g., gs) by defining arc/3, arc/2, % start/1, goal/1, f/3, and h/1. % this is the default goal. goal([1,2,3, 4,o,5, 6,7,8]). % here are some default start states. % ten steps start([1,7,5,4,o,2,6,8,3]). % four steps. start([o,2,3, 1,7,5, 4,6,8]). % this one takes 20 steps. start([3,6,4, 1,5,2, 8,7,o]). start([1,2,3, 4,5,o, 6,7,8]). start([1,2,3, 4,5,8, 6,o,7]). start([1,o,3, 4,2,8, 6,5,7]). % default cost of an arc is one. arc(X,Y,1) :- arc(X,Y). :- op(1000,xfx,'==>'). term_expansion((State1 ==> State2), arc(State1,State2)). % first position: 1,1 [o,B,C, D,E,F, G,H,I] ==> [B,o,C, D,E,F, G,H,I]. [o,B,C, D,E,F, G,H,I] ==> [D,B,C, o,E,F, G,H,I]. % second position: 1,2 [A,o,C, D,E,F, G,H,I] ==> [o,A,C, D,E,F, G,H,I]. [A,o,C, D,E,F, G,H,I] ==> [A,C,o, D,E,F, G,H,I]. [A,o,C, D,E,F, G,H,I] ==> [A,E,C, D,o,F, G,H,I]. % third position: 1,3 [A,B,o, D,E,F, G,H,I] ==> [A,o,B, D,E,F, G,H,I]. [A,B,o, D,E,F, G,H,I] ==> [A,B,F, D,E,o, G,H,I]. % fourth position: 2,1 [A,B,C, o,E,F, G,H,I] ==> [o,B,C, A,E,F, G,H,I]. [A,B,C, o,E,F, G,H,I] ==> [A,B,C, E,o,F, G,H,I]. [A,B,C, o,E,F, G,H,I] ==> [A,B,C, G,E,F, o,H,I]. % fifth position: 2,2 [A,B,C, D,o,F, G,H,I] ==> [A,o,C, D,B,F, G,H,I]. [A,B,C, D,o,F, G,H,I] ==> [A,B,C, o,D,F, G,H,I]. [A,B,C, D,o,F, G,H,I] ==> [A,B,C, D,F,o, G,H,I]. [A,B,C, D,o,F, G,H,I] ==> [A,B,C, D,H,F, G,o,I]. % sixth position: 2,3 [A,B,C, D,E,o, G,H,I] ==> [A,B,o, D,E,C, G,H,I]. [A,B,C, D,E,o, G,H,I] ==> [A,B,C, D,o,E, G,H,I]. [A,B,C, D,E,o, G,H,I] ==> [A,B,C, D,E,I, G,H,o]. % seventh position: 3,1 [A,B,C, D,E,F, o,H,I] ==> [A,B,C, o,E,F, D,H,I]. [A,B,C, D,E,F, o,H,I] ==> [A,B,C, D,E,F, H,o,I]. % eigth position: 3,2 [A,B,C, D,E,F, G,o,I] ==> [A,B,C, D,E,F, o,G,I]. [A,B,C, D,E,F, G,o,I] ==> [A,B,C, D,o,F, G,E,I]. [A,B,C, D,E,F, G,o,I] ==> [A,B,C, D,E,F, G,I,o]. % ninth position: 3,3 [A,B,C, D,E,F, G,H,o] ==> [A,B,C, D,E,o, G,H,F]. [A,B,C, D,E,F, G,H,o] ==> [A,B,C, D,E,F, G,o,H]. % here is the default evaluation function and some other possibilities. f(G,H,F) :- F is G+H. % algorithm A %f(G,_H,G). % uniform cost search %f(_G,H,H). % best first search %f(G,_H,F) :- F is -G. % depth first search (sort of) % Here is one Heuristic function: % h(n) is the distance from n to the goal where distance is defined as % the "manhatten distance" between each tile's current positon and goal % position. If, if tile A is at (X1,Y1) and want to be at (X2,Y2) then % the distance for A is |X2-X1| + |Y2-Y1|. h(S,H) :- goal(G), manhatten(S,G,H), !. manhatten(S1,S2,H) :- manhatten_coordinates(Coord), manhatten1(S1,Coord,Coord,S2,H), !. manhatten1([],_,_,_,0). manhatten1([Tile|Tiles],[(X1,Y1)|Coordinates],Coord,S2,D) :- mh2(Tile,Coord,S2,(X2,Y2)), Dtile is abs(X1-X2)+abs(Y1-Y2), manhatten1(Tiles,Coordinates,Coord,S2,Dtiles), D is Dtile+Dtiles. mh2(_,[],_,_) :- shouldnt("~nmh2 ran out of coordinates"). mh2(_,_,[],_) :- shouldnt("~nmh2 couldnt find tile"). mh2(Tile,[Coord|_],[Tile|_],Coord) :- !. mh2(Tile,[_|Coords],[_|Tiles],Coord) :- mh2(Tile,Coords,Tiles,Coord). manhatten_coordinates( [(0,0),(0,1),(0,2), (1,0),(1,1),(1,2), (2,0),(2,1),(2,2)]). writeState(_) :- fail.