
--- J�r�my_Bobbio
memcpy is available in Foreign.Marshal.Utils:
copyBytes :: Ptr a -> Ptr a -> Int -> IO ()
Copies the given number of bytes from the second area (source) into the first (destination);the copied areas may not overlap
Here is the result of a quick try to implement fast copy using it and Data.Array.Storable:
module FastArrrayCopy where
import Data.Array.Storable import Foreign.Ptr import Foreign.Storable import Foreign.Marshal.Utils ( copyBytes )
fastArrayCopy :: (Storable e1, Ix i, Ix i1) => StorableArray i1 e1 -> i1 -> StorableArray i e -> i -> Int -> IO () fastArrayCopy src srcStart dest destStart count | destOffset + count > rangeSize (bounds dest) = error "Out of bounds" | otherwise = withStorableArray src $ \ pSrc -> withStorableArray dest $ \ pDest -> do dummy <- peek pSrc copyBytes (pDest `plusPtr` (destOffset * sizeOf dummy)) (pSrc `plusPtr` (srcOffset * sizeOf dummy)) (count * sizeOf dummy) where srcOffset = index (bounds src) srcStart destOffset = index (bounds dest) destStart
main :: IO () main = do a <- newListArray (0, 100) ([0..] :: [Int]) a' <- newArray (0, 50) (42 :: Int) getElems a' >>= print copyRange a 10 a' 15 20 getElems a' >>= print
This should be in a FAQ somewhere for those of us damaged by years of coding in C. __________________________________ Do you Yahoo!? New and Improved Yahoo! Mail - 100MB free storage! http://promotions.yahoo.com/new_mail