
On Wed, Jun 25, 2014 at 15:02 +0200, Johan Tibell wrote:
On Wed, Jun 25, 2014 at 2:54 PM, Mihaly Barasz
wrote: Well, I don't know enough about how GC is specified in GHC, but _in practice_ calls to GC could happen only on entry to the exampleFn closure. Not between the address computation and the foreign call. (I simply looked at the generated code, I don't know if there is any guarantee for that.)
There can be additional heap checks at the start of any basic block in the generated assembly for the function. Right, in practice there's probably not an issue.
Thanks, I'll look into that. Are there any pointers/examples?
There's some code out there on the web that uses the extension. Here's an example: https://github.com/tibbe/hashable/blob/master/Data/Hashable/Class.hs#L470
Thanks, this works wonderfully. The code is much simplified: {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE MagicHash, UnliftedFFITypes #-} module FFIExample (exampleFn) where import Control.Monad.ST (runST) import Data.Primitive.ByteArray (ByteArray(..), ByteArray#, unsafeFreezeByteArray) import qualified Data.Vector.Primitive as P import qualified Data.Vector.Primitive.Mutable as PM import Data.Word (Word64) foreign import ccall unsafe "my_external_fn" myExternalFn :: ByteArray# -> Int -> Int -> Int exampleFn :: P.Vector Word64 -> Int exampleFn v = runST $ do PM.MVector off len mba <- P.unsafeThaw v ByteArray ba <- unsafeFreezeByteArray mba return $! myExternalFn ba off len And yeah, now the unsafeThaw followed immediately by the unsafeFreezeByteArray looks even sillier. (But again, it completely disappears in the generated code.) Mihaly
I don't know why, but the constructor for Vector is not exported, only for the MVector. But, this use of unsafeThaw is completely benign. (Actually, it fully disappears in the generated code. :))
Probably because it's a ByteArray#, not an Array#. For the latter unsafe thawing results in the object being put on the GC mutable list (in practice that means that the info table ptr changes).