The last implementation is type-driven, so I'm tryingš
Anton, I think the mapM inside searchBy is incorrect. You're threading state between exploration of different branches, which you I think shouldn't be doing.
I'm misunderstanding astar. I've thought that 'whole route'-heuristicšwill prevent algorithm from going in circles. The more you circle aroundthe more the whole route distance is. Thank you for showing this.šHere is an updated version. searchBy function contains a state.State value accumulates visited nodes:-- | Heuristic search. Nodes are visited from smaller to greater.searchBy :: Ord b => (a -> b) -> (a -> a -> Ordering) -> Tree a -> [a]searchBy f heur t = evalState (searchBy' f heur t) S.emptysearchBy' :: Ord bššš š=> (a -> b) -> (a -> a -> Ordering) -> Tree a -> State (S.Set b) [a]searchBy' f heur (Node v ts) = get >>= phišš šwhere phi visitedšš š š š š š| S.member (f v) visited = return []šš š š š š š| otherwise š š š š š=ššš š š š š š š šput (S.insert (f v) visited) >>šš š š š š š š š(v :) . foldr (mergeBy heur) [] <$>ššš š š š š š š šmapM (searchBy' f heur) tsI need to add functionšOrd b => (a -> b). Itconverts tree nodes into visited nodes. I'm using itšfor saving distance-values alongside with nodesin astar algorithm.In attachment you can find algorithm withšyour example.š2011/10/27 Ryan Ingram <ryani.spam@gmail.com>
Also, this wasn't clear in my message, but the edges in the graph only go one way; towards the top/right; otherwise the best path is ABCDEHIJ :)On Thu, Oct 27, 2011 at 10:48 AM, Ryan Ingram <ryani.spam@gmail.com> wrote:
You're missing one of the key insights from A-star (and simple djikstra, for that matter): once you visit a node, you don't have to visit it again.
Consider a 5x2 2d graph with these edge costs:
B 1 C 1 D 1 E 9 J
1šš 1šš 1šš 1šš 1
A 2 F 2 G 2 H 2 I
with the start node being A, the target node being J, and the heuristic being manhattan distance.š Your search will always try to take the top route, on every node along the bottom path, even though you visit every node along the top route in your first try at reaching the goal.š You need a way to mark that a node is visited and remove it from future consideration, or else you're wasting work.
A-star will visit the nodes in the order ABCDE FGHIJ; your algorithm visits the nodes in the order ABCDE FCDE GDE HE IJ.
š -- ryanOn Sat, Oct 22, 2011 at 5:28 AM, Anton Kholomiov <anton.kholomiov@gmail.com> wrote:
Recently I was looking for an A-star search algorithm.šI've found a packagešbut I couldn't understand the code.šThen I saw some blogposts but theyšwere difficult tošunderstand too. I thought about some easier solution thatrelies on laziness. And I've come to this:Heuristic search is like depth-first search but solutions in sub-treesšare concatenated with mergeBy function, that concatenates twošlist by specific order:module Search whereimport Control.Applicativeimport Data.Function(on)import Control.Arrow(second)import Data.Tree-- | Heuristic search. Nodes are visited from smaller to greater.searchBy :: (a -> a -> Ordering) -> Tree a -> [a]searchBy šheur (Node v ts) =ššš šv : foldr (mergeBy heur) [] (searchBy heur <$> ts)-- | Merge two lists. Elements concatenated in specified order.mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]mergeBy _ a š š š š [] š š š= amergeBy _ [] š š š šb š š š = bmergeBy p (a:as) š š(b:bs) ššš š| a `p` b == LT š š= a : mergeBy p as (b:bs)šš š| otherwise š š š š = b : mergeBy p bs (a:as)Now we can define specific heuristic search in terms of searchBy:-- | Heuristic is distance to goal.bestFirst :: Ord h => (a -> h) -> (a -> [a]) -> a -> [a]bestFirst dist alts =ššš šsearchBy (compare `on` dist) . unfoldTree (\a -> (a, alts a))-- | A-star search.-- Heuristic is estimated length of whole path.šastar :: (Ord h, Num h) => (a -> h) -> (a -> [(a, h)]) -> a -> [a]astar dist alts s0 = fmap fst $ššš šsearchBy (compare `on` astarDist) $ unfoldTree gen (s0, 0)šš šwhere astarDist (a, d) = dist a + dšš š š š šgen (a, d) š= d `seq` ((a, d), second (+d) <$> alts a)I'm wondering is it effective enough?Anton_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
<Search.hs>_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe