diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index c31cec086..4b98755fd 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -339,18 +339,18 @@ packChars cs = unsafePackLenChars (List.length cs) cs #-} unsafePackLenBytes :: Int -> [Word8] -> ByteString -unsafePackLenBytes len xs0 = - unsafeCreate len $ \p -> go p xs0 - where - go !_ [] = return () - go !p (x:xs) = poke p x >> go (p `plusPtr` 1) xs +unsafePackLenBytes len = + unsafeCreate len . foldr + (\x go p -> poke p x >> go (p `plusPtr` 1)) + (\_ -> return ()) +{-# INLINE unsafePackLenBytes #-} unsafePackLenChars :: Int -> [Char] -> ByteString -unsafePackLenChars len cs0 = - unsafeCreate len $ \p -> go p cs0 - where - go !_ [] = return () - go !p (c:cs) = poke p (c2w c) >> go (p `plusPtr` 1) cs +unsafePackLenChars len = + unsafeCreate len . foldr + (\x go p -> poke p (c2w x) >> go (p `plusPtr` 1)) + (\_ -> return ()) +{-# INLINE unsafePackLenChars #-} -- | /O(n)/ Pack a null-terminated sequence of bytes, pointed to by an diff --git a/bench/BenchAll.hs b/bench/BenchAll.hs index 451eebc65..641205124 100644 --- a/bench/BenchAll.hs +++ b/bench/BenchAll.hs @@ -23,6 +23,7 @@ import Prelude hiding (words) import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as S8 +import qualified Data.ByteString.Internal as SI import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy.Char8 as L8 @@ -481,6 +482,18 @@ main = do [ bench "lazy" $ nf L8.unlines (map (L8.pack . show) intData) , bench "strict" $ nf S8.unlines (map (S8.pack . show) intData) ] + , bgroup "pack" + [ bench "not fused" $ nf S.pack (replicate nRepl 0) + , bench "fused" $ nf (S.pack . replicate nRepl) 0 + ] + , bgroup "unsafePackLenBytes" + [ bench "not fused" $ nf (SI.unsafePackLenBytes nRepl) (replicate nRepl 0) + , bench "fused" $ nf (SI.unsafePackLenBytes nRepl . replicate nRepl) 0 + ] + , bgroup "unsafePackLenChar" + [ bench "not fused" $ nf (SI.unsafePackLenChars nRepl) (replicate nRepl 'A') + , bench "fused" $ nf (SI.unsafePackLenChars nRepl . replicate nRepl) 'A' + ] , benchBoundsCheckFusion , benchCount , benchCSV