@@ -5,7 +5,7 @@ module Main where
55import Control.Applicative (Const (Const , getConst ), pure )
66import Control.DeepSeq (rnf )
77import Control.Exception (evaluate )
8- import Test.Tasty.Bench (bench , defaultMain , whnf , nf )
8+ import Test.Tasty.Bench (bench , defaultMain , whnf , nf , bcompare )
99import Data.Functor.Identity (Identity (.. ))
1010import Data.List (foldl' )
1111import qualified Data.Map as M
@@ -15,13 +15,16 @@ import Data.Maybe (fromMaybe)
1515import Data.Functor ((<$) )
1616import Data.Coerce
1717import Prelude hiding (lookup )
18+ import Utils.Containers.Internal.StrictPair
1819
1920main = do
2021 let m = M. fromAscList elems :: M. Map Int Int
2122 m_even = M. fromAscList elems_even :: M. Map Int Int
2223 m_odd = M. fromAscList elems_odd :: M. Map Int Int
24+ m_odd_keys = M. keysSet m_odd
2325 evaluate $ rnf [m, m_even, m_odd]
2426 evaluate $ rnf elems_rev
27+ evaluate $ rnf m_odd_keys
2528 defaultMain
2629 [ bench " lookup absent" $ whnf (lookup evens) m_odd
2730 , bench " lookup present" $ whnf (lookup evens) m_even
@@ -95,8 +98,15 @@ main = do
9598 , bench " fromDistinctDescList" $ whnf M. fromDistinctDescList elems_rev
9699 , bench " fromDistinctDescList:fusion" $ whnf (\ n -> M. fromDistinctDescList [(i,i) | i <- [n,n- 1 .. 1 ]]) bound
97100 , bench " minView" $ whnf (\ m' -> case M. minViewWithKey m' of {Nothing -> 0 ; Just ((k,v),m'') -> k+ v+ M. size m''}) (M. fromAscList $ zip [1 .. 10 :: Int ] [100 .. 110 :: Int ])
101+
98102 , bench " eq" $ whnf (\ m' -> m' == m') m -- worst case, compares everything
99103 , bench " compare" $ whnf (\ m' -> compare m' m') m -- worst case, compares everything
104+
105+ , bench " restrictKeys+withoutKeys"
106+ $ whnf (\ ks -> M. restrictKeys m ks :*: M. withoutKeys m ks) m_odd_keys
107+ , bcompare " /restrictKeys+withoutKeys/"
108+ $ bench " partitionKeys"
109+ $ whnf (M. partitionKeys m) m_odd_keys
100110 ]
101111 where
102112 bound = 2 ^ 12
0 commit comments