Skip to content

Commit c3a4e78

Browse files
authored
Merge pull request #800 from Boarders/master
Change IntMap.lookup and add new IntMap.query function
2 parents eb2c8e2 + e6fbb98 commit c3a4e78

File tree

3 files changed

+46
-23
lines changed

3 files changed

+46
-23
lines changed

containers-tests/benchmarks/IntMap.hs

Lines changed: 28 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,10 +11,18 @@ import Data.Maybe (fromMaybe)
1111
import Prelude hiding (lookup)
1212

1313
main = do
14-
let m = M.fromAscList elems :: M.IntMap Int
15-
evaluate $ rnf [m]
14+
let m = M.fromAscList elems_hits :: M.IntMap Int
15+
let m' = M.fromAscList elems_mid :: M.IntMap Int
16+
let m'' = M.fromAscList elems_most :: M.IntMap Int
17+
let m''' = M.fromAscList elems_misses :: M.IntMap Int
18+
let m'''' = M.fromAscList elems_mixed :: M.IntMap Int
19+
evaluate $ rnf [m, m', m'', m''', m'''']
1620
defaultMain
17-
[ bench "lookup" $ whnf (lookup keys) m
21+
[ bench "lookup_hits" $ whnf (lookup keys) m
22+
, bench "lookup_half" $ whnf (lookup keys) m'
23+
, bench "lookup_most" $ whnf (lookup keys) m''
24+
, bench "lookup_misses" $ whnf (lookup keys'') m'''
25+
, bench "lookup_mixed" $ whnf (lookup keys) m''''
1826
, bench "insert" $ whnf (ins elems) M.empty
1927
, bench "insertWith empty" $ whnf (insWith elems) M.empty
2028
, bench "insertWith update" $ whnf (insWith elems) m
@@ -44,12 +52,23 @@ main = do
4452
(M.fromList $ zip [1..10] [1..10])
4553
]
4654
where
47-
elems = zip keys values
55+
elems = elems_hits
56+
elems_hits = zip keys values
57+
elems_mid = zip (map (+ (2^12 `div` 2)) keys) values
58+
elems_most = zip (map (+ (2^12 `div` 10)) keys) values
59+
elems_misses = zip (map (\x-> x * 2 + 1) keys) values
60+
elems_mixed = zip mixedKeys values
61+
--------------------------------------------------------
4862
keys = [1..2^12]
63+
keys' = fmap (+ 1000000) keys
64+
keys'' = fmap (* 2) [1..2^12]
65+
mixedKeys = interleave keys keys'
4966
values = [1..2^12]
67+
--------------------------------------------------------
5068
sum k v1 v2 = k + v1 + v2
5169
consPair k v xs = (k, v) : xs
5270

71+
------------------------------------------------------------
5372
add3 :: Int -> Int -> Int -> Int
5473
add3 x y z = x + y + z
5574
{-# INLINE add3 #-}
@@ -95,3 +114,8 @@ alt xs m = foldl' (\m k -> M.alter id k m) m xs
95114
maybeDel :: Int -> Maybe Int
96115
maybeDel n | n `mod` 3 == 0 = Nothing
97116
| otherwise = Just n
117+
118+
------------------------------------------------------------
119+
interleave :: [Int] -> [Int] -> [Int]
120+
interleave [] ys = ys
121+
interleave (x:xs) (y:ys) = x : y : interleave xs ys

containers-tests/tests/intmap-properties.hs

Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -295,12 +295,17 @@ test_notMember = do
295295

296296
test_lookup :: Assertion
297297
test_lookup = do
298-
employeeCurrency 1 @?= Just 1
299-
employeeCurrency 2 @?= Nothing
298+
employeeCurrency 1 @?= Just 1
299+
employeeCurrency 2 @?= Just 2
300+
employeeCurrency 3 @?= Just 3
301+
employeeCurrency 4 @?= Just 4
302+
employeeCurrency 5 @?= Nothing
303+
employeeCurrency (2^10) @?= Just 42
304+
employeeCurrency 6 @?= Nothing
300305
where
301-
employeeDept = fromList([(1,2), (3,1)])
302-
deptCountry = fromList([(1,1), (2,2)])
303-
countryCurrency = fromList([(1, 2), (2, 1)])
306+
employeeDept = fromList [(1,2), (2, 14), (3, 10), (4, 18), (2^10, 100)]
307+
deptCountry = fromList [(1,1), (14, 14), (10, 10), (18, 18), (100, 100), (2,2)]
308+
countryCurrency = fromList [(1, 2), (2, 1), (14, 2), (10, 3), (18, 4), (100, 42)]
304309
employeeCurrency :: Int -> Maybe Int
305310
employeeCurrency name = do
306311
dept <- lookup name employeeDept

containers/src/Data/IntMap/Internal.hs

Lines changed: 8 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -594,25 +594,22 @@ notMember k m = not $ member k m
594594

595595
-- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'.
596596

597-
-- See Note: Local 'go' functions and capturing]
597+
-- See Note: Local 'go' functions and capturing
598598
lookup :: Key -> IntMap a -> Maybe a
599599
lookup !k = go
600600
where
601-
go (Bin p m l r) | nomatch k p m = Nothing
602-
| zero k m = go l
603-
| otherwise = go r
601+
go (Bin _p m l r) | zero k m = go l
602+
| otherwise = go r
604603
go (Tip kx x) | k == kx = Just x
605604
| otherwise = Nothing
606605
go Nil = Nothing
607606

608-
609607
-- See Note: Local 'go' functions and capturing]
610608
find :: Key -> IntMap a -> a
611609
find !k = go
612610
where
613-
go (Bin p m l r) | nomatch k p m = not_found
614-
| zero k m = go l
615-
| otherwise = go r
611+
go (Bin _p m l r) | zero k m = go l
612+
| otherwise = go r
616613
go (Tip kx x) | k == kx = x
617614
| otherwise = not_found
618615
go Nil = not_found
@@ -943,8 +940,7 @@ adjust f k m
943940
-- > adjustWithKey f 7 empty == empty
944941

945942
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a
946-
adjustWithKey f !k t@(Bin p m l r)
947-
| nomatch k p m = t
943+
adjustWithKey f !k (Bin p m l r)
948944
| zero k m = Bin p m (adjustWithKey f k l) r
949945
| otherwise = Bin p m l (adjustWithKey f k r)
950946
adjustWithKey f k t@(Tip ky y)
@@ -976,8 +972,7 @@ update f
976972
-- > updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
977973

978974
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
979-
updateWithKey f !k t@(Bin p m l r)
980-
| nomatch k p m = t
975+
updateWithKey f !k (Bin p m l r)
981976
| zero k m = binCheckLeft p m (updateWithKey f k l) r
982977
| otherwise = binCheckRight p m l (updateWithKey f k r)
983978
updateWithKey f k t@(Tip ky y)
@@ -998,8 +993,7 @@ updateWithKey _ _ Nil = Nil
998993
-- > updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
999994

1000995
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a,IntMap a)
1001-
updateLookupWithKey f !k t@(Bin p m l r)
1002-
| nomatch k p m = (Nothing,t)
996+
updateLookupWithKey f !k (Bin p m l r)
1003997
| zero k m = let !(found,l') = updateLookupWithKey f k l
1004998
in (found,binCheckLeft p m l' r)
1005999
| otherwise = let !(found,r') = updateLookupWithKey f k r

0 commit comments

Comments
 (0)