Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
sergv committed Jan 2, 2024
1 parent 2c6d4a0 commit 416888c
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 9 deletions.
3 changes: 3 additions & 0 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,6 @@ benchmarks: True

-- package containers-tests
-- ghc-options: -Werror

allow-newer:
, ChasingBottoms:base
31 changes: 24 additions & 7 deletions containers-tests/benchmarks/Map.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,12 @@ module Main where
import Control.Applicative (Const(Const, getConst), pure)
import Control.DeepSeq (rnf)
import Control.Exception (evaluate)
import Test.Tasty.Bench (bench, defaultMain, whnf, nf, bcompare)
import Test.Tasty.Bench (bench, defaultMain, whnf, nf, bcompare, bgroup)
import Data.Functor.Identity (Identity(..))
import Data.List (foldl')
import qualified Data.Map as M
import qualified Data.Map.Strict as MS
import qualified Data.Set as S
import Data.Map (alterF)
import Data.Maybe (fromMaybe)
import Data.Functor ((<$))
Expand All @@ -22,9 +23,10 @@ main = do
m_even = M.fromAscList elems_even :: M.Map Int Int
m_odd = M.fromAscList elems_odd :: M.Map Int Int
m_odd_keys = M.keysSet m_odd
m_even_keys = M.keysSet m_even
evaluate $ rnf [m, m_even, m_odd]
evaluate $ rnf elems_rev
evaluate $ rnf m_odd_keys
evaluate $ rnf [m_odd_keys, m_even_keys]
defaultMain
[ bench "lookup absent" $ whnf (lookup evens) m_odd
, bench "lookup present" $ whnf (lookup evens) m_even
Expand Down Expand Up @@ -99,11 +101,26 @@ main = do
, bench "fromDistinctDescList:fusion" $ whnf (\n -> M.fromDistinctDescList [(i,i) | i <- [n,n-1..1]]) bound
, 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])

, bench "restrictKeys+withoutKeys"
$ whnf (\ks -> M.restrictKeys m ks :*: M.withoutKeys m ks) m_odd_keys
, bcompare "/restrictKeys+withoutKeys/"
$ bench "partitionKeys"
$ whnf (M.partitionKeys m) m_odd_keys
, bgroup "even"
[ bench "restrictKeys+withoutKeys"
$ nf (\ks -> (M.restrictKeys m ks, M.withoutKeys m ks)) m_even_keys
, bcompare "/even.restrictKeys+withoutKeys/"
$ bench "partitionKeys"
$ nf (M.partitionKeys m) m_even_keys
, bcompare "/even.restrictKeys+withoutKeys/"
$ bench "partitionWithKey"
$ nf (\ks -> M.partitionWithKey (\k _ -> S.member k ks) m) m_even_keys
]
, bgroup "odd"
[ bench "restrictKeys+withoutKeys"
$ nf (\ks -> (M.restrictKeys m ks, M.withoutKeys m ks)) m_odd_keys
, bcompare "/odd.restrictKeys+withoutKeys/"
$ bench "partitionKeys"
$ nf (M.partitionKeys m) m_odd_keys
, bcompare "/odd.restrictKeys+withoutKeys/"
$ bench "partitionWithKey"
$ nf (\ks -> M.partitionWithKey (\k _ -> S.member k ks) m) m_even_keys
]
]
where
bound = 2^12
Expand Down
4 changes: 2 additions & 2 deletions containers-tests/containers-tests.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ common deps
build-depends:
array >=0.4.0.0
, base >=4.10 && <5
, deepseq >=1.2 && <1.5
, deepseq >=1.2 && <1.6
, template-haskell

common test-deps
Expand All @@ -54,7 +54,7 @@ common benchmark-deps
import: deps
build-depends:
containers-tests
, deepseq >=1.1.0.0 && <1.5
, deepseq >=1.1.0.0 && <1.6
, tasty-bench >=0.3.1 && <0.4

-- Copy of containers library,
Expand Down

0 comments on commit 416888c

Please sign in to comment.