[Haskell-cafe] Sometimes pinned memory?

Bulat Ziganshin bulat.ziganshin at gmail.com
Wed Nov 11 16:31:16 EST 2009


Hello Gregory,

Thursday, November 12, 2009, 12:14:56 AM, you wrote:

> Hey everyone!  Do you have any suggestions for how I might allocate an
> aligned block of memory that I can pin while making foreign calls, but
> leave unpinned the rest of the time to potentially improve allocation
> and garbage collector performance?  Or is this even a good idea?

if your call FFI function marked as unsafe, you may expect that memory
block wouldn't moved across call. it's better to ask ghc gurus about
details. just an example where memcpy used across non-pinned arrays:

freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e)
freezeSTUArray (STUArray l u n marr#) = ST $ \s1# ->
    case sizeofMutableByteArray# marr#  of { n# ->
    case newByteArray# n# s1#           of { (# s2#, marr'# #) ->
    case memcpy_freeze marr'# marr# (fromIntegral (I# n#)) of { IO m ->
    case unsafeCoerce# m s2#            of { (# s3#, _ #) ->
    case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) ->
    (# s4#, UArray l u n arr# #) }}}}}

foreign import ccall unsafe "memcpy"
    memcpy_freeze :: MutableByteArray# s -> MutableByteArray# s -> CSize
           -> IO (Ptr a)


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list