
On Sun, Aug 19, 2007 at 11:25:49PM +0100, ChrisK wrote:
#ifdef __GLASGOW_HASKELL__ 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#, () #) }}
#else /* !__GLASGOW_HASKELL__ */
copySTU :: (MArray (STUArray s) e (ST s))=> STUArray s Tag e -> STUArray s Tag e -> ST s () copySTU source destination = do b@(start,stop) <- getBounds source b' <- getBounds destination -- traceCopy ("> copySTArray "++show b) $ do when (b/=b') (fail $ "Text.Regex.TDFA.RunMutState copySTUArray bounds mismatch"++show (b,b')) forM_ (range b) $ \index -> unsafeRead source index >>= unsafeWrite destination index #endif /* !__GLASGOW_HASKELL__ */
The entire point of using the ST monad is manage memory more efficiently than with (U)Array. The copySTU simply uses a "memcpy" to copy the whole source array into the destination efficiently. This lets me re-use the already allocated destination array. If there had been a high level "copyMArray" then this would not have been needed. The CPP is used to let non-GHC compilers copy element by element. The *right* solution is to patch the STUArray and/or MArray code to do this behind the scenes.
So how does one get the array pointer without GHC.Prim in 6.7 ?
Import GHC.Exts, which exports everything GHC.Prim does, and according to the docs is "GHC Extensions: this is the Approved Way to get at GHC-specific extensions.". (Can't help you with the CPP issue though.) Stefan