[Haskell-beginners] Why is this function that slow?
Daniel Fischer
daniel.is.fischer at web.de
Wed Jul 28 21:21:46 EDT 2010
On Thursday 29 July 2010 02:02:04, Bryce Verdier wrote:
> <Shameful plug>http://scrollingtext.org/project-euler-problem-4</Shameful
plug>
You wrote there:
"If anyone knows of a way to run haskell interpretively, and without using
ghci, please let me know."
a) what's wrong with ghci?
b) hugs [that is an interpreter only, no attached compiler]
>
> 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-numbe
>r-list-haskell.html numberToList = reverse . unfoldr (\x -> if x == 0
> then Nothing else let (a,b) = x `quotRem` 10 in Just (b,a))
Here you're only interested in whether it's a palindrome, so the `reverse'
is an unnecessary waste of time.
Removing it doesn't gain much time, though.
>
> 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 hope that is a typo, it takes approximately 0.6 seconds here.
>
> I'm posting this to share my answer, but also to get any feed back on
> how I could make this code better.
Without type signatures, the types default to Integer.
Everything comfortably fits in an Int, so specifying the type as Int gives
a small speedup (it's small because GHC special-cases small Integers and
uses Int-arithmetic throughout here, but it must do some checks to see
whether a large Integer is necessary, which can be avoided by using Int).
Here at least, using let s = show n in s == reverse s is the much faster
palindrome test.
You can halve the running time by using the property
x * y == y * x
of multiplication.
You can chop a further 10% off by eliminating multiples of 10 (which never
give palindromes).
You can make it much faster by considering only pairs which have a larger
product than the largest palindrome found so far (that means you can't use
such a simple list-comprehension, so if better code means shorter code,
that won't be better).
You can further speed it up by using a little math to find necessary
conditions for x * y to be a (six-digit) palindrome.
Alternatively, you can bring the runtime down by reversing your approach,
instead of checking whether the product is a palindrome, check whether a
palindrome can be written as a product of two three-digit numbers.
More information about the Beginners
mailing list