Repository : ssh://darcs.haskell.org//srv/darcs/packages/bytestring

On branch  : ghc-7.6

http://hackage.haskell.org/trac/ghc/changeset/7ee8a4523ceaf7b0d6e521f1bbd06df601282f8e

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

commit 7ee8a4523ceaf7b0d6e521f1bbd06df601282f8e
Author: Duncan Coutts <[email protected]>
Date:   Thu Sep 6 00:44:24 2012 +0000

    Export createUptoN and unsafeCreateUptoN afterall

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

 Data/ByteString/Internal.hs |    6 +++---
 1 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs
index 92978ea..ed8e459 100644
--- a/Data/ByteString/Internal.hs
+++ b/Data/ByteString/Internal.hs
@@ -35,9 +35,11 @@ module Data.ByteString.Internal (
 
         -- * Low level imperative construction
         create,                 -- :: Int -> (Ptr Word8 -> IO ()) -> IO 
ByteString
+        createUptoN,            -- :: Int -> (Ptr Word8 -> IO Int) -> IO 
ByteString
         createAndTrim,          -- :: Int -> (Ptr Word8 -> IO Int) -> IO  
ByteString
         createAndTrim',         -- :: Int -> (Ptr Word8 -> IO (Int, Int, a)) 
-> IO (ByteString, a)
         unsafeCreate,           -- :: Int -> (Ptr Word8 -> IO ()) ->  
ByteString
+        unsafeCreateUptoN,      -- :: Int -> (Ptr Word8 -> IO Int) ->  
ByteString
         mallocByteString,       -- :: Int -> IO (ForeignPtr a)
 
         -- * Conversion to and from ForeignPtrs
@@ -347,9 +349,7 @@ toForeignPtr (PS ps s l) = (ps, s, l)
 {-# INLINE toForeignPtr #-}
 
 -- | A way of creating ByteStrings outside the IO monad. The @Int@
--- argument gives the final size of the ByteString. Unlike
--- 'createAndTrim' the ByteString is not reallocated if the final size
--- is less than the estimated size.
+-- argument gives the final size of the ByteString.
 unsafeCreate :: Int -> (Ptr Word8 -> IO ()) -> ByteString
 unsafeCreate l f = unsafeDupablePerformIO (create l f)
 {-# INLINE unsafeCreate #-}



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to