[commit: packages/bytestring] ghc-head: Move D.B.Unsafe.unsafePackAddr to D.B.Internal (3a42bb1)

git at git.haskell.org git at git.haskell.org
Thu Aug 29 10:19:02 CEST 2013


Repository : ssh://git@git.haskell.org/bytestring

On branch  : ghc-head
Link       : http://git.haskell.org/?p=packages/bytestring.git;a=commit;h=3a42bb13393c3db160bc8428bb4d0fb342fbbb08

>---------------------------------------------------------------

commit 3a42bb13393c3db160bc8428bb4d0fb342fbbb08
Author: Patrick Palka <patrick at parcs.ath.cx>
Date:   Fri Mar 1 21:57:58 2013 -0500

    Move D.B.Unsafe.unsafePackAddr to D.B.Internal
    
    But continue to export it from D.B.Unsafe


>---------------------------------------------------------------

3a42bb13393c3db160bc8428bb4d0fb342fbbb08
 Data/ByteString/Internal.hs |   31 ++++++++++++++++++++++++++-----
 Data/ByteString/Unsafe.hs   |   25 -------------------------
 2 files changed, 26 insertions(+), 30 deletions(-)

diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs
index c48c693..2df1e1f 100644
--- a/Data/ByteString/Internal.hs
+++ b/Data/ByteString/Internal.hs
@@ -32,7 +32,7 @@ module Data.ByteString.Internal (
         packChars, packUptoLenChars, unsafePackLenChars,
         unpackBytes, unpackAppendBytesLazy, unpackAppendBytesStrict,
         unpackChars, unpackAppendCharsLazy, unpackAppendCharsStrict,
-        unsafePackAddr,
+        unsafePackAddress,
 
         -- * Low level imperative construction
         create,                 -- :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString
@@ -235,7 +235,7 @@ packChars cs = unsafePackLenChars (List.length cs) cs
 
 {-# RULES
 "ByteString packChars/packAddress" forall s .
-   packChars (unpackCString# s) = inlinePerformIO (unsafePackAddr s)
+   packChars (unpackCString# s) = inlinePerformIO (unsafePackAddress s)
  #-}
 #endif
 
@@ -254,15 +254,36 @@ unsafePackLenChars len cs0 =
     go !p (c:cs) = poke p (c2w c) >> go (p `plusPtr` 1) cs
 
 #if defined(__GLASGOW_HASKELL__)
-unsafePackAddr :: Addr# -> IO ByteString
-unsafePackAddr addr# = do
+-- | /O(n)/ Pack a null-terminated sequence of bytes, pointed to by an
+-- Addr\# (an arbitrary machine address assumed to point outside the
+-- garbage-collected heap) into a @ByteString at . A much faster way to
+-- create an Addr\# is with an unboxed string literal, than to pack a
+-- boxed string. A unboxed string literal is compiled to a static @char
+-- []@ by GHC. Establishing the length of the string requires a call to
+-- @strlen(3)@, so the Addr# must point to a null-terminated buffer (as
+-- is the case with "string"# literals in GHC). Use 'unsafePackAddressLen'
+-- if you know the length of the string statically.
+--
+-- An example:
+--
+-- > literalFS = unsafePackAddress "literal"#
+--
+-- This function is /unsafe/. If you modify the buffer pointed to by the
+-- original Addr# this modification will be reflected in the resulting
+-- @ByteString@, breaking referential transparency.
+--
+-- Note this also won't work if you Add# has embedded '\0' characters in
+-- the string (strlen will fail).
+--
+unsafePackAddress :: Addr# -> IO ByteString
+unsafePackAddress addr# = do
     p <- newForeignPtr_ (castPtr cstr)
     l <- c_strlen cstr
     return $ PS p 0 (fromIntegral l)
   where
     cstr :: CString
     cstr = Ptr addr#
-{-# INLINE unsafePackAddr #-}
+{-# INLINE unsafePackAddress #-}
 #endif
 
 packUptoLenBytes :: Int -> [Word8] -> (ByteString, [Word8])
diff --git a/Data/ByteString/Unsafe.hs b/Data/ByteString/Unsafe.hs
index 6f8f7de..373f78f 100644
--- a/Data/ByteString/Unsafe.hs
+++ b/Data/ByteString/Unsafe.hs
@@ -150,31 +150,6 @@ unsafeDrop n (PS x s l) = assert (0 <= n && n <= l) $ PS x (s+n) (l-n)
 
 
 #if defined(__GLASGOW_HASKELL__)
--- | /O(n)/ Pack a null-terminated sequence of bytes, pointed to by an
--- Addr\# (an arbitrary machine address assumed to point outside the
--- garbage-collected heap) into a @ByteString at . A much faster way to
--- create an Addr\# is with an unboxed string literal, than to pack a
--- boxed string. A unboxed string literal is compiled to a static @char
--- []@ by GHC. Establishing the length of the string requires a call to
--- @strlen(3)@, so the Addr# must point to a null-terminated buffer (as
--- is the case with "string"# literals in GHC). Use 'unsafePackAddressLen'
--- if you know the length of the string statically.
---
--- An example:
---
--- > literalFS = unsafePackAddress "literal"#
---
--- This function is /unsafe/. If you modify the buffer pointed to by the
--- original Addr# this modification will be reflected in the resulting
--- @ByteString@, breaking referential transparency.
---
--- Note this also won't work if you Add# has embedded '\0' characters in
--- the string (strlen will fail).
---
-unsafePackAddress :: Addr# -> IO ByteString
-unsafePackAddress = unsafePackAddr
-{-# INLINE unsafePackAddress #-}
-
 -- | /O(1)/ 'unsafePackAddressLen' provides constant-time construction of
 -- 'ByteStrings' which is ideal for string literals. It packs a sequence
 -- of bytes into a 'ByteString', given a raw 'Addr#' to the string, and





More information about the ghc-commits mailing list