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

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. -- ryan

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

Your code is broken in a most evil and insidious way.
Interesting. This is for a toy project, so I'm not too worried, but lets say I wanted to do this "correctly" and I was set on using IOUArray for some reason. (The Haskell wiki claims that StorableArray is slower; is that actually the case?) Which of the following fixes would work now? Which has the lowest probability of not working in the future? 1) Declare f to take Addr# and don't construct a Ptr Word32 I suspect this would be enough unless the GC changed to some sort of continous GC which can happen even without an allocation 2) Declare f to take MutableByteArray# Is this good enough to make the collector happy? 3) Something else I haven't thought of? If there was no other option, and StorableArray wasn't slower, and I was working on a real project, I'd probably wrap my own around ForeignPtr like Data.ByteString. -- ryan

On Mon, Aug 20, 2007 at 11:47:06PM -0700, Ryan Ingram wrote:
Your code is broken in a most evil and insidious way.
Interesting. This is for a toy project, so I'm not too worried, but lets say I wanted to do this "correctly" and I was set on using IOUArray for some reason.
Heh, I'm a lot less worried now. (Somehow I thought this was going into a high-visibility library!)
(The Haskell wiki claims that StorableArray is slower; is that actually the case?)
Good question! I wrote a basic CA benchmark and a much simpler array benchmark, both parameterized by the array type, and couldn't get consistent results, so I'll take this as a "no". stefan@stefans:/tmp$ cat ArrayTest.hs {-# OPTIONS_GHC -fglasgow-exts -cpp #-} import Data.Array.MArray import Data.Bits import Data.Array.IO import Data.Array.Base import Data.Array.Storable import GHC.Exts -- #define ARRAY IOUArray -- uch! iter :: Int -> ARRAY Int Word -> IO () iter 4096 arr = arr `seq` return () iter ix arr = do unsafeWrite arr ix . succ =<< unsafeRead arr ix iter (ix+1) arr bench 100000 arr = arr `seq` return () bench ct arr = do iter 0 arr bench (ct+1) arr main = do arr <- newListArray (0,4095) [1..] bench 0 arr print =<< getElems arr stefan@stefans:/tmp$ ghc -fforce-recomp -DARRAY=IOUArray -O2 ArrayTest.hs && time ./a.out > /dev/null real 0m2.006s user 0m2.028s sys 0m0.008s stefan@stefans:/tmp$ ghc -fforce-recomp -DARRAY=StorableArray -O2 ArrayTest.hs && time ./a.out > /dev/null real 0m1.845s user 0m1.872s sys 0m0.004s stefan@stefans:/tmp$
Which of the following fixes would work now? Which has the lowest probability of not working in the future?
1) Declare f to take Addr# and don't construct a Ptr Word32 I suspect this would be enough unless the GC changed to some sort of continous GC which can happen even without an allocation
Would work now, I think.
2) Declare f to take MutableByteArray# Is this good enough to make the collector happy?
Maybe. In theory the collector should know that an argument passed to a foreign function as a pointer type, should be followed. I'd tentatively call it a bug if this breaks, but it's fragile enough that you should expect to find yourself reporting said bug.
3) Something else I haven't thought of?
If there was no other option, and StorableArray wasn't slower, and I was working on a real project, I'd probably wrap my own around ForeignPtr like Data.ByteString.
Stefan

ryani.spam:
Your code is broken in a most evil and insidious way.
Interesting. This is for a toy project, so I'm not too worried, but lets say I wanted to do this "correctly" and I was set on using IOUArray for some reason. (The Haskell wiki claims that StorableArray is slower; is that actually the case?)
Which of the following fixes would work now? Which has the lowest probability of not working in the future?
1) Declare f to take Addr# and don't construct a Ptr Word32
I suspect this would be enough unless the GC changed to some sort of continous GC which can happen even without an allocation
2) Declare f to take MutableByteArray#
Is this good enough to make the collector happy?
3) Something else I haven't thought of?
If there was no other option, and StorableArray wasn't slower, and I was working on a real project, I'd probably wrap my own around ForeignPtr like Data.ByteString.
Yeah, we have ForeignPtr arrays and Foreign.Array /exactly/ for calling to C safely. I don't know why people suggest all these other dodgy solutions, when there's one that's guaranteed by the FFI spec to work. -- Don

Hello Ryan, Tuesday, August 21, 2007, 10:47:06 AM, you wrote:
Your code is broken in a most evil and insidious way. Interesting. This is for a toy project, so I'm not too worried, but lets say I wanted to do this "correctly" and I was set on using IOUArray for some reason. (The Haskell wiki claims that StorableArray is slower; is that actually the case?)
it was in 6.4. in 6.6 it has the same speed as IOArray the Arrays wiki page was written primarily by me and suggestion to use unsafeCoerce# based solely on the code fragment i just citated. so this page is broken in that it says primarily about rather old 6.4 version and that it suggests unreliable trick without much understanding of ghc intrinsics :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Stefan, Tuesday, August 21, 2007, 10:08:59 AM, you wrote:
Your code is broken in a most evil and insidious way.
and this code, too? :) freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e) freezeSTUArray (STUArray l u marr#) = ST $ \s1# -> case sizeofMutableByteArray# marr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr'# #) -> case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -> case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -> (# s4#, UArray l u arr# #) }}}}
Unreproducable bugs are rarely reported, but they do add to people's impression of how unstable a language/library is.
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Ah, sneaky. That code is fine because it uses unsafeCoerce# on "memcpy",
changing memcpy from whatever type it is, into
MutableByteArray# s# -> MutableByteArray# s# -> Int# -> s# -> (# s#, () #)
So as long as the GC understands MutableByteArray# it's safe; it's relying
on the C calling convention being handled properly.
On 8/21/07, Bulat Ziganshin
Hello Stefan,
Tuesday, August 21, 2007, 10:08:59 AM, you wrote:
Your code is broken in a most evil and insidious way.
and this code, too? :)
freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e) freezeSTUArray (STUArray l u marr#) = ST $ \s1# -> case sizeofMutableByteArray# marr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr'# #) -> case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -> case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -> (# s4#, UArray l u arr# #) }}}}
Unreproducable bugs are rarely reported, but they do add to people's impression of how unstable a language/library is.
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Tue, Aug 21, 2007 at 12:50:22AM -0700, Ryan Ingram wrote:
Ah, sneaky. That code is fine because it uses unsafeCoerce# on "memcpy", changing memcpy from whatever type it is, into MutableByteArray# s# -> MutableByteArray# s# -> Int# -> s# -> (# s#, () #)
So as long as the GC understands MutableByteArray# it's safe; it's relying on the C calling convention being handled properly.
Which still isn't quite correct, because the code for base-2.1:Data.Array.Base.memcpy could still be perverse and trigger a GC. However, since base is version-locked to GHC, it can depend on as much undocumented behaviour as it needs. The worst that can happen is a few more testsuite failures when someone tries to change the compiler.
On 8/21/07, Bulat Ziganshin
wrote: Hello Stefan,
Tuesday, August 21, 2007, 10:08:59 AM, you wrote:
Your code is broken in a most evil and insidious way.
and this code, too? :)
freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e) freezeSTUArray (STUArray l u marr#) = ST $ \s1# -> case sizeofMutableByteArray# marr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr'# #) -> case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -> case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -> (# s4#, UArray l u arr# #) }}}}
Unreproducable bugs are rarely reported, but they do add to people's impression of how unstable a language/library is.
Stefan
participants (4)
-
Bulat Ziganshin
-
dons@cse.unsw.edu.au
-
Ryan Ingram
-
Stefan O'Rear