[project @ 2006-01-06 11:04:07 by simonmar]
[ghc-hetmet.git] / ghc / compiler / utils / PrimPacked.lhs
index 1a47e30..f2d034d 100644 (file)
@@ -185,7 +185,7 @@ freeze_ps_array :: MBA s -> Int# -> ST s BA
 #if __GLASGOW_HASKELL__ < 411
 #define NEW_BYTE_ARRAY newCharArray#
 #else 
-#define NEW_BYTE_ARRAY newByteArray#
+#define NEW_BYTE_ARRAY newPinnedByteArray#
 #endif
 
 new_ps_array size = ST $ \ s ->
@@ -208,52 +208,58 @@ Compare two equal-length strings for equality:
 \begin{code}
 eqStrPrefix :: Addr# -> ByteArray# -> Int# -> Bool
 eqStrPrefix a# barr# len# = 
-  unsafePerformIO $ do
+  inlinePerformIO $ do
    x <- memcmp_ba a# barr# (I# len#)
    return (x == 0)
 
 #ifdef UNUSED
 eqCharStrPrefix :: Addr# -> Addr# -> Int# -> Bool
 eqCharStrPrefix a1# a2# len# = 
-  unsafePerformIO $ do
+  inlinePerformIO $ do
    x <- memcmp a1# a2# (I# len#)
    return (x == 0)
 #endif
 
 eqStrPrefixBA :: ByteArray# -> ByteArray# -> Int# -> Int# -> Bool
 eqStrPrefixBA b1# b2# start# len# = 
-  unsafePerformIO $ do
+  inlinePerformIO $ do
     x <- memcmp_baoff_ba b2# (I# start#) b1# (I# len#)
     return (x == 0)
 
 #ifdef UNUSED
 eqCharStrPrefixBA :: Addr# -> ByteArray# -> Int# -> Int# -> Bool
 eqCharStrPrefixBA a# b2# start# len# = 
-  unsafePerformIO $ do
+  inlinePerformIO $ do
     x <- memcmp_baoff b2# (I# start#) a# (I# len#) 
     return (x == 0)
 #endif
 \end{code}
 
 \begin{code}
+-- Just like unsafePerformIO, but we inline it.  This is safe when
+-- there are no side effects, and improves performance.
+{-# INLINE inlinePerformIO #-}
+inlinePerformIO :: IO a -> a
+inlinePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
+
 #if __GLASGOW_HASKELL__ <= 408
 strLength (Ptr a#) = ghc_strlen a#
-foreign import ccall "ghc_strlen" unsafe
+foreign import ccall unsafe "ghc_strlen" 
   ghc_strlen :: Addr# -> Int
 #else
-foreign import ccall "ghc_strlen" unsafe
+foreign import ccall unsafe "ghc_strlen" 
   strLength :: Ptr () -> Int
 #endif
 
-foreign import ccall "ghc_memcmp" unsafe 
+foreign import ccall unsafe "ghc_memcmp"
   memcmp :: Addr# -> Addr# -> Int -> IO Int
 
-foreign import ccall "ghc_memcmp" unsafe 
+foreign import ccall unsafe "ghc_memcmp" 
   memcmp_ba :: Addr# -> ByteArray# -> Int -> IO Int
 
-foreign import ccall "ghc_memcmp_off" unsafe
+foreign import ccall unsafe "ghc_memcmp_off"
   memcmp_baoff :: ByteArray# -> Int -> Addr# -> Int -> IO Int
 
-foreign import ccall "ghc_memcmp_off" unsafe
+foreign import ccall unsafe "ghc_memcmp_off"
   memcmp_baoff_ba :: ByteArray# -> Int -> ByteArray# -> Int -> IO Int
 \end{code}