[Haskell-cafe] Space leaks in function that uses Data.Vector.Mutable

Johan Tibell johan.tibell at gmail.com
Thu Jan 24 00:03:57 CET 2013


Hi!

You have to look outside the place function, which is strict enough. I
would look for a call to unsafeWrite that doesn't evaluate it's
argument before writing it into the vector. Perhaps you're doing
something like:

    MV.unsafeWrite (i + 1, ...)

Since tuples are lazy the i + 1 will be stored as a thunk. I recommend doing:

    data DescriptiveName a = DescriptiveName {-# UNPACK #-} !Int a

and using a

    MV.MVector (PrimState m) (DescriptiveName t)

if speed is really of the essence.

Aside: You can't optimize place slightly by:

 * Making it strict in val1, and
 * Making it inline.

The reason you want it to inline* is that's the function is
polymorphic and inlining it at a call site when you know if you're
working in IO and ST will improve performance.

Here's the slightly optimized version:

place :: (PrimMonad m) =>
     MV.MVector (PrimState m) (Int, t) -> (Int, t) -> Int -> m ()
place v max@(!val1,_) i = place' i
 where
  place' i = do
    let j = i - 1
    if j < 0
    then return ()
    else do
      curr@(val2, _) <- MV.unsafeRead v j
      if val2 > val1
      then do
        MV.unsafeWrite v j max
        MV.unsafeWrite v i curr
        place' j
      else return ()
{-# INLINE place #-}

* It should be enough to write two SPECIALIZE pragmas, one for IO and
one for ST, but GHC doesn't seem to like that for some reason:

/tmp/Test.hs:24:1: Warning:
    RULE left-hand side too complicated to desugar
      (place @ (ST s) @ t ($fPrimMonadST @ s ($fMonadST @ s))) `cast` ...

/tmp/Test.hs:25:1: Warning:
    RULE left-hand side too complicated to desugar
      (place @ IO @ t $fPrimMonadIO) `cast` ...

Cheers,
Johan



More information about the Haskell-Cafe mailing list