[Haskell-cafe] Memory corruption issues when using newAlignedPinnedByteArray, GC kicking in?

Thomas Schilling nominolo at googlemail.com
Tue Jul 10 21:18:48 CEST 2012


I think you should ask this question on the glasgow-haskell-users
mailing list: http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 10 July 2012 18:20, Nicolas Trangez <nicolas at incubaid.com> wrote:
> 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
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
Push the envelope. Watch it bend.



More information about the Haskell-Cafe mailing list