-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

On 15 juil. 04, at 13:26, John Meacham wrote:
Perhaps I am just missing something, but a major piece of efficient
array functionality seems to be missing. Namely the ability to
efficiently copy spans of arrays into one another and/or compare spans
of memory. (basically memcpy and memcmp from C).

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

It seems to work on GHC 6.2.1, though I did not made further tests than this main.

Hope this helps,
Jérémy.
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.2.4 (Darwin)

iD8DBQFA9pK8JhPEcwATZDwRAhSnAJ9BELp+L/L2rFaYwFFzg/axQjEJ8wCcC+YV
iN+XPdynHWROb3x27eVa5wE=
=f5Vo
-----END PGP SIGNATURE-----

_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to