[Fwd: Memory corruption issues when using newAlignedPinnedByteArray, GC kicking in?]

Nicolas Trangez nicolas at incubaid.com
Wed Jul 11 00:03:29 CEST 2012


All,

I sent this mail to Haskell Cafe earlier today, and was pointed [1] at
this list. As such...

Any help/advice would be greatly appreciated!

Thanks,

Nicolas

[1] http://www.haskell.org/pipermail/haskell-cafe/2012-July/102242.html

-------- Forwarded Message --------
> From: Nicolas Trangez <nicolas at incubaid.com>
> To: haskell-cafe at haskell.org
> Cc: Roman Leshchinskiy <rl at cse.unsw.edu.au>
> Subject: Memory corruption issues when using
> newAlignedPinnedByteArray, GC kicking in?
> Date: Tue, 10 Jul 2012 19:20:01 +0200
> 
> All,
> 
> While working on my vector-simd library, I noticed somehow memory I'm
> using gets corrupted/overwritten. I reworked this into a test case, and
> would love to get some help on how to fix this.
> 
> Previously I used some custom FFI calls to C to allocate aligned memory,
> which yields correct results, but this has a significant (+- 10x)
> performance impact on my benchmarks. Later on I discovered the
> newAlignedPinnedByteArray# function, and wrote some code using this.
> 
> Here's what I did in the test case: I created an MVector instance, with
> the exact same implementation as vector's
> Data.Vector.Storable.Mutable.MVector instance, except for basicUnsafeNew
> where I pass one more argument to mallocVector [1].
> 
> I also use 3 different versions of mallocVector (depending on
> compile-time flags):
> 
> mallocVectorOrig [2]: This is the upstream version, discarding the
> integer argument I added.
> 
> Then here's my first attempt, very similar to the implementation of
> mallocPlainForeignPtrBytes [3] at [4] using GHC.* libraries.
> 
> Finally there's something similar at [5] which uses the 'primitive'
> library.
> 
> The test case creates vectors of increasing size, then checks whether
> they contain the expected values. For the default implementation this
> works correctly. For both others it fails at some random size, and the
> values stored in the vector are not exactly what they should be.
> 
> I don't understand what's going on here. I suspect I lack a reference
> (or something along those lines) so GC kicks in, or maybe the buffer
> gets relocated, whilst it shouldn't.
> 
> Basically I'd need something like
> 
> GHC.ForeignPtr.mallocPlainAlignedForeignPtrBytes :: Int -> Int -> IO
> (ForeignPtr a)
> 
> Thanks,
> 
> Nicolas
> 
> [1] https://gist.github.com/3084806#LC37
> [2] https://gist.github.com/3084806#LC119
> [3]
> http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/GHC-ForeignPtr.html
> [4] https://gist.github.com/3084806#LC100
> [5] https://gist.github.com/3084806#LC81
> 
> 





More information about the Glasgow-haskell-users mailing list