Sorry for my English.<div>I mean &quot;can be used in practice, no only for toy examples&quot;<br><br><div class="gmail_quote">2011/10/22 Richard Senington <span dir="ltr">&lt;<a href="mailto:sc06r2s@leeds.ac.uk">sc06r2s@leeds.ac.uk</a>&gt;</span><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;"><u></u>

  
    
  
  <div text="#000000" bgcolor="#ffffff"><div class="im">
    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>
    &quot;Modular Lazy Search for Constraint Satisfaction Problems&quot; by Nordin
    &amp; Tolmach.<br>
    <a href="http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.34.4704" target="_blank">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:
    </div><blockquote type="cite"><div><div></div><div class="h5">Recently I was looking for an A-star search
      algorithm. I&#39;ve found a package 
      <div>but I couldn&#39;t understand the code. Then I saw some blogposts
        but they</div>
      <div> were difficult to understand too. I thought about some
        easier solution that</div>
      <div>relies on laziness. And I&#39;ve come to this:</div>
      <div><br>
      </div>
      <div>Heuristic search is like depth-first search but solutions in
        sub-trees </div>
      <div>are concatenated with <font color="#000099">mergeBy</font> function, that concatenates
        two </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  heur (Node v ts) = </div>
        <div>    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         []      = a</div>
        <div>mergeBy _ []        b       = b</div>
        <div>mergeBy p (a:as)    (b:bs)  </div>
        <div>    | a `p` b == LT    = a : mergeBy p as (b:bs)</div>
        <div>    | otherwise         = 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 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 = </div>
        <div>    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. </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 $ </div>
        <div>    searchBy (compare `on` astarDist) $ unfoldTree gen (s0,
          0)</div>
        <div>    where astarDist (a, d) = dist a + d</div>
        <div>          gen (a, d)  = d `seq` ((a, d), second (+d)
          &lt;$&gt; alts a)</div>
      </div>
      <div><br>
      </div>
      <div>I&#39;m wondering is it effective enough?</div>
      <div><br>
      </div>
      <div><br>
      </div>
      <div>Anton</div>
      </div></div><pre><fieldset></fieldset>
_______________________________________________
Haskell-Cafe mailing list
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a>
</pre>
    </blockquote>
    <br>
  </div>

<br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br></div>