[commit: packages/bytestring] master, revert-46-patch-1, wip/nix-local-build: Merge https://github.com/haskell/bytestring (1eff53d)

git at git.haskell.org git at git.haskell.org
Tue May 3 22:43:36 UTC 2016


Repository : ssh://git@git.haskell.org/bytestring

On branches: master,revert-46-patch-1,wip/nix-local-build
Link       : http://git.haskell.org/packages/bytestring.git/commitdiff/1eff53d49f4566416cf108a7a6d74e1b58280761

>---------------------------------------------------------------

commit 1eff53d49f4566416cf108a7a6d74e1b58280761
Merge: c72f64f dd3c07d
Author: Sean <burton.seanr at gmail.com>
Date:   Mon Nov 2 15:33:27 2015 +0000

    Merge https://github.com/haskell/bytestring
    
    Conflicts:
    	Data/ByteString.hs
    	bench/BenchAll.hs



>---------------------------------------------------------------

1eff53d49f4566416cf108a7a6d74e1b58280761
 Data/ByteString.hs                                 | 196 ++++-----------------
 Data/ByteString/Builder/ASCII.hs                   |   4 +-
 Data/ByteString/Builder/Internal.hs                |  10 +-
 .../Builder/Prim/Internal/UncheckedShifts.hs       |  13 +-
 Data/ByteString/Char8.hs                           |  12 +-
 Data/ByteString/Internal.hs                        |  95 +---------
 Data/ByteString/Lazy.hs                            |  19 +-
 Data/ByteString/Lazy/Char8.hs                      |   5 -
 Data/ByteString/Lazy/Internal.hs                   |  24 +--
 Data/ByteString/Short/Internal.hs                  |   4 -
 Data/ByteString/Unsafe.hs                          |  22 ---
 bench/BenchAll.hs                                  |  54 +++++-
 bytestring.cabal                                   |   1 +
 tests/builder/Data/ByteString/Builder/Tests.hs     |   6 -
 14 files changed, 107 insertions(+), 358 deletions(-)

diff --cc bench/BenchAll.hs
index c1a3f1f,1f8f69c..908af4e
--- a/bench/BenchAll.hs
+++ b/bench/BenchAll.hs
@@@ -38,10 -38,8 +38,9 @@@ import qualified "bytestring" Data.Byte
  
  import           Foreign
  
- import           Paths_bench_bytestring
+ import System.Random
  
- import           System.Random
 +
  ------------------------------------------------------------------------------
  -- Benchmark support
  ------------------------------------------------------------------------------
@@@ -153,42 -151,30 +152,64 @@@ benchIntEncodingB n0 
        | n <= 0    = return op
        | otherwise = PI.runB w n op >>= loop (n - 1)
  
- easySubstrings, randomSubstrings :: Int -> Int -> (S.ByteString, S.ByteString)
- hardSubstrings, pathologicalSubstrings :: Int ->
-                                           Int -> (S.ByteString, S.ByteString)
+ hashInt :: Int -> Int
+ hashInt x = iterate step x !! 10
+   where
+     step a = e
+       where b = (a `xor` 61) `xor` (a `shiftR` 16)
+             c = b + (b `shiftL` 3)
+             d = c `xor` (c `shiftR` 4)
+             e = d * 0x27d4eb2d
+             f = e `xor` (e `shiftR` 15)
  
 -hashWord8 :: Word8 -> Word8
 -hashWord8 = fromIntegral . hashInt . fromIntegral
 -
  w :: Int -> Word8
  w = fromIntegral
  
++hashWord8 :: Word8 -> Word8
++hashWord8 = fromIntegral . hashInt . w
++
+ partitionStrict p = nf (S.partition p) . randomStrict $ mkStdGen 98423098
+   where randomStrict = fst . S.unfoldrN 10000 (Just . random)
+ 
+ partitionLazy p = nf (L.partition p) . randomLazy $ (0, mkStdGen 98423098)
 -  where  step (k, g)
 -           | k >= 10000 = Nothing
 -           | otherwise  = let (x, g') = random g in Just (x, (k + 1, g'))
 -         randomLazy = L.unfoldr step
++  where step (k, g)
++          | k >= 10000 = Nothing
++          | otherwise  = let (x, g') = random g in Just (x, (k + 1, g'))
++        randomLazy = L.unfoldr step
++
++easySubstrings, randomSubstrings :: Int -> Int -> (S.ByteString, S.ByteString)
++hardSubstrings, pathologicalSubstrings :: Int ->
++                                          Int -> (S.ByteString, S.ByteString)
++
 +{-# INLINE easySubstrings #-}
 +easySubstrings n h = (S.replicate n $ w 1,
 +                      S.replicate h $ w 0)
 +
 +{-# INLINE randomSubstrings #-}
 +randomSubstrings n h = (f 48278379 n, f 98403980 h)
 +  where
 +    next' g = let (x, g') = next g in (w x, g')
 +    f g l = fst $ S.unfoldrN l (Just . next') (mkStdGen g)
 +
 +{-# INLINE hardSubstrings #-}
 +hardSubstrings n h = (f 48278379 n, f 98403980 h)
 +  where
 +    next' g = let (x, g') = next g
 +              in (w $ x `mod` 4, g')
 +    f g l = fst $ S.unfoldrN l (Just . next') (mkStdGen g)
 +
 +{-# INLINE pathologicalSubstrings #-}
 +pathologicalSubstrings n h =
 +  (S.replicate n (w 0),
 +   S.concat . replicate (h `div` n) $ S.replicate (n - 1) (w 0) `S.snoc` w 1)
 +
 +htmlSubstrings :: S.ByteString -> Int -> Int -> IO (S.ByteString, S.ByteString)
 +htmlSubstrings s n h =
 +    do i <- randomRIO (0, l - n)
 +       return (S.take n . S.drop i $ s', s')
 +  where
 +    s' = S.take h s
 +    l  = S.length s'
  
  -- benchmarks
  -------------



More information about the ghc-commits mailing list