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 4a15a7a commit d117f3e
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 8 deletions.
9 changes: 3 additions & 6 deletions containers-tests/benchmarks/Map.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,12 +98,9 @@ main = do
, bench "fromDistinctDescList" $ whnf M.fromDistinctDescList elems_rev
, 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
, 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 #-}
#endif
#define USE_MAGIC_PROXY 1

Expand Down Expand Up @@ -1954,7 +1953,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 d117f3e

Please sign in to comment.