
Here's a completely naive implementation, it's slow as cold molasses going uphill during a blizzard, but it doesn't seem to be wrong. I let it run in the interpreter for the last 3 minutes or so and it's reproduced the given list up to 126 (and hasn't crapped out yet). I imagine there's probably a less naive algorithm that could be done, but I rather like the straightforwardness of this one... /Joe ---------------------------- module Main where import Control.Monad(filterM) import Data.List(sort) divisors :: Int -> [Int] divisors n = [d | d <- [1..n], n `mod` d == 0] powerset = filterM (const [True, False]) (><) :: Eq a => [a] -> [a] -> [(a,a)] x >< y = [(x', y') | x' <- x, y' <- y, x' /= y'] (/\) :: Eq a => [a] -> [a] -> Bool x /\ y = null $ filter (`elem` x) y prod m n = filter (uncurry (/\)) (m >< n) eqSum :: ([Int], [Int]) -> Bool eqSum (m, n) = sum m == sum n containsAllDivisors i l = filter (\x -> (sort . uncurry (++) $ x) == divisors i) l zumkeller :: Int -> [([Int], [Int])] zumkeller n = containsAllDivisors n . filter eqSum . (\x -> prod x x) $ allParts where divs = divisors n allParts = powerset divs zumkellerP :: Int -> Bool zumkellerP = not . null . zumkeller --------------------------------------- On Dec 7, 2009, at 4:33 PM, Frank Buss wrote:
Anyone interested in writing some lines of Haskell code for generating the Zumkeller numbers?
http://www.luschny.de/math/seq/ZumkellerNumbers.html
My C/C# solutions looks clumsy (but is fast). I think this can be done much more elegant in Haskell with lazy evaluation.
Not related to Haskell, but do you think semi-Zumkeller numbers are semi-perfect numbers? Maybe some Haskell code for testing it for some numbers?
-- Frank Buss, fb@frank-buss.de http://www.frank-buss.de, http://www.it4-systems.de
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe