Repository : ssh://g...@git.haskell.org/bytestring On branch : ghc-head Link : http://git.haskell.org/packages/bytestring.git/commitdiff/2fdf6fccd174f4b0ac74119081bc18fc758343e2
>--------------------------------------------------------------- commit 2fdf6fccd174f4b0ac74119081bc18fc758343e2 Author: Duncan Coutts <dun...@community.haskell.org> Date: Sat Oct 5 00:26:35 2013 +0100 A few minor documentation tweaks and improvements >--------------------------------------------------------------- 2fdf6fccd174f4b0ac74119081bc18fc758343e2 Data/ByteString.hs | 15 +++++++++------ Data/ByteString/Builder/Internal.hs | 2 +- Data/ByteString/Internal.hs | 10 ++++++---- Data/ByteString/Lazy.hs | 2 +- Data/ByteString/Lazy/Internal.hs | 8 +++++--- 5 files changed, 22 insertions(+), 15 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index 04fdc9f..4dc9d16 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -15,7 +15,7 @@ -- (c) Simon Marlow 2005, -- (c) Bjorn Bringert 2006, -- (c) Don Stewart 2005-2008, --- (c) Duncan Coutts 2006-2011 +-- (c) Duncan Coutts 2006-2013 -- License : BSD-style -- -- Maintainer : don...@gmail.com, dun...@community.haskell.org @@ -28,6 +28,9 @@ -- are encoded as strict 'Word8' arrays of bytes, held in a 'ForeignPtr', -- and can be passed between C and Haskell with little effort. -- +-- The recomended way to assemble ByteStrings from smaller parts +-- is to use the builder monoid from "Data.ByteString.Builder". +-- -- This module is intended to be imported @qualified@, to avoid name -- clashes with "Prelude" functions. eg. -- @@ -406,7 +409,7 @@ infixr 5 `cons` --same as list (:) infixl 5 `snoc` -- | /O(n)/ 'cons' is analogous to (:) for lists, but of different --- complexity, as it requires a memcpy. +-- complexity, as it requires making a copy. cons :: Word8 -> ByteString -> ByteString cons c (PS x s l) = unsafeCreate (l+1) $ \p -> withForeignPtr x $ \f -> do poke p c @@ -539,7 +542,7 @@ foldl f z (PS fp off len) = in f (go (p `plusPtr` (-1)) q) x {-# INLINE foldl #-} --- | 'foldl\'' is like 'foldl', but strict in the accumulator. +-- | 'foldl'' is like 'foldl', but strict in the accumulator. -- foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a foldl' f v (PS fp off len) = @@ -569,7 +572,7 @@ foldr k z (PS fp off len) = in k x (go (p `plusPtr` 1) q) {-# INLINE foldr #-} --- | 'foldr\'' is like 'foldr', but strict in the accumulator. +-- | 'foldr'' is like 'foldr', but strict in the accumulator. foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a foldr' k v (PS fp off len) = inlinePerformIO $ withForeignPtr fp $ \p -> @@ -1614,8 +1617,8 @@ sort (PS x s l) = unsafeCreate l $ \p -> withForeignPtr x $ \f -> do -- Low level constructors -- | /O(n) construction/ Use a @ByteString@ with a function requiring a --- null-terminated @CString@. The @CString@ will be freed --- automatically. This is a memcpy(3). +-- null-terminated @CString@. The @CString@ is a copy and will be freed +-- automatically. useAsCString :: ByteString -> (CString -> IO a) -> IO a useAsCString (PS fp o l) action = do allocaBytes (l+1) $ \buf -> diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs index b48a464..11cf043 100644 --- a/Data/ByteString/Builder/Internal.hs +++ b/Data/ByteString/Builder/Internal.hs @@ -649,7 +649,7 @@ hPut h p = do fillBuffer buf | freeSpace buf < minFree = error $ unlines - [ "Data.ByteString.Lazy.Builder.Internal.hPut: internal error." + [ "Data.ByteString.Builder.Internal.hPut: internal error." , " Not enough space after flush." , " required: " ++ show minFree , " free: " ++ show (freeSpace buf) diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index 28f6ad7..ca1326c 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -11,7 +11,7 @@ -- | -- Module : Data.ByteString.Internal -- Copyright : (c) Don Stewart 2006-2008 --- (c) Duncan Coutts 2006-2011 +-- (c) Duncan Coutts 2006-2012 -- License : BSD-style -- Maintainer : don...@gmail.com, dun...@community.haskell.org -- Stability : unstable @@ -183,10 +183,12 @@ assertS s False = error ("assertion failed at "++s) -- ----------------------------------------------------------------------------- --- | A space-efficient representation of a Word8 vector, supporting many --- efficient operations. A 'ByteString' contains 8-bit characters only. +-- | A space-efficient representation of a 'Word8' vector, supporting many +-- efficient operations. -- --- Instances of Eq, Ord, Read, Show, Data, Typeable +-- A 'ByteString' contains 8-bit bytes, or by using the operations from +-- "Data.ByteString.Char8" it can be interpreted as containing 8-bit +-- characters. -- data ByteString = PS {-# UNPACK #-} !(ForeignPtr Word8) -- payload {-# UNPACK #-} !Int -- offset diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 56ee7a0..a8faac2 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -34,7 +34,7 @@ -- strict ones. -- -- The recomended way to assemble lazy ByteStrings from smaller parts --- is to use the builder monoid from "Data.ByteString.Lazy.Builder". +-- is to use the builder monoid from "Data.ByteString.Builder". -- -- This module is intended to be imported @qualified@, to avoid name -- clashes with "Prelude" functions. eg. diff --git a/Data/ByteString/Lazy/Internal.hs b/Data/ByteString/Lazy/Internal.hs index ade4968..2de77af 100644 --- a/Data/ByteString/Lazy/Internal.hs +++ b/Data/ByteString/Lazy/Internal.hs @@ -72,10 +72,12 @@ import Data.Data (mkNorepType) import Data.Generics (Data(..), mkNorepType) #endif --- | A space-efficient representation of a Word8 vector, supporting many --- efficient operations. A 'ByteString' contains 8-bit characters only. +-- | A space-efficient representation of a 'Word8' vector, supporting many +-- efficient operations. -- --- Instances of Eq, Ord, Read, Show, Data, Typeable +-- A lazy 'ByteString' contains 8-bit bytes, or by using the operations +-- from "Data.ByteString.Lazy.Char8" it can be interpreted as containing +-- 8-bit characters. -- data ByteString = Empty | Chunk {-# UNPACK #-} !S.ByteString ByteString _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits