
Hello, I want to access the contents of a Data.Vector.Primitive from FFI. I came up with the following so far: {-# LANGUAGE ForeignFunctionInterface #-} module FFIExample (exampleFn) where import Control.Monad.Primitive (touch) import Control.Monad.ST (runST) import Data.Primitive.Addr (Addr(..)) import Data.Primitive.ByteArray (mutableByteArrayContents) import qualified Data.Vector.Primitive as P import qualified Data.Vector.Primitive.Mutable as PM import GHC.Ptr (Ptr(..), plusPtr) import Data.Word (Word64) foreign import ccall unsafe "my_external_fn" myExternalFn :: Ptr Word64 -> Int -> Int exampleFn :: P.Vector Word64 -> Int exampleFn v = runST $ do PM.MVector off len mba <- P.unsafeThaw v let ptr = case mutableByteArrayContents mba of Addr addr -> Ptr addr `plusPtr` off result = myExternalFn ptr len result `seq` touch mba return result This seems to work, but I have questions that I haven't been able to find the answers to on my own: 1. Is this actually OK to do? I guess that this wouldn't be OK if the foreign import were "safe", as then the GC could move the contents of the byte array while the foreign function is running. But is it safe like this? 2. If the answer to the previous question is no, then is there a way to do it properly? Or there is just no way to pass an unpinned byte array to a foreign call? What about foreign import prim? 3. If the answer to Q1 is no, then would it be OK if the underlying byte array were pinned? 4. Any other simplifications? Pointers to resources on these topics would be more than welcome! But, I haven't been able to find any. Thanks, Mihaly