[Haskell-cafe] Re: Array copying

Reinier Lamers reinier.lamers at phil.uu.nl
Mon Dec 3 05:19:57 EST 2007


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.
>  
>
How does this guarantee that it doesn't overflow the buffer of the 
destination array?

Reinier


More information about the Haskell-Cafe mailing list