Skip to content

Commit 0645428

Browse files
committed
Avoid per-byte loop in cstring{,Utf8} builders
Copy chunks of the input to the output buffer with 'memcpy', up to the shorter of the available buffer space and the "null-free" portion of the remaining string. For the UTF8 version, encoded NUL bytes are located via strstr(3).
1 parent 0bd68ca commit 0645428

File tree

8 files changed

+164
-74
lines changed

8 files changed

+164
-74
lines changed

Data/ByteString/Builder.hs

Lines changed: 14 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -263,12 +263,14 @@ import qualified Data.ByteString.Builder.Prim as P
263263
import qualified Data.ByteString.Lazy.Internal as L
264264
import Data.ByteString.Builder.ASCII
265265
import Data.ByteString.Builder.RealFloat
266+
import Data.ByteString.Internal (byteCountLiteral)
266267

267268
import Data.String (IsString(..))
268269
import System.IO (Handle, IOMode(..), withBinaryFile)
269270
import Foreign
270271
import GHC.Base (unpackCString#, unpackCStringUtf8#,
271272
unpackFoldrCString#, build)
273+
import GHC.Ptr (Ptr(..))
272274

273275
-- | Execute a 'Builder' and return the generated chunks as a lazy 'L.ByteString'.
274276
-- The work is performed lazy, i.e., only when a chunk of the lazy 'L.ByteString'
@@ -440,18 +442,20 @@ char8 :: Char -> Builder
440442
char8 = P.primFixed P.char8
441443

442444
-- | Char8 encode a 'String'.
443-
{-# INLINE [1] string8 #-} -- phased to allow P.cstring rewrite
445+
{-# NOINLINE string8 #-}
444446
string8 :: String -> Builder
445447
string8 = P.primMapListFixed P.char8
446448

447449
-- GHC desugars string literals with unpackCString# which the simplifier tends
448450
-- to promptly turn into build (unpackFoldrCString# s), so we match on both.
449451
{-# RULES
450452
"string8/unpackCString#" forall s.
451-
string8 (unpackCString# s) = P.cstring s
453+
string8 (unpackCString# s) =
454+
ascLiteralCopy (Ptr s) (byteCountLiteral s)
452455

453456
"string8/unpackFoldrCString#" forall s.
454-
string8 (build (unpackFoldrCString# s)) = P.cstring s
457+
string8 (build (unpackFoldrCString# s)) =
458+
ascLiteralCopy (Ptr s) (byteCountLiteral s)
455459
#-}
456460

457461
------------------------------------------------------------------------------
@@ -467,19 +471,22 @@ charUtf8 = P.primBounded P.charUtf8
467471
--
468472
-- Note that 'stringUtf8' performs no codepoint validation and consequently may
469473
-- emit invalid UTF-8 if asked (e.g. single surrogates).
470-
{-# INLINE [1] stringUtf8 #-} -- phased to allow P.cstring rewrite
474+
{-# NOINLINE stringUtf8 #-}
471475
stringUtf8 :: String -> Builder
472476
stringUtf8 = P.primMapListBounded P.charUtf8
473477

474478
{-# RULES
475479
"stringUtf8/unpackCStringUtf8#" forall s.
476-
stringUtf8 (unpackCStringUtf8# s) = P.cstringUtf8 s
480+
stringUtf8 (unpackCStringUtf8# s) =
481+
modUtf8LitCopy (Ptr s) (byteCountLiteral s)
477482

478483
"stringUtf8/unpackCString#" forall s.
479-
stringUtf8 (unpackCString# s) = P.cstring s
484+
stringUtf8 (unpackCString# s) =
485+
ascLiteralCopy (Ptr s) (byteCountLiteral s)
480486

481487
"stringUtf8/unpackFoldrCString#" forall s.
482-
stringUtf8 (build (unpackFoldrCString# s)) = P.cstring s
488+
stringUtf8 (build (unpackFoldrCString# s)) =
489+
ascLiteralCopy (Ptr s) (byteCountLiteral s)
483490
#-}
484491

485492
instance IsString Builder where

Data/ByteString/Builder/Internal.hs

Lines changed: 75 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
{-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, RankNTypes, TupleSections #-}
2-
{-# LANGUAGE Unsafe #-}
2+
{-# LANGUAGE MagicHash, ViewPatterns, Unsafe #-}
33
{-# OPTIONS_HADDOCK not-home #-}
44
-- | Copyright : (c) 2010 - 2011 Simon Meier
55
-- License : BSD3-style (see LICENSE)
@@ -84,6 +84,8 @@ module Data.ByteString.Builder.Internal (
8484
-- , sizedChunksInsert
8585

8686
, byteStringCopy
87+
, ascLiteralCopy
88+
, modUtf8LitCopy
8789
, byteStringInsert
8890
, byteStringThreshold
8991

@@ -127,6 +129,7 @@ module Data.ByteString.Builder.Internal (
127129
) where
128130

129131
import Control.Arrow (second)
132+
import Control.Monad (when)
130133

131134
#if !(MIN_VERSION_base(4,11,0))
132135
import Data.Semigroup (Semigroup((<>)))
@@ -140,10 +143,12 @@ import qualified Data.ByteString.Short.Internal as Sh
140143
import qualified GHC.IO.Buffer as IO (Buffer(..), newByteBuffer)
141144
import GHC.IO.Handle.Internals (wantWritableHandle, flushWriteBuffer)
142145
import GHC.IO.Handle.Types (Handle__, haByteBuffer, haBufferMode)
146+
import GHC.Ptr (Ptr(..))
143147
import System.IO (hFlush, BufferMode(..), Handle)
144148
import Data.IORef
145149

146150
import Foreign
151+
import Foreign.C.String (CString)
147152
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
148153
import System.IO.Unsafe (unsafeDupablePerformIO)
149154

@@ -857,6 +862,75 @@ byteStringInsert :: S.ByteString -> Builder
857862
byteStringInsert =
858863
\bs -> builder $ \k (BufferRange op _) -> return $ insertChunk op bs k
859864

865+
866+
------------------------------------------------------------------------------
867+
-- Raw CString encoding
868+
------------------------------------------------------------------------------
869+
870+
-- | Builder for raw 'Addr#' pointers to null-terminated primitive ASCII
871+
-- strings that are free of embedded (overlong-encoded as the two-byte sequence
872+
-- @0xC0 0x80@) null characters.
873+
--
874+
-- @since 0.11.5.0
875+
{-# INLINABLE ascLiteralCopy #-}
876+
ascLiteralCopy :: Ptr Word8 -> Int -> Builder
877+
ascLiteralCopy = \ !ip !len -> builder $ \k br -> do
878+
let !ipe = ip `plusPtr` len
879+
wrappedBytesCopyStep (BufferRange ip ipe) k br
880+
881+
-- | GHC represents @NUL@ in string literals via an overlong 2-byte encoding,
882+
-- which is part of "modified UTF-8" (GHC does not also implement CESU-8).
883+
modifiedUtf8NUL :: CString
884+
modifiedUtf8NUL = Ptr "\xc0\x80"#
885+
886+
-- | Builder for raw 'Addr#' pointers to null-terminated primitive UTF-8
887+
-- encoded strings that may contain embedded overlong-encodings (as the
888+
-- two-byte sequence @0xC0 0x80@) of null characters.
889+
--
890+
-- @since 0.11.5.0
891+
{-# INLINABLE modUtf8LitCopy #-}
892+
modUtf8LitCopy :: Ptr Word8 -> Int -> Builder
893+
modUtf8LitCopy = \ !ip !len -> builder $ \k br -> do
894+
nullAt <- c_strstr (castPtr ip) modifiedUtf8NUL
895+
modUtf8_step ip len nullAt k br
896+
897+
modUtf8_step :: Ptr Word8 -> Int -> Ptr Word8 -> BuildStep r -> BuildStep r
898+
modUtf8_step !ip !len ((== nullPtr) -> True) k br =
899+
-- Contains no encoded nulls, use simple copy codepath
900+
wrappedBytesCopyStep (BufferRange ip ipe) k br
901+
where
902+
!ipe = ip `plusPtr` len
903+
modUtf8_step !ip !len !nullAt k (BufferRange op0 ope)
904+
-- Copy as much of the null-free portion of the string as fits into the
905+
-- available buffer space. If the string is long enough, we may have asked
906+
-- for less than its full length, filling the buffer with the rest will go
907+
-- into the next builder step.
908+
| avail > nullFree = do
909+
when (nullFree > 0) (copyBytes op0 ip nullFree)
910+
pokeElemOff op0 nullFree 0
911+
let used = nullFree + 2
912+
len' = len - used
913+
!ip' = ip `plusPtr` used
914+
!op' = op0 `plusPtr` (nullFree + 1)
915+
nullAt' <- c_strstr ip' modifiedUtf8NUL
916+
modUtf8_step ip' len' nullAt' k (BufferRange op' ope)
917+
| avail > 0 = do
918+
-- avail <= nullFree
919+
copyBytes op0 ip avail
920+
let len' = len - avail
921+
!ip' = ip `plusPtr` avail
922+
!op' = op0 `plusPtr` avail
923+
return $ bufferFull 1 op' (modUtf8_step ip' len' nullAt k)
924+
| otherwise =
925+
return $ bufferFull 1 op0 (modUtf8_step ip len nullAt k)
926+
where
927+
!avail = ope `minusPtr` op0
928+
!nullFree = nullAt `minusPtr` ip
929+
930+
foreign import ccall unsafe "string.h strstr" c_strstr
931+
:: CString -> CString -> IO (Ptr Word8)
932+
933+
860934
-- Short bytestrings
861935
------------------------------------------------------------------------------
862936

Data/ByteString/Builder/Prim.hs

Lines changed: 12 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -663,59 +663,25 @@ primMapLazyByteStringBounded w =
663663
L.foldrChunks (\x b -> primMapByteStringBounded w x `mappend` b) mempty
664664

665665

666-
------------------------------------------------------------------------------
667-
-- Raw CString encoding
668-
------------------------------------------------------------------------------
669-
670-
-- | A null-terminated ASCII encoded 'Foreign.C.String.CString'.
671-
-- Null characters are not representable.
666+
-- | Builder for raw 'Addr#' pointers to null-terminated primitive ASCII
667+
-- strings that are free of embedded (overlong-encoded as the two-byte sequence
668+
-- @0xC0 0x80@) null characters.
672669
--
673670
-- @since 0.11.0.0
671+
{-# DEPRECATED cstring "Use ascLiteralCopy instead" #-}
674672
cstring :: Addr# -> Builder
675-
cstring =
676-
\addr0 -> builder $ step addr0
677-
where
678-
step :: Addr# -> BuildStep r -> BuildStep r
679-
step !addr !k br@(BufferRange op0@(Ptr op0#) ope)
680-
| W8# ch == 0 = k br
681-
| op0 == ope =
682-
return $ bufferFull 1 op0 (step addr k)
683-
| otherwise = do
684-
IO $ \s -> case writeWord8OffAddr# op0# 0# ch s of
685-
s' -> (# s', () #)
686-
let br' = BufferRange (op0 `plusPtr` 1) ope
687-
step (addr `plusAddr#` 1#) k br'
688-
where
689-
!ch = indexWord8OffAddr# addr 0#
673+
cstring s = ascLiteralCopy (Ptr s) (S.byteCountLiteral s)
674+
{-# INLINE cstring #-}
690675

691-
-- | A null-terminated UTF-8 encoded 'Foreign.C.String.CString'.
692-
-- Null characters can be encoded as @0xc0 0x80@.
676+
-- | Builder for raw 'Addr#' pointers to null-terminated primitive UTF-8
677+
-- encoded strings that may contain embedded overlong-encodings (as the
678+
-- two-byte sequence @0xC0 0x80@) of null characters.
693679
--
694680
-- @since 0.11.0.0
681+
{-# DEPRECATED cstringUtf8 "Use modUtf8LitCopy instead" #-}
695682
cstringUtf8 :: Addr# -> Builder
696-
cstringUtf8 =
697-
\addr0 -> builder $ step addr0
698-
where
699-
step :: Addr# -> BuildStep r -> BuildStep r
700-
step !addr !k br@(BufferRange op0@(Ptr op0#) ope)
701-
| W8# ch == 0 = k br
702-
| op0 == ope =
703-
return $ bufferFull 1 op0 (step addr k)
704-
-- NULL is encoded as 0xc0 0x80
705-
| W8# ch == 0xc0
706-
, W8# (indexWord8OffAddr# addr 1#) == 0x80 = do
707-
let !(W8# nullByte#) = 0
708-
IO $ \s -> case writeWord8OffAddr# op0# 0# nullByte# s of
709-
s' -> (# s', () #)
710-
let br' = BufferRange (op0 `plusPtr` 1) ope
711-
step (addr `plusAddr#` 2#) k br'
712-
| otherwise = do
713-
IO $ \s -> case writeWord8OffAddr# op0# 0# ch s of
714-
s' -> (# s', () #)
715-
let br' = BufferRange (op0 `plusPtr` 1) ope
716-
step (addr `plusAddr#` 1#) k br'
717-
where
718-
!ch = indexWord8OffAddr# addr 0#
683+
cstringUtf8 s = modUtf8LitCopy (Ptr s) (S.byteCountLiteral s)
684+
{-# INLINE cstringUtf8 #-}
719685

720686
------------------------------------------------------------------------------
721687
-- Char8 encoding

Data/ByteString/Internal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ module Data.ByteString.Internal (
3636
unpackBytes, unpackAppendBytesLazy, unpackAppendBytesStrict,
3737
unpackChars, unpackAppendCharsLazy, unpackAppendCharsStrict,
3838
unsafePackAddress, unsafePackLenAddress,
39-
unsafePackLiteral, unsafePackLenLiteral,
39+
unsafePackLiteral, unsafePackLenLiteral, byteCountLiteral,
4040

4141
-- * Low level imperative construction
4242
empty,

Data/ByteString/Internal/Type.hs

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ module Data.ByteString.Internal.Type (
3939
unpackBytes, unpackAppendBytesLazy, unpackAppendBytesStrict,
4040
unpackChars, unpackAppendCharsLazy, unpackAppendCharsStrict,
4141
unsafePackAddress, unsafePackLenAddress,
42-
unsafePackLiteral, unsafePackLenLiteral,
42+
unsafePackLiteral, unsafePackLenLiteral, byteCountLiteral,
4343

4444
-- * Low level imperative construction
4545
empty,
@@ -434,13 +434,22 @@ unsafePackLenAddress len addr# = do
434434
-- @since 0.11.1.0
435435
unsafePackLiteral :: Addr# -> ByteString
436436
unsafePackLiteral addr# =
437+
unsafePackLenLiteral (byteCountLiteral addr#) addr#
438+
{-# INLINE unsafePackLiteral #-}
439+
440+
-- | Byte count of null-terminated primitive literal string excluding the
441+
-- terminating null byte.
442+
byteCountLiteral :: Addr# -> Int
443+
byteCountLiteral addr# =
437444
#if __GLASGOW_HASKELL__ >= 811
438-
unsafePackLenLiteral (I# (cstringLength# addr#)) addr#
445+
I# (cstringLength# addr#)
439446
#else
440-
let len = accursedUnutterablePerformIO (c_strlen (Ptr addr#))
441-
in unsafePackLenLiteral (fromIntegral len) addr#
447+
fromIntegral (pure_strlen (Ptr addr#))
448+
449+
foreign import ccall unsafe "string.h strlen" pure_strlen
450+
:: CString -> CSize
442451
#endif
443-
{-# INLINE unsafePackLiteral #-}
452+
{-# INLINE byteCountLiteral #-}
444453

445454

446455
-- | See 'unsafePackLiteral'. This function is similar,

bench/BenchAll.hs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import qualified Data.ByteString as S
2525
import qualified Data.ByteString.Char8 as S8
2626
import qualified Data.ByteString.Lazy as L
2727
import qualified Data.ByteString.Lazy.Char8 as L8
28+
import Data.ByteString.Internal (byteCountLiteral)
2829

2930
import Data.ByteString.Builder
3031
import Data.ByteString.Builder.Extra (byteStringCopy,
@@ -33,10 +34,13 @@ import Data.ByteString.Builder.Extra (byteStringCopy,
3334
import Data.ByteString.Builder.Internal (ensureFree)
3435
import Data.ByteString.Builder.Prim (BoundedPrim, FixedPrim,
3536
(>$<))
37+
import qualified Data.ByteString.Builder.Internal as BI
3638
import qualified Data.ByteString.Builder.Prim as P
3739
import qualified Data.ByteString.Builder.Prim.Internal as PI
3840

3941
import Foreign
42+
import GHC.Exts (Addr#)
43+
import GHC.Ptr (Ptr(..))
4044

4145
import System.Random
4246

@@ -247,6 +251,18 @@ largeTraversalInput = S.concat (replicate 10 byteStringData)
247251
smallTraversalInput :: S.ByteString
248252
smallTraversalInput = S8.pack "The quick brown fox"
249253

254+
ascBuf, utfBuf :: Ptr Word8
255+
ascBuf = Ptr "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"#
256+
utfBuf = Ptr "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx\xc0\x80xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"#
257+
258+
asclit, utflit :: Ptr Word8 -> Builder
259+
asclit str@(Ptr addr) = BI.ascLiteralCopy str (byteCountLiteral addr)
260+
utflit str@(Ptr addr) = BI.modUtf8LitCopy str (byteCountLiteral addr)
261+
262+
ascStr, utfStr :: String
263+
ascStr = "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"
264+
utfStr = "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx\0xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"
265+
250266
main :: IO ()
251267
main = do
252268
defaultMain
@@ -256,9 +272,15 @@ main = do
256272
, benchB' "ensureFree 8" () (const (ensureFree 8))
257273
, benchB' "intHost 1" 1 intHost
258274
, benchB' "UTF-8 String (naive)" "hello world\0" fromString
259-
, benchB' "UTF-8 String" () $ \() -> P.cstringUtf8 "hello world\0"#
275+
, benchB' "UTF-8 String" () $ \() -> utflit (Ptr "hello world\xc0\x80"#)
260276
, benchB' "String (naive)" "hello world!" fromString
261-
, benchB' "String" () $ \() -> P.cstring "hello world!"#
277+
, benchB' "String" () $ \() -> asclit (Ptr "hello world!"#)
278+
, benchB' "AsciiLit" () $ \() -> asclit ascBuf
279+
, benchB' "Utf8Lit" () $ \() -> utflit utfBuf
280+
, benchB' "strLit" () $ \() -> string8 ascStr
281+
, benchB' "utfLit" () $ \() -> stringUtf8 utfStr
282+
, benchB' "strLitInline" () $ \() -> string8 "XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX"
283+
, benchB' "utfLitInline" () $ \() -> stringUtf8 "XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX\0XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX"
262284
]
263285

264286
, bgroup "Encoding wrappers"

tests/builder/Data/ByteString/Builder/Prim/Tests.hs

Lines changed: 1 addition & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -24,17 +24,7 @@ import Test.Tasty.QuickCheck
2424

2525
tests :: [TestTree]
2626
tests = concat [ testsBinary, testsASCII, testsChar8, testsUtf8
27-
, testsCombinatorsB, [testCString, testCStringUtf8] ]
28-
29-
testCString :: TestTree
30-
testCString = testProperty "cstring" $
31-
toLazyByteString (BP.cstring "hello world!"#) ==
32-
LC.pack "hello" `L.append` L.singleton 0x20 `L.append` LC.pack "world!"
33-
34-
testCStringUtf8 :: TestTree
35-
testCStringUtf8 = testProperty "cstringUtf8" $
36-
toLazyByteString (BP.cstringUtf8 "hello\xc0\x80world!"#) ==
37-
LC.pack "hello" `L.append` L.singleton 0x00 `L.append` LC.pack "world!"
27+
, testsCombinatorsB ]
3828

3929
------------------------------------------------------------------------------
4030
-- Binary

0 commit comments

Comments
 (0)