Skip to content

Commit

Permalink
Merge commit 'df039bd80fa61745' into no-deque
Browse files Browse the repository at this point in the history
  • Loading branch information
clyring committed Feb 4, 2024
2 parents 0ced807 + df039bd commit 071a062
Show file tree
Hide file tree
Showing 4 changed files with 38 additions and 24 deletions.
27 changes: 11 additions & 16 deletions Data/ByteString/Builder/ASCII.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,7 @@ import Data.ByteString.Builder.RealFloat (floatDec, doubleDec)

import Foreign
import Foreign.C.Types
import Data.List.NonEmpty (NonEmpty(..))

------------------------------------------------------------------------------
-- Decimal Encoding
Expand Down Expand Up @@ -276,37 +277,31 @@ integerDec i
| i < 0 = P.primFixed P.char8 '-' `mappend` go (-i)
| otherwise = go i
where
errImpossible fun =
error $ "integerDec: " ++ fun ++ ": the impossible happened."

go :: Integer -> Builder
go n | n < maxPow10 = intDec (fromInteger n)
| otherwise =
case putH (splitf (maxPow10 * maxPow10) n) of
(x:xs) -> intDec x `mappend` P.primMapListBounded intDecPadded xs
[] -> errImpossible "integerDec: go"
x:|xs -> intDec x `mappend` P.primMapListBounded intDecPadded xs

splitf :: Integer -> Integer -> [Integer]
splitf :: Integer -> Integer -> NonEmpty Integer
splitf pow10 n0
| pow10 > n0 = [n0]
| pow10 > n0 = n0 :| []
| otherwise = splith (splitf (pow10 * pow10) n0)
where
splith [] = errImpossible "splith"
splith (n:ns) =
splith (n:|ns) =
case n `quotRem` pow10 of
(q,r) | q > 0 -> q : r : splitb ns
| otherwise -> r : splitb ns
(q,r) | q > 0 -> q :| r : splitb ns
| otherwise -> r :| splitb ns

splitb [] = []
splitb (n:ns) = case n `quotRem` pow10 of
(q,r) -> q : r : splitb ns

putH :: [Integer] -> [Int]
putH [] = errImpossible "putH"
putH (n:ns) = case n `quotRem` maxPow10 of
putH :: NonEmpty Integer -> NonEmpty Int
putH (n:|ns) = case n `quotRem` maxPow10 of
(x,y)
| q > 0 -> q : r : putB ns
| otherwise -> r : putB ns
| q > 0 -> q :| r : putB ns
| otherwise -> r :| putB ns
where q = fromInteger x
r = fromInteger y

Expand Down
10 changes: 5 additions & 5 deletions Data/ByteString/Short.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,20 +33,20 @@ module Data.ByteString.Short (
-- | With GHC, the memory overheads are as follows, expressed in words and
-- in bytes (words are 4 and 8 bytes on 32 or 64bit machines respectively).
--
-- * 'B.ByteString' unshared: 8 words; 32 or 64 bytes.
-- * t'Data.ByteString.ByteString' unshared: 8 words; 32 or 64 bytes.
--
-- * 'B.ByteString' shared substring: 4 words; 16 or 32 bytes.
-- * t'Data.ByteString.ByteString' shared substring: 4 words; 16 or 32 bytes.
--
-- * 'ShortByteString': 4 words; 16 or 32 bytes.
--
-- For the string data itself, both 'ShortByteString' and 'B.ByteString' use
-- For the string data itself, both 'ShortByteString' and t'Data.ByteString.ByteString' use
-- one byte per element, rounded up to the nearest word. For example,
-- including the overheads, a length 10 'ShortByteString' would take
-- @16 + 12 = 28@ bytes on a 32bit platform and @32 + 16 = 48@ bytes on a
-- 64bit platform.
--
-- These overheads can all be reduced by 1 word (4 or 8 bytes) when the
-- 'ShortByteString' or 'B.ByteString' is unpacked into another constructor.
-- 'ShortByteString' or t'Data.ByteString.ByteString' is unpacked into another constructor.
--
-- For example:
--
Expand All @@ -58,7 +58,7 @@ module Data.ByteString.Short (
-- string data.

-- ** Heap fragmentation
-- | With GHC, the 'B.ByteString' representation uses /pinned/ memory,
-- | With GHC, the t'Data.ByteString.ByteString' representation uses /pinned/ memory,
-- meaning it cannot be moved by the GC. This is usually the right thing to
-- do for larger strings, but for small strings using pinned memory can
-- lead to heap fragmentation which wastes space. The 'ShortByteString'
Expand Down
1 change: 1 addition & 0 deletions Data/ByteString/Short/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1309,6 +1309,7 @@ isInfixOf :: ShortByteString -> ShortByteString -> Bool
isInfixOf sbs = \s -> null sbs || not (null $ snd $ (GHC.Exts.inline breakSubstring) sbs s)

-- |/O(n)/ The 'isPrefixOf' function takes two ShortByteStrings and returns 'True'
-- iff the first is a prefix of the second.
--
-- @since 0.11.3.0
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
Expand Down
24 changes: 21 additions & 3 deletions bench/BenchAll.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ import Data.Semigroup
import Data.String
import Test.Tasty.Bench
import Prelude hiding (words)
import qualified Data.List as List
import Control.DeepSeq

import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S8
Expand Down Expand Up @@ -99,9 +101,12 @@ lazyByteStringData = case S.splitAt (nRepl `div` 2) byteStringData of

{-# NOINLINE smallChunksData #-}
smallChunksData :: L.ByteString
smallChunksData
= L.fromChunks [S.take sz (S.drop n byteStringData)
| let sz = 48, n <- [0, sz .. S.length byteStringData]]
smallChunksData = L.fromChunks $ List.unfoldr step (byteStringData, 1)
where
step (!s, !i)
| S.null s = Nothing
| otherwise = case S.splitAt i s of
(!s1, !s2) -> Just (s1, (s2, i * 71 `mod` 97))

{-# NOINLINE byteStringChunksData #-}
byteStringChunksData :: [S.ByteString]
Expand Down Expand Up @@ -419,6 +424,19 @@ main = do
[ bench "strict" $ nf S.tails byteStringData
, bench "lazy" $ nf L.tails lazyByteStringData
]
, bgroup "splitAtEnd (lazy)" $ let
testSAE op = \bs -> [op i bs | i <- [0,5..L.length bs]] `deepseq` ()
{-# INLINE testSAE #-}
in
[ bench "takeEnd" $
nf (testSAE L.takeEnd) lazyByteStringData
, bench "takeEnd (small chunks)" $
nf (testSAE L.takeEnd) smallChunksData
, bench "dropEnd" $
nf (testSAE L.dropEnd) lazyByteStringData
, bench "dropEnd (small chunks)" $
nf (testSAE L.dropEnd) smallChunksData
]
, bgroup "sort" $ map (\s -> bench (S8.unpack s) $ nf S.sort s) sortInputs
, bgroup "stimes" $ let st = stimes :: Int -> S.ByteString -> S.ByteString
in
Expand Down

0 comments on commit 071a062

Please sign in to comment.