<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
<html>
  <head>
    <meta content="text/html; charset=ISO-8859-1"
      http-equiv="Content-Type">
  </head>
  <body text="#000000" bgcolor="#ffffff">
    How do you mean effective?<br>
    <br>
    While I am not sure they mention A* search, you might like to look
    at the paper<br>
    "Modular Lazy Search for Constraint Satisfaction Problems" by Nordin
    &amp; Tolmach.<br>
    <a class="moz-txt-link-freetext"
      href="http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.34.4704">http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.34.4704</a><br>
    <br>
    RS<br>
    <br>
    <br>
    On 22/10/11 13:28, Anton Kholomiov wrote:
    <blockquote
cite="mid:CADDxdqPDcNuUoWT283zvzhctVGm7wvXjFkH9qDSD6hyJMz9JsA@mail.gmail.com"
      type="cite">Recently I was looking for an A-star search
      algorithm.&nbsp;I've found a package&nbsp;
      <div>but I couldn't understand the code.&nbsp;Then I saw some blogposts
        but they</div>
      <div>&nbsp;were difficult to&nbsp;understand too. I thought about some
        easier solution that</div>
      <div>relies on laziness. And I've come to this:</div>
      <div><br>
      </div>
      <div>Heuristic search is like depth-first search but solutions in
        sub-trees&nbsp;</div>
      <div>are concatenated with <font class="Apple-style-span"
          color="#000099">mergeBy</font> function, that concatenates
        two&nbsp;</div>
      <div>list by specific order:</div>
      <div><br>
      </div>
      <div>
        <div>module Search where</div>
        <div><br>
        </div>
        <div>import Control.Applicative</div>
        <div>import Data.Function(on)</div>
        <div>import Control.Arrow(second)</div>
        <div>import Data.Tree</div>
      </div>
      <div><br>
      </div>
      <div>
        <div>-- | Heuristic search. Nodes are visited from smaller to
          greater.</div>
        <div>searchBy :: (a -&gt; a -&gt; Ordering) -&gt; Tree a -&gt;
          [a]</div>
        <div>searchBy &nbsp;heur (Node v ts) =&nbsp;</div>
        <div>&nbsp;&nbsp; &nbsp;v : foldr (mergeBy heur) [] (searchBy heur &lt;$&gt;
          ts)</div>
        <div><br>
        </div>
        <div>-- | Merge two lists. Elements concatenated in specified
          order.</div>
        <div>mergeBy :: (a -&gt; a -&gt; Ordering) -&gt; [a] -&gt; [a]
          -&gt; [a]</div>
        <div>mergeBy _ a &nbsp; &nbsp; &nbsp; &nbsp; [] &nbsp; &nbsp; &nbsp;= a</div>
        <div>mergeBy _ [] &nbsp; &nbsp; &nbsp; &nbsp;b &nbsp; &nbsp; &nbsp; = b</div>
        <div>mergeBy p (a:as) &nbsp; &nbsp;(b:bs) &nbsp;</div>
        <div>&nbsp;&nbsp; &nbsp;| a `p` b == LT &nbsp; &nbsp;= a : mergeBy p as (b:bs)</div>
        <div>&nbsp;&nbsp; &nbsp;| otherwise &nbsp; &nbsp; &nbsp; &nbsp; = b : mergeBy p bs (a:as)</div>
      </div>
      <div><br>
      </div>
      <div><br>
      </div>
      <div>Now we can define specific heuristic search in terms of <font
          class="Apple-style-span" color="#000099">searchBy</font>:</div>
      <div><br>
      </div>
      <div>
        <div>-- | Heuristic is distance to goal.</div>
        <div>bestFirst :: Ord h =&gt; (a -&gt; h) -&gt; (a -&gt; [a])
          -&gt; a -&gt; [a]</div>
        <div>bestFirst dist alts =&nbsp;</div>
        <div>&nbsp;&nbsp; &nbsp;searchBy (compare `on` dist) . unfoldTree (\a -&gt; (a,
          alts a))</div>
        <div><br>
        </div>
        <div>-- | A-star search.</div>
        <div>-- Heuristic is estimated length of whole path.&nbsp;</div>
        <div>astar :: (Ord h, Num h) =&gt; (a -&gt; h) -&gt; (a -&gt;
          [(a, h)]) -&gt; a -&gt; [a]</div>
        <div>astar dist alts s0 = fmap fst $&nbsp;</div>
        <div>&nbsp;&nbsp; &nbsp;searchBy (compare `on` astarDist) $ unfoldTree gen (s0,
          0)</div>
        <div>&nbsp;&nbsp; &nbsp;where astarDist (a, d) = dist a + d</div>
        <div>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp;gen (a, d) &nbsp;= d `seq` ((a, d), second (+d)
          &lt;$&gt; alts a)</div>
      </div>
      <div><br>
      </div>
      <div>I'm wondering is it effective enough?</div>
      <div><br>
      </div>
      <div><br>
      </div>
      <div>Anton</div>
      <pre wrap="">
<fieldset class="mimeAttachmentHeader"></fieldset>
_______________________________________________
Haskell-Cafe mailing list
<a class="moz-txt-link-abbreviated" href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a>
<a class="moz-txt-link-freetext" href="http://www.haskell.org/mailman/listinfo/haskell-cafe">http://www.haskell.org/mailman/listinfo/haskell-cafe</a>
</pre>
    </blockquote>
    <br>
  </body>
</html>