Skip to content

Commit 2c1d08c

Browse files
committed
Introduce ‘partitionKeys’ that fuses ‘restrictKeys’ and ‘withoutKeys’ in one go
1 parent e8dbba8 commit 2c1d08c

File tree

6 files changed

+67
-2
lines changed

6 files changed

+67
-2
lines changed

containers-tests/benchmarks/Map.hs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module Main where
55
import Control.Applicative (Const(Const, getConst), pure)
66
import Control.DeepSeq (rnf)
77
import Control.Exception (evaluate)
8-
import Test.Tasty.Bench (bench, defaultMain, whnf, nf)
8+
import Test.Tasty.Bench (bench, defaultMain, whnf, nf, bcompare)
99
import Data.Functor.Identity (Identity(..))
1010
import Data.List (foldl')
1111
import qualified Data.Map as M
@@ -15,13 +15,16 @@ import Data.Maybe (fromMaybe)
1515
import Data.Functor ((<$))
1616
import Data.Coerce
1717
import Prelude hiding (lookup)
18+
import Utils.Containers.Internal.StrictPair
1819

1920
main = 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

containers-tests/tests/map-properties.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,7 @@ main = defaultMain $ testGroup "map-properties"
173173
, testProperty "withoutKeys" prop_withoutKeys
174174
, testProperty "intersection" prop_intersection
175175
, testProperty "restrictKeys" prop_restrictKeys
176+
, testProperty "partitionKeys" prop_partitionKeys
176177
, testProperty "intersection model" prop_intersectionModel
177178
, testProperty "intersectionWith" prop_intersectionWith
178179
, testProperty "intersectionWithModel" prop_intersectionWithModel
@@ -1140,6 +1141,12 @@ prop_withoutKeys m s0 = valid reduced .&&. (m `withoutKeys` s === filterWithKey
11401141
s = keysSet s0
11411142
reduced = withoutKeys m s
11421143

1144+
prop_partitionKeys :: IMap -> IMap -> Property
1145+
prop_partitionKeys m s0 = valid with .&&. valid without .&&. (m `partitionKeys` s === (m `restrictKeys` s, m `withoutKeys` s))
1146+
where
1147+
s = keysSet s0
1148+
(with, without) = partitionKeys m s
1149+
11431150
prop_intersection :: IMap -> IMap -> Bool
11441151
prop_intersection t1 t2 = valid (intersection t1 t2)
11451152

containers/src/Data/Map/Internal.hs

Lines changed: 44 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
{-# LANGUAGE StandaloneDeriving #-}
88
{-# LANGUAGE Trustworthy #-}
99
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE ScopedTypeVariables #-}
1011
#define USE_MAGIC_PROXY 1
1112
#endif
1213

@@ -299,6 +300,7 @@ module Data.Map.Internal (
299300

300301
, restrictKeys
301302
, withoutKeys
303+
, partitionKeys
302304
, partition
303305
, partitionWithKey
304306

@@ -1966,6 +1968,48 @@ withoutKeys m (Set.Bin _ k ls rs) = case splitMember k m of
19661968
{-# INLINABLE withoutKeys #-}
19671969
#endif
19681970

1971+
-- | \(O\bigl(m \log\bigl(\frac{n}{m}+1\bigr)\bigr), \; 0 < m \leq n\). Partition the map according to a set.
1972+
-- The first map contains the input 'Map' restricted to those keys found in the 'Set',
1973+
-- the second map contains the input 'Map' without all keys in the 'Set'.
1974+
-- This is more efficient than using 'restrictKeys' and 'withoutKeys' together.
1975+
--
1976+
-- @
1977+
-- m \`partitionKeys\` s = (m ``restrictKeys`` s, m ``withoutKeys`` s)
1978+
-- @
1979+
partitionKeys :: forall k a. Ord k => Map k a -> Set k -> (Map k a, Map k a)
1980+
partitionKeys xs ys =
1981+
case go xs ys of
1982+
xs' :*: ys' -> (xs', ys')
1983+
where
1984+
go :: Map k a -> Set k -> StrictPair (Map k a) (Map k a)
1985+
go Tip _ = Tip :*: Tip
1986+
go m Set.Tip = Tip :*: m
1987+
go m@(Bin _ k x lm rm) s@Set.Bin{} =
1988+
case b of
1989+
True -> with :*: without
1990+
where
1991+
with =
1992+
if lmWith `ptrEq` lm && rmWith `ptrEq` rm
1993+
then m
1994+
else link k x lmWith rmWith
1995+
without =
1996+
link2 lmWithout rmWithout
1997+
False -> with :*: without
1998+
where
1999+
with = link2 lmWith rmWith
2000+
without =
2001+
if lmWithout `ptrEq` lm && rmWithout `ptrEq` rm
2002+
then m
2003+
else link k x lmWithout rmWithout
2004+
where
2005+
!(lmWith :*: lmWithout) = go lm ls'
2006+
!(rmWith :*: rmWithout) = go rm rs'
2007+
2008+
!(!ls', b, !rs') = Set.splitMember k s
2009+
#if __GLASGOW_HASKELL__
2010+
{-# INLINABLE partitionKeys #-}
2011+
#endif
2012+
19692013
-- | \(O(n+m)\). Difference with a combining function.
19702014
-- When two equal keys are
19712015
-- encountered, the combining function is applied to the values of these keys.

containers/src/Data/Map/Lazy.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -231,6 +231,7 @@ module Data.Map.Lazy (
231231
, filterWithKey
232232
, restrictKeys
233233
, withoutKeys
234+
, partitionKeys
234235
, partition
235236
, partitionWithKey
236237
, takeWhileAntitone

containers/src/Data/Map/Strict.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -246,6 +246,7 @@ module Data.Map.Strict
246246
, filterWithKey
247247
, restrictKeys
248248
, withoutKeys
249+
, partitionKeys
249250
, partition
250251
, partitionWithKey
251252

containers/src/Data/Map/Strict/Internal.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -256,6 +256,7 @@ module Data.Map.Strict.Internal
256256
, filterWithKey
257257
, restrictKeys
258258
, withoutKeys
259+
, partitionKeys
259260
, partition
260261
, partitionWithKey
261262
, takeWhileAntitone
@@ -418,7 +419,8 @@ import Data.Map.Internal
418419
, toDescList
419420
, union
420421
, unions
421-
, withoutKeys )
422+
, withoutKeys
423+
, partitionKeys )
422424

423425
import Data.Map.Internal.Debug (valid)
424426

0 commit comments

Comments
 (0)