[Haskell-cafe] How can I pass IOUArrays to FFI functions?

Stefan O'Rear stefanor at cox.net
Tue Aug 21 02:08:59 EDT 2007


On Mon, Aug 20, 2007 at 11:03:45PM -0700, Ryan Ingram wrote:
>  Thanks to everyone, especially Bulat Ziganshin.
> 
> In http://haskell.org/haskellwiki/Modern_array_libraries there is enough
> information to do what I want.  It specifically mentions that it's OK to
> pass ByteArray# and MutableByteArray# to an "unsafe foreign" procedure as
> long as that procedure doesn't save the pointer, and that worked for me.
> 
> Here is what I ended up using, which worked great and the FFI usage for a
> couple of key functions sped up my code by a large factor:
>  import Data.Array.Base
> import Data.Array.IO.Internals
> import GHC.Exts
> 
> {-# INLINE unsafeByteArrayToPtr #-}
> unsafeByteArrayToPtr :: IOUArray Int Word32 -> Ptr Word32
> unsafeByteArrayToPtr (IOUArray (STUArray _ _ array#)) = Ptr (unsafeCoerce#
> array#)
> 
> Possibly a better thing to do would be to declare that the call takes a
> MutableByteArray# directly in the foreign import statement, which I believe
> would let me avoid using unsafeCoerce# at all, but this was good enough for
> my purposes.
> 
> Afterwards I used -ddump-simpl to check on the generated Core for the
> foreign call and it looked good.

Your code is broken in a most evil and insidious way.

Addr# is an uninterpreted address.  Since it might point to arbitrary
memory, or even be a coerced integer, it is meaningless for the garbage
collector to try to follow it.

MutableByteArray#s are objects in the heap, and can move.

If a garbage collection happens after the unsafeCoerce# but before the
foreign call, then you will pass a dangling pointer to memcpy.  Massive
memory corruption will ensue.

As it stands, 1. the garbage collector is only called when all threads
run out of memory in their local 4k blocks and 2. the optimizer will
eliminate all allocation between the Ptr construction and the call.  So
you'll never notice anything wrong.

Suppose some unsuspecting developer tries to compile without
optimizations.  Then that Ptr construction will remain, and each time
your function is called, there is a 1/32,768 chance of catastrophe.
Unreproducable bugs are rarely reported, but they do add to people's
impression of how unstable a language/library is.

"But I can just add a comment saying -O only."

Then suppose in the mists of future time one of those parameters of GHC
itself that I described, changes.

Stefan
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20070820/3a3ee425/attachment.bin


More information about the Haskell-Cafe mailing list