Skip to content

Commit

Permalink
More review suggestions
Browse files Browse the repository at this point in the history
  • Loading branch information
sergv committed Apr 6, 2024
1 parent b6d6533 commit 9f7c5bd
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 9 deletions.
11 changes: 4 additions & 7 deletions containers-tests/benchmarks/Map.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ 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)
import Data.Functor.Identity (Identity(..))
import Data.List (foldl')
import qualified Data.Map as M
Expand All @@ -15,7 +15,6 @@ import Data.Maybe (fromMaybe)
import Data.Functor ((<$))
import Data.Coerce
import Prelude hiding (lookup)
import Utils.Containers.Internal.StrictPair

main = do
let m = M.fromAscList elems :: M.Map Int Int
Expand Down Expand Up @@ -102,11 +101,9 @@ main = do
, bench "eq" $ whnf (\m' -> m' == m') m -- worst case, compares everything
, bench "compare" $ whnf (\m' -> compare m' m') m -- worst case, compares everything

, 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
, bench "restrictKeys" $ whnf (M.restrictKeys m) m_odd_keys
, bench "withoutKeys" $ whnf (M.withoutKeys m) m_odd_keys
, bench "partitionKeys" $ whnf (M.partitionKeys m) m_odd_keys
]
where
bound = 2^12
Expand Down
3 changes: 1 addition & 2 deletions containers/src/Data/Map/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
#define USE_MAGIC_PROXY 1
#endif

Expand Down Expand Up @@ -1977,7 +1976,7 @@ withoutKeys m (Set.Bin _ k ls rs) = case splitMember k m of
-- @
-- m \`partitionKeys\` s = (m ``restrictKeys`` s, m ``withoutKeys`` s)
-- @
partitionKeys :: forall k a. Ord k => Map k a -> Set k -> (Map k a, Map k a)
partitionKeys :: Ord k => Map k a -> Set k -> (Map k a, Map k a)
partitionKeys xs ys =
case partitionKeysWorker xs ys of
xs' :*: ys' -> (xs', ys')
Expand Down

0 comments on commit 9f7c5bd

Please sign in to comment.