
Andrew Coppin wrote:
ChrisK wrote:
For GHC 6.6 I created
foreign import ccall unsafe "memcpy" memcpy :: MutableByteArray# RealWorld -> MutableByteArray# RealWorld -> Int# -> IO ()
{-# INLINE copySTU #-} copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) => STUArray s i e -> STUArray s i e -> ST s () copySTU (STUArray _ _ msource) (STUArray _ _ mdest) = -- do b1 <- getBounds s1 -- b2 <- getBounds s2 -- when (b1/=b2) (error ("\n\nWTF copySTU: "++show (b1,b2))) ST $ \s1# -> case sizeofMutableByteArray# msource of { n# -> case unsafeCoerce# memcpy mdest msource n# s1# of { (# s2#, () #) -> (# s2#, () #) }}
To allow efficient copying of STUArrays.
So... that copies the entire array into another array of the same size? (I'm having a lot of trouble understanding the code...)
Yes, that is what it does. The "STUArray" data type has the STUArray constructor which I import and pattern match against. The imports are:
import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..)) import GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
in 6.6.1 this is defined as
data STUArray s i a = STUArray !i !i (MutableByteArray# s) in 6.8.1 this is defined as data STUArray s i a = STUArray !i !i !Int (MutableByteArray# s)
I use sizeofMutableByteArray# to get the source size, n#. I have lost track of how unsafeCoerce# and s1# are being used...oops. It is similar to data-dependency tricks used inside Data.Array.Base, though. -- Chris