[Haskell-cafe] Memory leak or wrong use of Array ?
L.Guo
leaveye.guo at gmail.com
Thu Sep 13 12:19:34 EDT 2007
Hi MailList Haskell-Cafe:
I am tring to solve Project Euler problem 70.
And write some code. (will at the end of this mail)
And, I run the code in GHCi.
The problem is that, when the input is 1,000,000, it works
fine, when the input is up to 10,000,000, the memory GHCi
used increase very fast and did not stop.
Is this a memory leak ? or, is there some mis-understand
about array ?
Regards
--------------
-- Mudules :
import Data.Array.IO
import Foreign ( unsafePerformIO )
-- Codes :
p070_solve = putStrLn . show $ solutionOf 10000000
where
isPerm a b = sort (show a) == sort (show b)
phis n = unsafePerformIO $ do
arr <- newArray (2,n) (False,1/1) :: Fractional t => IO (IOArray Int (Bool,t))
mapM_ (sieve arr n) [2..n]
factors <- getElems arr
return . map (\(n,(b,f)) -> (n,floor $ toRational n*f)) $ zip [2..n] factors
where
sieve arr ubound p = do
(b,o) <- readArray arr p
if b then return () else
mapM_ (update arr (toRational p)) . takeWhile (<=ubound) $ iterate (+p) p
update arr p i = do
(_,o) <- readArray arr i
writeArray arr i (True,o*(p-1)/p)
solutionOf = snd . minimum
. map (\(n,phi)->(toRational n / toRational phi,n))
. filter (uncurry isPerm) . phis
--------------
L.Guo
2007-09-14
More information about the Haskell-Cafe
mailing list