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.
30.10.2011, в 19:44, Anton Kholomiov <anton.kholom...@gmail.com> написал(а): > I'm misunderstanding astar. I've thought that 'whole route'-heuristic > will prevent algorithm from going in circles. The more you circle around > the 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.empty > > searchBy' :: 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) ts > > I need to add function Ord b => (a -> b). It > converts tree nodes into visited nodes. I'm using it > for saving distance-values alongside with nodes > in astar algorithm. > > In attachment you can find algorithm with your example. > > 2011/10/27 Ryan Ingram <ryani.s...@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.s...@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. > > -- ryan > > On Sat, Oct 22, 2011 at 5:28 AM, Anton Kholomiov <anton.kholom...@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 that > relies 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 where > > import Control.Applicative > import 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 [] = a > mergeBy _ [] b = b > mergeBy 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe