[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Add insertAt benchmark (a3f3921)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:42:56 UTC 2017


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

On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/a3f39212419df9e74b4a0f489a01b55a00db664e

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

commit a3f39212419df9e74b4a0f489a01b55a00db664e
Author: David Feuer <David.Feuer at gmail.com>
Date:   Mon May 30 00:46:58 2016 -0400

    Add insertAt benchmark
    
    Make `insertAt` rebuild the tree eagerly, which saves a little
    time and avoids the possibility that large thunks will build
    up at the root of the tree when multiple elements are inserted.
    
    For long sequences `insertAt` is around 4.6 times as fast as
    splitting the sequence and re-forming it around the new element.


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

a3f39212419df9e74b4a0f489a01b55a00db664e
 Data/Sequence.hs       |  5 +++--
 benchmarks/Sequence.hs | 16 ++++++++++++++++
 2 files changed, 19 insertions(+), 2 deletions(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 335df84..46a6e0f 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -1788,8 +1788,9 @@ insTree f i (Single x) = case f i x of
 insTree f i (Deep s pr m sf)
   | i < spr     = case insLeftDigit f i pr of
      InsLeftDig pr' -> Deep (s + 1) pr' m sf
-     InsDigNode pr' n -> Deep (s + 1) pr' (consTree n m) sf
-  | i < spm     = Deep (s + 1) pr (insTree (insNode f) (i - spr) m) sf
+     InsDigNode pr' n -> Deep (s + 1) pr' (n `consTree` m) sf
+  | i < spm     = let !m' = insTree (insNode f) (i - spr) m
+                  in Deep (s + 1) pr m' sf
   | otherwise   = case insRightDigit f (i - spm) sf of
      InsRightDig sf' -> Deep (s + 1) pr m sf'
      InsNodeDig n sf' -> Deep (s + 1) pr (m `snocTree` n) sf'
diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs
index dd30067..717daf9 100644
--- a/benchmarks/Sequence.hs
+++ b/benchmarks/Sequence.hs
@@ -35,6 +35,11 @@ main = do
          , bench "100" $ nf (shuffle r100) s100
          , bench "1000" $ nf (shuffle r1000) s1000
          ]
+      , bgroup "insertAt"
+         [ bench "10" $ nf (insertAtPoints r10 10) s10
+         , bench "100" $ nf (insertAtPoints r100 10) s100
+         , bench "1000" $ nf (insertAtPoints r1000 10) s1000
+         ]
       , bgroup "traverseWithIndex/State"
          [ bench "10" $ nf multiplyDown s10
          , bench "100" $ nf multiplyDown s100
@@ -85,6 +90,17 @@ main = do
          ]
       ]
 
+{-
+-- This is around 4.6 times as slow as insertAt
+fakeInsertAt :: Int -> a -> S.Seq a -> S.Seq a
+fakeInsertAt i x xs = case S.splitAt i xs of
+  (before, after) -> before S.>< x S.<| after
+-}
+
+insertAtPoints :: [Int] -> a -> S.Seq a -> S.Seq a
+insertAtPoints points x xs =
+  foldl' (\acc k -> S.insertAt k x acc) xs points
+
 -- splitAt+append: repeatedly cut the sequence at a random point
 -- and rejoin the pieces in the opposite order.
 -- Finally getting the middle element forces the whole spine.



More information about the ghc-commits mailing list