diff --git a/Data/ByteString/Builder.hs b/Data/ByteString/Builder.hs index 1032526da..8fdd58d67 100644 --- a/Data/ByteString/Builder.hs +++ b/Data/ByteString/Builder.hs @@ -255,7 +255,6 @@ import Prelude hiding (writeFile) import Data.ByteString.Builder.Internal import qualified Data.ByteString.Builder.Prim as P -import qualified Data.ByteString.Lazy.Internal as L import Data.ByteString.Builder.ASCII import Data.ByteString.Builder.RealFloat @@ -265,14 +264,6 @@ import Foreign import GHC.Base (unpackCString#, unpackCStringUtf8#, unpackFoldrCString#, build) --- | Execute a 'Builder' and return the generated chunks as a 'L.LazyByteString'. --- The work is performed lazy, i.e., only when a chunk of the 'L.LazyByteString' --- is forced. -{-# NOINLINE toLazyByteString #-} -- ensure code is shared -toLazyByteString :: Builder -> L.LazyByteString -toLazyByteString = toLazyByteStringWith - (safeStrategy L.smallChunkSize L.defaultChunkSize) L.Empty - {- Not yet stable enough. See note on 'hPut' in Data.ByteString.Builder.Internal -} diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs index 109c762e2..940246d37 100644 --- a/Data/ByteString/Builder/Internal.hs +++ b/Data/ByteString/Builder/Internal.hs @@ -1,4 +1,6 @@ {-# LANGUAGE Unsafe #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE NoMonoLocalBinds #-} {-# OPTIONS_HADDOCK not-home #-} @@ -99,6 +101,7 @@ module Data.ByteString.Builder.Internal ( , lazyByteString -- ** Execution + , toLazyByteString , toLazyByteStringWith , AllocationStrategy , safeStrategy @@ -128,6 +131,7 @@ module Data.ByteString.Builder.Internal ( ) where import Control.Arrow (second) +import GHC.Exts (IsList(..)) import Data.Semigroup (Semigroup(..)) import Data.List.NonEmpty (NonEmpty(..)) @@ -414,6 +418,12 @@ instance Monoid Builder where {-# INLINE mconcat #-} mconcat = foldr mappend mempty +instance IsList Builder where + type Item Builder = Word8 + fromList = lazyByteString . fromList + fromListN n = lazyByteString . fromListN n + toList = toList . toLazyByteString + -- | Flush the current buffer. This introduces a chunk boundary. {-# INLINE flush #-} flush :: Builder @@ -1040,19 +1050,27 @@ safeStrategy firstSize bufSize = nextBuffer Nothing = newBuffer $ sanitize firstSize nextBuffer (Just (_, minSize)) = newBuffer minSize +-- | Execute a 'Builder' and return the generated chunks as a 'L.LazyByteString'. +-- The work is performed lazy, i.e., only when a chunk of the 'L.LazyByteString' +-- is forced. +{-# NOINLINE toLazyByteString #-} -- ensure code is shared +toLazyByteString :: Builder -> L.LazyByteString +toLazyByteString = toLazyByteStringWith + (safeStrategy L.smallChunkSize L.defaultChunkSize) L.Empty + -- | /Heavy inlining./ Execute a 'Builder' with custom execution parameters. -- -- This function is inlined despite its heavy code-size to allow fusing with -- the allocation strategy. For example, the default 'Builder' execution --- function 'Data.ByteString.Builder.toLazyByteString' is defined as follows. +-- function 'Data.ByteString.Builder.Internal.toLazyByteString' is defined as follows. -- -- @ -- {-\# NOINLINE toLazyByteString \#-} -- toLazyByteString = --- toLazyByteStringWith ('safeStrategy' 'L.smallChunkSize' 'L.defaultChunkSize') L.empty +-- toLazyByteStringWith ('safeStrategy' 'L.smallChunkSize' 'L.defaultChunkSize') L.Empty -- @ -- --- where @L.empty@ is the zero-length 'L.LazyByteString'. +-- where @L.Empty@ is the zero-length 'L.LazyByteString'. -- -- In most cases, the parameters used by 'Data.ByteString.Builder.toLazyByteString' give good -- performance. A sub-performing case of 'Data.ByteString.Builder.toLazyByteString' is executing short @@ -1060,7 +1078,7 @@ safeStrategy firstSize bufSize = -- 4kb buffer and the trimming cost dominate the cost of executing the -- 'Builder'. You can avoid this problem using -- --- >toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.empty +-- >toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.Empty -- -- This reduces the allocation and trimming overhead, as all generated -- 'L.LazyByteString's fit into the first buffer and there is no trimming diff --git a/Data/ByteString/Internal/Type.hs b/Data/ByteString/Internal/Type.hs index 1759ab93e..1270be882 100644 --- a/Data/ByteString/Internal/Type.hs +++ b/Data/ByteString/Internal/Type.hs @@ -366,6 +366,7 @@ instance Read ByteString where instance IsList ByteString where type Item ByteString = Word8 fromList = packBytes + fromListN n = fst . packUptoLenBytes n toList = unpackBytes -- | Beware: 'fromString' truncates multi-byte characters to octets. diff --git a/Data/ByteString/Lazy/Internal.hs b/Data/ByteString/Lazy/Internal.hs index 8135c8234..11f42f68d 100644 --- a/Data/ByteString/Lazy/Internal.hs +++ b/Data/ByteString/Lazy/Internal.hs @@ -138,6 +138,7 @@ instance Read ByteString where instance IsList ByteString where type Item ByteString = Word8 fromList = packBytes + fromListN n = fromStrict . fromListN n toList = unpackBytes -- | Beware: 'fromString' truncates multi-byte characters to octets.