Hi Brent, 
  You are the man!

  After such a little refactoring, it solved the problem around 12s.

-Haisheng


On Tue, Dec 13, 2011 at 8:37 PM, Brent Yorgey <byorgey@seas.upenn.edu> wrote:
On Tue, Dec 13, 2011 at 11:49:03AM +0800, Haisheng Wu wrote:
> Hello,
>   I'm trying to solve Euler problem 104 with the solution "My Solution"
> below but it takes quite long time therefore I quite.
>   Then I turn to haskell wiki for better solution which work well but I can
> not figure out why it is better than mine.
>   I'm wondering whether more function call decrease the performance.
>
>   Could you please help a little?
>   Thank you.
>
> *-- | My Solution *
> main = print $ snd $ head $ dropWhile (\(x,y) -> (not . bothNinePandigit
> "123456789") x) (zip fibs [1..])
>
> bothNinePandigit digits n = isFirstNinePandigit digits n &&
> isLastNinePandigit digits n
>
> isLastNinePandigit  digits n = digits == sort (lastDigits 9 n)
> isFirstNinePandigit digits n = digits == sort (firstDigits 9 n)
>
> firstDigits k n = take k (show n)
> lastDigits  k n = show (n `mod` 10^k)
>
> fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
>
> *-- | From Haskell Wiki *
> fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
>
> isFibPan n =
>   let a = n `mod` 1000000000
>       b = sort (show a)
>       c = sort $ take 9 $ show n
>   in  b == "123456789" && c == "123456789"
>
> ex_104 = snd $ head $ dropWhile (\(x,y) -> (not . isFibPan) x) (zip fibs
> [1..])

Aha, this is sneaky!

Having a bunch of function calls should not make
a difference if you are compiling with -O2 (you are compiling with
-O2, aren't you)?  Nonetheless, even compiling with -O2 I was also
getting the results you mention -- the wiki version was pretty fast
(about 24s) whereas your version took more than 15 minutes.

So I ran your version with profiling to help figure out what was going
on.  I compiled with

 ghc --make -O2 -prof -auto-all -rtsopts PE104.hs

and then ran with

 ./PE104 +RTS -p -RTS

This causes a file "PE104.prof" to be written which has a bunch of
data on execution time and allocation broken down by function. The
results showed that 95% of the program's run time was being spent in
'firstDigits'.

And then it hit me -- the difference is due to the fact that your
version and the wiki version test the first digits and the last digits
in a different order!

'show' on integers is (relatively) very slow.  Your version first
tests the first 9 digits of the number -- note that computing the
first digits of a number requires computing all the digits, even the
ones that don't get shown.  Only if the first 9 digits are "123456789"
does your version go on to test the last nine digits (since (&&) is
lazy).  The wiki version, on the other hand, first tests the last 9
digits (much faster) and only if those are "123456789" does it bother
doing the (expensive) test for the first 9 digits.  Since only 112 out
of the first 329000 or so Fibonacci numbers end in the digits 1..9,
this makes a huge difference.

-Brent

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners