[Haskell-cafe] Array copy performance

Bulat Ziganshin bulat.ziganshin at gmail.com
Fri Feb 2 09:02:42 EST 2007


Hello Chris,

Friday, February 2, 2007, 4:44:37 PM, you wrote:

> If I have two identical STUArrays (same type and bounds) then what is the most
> efficient way to overwrite the data in the destination with the data in the
> source?  Does this work for STArrays?

> Is there a way to avoid the long loop?
>>   forM_ (range b) $ \index ->
>>     readArray source index >>= writeArray destination index

the topic of efficient looping over arrays is briefly covered in
http://haskell.org/haskellwiki/Modern_array_libraries


> Is there a GHC only solution?

yes, use "unsafeCoerce# memcpy":

module Data.Array.Base where
...
#ifdef __GLASGOW_HASKELL__
thawSTUArray :: Ix i => UArray i e -> ST s (STUArray s i e)
thawSTUArray (UArray l u arr#) = ST $ \s1# ->
    case sizeofByteArray# arr#          of { n# ->
    case newByteArray# n# s1#           of { (# s2#, marr# #) ->
    case unsafeCoerce# memcpy marr# arr# n# s2# of { (# s3#, () #) ->
    (# s3#, STUArray l u marr# #) }}}

foreign import ccall unsafe "memcpy"
    memcpy :: MutableByteArray# RealWorld -> ByteArray# -> Int# -> IO ()
#endif /* __GLASGOW_HASKELL__ */


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



More information about the Haskell-Cafe mailing list