% Author: Alex Roque % Assignment #: 5 % Due Date:11/08/01 % Program Title: Assignment 5 % Program Description: Solution to 8 Puzzle % % I certify that this is my work and have not consulted with anyone else. % % % % ======================A star serach ============================ % bestfirst(Start,Solution) is a path from Start to a goal bestfirst(Start,Solution) :- expand([],l(Start,0/0),9999,_,yes,Solution). % assume that 9999 is bigger than any f-value % expand( Path,Tree,Bound,Tree1, Solved, Solution) % Path is a path from the start node to subtree Tree, % Tree1 is Tree expanded within Bound, % if goal found, construct a solution path. % case 1: N is a solution and a leaf node. expand(P,l(N,_),_,_,yes,[N|P]):- goal_reached(N). % case 2: N is a leaf node with f-value less than Bound expand(P,l(N,F/G),Bound,Tree1,Solved,Sol):- F =< Bound, (bagof(M/C,(successor(N,M,C),not(member(M,P))),Succ), !, %N has succesors succlist(G,Succ,Ts), % make subtress Ts bestf(Ts,F1), % the value of the best successor expand(P,t(N,F1/G,Ts),Bound,Tree1,Solved,Sol) ; Solved = never %N has no successors ). % Case 3: N is a non-leaf, its value is less than Bound % Expand the most promising subtree % Depending on the result the procedure will decide how to proceed expand(P, t(N,F/G,[T|Ts]),Bound,Tree1,Solved,Sol) :- F =< Bound, bestf(Ts,BF), min(Bound,BF,Bound1), % Bound1 = min (Bound,BF) expand( [N|P],T,Bound1,T1, Solved1, Sol), continue(P, t(N,F/G,[T1|Ts]), Bound, Tree1, Solved1, Solved, Sol). % Case 4: a non-leaf with empty subtrees % This is dead end which will never be solved expand(_,t(_,_,[]),_,_,never,_) :- !. % Case 5: value greater than Bound. % The tree may not grow expand(_, Tree, Bound, Tree, no, _) :- f(Tree,F), F>Bound. % continue(Path,Tree,Bound,NewTree,SubtreeSolved,TreeSolved, Solution) continue(_,_,_,_,yes,yes,Sol). continue(P,t(N,F/G,[T1|Ts]),Bound,Tree1,no,Solved,Sol) :- insert(T1,Ts,NTs), bestf(NTs,F1), expand(P,t(N,F1/G,NTs), Bound, Tree1, Solved, Sol). continue(P,t(N,F/G,[_|Ts]),Bound,Tree1,never,Solved,Sol) :- bestf(Ts,F1), expand(P,t(N,F1/G,Ts),Bound,Tree1,Solved,Sol). % succlist(G0, [Node1/Cost1,...],[l(BestNode,BestF/G),...]): % make list of search leaves ordered by their f-values succlist(_,[],[]). succlist(G0,[N/C | NCs],Ts) :- G is G0 + C, h(N,H), % heuristic function F is G + H, succlist(G0, NCs, Ts1), insert(l(N,F/G),Ts1,Ts). % insert T into the list Ts preserving order with respect to f-values insert(T,Ts,[T|Ts]) :- f(T,F), bestf( Ts,F1), F =< F1, !. insert(T,[T1|Ts],[T1|Ts1]):- insert(T,Ts,Ts1). % extract f-values f(l(_,F/_),F). % f-value of a leaf f(t(_,F/_,_),F). % f-value of a tree % bestf is the best f value of a list of tree bestf( [T|_],F):- f(T,F). bestf( [],9999). % no trees % not not(X) :- X,!,fail. not(X). % member(Item,List) is satisfied if Item is in List member(Item, [Item|_]). member(Item,[_|Tail]):- member(Item,Tail). % min(X,Y,Z) is satisfied if Z is the samllest of X and Y min(X,Y,X) :- X < Y. min(X,Y,Y) :- Y =< X. % ===================== 8-puzzle specifics ===================== % heuristic , Tile is out of place h(State,C) :- compute_h(State,1,C). compute_h([I|Tail],I,Sum):- J is I + 1, compute_h(Tail,J,Sum). compute_h([_X|Tail],I,Sum):- J is I +1, compute_h(Tail,J,Sum1), Sum is Sum1 + 1. compute_h([],_,0). % rewritten successor function successor(State,NextState,1):- move(State,NextState). % Moves % move up move([X1,X2,X3,X9|Tail],[X9,X2,X3,X1|Tail]):- X9==9. move([X|Tail],[X|Tail1]):- move(Tail,Tail1). % move down move([X9,X1,X2,X3|Tail],[X3,X1,X2,X9|Tail]):- X9==9. %move([X|Tail],[X|Tail1]):- % move(Tail,Tail1). % move left move([X1,X9,X3,X4,X5,X6,X7,X8],[X9,X1,X3,X4,X5,X6,X7,X8]):- X9==9. move([X1,X9,X3,X4,X5],[X9,X1,X3,X4,X5]):- X9==9. move([X1,X9,X3],[X9,X1,X3]):- X9==9. move([X1,X2,X9,X4,X5,X6,X7,X8],[X1,X9,X2,X4,X5,X6,X7,X8]):- X9==9. move([X1,X2,X9,X4,X5,X6],[X1,X9,X2,X4,X5,X6]):- X9==9. move([X1,X2,X9],[X1,X9,X2]):- X9==9. %move([X|Tail],[X|Tail1]):- % move(Tail,Tail1). move([X9,X2,X3,X4,X5,X6,X7,X8],[X2,X9,X3,X4,X5,X6,X7,X8]):- X9==9. move([X9,X2,X3,X4,X5,X6],[X2,X9,X3,X4,X5,X6]):- X9==9. move([X9,X2,X3],[X2,X9,X3]):- X9==9. move([X1,X9,X3,X4,X5,X6,X7,X8],[X1,X3,X9,X4,X5,X6,X7,X8]):- X9==9. move([X1,X9,X3,X4,X5,X6],[X1,X3,X9,X4,X5,X6]):- X9==9. move([X1,X9,X3],[X1,X3,X9]):- X9==9. %move([X|Tail],[X|Tail1]):- % move(Tail,Tail1). % Goal represents the goal state of the tiles in the n puzzle % The numbers on the list represent the tiles on the grid from left to right , top to % bottom, so this goal state is % | 1 | 2 | 3 | % | 8 | 9 | 4 | % | 7 | 6 | 5 | % and the number 9 represents the blank tile goal_reached([1,2,3,4,5,6,7,8,9]). start1([1,3,4,8,9,2,7,6,5]). % Requires 4 steps start2([2,8,3,1,6,4,7,9,5]). % Requires 5 steps start3([2,1,6,4,9,8,7,5,3]). % Requires 18 steps % Homework states hw1([4,6,2,7,9,3,1,8,5]). hw2([4,2,6,7,9,3,1,8,5]). hw3([1,8,2,4,7,3,5,9,6]). hw4([1,8,2,5,7,3,4,9,6]). % Display a board position printOutput(OriginalState,FinalMoves):- write('8 Puzzle'),nl, write('============================='), nl,nl, write('original state is: '), nl,nl, write(' | '), printState(OriginalState,0), nl,nl, write('Result is: '), nl, printFState(FinalMoves). printFState([H|Tail]):- nl, write('Goal state achieved is: '), nl,nl, write(' | '), printState(H,0), nl,nl, write('The moves to attain the goal state in reverse order are: '), nl, printMoves(Tail). printMoves([]). printMoves([H|Tail]):- nl, write(' | '), printState(H,0), nl, printMoves(Tail). printState([],_). printState([H|Tail],I):- I==3, nl, write(' | '), write(H), write(' | '), J is 3 + 1, printState(Tail,J); I==6, nl, write(' | '), write(H), write(' | '), J is 3 + 1, printState(Tail,J); write(H), write(' | '), J is I + 1, printState(Tail,J). testSolvable(Pos) :- solvable(Pos,Binary), Binary == 0, bestfirst(Pos,Sol), printOutput(Pos,Sol); write('State: '),nl,nl, printState(Pos,0),nl,nl, write('is not solvable'). solvable(State,Binary):- getInversions(State,NumInversions), Binary is NumInversions mod 2. getInversions([],_). getInversions([H|Tail],NumInversions):- lessthan(H,Tail,Num1), getInversions(Tail,Num2), NumInversions is Num1 + Num2. lessthan(_,[],_). lessthan(Num,[H|Tail],NumInversions):- Num > H, lessthan(Num,Tail,Num1), NumInversions is Num1 +1; lessthan(Num,Tail,NumInversions). go1 :- hw1(Pos), bestfirst(Pos,Sol), printOutput(Pos,Sol). testSolvable(Pos). go2 :- hw2(Pos), bestfirst(Pos,Sol), printOutput(Pos,Sol). testSolvable(Pos). go3 :- hw3(Pos), bestfirst(Pos,Sol), printOutput(Pos,Sol). testSolvable(Pos). go4 :- hw4(Pos), bestfirst(Pos,Sol), printOutput(Pos,Sol). testSolvable(Pos).