[Haskell-beginners] Perfect numbers

David Frey dpfrey at shaw.ca
Fri Oct 3 13:20:35 EDT 2008


On 10/2/2008, "Ben Deane" <haskell at elbeno.com> wrote:

>On Thu, 2008-10-02 at 05:45 +0100, Matthew Williams wrote:
>> Hi Guys,
>>
>> I'm new to Haskell and I was wondering if you can help me:
>>
>> One of the first program's I tend to write when I'm looking at a new
>> language is a program to generate a list of perfect numbers:
>>
>> --My First Perfect Number Generator
>> factors :: Integer -> [Integer]
>> factors x = [z | z <- [1..x-1], x `mod` z == 0]
>
>Hi Matthew,
>
>A big optimization for larger numbers is that you only need to go up to
>the square root of x here and add both z and x/z to the list. (Where x
>is a perfect square you need to avoid adding the root twice.) It's late
>and there is probably a better way to do this, but:
>
>import List
>
>semi_factors :: Int -> [Int]
>semi_factors x = takeWhile (\n -> n * n <= x) [z | z <- [2..x-1], x
>`mod` z == 0]
>
>factors n =
>  let xs = semi_factors n
>  in nub (1 : (xs ++ (map (n `div`) xs)))
>
>>
>> is_perfect :: Integer -> Bool
>> is_perfect x = if sum(factors x) == x then True else False
>
>"if <something> then True else False" should ring alarm bells!
>Immediately replace with simply "<something>":
>
>is_perfect x = sum (factors x) == x
>
>you could also use
>
>is_perfect x = foldl' (+) 0 (factors x) == x
>
>(strict foldl from Data.List)
>
>>
>> do_perfect :: [Integer] -> [Integer]
>> do_perfect x = [z |z <- x, is_perfect z ]
>>
>> Then to run it:
>> > do_perfect [1..9000]
>
>I think more idiomatic would be:
>
>do_perfect x = filter is_perfect [2..x]
>
>All this speeds it up a bit. But I can't think any more - time to sleep.
>
>thanks
>Ben
>
>>
>>
>> I'm using GHC to run it. My problem / question is this: It's running
>quite a lot slower than equivalent programs in erlang and python. I
>suspect it's down to the way I've written it. Any thoughts (or comments
>in general)
>>
>> Many thanks
>>
>> Matt
>>



This isn't really important for this application, because the numbers
being factored are relatively small, but there are some inefficiencies
in the factors function that Ben presented that are fairly easy to
overcome.

Here's my version:

factors :: (Integral a) => a -> [a]
factors n = let
    p1 = [x | x <- [1 .. floor $ sqrt $ fromIntegral n], n `mod` x == 0]
    p2 = map (div n) (tail p1)
    in p1 `concatNoDupe` (reverse p2) where
        concatNoDupe :: (Eq a) => [a] -> [a] -> [a]
        concatNoDupe [] ys = ys
        concatNoDupe [x] (y:ys) = if x == y then (y : ys) else (x : y :
ys)
        concatNoDupe (x:xs) ys = x : (concatNoDupe xs ys)

Since my two lists of factors are ordered, I can exploit this to avoid
calling nub and instead call 'concatNoDupe' which is more efficient.

The other thing I optimized was the creation of the list of potential
factors.  Ben's solution required the evaluation of a predicate for
each element in the list.  My solution simply computes the maximum value
of the list up front.

To demonstrate how these changes affect performance, when I run this on
my computer:
main = print $ sum $ concat $ map factors [1..80000]

Matthew's version: 194 seconds
Ben's version: 32 seconds
My version: 1 second

I don't mean to suggest that my version is optimal.  I just want to
point out that seemingly small changes to an algorithm can have large
consequences.

David


More information about the Beginners mailing list