Lab 4 Best First Heuristic Search

Embed Size (px)

Citation preview

  • 8/9/2019 Lab 4 Best First Heuristic Search

    1/8

    BIRLA INSTITUTE OF TECHNOLOGY AND SCIENCE

    PILANI-333031 (RAJASTHAN) INDIA

    Second Semester 2007-2008

    Course: EA C461 (ArtificialIntelligence)

    Lab 4: Best-First HeuristicSearch

    Prepared By: Dr. Mukesh Kumar Rohil [email protected]

    This Lab is based on the book by Ivan Bratko, Prolog Programming for Artificial Intelligence, Third

    Edition, 2001, Pearson Education Ltd., Second Impression 2007 (in India).

    Given the heuristic function f(n) = g(n) + h(n), where g(n) is an estimate of the cost of an optimal path

    from starting node, s, to current node, n, and h(n) is an estimate of the cost of an optimal path from

    node n to the goal node t.

    When node n is encountered by the search process we have following situation: a path from s to n

    must have already been found and its cost can be computed as the sum of the arc-costs on the path. It

    may not be optimal cost but its cost can serve as an estimate g(n) of the minimal cost from s to n.Theother term, h(n), is more problematic because the world between n and t has not been explored by the

    search until this point. Therefore, h(n) is typically is real heuristic guess, based on the algorithmsgeneral knowledge about the particular problem.

    Starting with the start node, the search keeps generating new successor nodes, always expanding in themost promising direction according to the f-values. During this process, a search tree is generated

    whose root is the start node of the search. The best-first search program will thus kep expanding this

    search tree until a solution is found. This tree will be represented in the program by terms of two

    forms:

    1. l(N, F/G) represents a single node tree (a leaf); N is a node in the state space, G is g(N) (cost ofthe path found from the start node to N); F is f(N) = G + h(N).2. t(N, F/G, Subs) represents a tree with non-empty subtree; N is the root of the tree, Subs is a list

    of its subtrees; G is g(N); F is updated f-value of N that is, the f-value of the most promising

    successor of N; the list Subs is ordered according to increasing f-values of the sub-trees.

    The updating of the f-values is necessary to enable the program to recognize the most promising

    subtree at each level of the search tree. This modification of f-estimates lead, in fact, to a function f

    from nodes to tree. For a single node tree (a leaf), n, we have the original definition of f(n) i.e. f(n) =g(n) + h(n). For a tree, T, hose root is n, and ns subtrees are S1, S2, etc., f(T) = minif(Si).

    A best-first program along these lines is shown in Table 1. Some more explanation of this programfollows.

    The key procedure is expand, which has six arguments:expand(P, Tree, Bound, Tree1, Solved, Solution).

    It expands a current (sub)tree as long as the f-value of this tree remains less or equal to Bound. Thearguments of expand are given in Table 2.

    P, Tree and Bound are input parameters to expand. Expand produces three kinds of results which is

    indicated by the value of the argument Solved as follows:

    mailto:[email protected]:[email protected]
  • 8/9/2019 Lab 4 Best First Heuristic Search

    2/8

    (1). Solved = yes.Solution = a solution path found by expanding Tree within Bound.

    Tree1 = uninstantiated.

    (2). Solved = no.Solution = Tree expanded so that its f-value exceeds Bound.

    Tree1 = uninstantiated.

    (3). Solved = never.

    Solution and Tree1 = uninstantiated.

    A Prolog program (based on the best first search) to solve 8-puzzle problem is given in Table 3.

    However, some predicates need more clauses to be added.

    Do the following:

    1. Apply the Best-first search (Table 2) to

    solve the routing problem (as given in

    Fig. 1) to find the shortest path fromnode s to node t.

    2. Find the time taken by the method to

    find the shortest path for problem 1above. [Hint: Read and Use time/2

    predicate given in the LPA Win-

    Prolog help]3. Comparing the program in Table 1

    and Table 3, make a table of predicates

    of Table 1 and Table 3 by stating

    which predicate(s) in Table 3 does the

    analogous or similar work of whichpredicate(s) in Table 1.

    4. The Table 3 (Best-first search appliedto 8-puzzle problem) does not have some clauses of some predicate. Complete

    those and run the program for five initial conditions to reach to the goal state.

    The goal state is given in Fig. 2.5. Name your files as L4_AI_YourID_pN and zip them as L4_AI_YourID.zip and

    transmit to instructors email id. Replace the text YourID by your BITS

    IDNumber and N in pN by problem number 1, 2, 3, or 4 as the case may be.

    Figure 1: A routing network [The numbers along

    arcs are g(n) and numbers in square are h(n)]

    1 2

    3 4 5

    6 7 8

    Figure 2

  • 8/9/2019 Lab 4 Best First Heuristic Search

    3/8

    % A best-first search program.

    % bestfirst( Start, Solution): Solution is a path from Start to a goal

    bestfirst(Start,Solution):-

    expand([],l(Start,0/0), 9999,_,yes,Solution).

    % Assume 9999 is greater than any f-value

    % expand( Path, Tree, Bound, Tree1, Solved, Solution):

    % Path is path between start node of search and subtree Tree,

    % Tree1 is Tree expanded within Bound,

    % if goal found then Solution is solution path and Solved = yes

    % Case 1: goal leaf-node, construct a solution path

    expand(P,l(N,_),_,_,yes,[N|P]) :-

    goal(N).

    % Case 2: leaf-node, f-value less than Bound

    % Generate successors and expand them within Bound.

    expand(P,l(N,F/G),Bound,Tree1,Solved,Sol) :-

    F =

  • 8/9/2019 Lab 4 Best First Heuristic Search

    4/8

    expand( [N|P], T, Bound1, T1, Solved1, Sol),

    continue( P, t(N,F/G,[T1|Ts]), Bound, Tree1, Solved1, Solved, Sol).

    % Case 4: non-leaf with empty subtrees

    % This is a dead end which will never be solved

    expand( _, t(_,_,[]), _, _, never, _) :- !.

    % Case 5: f-value greater than Bound

    % 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 term h(N)

    F is G + H,

    succlist( G0, NCs, Ts1),

    insert( l(N,F/G), Ts1, Ts).

    % Insert T into list of trees Ts preserving order w.r.t. f-values

  • 8/9/2019 Lab 4 Best First Heuristic Search

    5/8

    insert(T,Ts,[T|Ts]) :-

    f(T,F),bestf(Ts,F1),

    F =

  • 8/9/2019 Lab 4 Best First Heuristic Search

    6/8

    Example:

    This position is represented by:

    3 1 2 3

    [2/2, 1/3, 2/3, 3/3, 3/2, 3/1, 2/1, 1/1, 1/2]2 8 4

    1 7 6 5

    1 2 3

    "Empty' can move to any of its neighbours which means

    that "empty' and its neighbour interchange their positions.

    */

    % s( Node, SuccessorNode, Cost)

    s([Empty|Tiles],[Tile|Tiles1],1) :- % All arc costs are 1

    swap(Empty,Tile,Tiles,Tiles1). % Swap Empty and Tile in Tiles

    swap(Empty,Tile,[Tile|Ts],[Empty|Ts]) :-

    mandist(Empty,Tile,1). % Manhattan distance = 1

    swap( Empty, Tile, [T1 | Ts], [T1 | Ts1] ) :-

    swap( Empty, Tile, Ts, Ts1).

    mandist( X/Y, X1/Y1, D) :- % D is Manhhattan dist. between two

    squares

    dif( X, X1, Dx),

    dif( Y, Y1, Dy),

    D is Dx + Dy.

    dif( A, B, D) :- % D is |A-B|

    D is A-B, D >= 0, !

    ;

    D is B-A.

    % Heuristic estimate h is the sum of distances of each tile

    % from its "home' square plus 3 times "sequence' score

    h( [Empty | Tiles], H) :-

    goal( [Empty1 | GoalSquares] ),

  • 8/9/2019 Lab 4 Best First Heuristic Search

    7/8

    totdist( Tiles, GoalSquares, D), % Total distance from home squares

    seq( Tiles, S), % Sequence score

    H is D + 3*S.

    totdist( [], [], 0).

    totdist( [Tile | Tiles], [Square | Squares], D) :-

    mandist( Tile, Square, D1),

    totdist( Tiles, Squares, D2),

    D is D1 + D2.

    % seq( TilePositions, Score): sequence score

    seq( [First | OtherTiles], S) :-

    seq( [First | OtherTiles ], First, S).

    seq( [Tile1, Tile2 | Tiles], First, S) :-

    score( Tile1, Tile2, S1),

    seq( [Tile2 | Tiles], First, S2),

    S is S1 + S2.

    seq( [Last], First, S) :-

    score( Last, First, S).

    score( 2/2, _, 1) :- !. % Tile in centre scores 1

    score( 1/3, 2/3, 0) :- !. % Proper successor scores 0

    score( 2/3, 3/3, 0) :- !.

    score( 3/3, 3/2, 0) :- !.

    score( 3/2, 3/1, 0) :- !.

    score( 3/1, 2/1, 0) :- !.

    score( 2/1, 1/1, 0) :- !.

    score( 1/1, 1/2, 0) :- !.

    score( 1/2, 1/3, 0) :- !.

    score( _, _, 2). % Tiles out of sequence score 2

    goal( [2/2,1/3,2/3,3/3,3/2,3/1,2/1,1/1,1/2] ). % Goal squares for tiles

    % Display a solution path as a list of board positions

  • 8/9/2019 Lab 4 Best First Heuristic Search

    8/8

    showsol( [] ).

    showsol([P|L]) :-

    showsol(L),

    nl,write('---'),

    showpos(P).

    % Display a board position

    showpos([S0,S1,S2,S3,S4,S5,S6,S7,S8]) :-

    member(Y,[3,2,1]), % Order of Y-coordinates

    nl,member(X,[1,2,3]), % Order of X-coordinates

    member(Tile-X/Y, % Tile on square X/Y

    [' '-S0,1-S1,2-S2,3-S3,4-S4,5-S5,6-S6,7-S7,8-S8]),

    write(Tile),

    fail % Backtrack to next square

    ;

    true. % All squares done

    % Starting positions for some puzzles

    start1([2/2,1/3,3/2,2/3,3/3,3/1,2/1,1/1,1/2]). % Requires 4 steps

    start2([2/1,1/2,1/3,3/3,3/2,3/1,2/2,1/1,2/3]). % Requires 5 steps

    start3([2/2,2/3,1/3,3/1,1/2,2/1,3/3,1/1,3/2]). % Requires 18 steps

    % An example query: ?- start1( Pos), bestfirst( Pos, Sol), showsol( Sol).

    Table 3