Sorry for my English.
How do you mean effective?
While I am not sure they mention A* search, you might like to look at the paper
"Modular Lazy Search for Constraint Satisfaction Problems" by Nordin & Tolmach.
http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.34.4704
RS
On 22/10/11 13:28, Anton Kholomiov wrote:_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafeRecently I was looking for an A-star search algorithm. I've found a packagebut I couldn't understand the code. Then I saw some blogposts but theywere 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-treesare concatenated with mergeBy function, that concatenates twolist by specific order:
module Search where
import 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 + dgen (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