[Haskell-beginners] Why is this function that slow?
Bryce Verdier
bryceverdier at gmail.com
Wed Jul 28 20:02:04 EDT 2010
<Shameful
plug>http://scrollingtext.org/project-euler-problem-4</Shameful plug>
to get the numeric check I had to do change the number to a list (to
reverse it).
module Main where
import Data.List
--Stole numberToList code from:
--http://www.rhinocerus.net/forum/lang-functional/95473-converting-number-list-haskell.html
numberToList = reverse . unfoldr (\x -> if x == 0 then Nothing else let
(a,b) = x `quotRem` 10 in Just (b,a))
is_palimdrome number = num_list == reverse num_list
where
num_list = numberToList number
main :: IO ()
main = print . maximum $ [ x * y | x <- nums, y <- nums, is_palimdrome
(x * y)]
where nums = [1000,999..100]
on my quadcore box w/ 3G of Ram the compiled code runs in .6 ms.
I'm posting this to share my answer, but also to get any feed back on
how I could make this code better.
Bryce
On 07/28/2010 04:33 PM, Daniel Fischer wrote:
> On Thursday 29 July 2010 00:29:56, Andreas Flierl wrote:
>
>> Hello everyone,
>>
>> I am a newbie to Haskell coming from a Java/Scala/Ruby background. As
>> first few exercises, I was trying to translate my Scala solutions for
>> some Project Euler [1] problems to Haskell. The function that solves
>> problem 4 turns out to be quite slow (6s in Haskell as opposed to 400ms
>> in Scala) and I cannot understand why. Here's the function:
>>
>> euler4 = solve 100 999
>> where solve min max = maximum palindromes
>> where palindromes = [n | a<- range, b<- range, let n = a
>> * b, isPalindrome n] range = [max, max - 1 .. min]
>> isPalindrome n = (n :: Int) == (read $ reverse $ show n)
>>
> Try
>
> isPalindrome n = let s = show n in s == reverse s
>
> `read' is slow, though I didn't expect it to be that slow, to be honest.
> The above change brought time down from ~5.1 secs to 0.22 secs here.
>
> You can make it still faster if you make an arithmetic palindrome check
> instead of converting to String (0.1 secs).
>
> With algorithmic improvements more can be gained.
>
>
>> Using +RTS -sstderr I see that the allocation rate is 12M/s, which seems
>> rather high to me. My guess would be that this is somehow related to
>> lazy evaluation but all in all, I've got no real clue and would be
>> thankful for any advice.
>>
> The problem (part of it at least) is that the Read instances for number
> types has been written more with elegance in mind than efficiency,
> apparently.
> Thus when you want to read an Int, first a generic number, possibly
> including a fractional part and an exponent or represented in base 8 or 16
> is tried to be read.
> That number is read as an Integer or a Rational (depending on the presence
> of a fractional part and an exponent [and its value]).
> If the read produced an Integer, that is then converted to the appropriate
> number type [Int in this case].
>
> That gives very elegant, but not very fast code.
>
>
>> Thank you
>> Andreas
>>
>>
> Cheers,
> Daniel
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100728/8df2ebc8/attachment.html
More information about the Beginners
mailing list