<div dir="ltr"><div><div>I tried a set-based solution and it can process ~1600 items in 25 seconds on this i7. Seems really slow compared to the times posted here:<br><a href="http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-wolves.html">http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-wolves.html</a><br>
<br></div>I'm curious if anyone spots any major flaw. If not, I'll profile it tonight -- I can't afford to spend more time on this at work<br><br></div>Tim<br><div><div><br></div></div></div><div class="gmail_extra">
<br><br><div class="gmail_quote">On Fri, Jun 13, 2014 at 8:54 AM, Elric <span dir="ltr"><<a href="mailto:elric@kiosa.org" target="_blank">elric@kiosa.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

  
    
  
  <div bgcolor="#FFFFFF" text="#000000">
    Thank You Bob,<br>
    <br>
    I learnt quite a bit from your solution. I have been restricting
    myself to Lists so far. I think I will have to start exploring other
    data structures like Sets in Haskell as well. :)<br>
    <br>
    Thank You,<br>
    Elric<div><div class="h5"><br>
    <br>
    <div>On 06/08/2014 03:41 PM, Bob Ippolito
      wrote:<br>
    </div>
    <blockquote type="cite">
      <div dir="ltr">Here's another approach that more closely models
        what's going on in the C++ version. I defined an ordNub rather
        than using nub as nub is O(n^2) as it only requires Eq.
        <div><br>
        </div>
        <div><a href="https://gist.github.com/etrepum/5bfedc8bbe576f89fe09" target="_blank">https://gist.github.com/etrepum/5bfedc8bbe576f89fe09</a><br>
        </div>
        <div><br>
        </div>
        <div>
          <div>import qualified Data.Set as S</div>
          <div>import Data.List (partition)</div>
          <div>import System.Environment (getArgs)</div>
          <div><br>
          </div>
          <div>data LWG = LWG { _lion, _wolf, _goat :: {-# UNPACK #-}
            !Int }</div>
          <div>     deriving (Show, Ord, Eq)</div>
          <div><br>
          </div>
          <div>lionEatGoat, lionEatWolf, wolfEatGoat :: LWG -> LWG</div>
          <div>lionEatGoat (LWG l w g) = LWG (l - 1) (w + 1) (g - 1)</div>
          <div>lionEatWolf (LWG l w g) = LWG (l - 1) (w - 1) (g + 1)</div>
          <div>wolfEatGoat (LWG l w g) = LWG (l + 1) (w - 1) (g - 1)</div>
          <div><br>
          </div>
          <div>stableState :: LWG -> Bool</div>
          <div>stableState (LWG l w g) = length (filter (==0) [l, w, g])
            >= 2</div>
          <div><br>
          </div>
          <div>validState :: LWG -> Bool</div>
          <div>validState (LWG l w g) = all (>=0) [l, w, g]</div>
          <div><br>
          </div>
          <div>possibleMeals :: LWG -> [LWG]</div>
          <div>possibleMeals state =</div>
          <div>  filter validState .</div>
          <div>  map ($ state) $ [lionEatGoat, lionEatWolf, wolfEatGoat]</div>
          <div><br>
          </div>
          <div>ordNub :: Ord a => [a] -> [a]</div>
          <div>ordNub = S.toList . S.fromList</div>
          <div><br>
          </div>
          <div>endStates :: [LWG] -> [LWG]</div>
          <div>endStates states</div>
          <div>  | not (null stable)   = stable</div>
          <div>  | not (null unstable) = endStates (concatMap
            possibleMeals unstable)</div>
          <div>  | otherwise           = []</div>
          <div>  where (stable, unstable) = partition stableState
            (ordNub states)</div>
          <div>  </div>
          <div>main :: IO ()</div>
          <div>main = do</div>
          <div>  [l, w, g] <- map read `fmap` getArgs</div>
          <div>  mapM_ print . endStates $ [LWG l w g]</div>
        </div>
        <div><br>
        </div>
      </div>
      <div class="gmail_extra"><br>
        <br>
        <div class="gmail_quote">On Sat, Jun 7, 2014 at 11:33 PM,
          Francesco Ariis <span dir="ltr"><<a href="mailto:fa-ml@ariis.it" target="_blank">fa-ml@ariis.it</a>></span>
          wrote:<br>
          <blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">On Sat,
            Jun 07, 2014 at 08:04:09PM -0400, Elric wrote:<br>
            > Hi,<br>
            <div>><br>
              > I came across this article: <a href="http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-wolves.html" target="_blank">http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-wolves.html</a><br>

              > a couple of days ago. This compares performance of
              solving a problem<br>
              > (which I will get to) using the functional constructs
              alone in<br>
              > languages like C++11 and Java 8.<br>
              > Since, Haskell is my first foray into FP, I thought I
              should try<br>
              > solving this in Haskell.<br>
              ><br>
              <br>
            </div>
            Hello Elric,<br>
                I gave a go at the problem, managed to get a result
            (23).<br>
            I attach the .hs file (not my best Haskell, but hopefully
            clear enough).<br>
            <br>
            The crucial point in my solution lies in this lines:<br>
            <br>
                carnage :: [Forest] -> [Forest]<br>
                let wodup = nub aa in<br>
                -- etc. etc.<br>
            <br>
            Which means after every iteration I call |nub| on my list of
            possible<br>
            states; nub is a function from |Data.List| and removes
            duplicate<br>
            elements from a list.<br>
            <br>
            If I omit that nub call, the program doesn't reach a
            solution (as it<br>
            is computationally quite inefficient). I think that's the
            problem<br>
            with your versions.<br>
            <br>
            Let me know if this helps<br>
            <br>
            <br>
            <br>
            <br>
            <br>
            <br>
            <br>
            _______________________________________________<br>
            Beginners mailing list<br>
            <a href="mailto:Beginners@haskell.org" target="_blank">Beginners@haskell.org</a><br>
            <a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
            <br>
          </blockquote>
        </div>
        <br>
      </div>
      <br>
      <fieldset></fieldset>
      <br>
      <pre>_______________________________________________
Beginners mailing list
<a href="mailto:Beginners@haskell.org" target="_blank">Beginners@haskell.org</a>
<a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a>
</pre>
    </blockquote>
    <br>
  </div></div></div>

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