Haskell Quiz/Weird Numbers/Solution Dolio
A first, rather naive solution:
module Main where
import Control.Monad.Reader
import Data.List
import System
power = filterM $ const [True,False]
divisors n = sort $ 1 : join [ [x, n `div` x] | x <- l ]
where l = filter ((==0) . (mod n)) . takeWhile ((<n) . join (*)) $ [2..]
weird n = sum s > n && all (n/=) (map sum ss)
where (s:ss) = power $ divisors n
main = print . filter weird . enumFromThenTo 70 72 . read . head =<< getArgs
A much more efficient solution, implementing some of the techniques from the rubyquiz discussion:
module Main where
import Control.Monad.Reader
import Data.List
import System
power = filterM $ const [True,False]
divisors n = nub $ 1 : l ++ map (div n) (reverse l)
where l = filter ((==0) . (mod n)) . takeWhile ((<=n) . join (*)) $ [2..]
weird n
| a <= 0 = False
| a `elem` d = False
| sd == a = False
| sd < a = True
| otherwise = checkSubset a d
where d = divisors n
sd = sum d
a = sd - n
checkSubset a [] = True
checkSubset a l@(x:xs)
| a `seq` False = undefined -- strictness
| a < 0 = True
| a `elem` l = False
| null xs = True
| otherwise = checkSubset (a - x) xs && checkSubset a xs
main = print . filter weird . enumFromThenTo 70 72 . read . head =<< getArgs