[Haskell-cafe] Memory Leak Help

J. Garrett Morris trevion at gmail.com
Mon Nov 12 00:27:57 EST 2007


Hello,

I have code which seems to contain a memory leak, but I'm not sure
where it is or what's causing it.  Any help would be greatly
appreciated:

The code is:

data Ratings = Ratings { movieCount :: Int
                       , movieLookup :: IOUArray Int Word32
                       , movieRatings :: IOUArray Word32 Word32 }

readRatingsFromText :: Int -> Int -> C.ByteString -> IO Ratings
readRatingsFromText movieCount ratingCount text =
    do movieLookup <- newArray_ (0, movieCount - 1)
       movieRatings <- newArray_ (0, fromIntegral ratingCount - 1)
       iter movieLookup movieRatings 0 (C.lines text)
       return (Ratings movieCount movieLookup movieRatings)
    where iter :: IOUArray Int Word32 -> IOUArray Word32 Word32 ->
Word32 -> [C.ByteString] -> IO ()
          iter !movieLookup !movieRatings !i [] = return ()
          iter !movieLookup !movieRatings !i (s:ss)
              | c == ':' = do writeArray movieLookup movie i
                              iter movieLookup movieRatings i ss
              | otherwise = do writeArray movieRatings i rating    -- ***
                               iter movieLookup movieRatings (i + 1) ss
              where Just (x, rest) = C.readInt s
                    c              = C.head rest
                    Just (y, _)    = C.readInt (C.tail rest)
                    movie          = x - 1
                    rating         = fromIntegral x `shiftL` 3 .|.
fromIntegral y :: Word32

main = do args <- getArgs
          ratings <- readRatingsFromText (read $ args !! 0) (read $
args !! 1) =<< B.readFile (args !! 2)
          return ()


This attempts to read a file that looks like:

1:
401,2
503,1
...
2:
506,5
230,4

possibly with additional junk at the end of each line into an array.
When I run this, memory usage grows without bound.

If I comment out the line with -- ***, the memory profile is flat.
Without storing the ratings, it's not fantastically useful; however,
it does demonstrate that it should be possible to iterate through the
file with a flat memory profile (which is my goal).

I'm compiling with ghc --make -O2

Any help would be greatly appreciated.  Thanks!

 /g

-- 
The man who'd introduced them didn't much like either of them, though
he acted as if he did, anxious as he was to preserve good relations at
all times. One never knew, after all, now did one now did one now did
one.


More information about the Haskell-Cafe mailing list