[Haskell-cafe] Memory leak or wrong use of Array ?
L.Guo
leaveye.guo at gmail.com
Fri Sep 14 21:35:14 EDT 2007
Hi Stuart.
Thanks for your advice about thunk, though I do not understand *thunk*
very well. Is there any other discriptions about thunk ?
I have tried the *seq* operation. When input is 10,000,000, the memory
still "leak", and there is still a "stack overflow".
I changed some mapM_ to sequence . map f, and tried to save some division.
The key functions now looks like this:
proportions n = unsafePerformIO $ do
arr <- newArray (2,n) (False,1/1) :: Fractional t => IO (IOArray Int (Bool,t))
sequence_ $ map (sieve arr n) [2..n]
factors <- getElems arr
return . map (\(n,(b,f)) -> (f,n)) $ zip [2..n] factors
where
sieve arr ubound p = do
(b,o) <- readArray arr p
if b then return () else
sequence_ . map (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)
let val = o * p / (p-1)
val `seq` return () -- force the thunk
writeArray arr i (True, val)
solutionOf = snd . minimum
. filter (\(f,n) -> isPerm (floor $ toRational n/f) n) . proportions
------------------
L.Guo
2007-09-15
More information about the Haskell-Cafe
mailing list