
Andrew Coppin wrote:
Andrew Coppin wrote:
copy :: Word32 -> IOUArray Word32 Bool -> Word32 -> IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' <- newArray (1,size') False
mapM_ (\n -> do b <- readArray grid n if b then mapM_ (\x -> writeArray grid' (n + size*x) True) [0..p-1] else return () ) [1..size]
return grid'
Actually, thinking about this... for most kinds of arrays (whether boxed or unboxed, mutable or immutable) there's probably a more efficient way to copy the data then this. Maybe we should add something to the various array APIs to allow efficient copying of arrays / large chunks of arrays?
(In the case of an unboxed array of bits, you can probably copy whole 32-bit or 64-bit words with a few machine instructions, for example.)
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.