Skip to content

Commit d1aebfb

Browse files
instance IsList Builder (#672)
1 parent 595847e commit d1aebfb

File tree

3 files changed

+24
-13
lines changed

3 files changed

+24
-13
lines changed

Data/ByteString/Builder.hs

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -255,7 +255,6 @@ import Prelude hiding (writeFile)
255255

256256
import Data.ByteString.Builder.Internal
257257
import qualified Data.ByteString.Builder.Prim as P
258-
import qualified Data.ByteString.Lazy.Internal as L
259258
import Data.ByteString.Builder.ASCII
260259
import Data.ByteString.Builder.RealFloat
261260

@@ -265,14 +264,6 @@ import Foreign
265264
import GHC.Base (unpackCString#, unpackCStringUtf8#,
266265
unpackFoldrCString#, build)
267266

268-
-- | Execute a 'Builder' and return the generated chunks as a 'L.LazyByteString'.
269-
-- The work is performed lazy, i.e., only when a chunk of the 'L.LazyByteString'
270-
-- is forced.
271-
{-# NOINLINE toLazyByteString #-} -- ensure code is shared
272-
toLazyByteString :: Builder -> L.LazyByteString
273-
toLazyByteString = toLazyByteStringWith
274-
(safeStrategy L.smallChunkSize L.defaultChunkSize) L.Empty
275-
276267
{- Not yet stable enough.
277268
See note on 'hPut' in Data.ByteString.Builder.Internal
278269
-}

Data/ByteString/Builder/Internal.hs

Lines changed: 23 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
{-# LANGUAGE Unsafe #-}
2+
{-# LANGUAGE TypeFamilies #-}
3+
{-# LANGUAGE NoMonoLocalBinds #-}
24

35
{-# OPTIONS_HADDOCK not-home #-}
46

@@ -99,6 +101,7 @@ module Data.ByteString.Builder.Internal (
99101
, lazyByteString
100102

101103
-- ** Execution
104+
, toLazyByteString
102105
, toLazyByteStringWith
103106
, AllocationStrategy
104107
, safeStrategy
@@ -129,6 +132,7 @@ module Data.ByteString.Builder.Internal (
129132

130133
import Control.Arrow (second)
131134
import Control.DeepSeq (NFData(..))
135+
import GHC.Exts (IsList(..))
132136

133137
import Data.Semigroup (Semigroup(..))
134138
import Data.List.NonEmpty (NonEmpty(..))
@@ -426,6 +430,13 @@ instance Monoid Builder where
426430
{-# INLINE mconcat #-}
427431
mconcat = foldr mappend mempty
428432

433+
-- | For long or infinite lists use 'fromList' because it uses 'LazyByteString' otherwise use 'fromListN' which uses 'StrictByteString'.
434+
instance IsList Builder where
435+
type Item Builder = Word8
436+
fromList = lazyByteString . fromList
437+
fromListN n = byteString . fromListN n
438+
toList = toList . toLazyByteString
439+
429440
-- | Flush the current buffer. This introduces a chunk boundary.
430441
{-# INLINE flush #-}
431442
flush :: Builder
@@ -1052,27 +1063,35 @@ safeStrategy firstSize bufSize =
10521063
nextBuffer Nothing = newBuffer $ sanitize firstSize
10531064
nextBuffer (Just (_, minSize)) = newBuffer minSize
10541065

1066+
-- | Execute a 'Builder' and return the generated chunks as a 'L.LazyByteString'.
1067+
-- The work is performed lazy, i.e., only when a chunk of the 'L.LazyByteString'
1068+
-- is forced.
1069+
{-# NOINLINE toLazyByteString #-} -- ensure code is shared
1070+
toLazyByteString :: Builder -> L.LazyByteString
1071+
toLazyByteString = toLazyByteStringWith
1072+
(safeStrategy L.smallChunkSize L.defaultChunkSize) L.Empty
1073+
10551074
-- | /Heavy inlining./ Execute a 'Builder' with custom execution parameters.
10561075
--
10571076
-- This function is inlined despite its heavy code-size to allow fusing with
10581077
-- the allocation strategy. For example, the default 'Builder' execution
1059-
-- function 'Data.ByteString.Builder.toLazyByteString' is defined as follows.
1078+
-- function 'Data.ByteString.Builder.Internal.toLazyByteString' is defined as follows.
10601079
--
10611080
-- @
10621081
-- {-\# NOINLINE toLazyByteString \#-}
10631082
-- toLazyByteString =
1064-
-- toLazyByteStringWith ('safeStrategy' 'L.smallChunkSize' 'L.defaultChunkSize') L.empty
1083+
-- toLazyByteStringWith ('safeStrategy' 'L.smallChunkSize' 'L.defaultChunkSize') L.Empty
10651084
-- @
10661085
--
1067-
-- where @L.empty@ is the zero-length 'L.LazyByteString'.
1086+
-- where @L.Empty@ is the zero-length 'L.LazyByteString'.
10681087
--
10691088
-- In most cases, the parameters used by 'Data.ByteString.Builder.toLazyByteString' give good
10701089
-- performance. A sub-performing case of 'Data.ByteString.Builder.toLazyByteString' is executing short
10711090
-- (<128 bytes) 'Builder's. In this case, the allocation overhead for the first
10721091
-- 4kb buffer and the trimming cost dominate the cost of executing the
10731092
-- 'Builder'. You can avoid this problem using
10741093
--
1075-
-- >toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.empty
1094+
-- >toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.Empty
10761095
--
10771096
-- This reduces the allocation and trimming overhead, as all generated
10781097
-- 'L.LazyByteString's fit into the first buffer and there is no trimming

Data/ByteString/Internal/Type.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -337,6 +337,7 @@ instance Read ByteString where
337337
instance IsList ByteString where
338338
type Item ByteString = Word8
339339
fromList = packBytes
340+
fromListN n = fst . packUptoLenBytes n
340341
toList = unpackBytes
341342

342343
-- | Beware: 'fromString' truncates multi-byte characters to octets.

0 commit comments

Comments
 (0)