Skip to content

Commit

Permalink
Change IntMap.lookup and add new IntMap.query function
Browse files Browse the repository at this point in the history
  - `IntMap.lookup` no longer checks for short circuit failure.
  - Add a new function `IntMap.query` with the old fast-fail behaviour.
  • Loading branch information
Boarders committed Sep 9, 2021
1 parent ff3d6af commit 6fe267e
Show file tree
Hide file tree
Showing 6 changed files with 72 additions and 5 deletions.
40 changes: 36 additions & 4 deletions containers-tests/benchmarks/IntMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,23 @@ import Data.Maybe (fromMaybe)
import Prelude hiding (lookup)

main = do
let m = M.fromAscList elems :: M.IntMap Int
evaluate $ rnf [m]
let m = M.fromAscList elems_hits :: M.IntMap Int
let m' = M.fromAscList elems_mid :: M.IntMap Int
let m'' = M.fromAscList elems_most :: M.IntMap Int
let m''' = M.fromAscList elems_misses :: M.IntMap Int
let m'''' = M.fromAscList elems_mixed :: M.IntMap Int
evaluate $ rnf [m, m', m'', m''', m'''']
defaultMain
[ bench "lookup" $ whnf (lookup keys) m
[ bench "query_hits" $ whnf (query keys) m
, bench "query_half" $ whnf (query keys) m'
, bench "query_most" $ whnf (query keys) m''
, bench "query_misses" $ whnf (query keys'') m'''
, bench "query_mixed" $ whnf (query keys) m''''
, bench "lookup_hits" $ whnf (lookup keys) m
, bench "lookup_half" $ whnf (lookup keys) m'
, bench "lookup_most" $ whnf (lookup keys) m''
, bench "lookup_misses" $ whnf (lookup keys'') m'''
, bench "lookup_mixed" $ whnf (lookup keys) m''''
, bench "insert" $ whnf (ins elems) M.empty
, bench "insertWith empty" $ whnf (insWith elems) M.empty
, bench "insertWith update" $ whnf (insWith elems) m
Expand Down Expand Up @@ -44,19 +57,33 @@ main = do
(M.fromList $ zip [1..10] [1..10])
]
where
elems = zip keys values
elems = elems_hits
elems_hits = zip keys values
elems_mid = zip (map (+ (2^12 `div` 2)) keys) values
elems_most = zip (map (+ (2^12 `div` 10)) keys) values
elems_misses = zip (map (\x-> x * 2 + 1) keys) values
elems_mixed = zip mixedKeys values
--------------------------------------------------------
keys = [1..2^12]
keys' = fmap (+ 1000000) keys
keys'' = fmap (* 2) [1..2^12]
mixedKeys = interleave keys keys'
values = [1..2^12]
--------------------------------------------------------
sum k v1 v2 = k + v1 + v2
consPair k v xs = (k, v) : xs

------------------------------------------------------------
add3 :: Int -> Int -> Int -> Int
add3 x y z = x + y + z
{-# INLINE add3 #-}

lookup :: [Int] -> M.IntMap Int -> Int
lookup xs m = foldl' (\n k -> fromMaybe n (M.lookup k m)) 0 xs

query :: [Int] -> M.IntMap Int -> Int
query xs m = foldl' (\n k -> fromMaybe n (M.query k m)) 0 xs

ins :: [(Int, Int)] -> M.IntMap Int -> M.IntMap Int
ins xs m = foldl' (\m (k, v) -> M.insert k v m) m xs

Expand Down Expand Up @@ -95,3 +122,8 @@ alt xs m = foldl' (\m k -> M.alter id k m) m xs
maybeDel :: Int -> Maybe Int
maybeDel n | n `mod` 3 == 0 = Nothing
| otherwise = Just n

------------------------------------------------------------
interleave :: [Int] -> [Int] -> [Int]
interleave [] ys = ys
interleave (x:xs) (y:ys) = x : y : interleave xs ys
15 changes: 15 additions & 0 deletions containers-tests/tests/intmap-properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ main = defaultMain $ testGroup "intmap-properties"
, testCase "member" test_member
, testCase "notMember" test_notMember
, testCase "lookup" test_lookup
, testCase "query " test_query
, testCase "findWithDefault" test_findWithDefault
, testCase "lookupLT" test_lookupLT
, testCase "lookupGT" test_lookupGT
Expand Down Expand Up @@ -307,6 +308,20 @@ test_lookup = do
country <- lookup dept deptCountry
lookup country countryCurrency

test_query :: Assertion
test_query = do
employeeCurrency 1 @?= Just 1
employeeCurrency 2 @?= Nothing
where
employeeDept = fromList([(1,2), (3,1)])
deptCountry = fromList([(1,1), (2,2)])
countryCurrency = fromList([(1, 2), (2, 1)])
employeeCurrency :: Int -> Maybe Int
employeeCurrency name = do
dept <- query name employeeDept
country <- query dept deptCountry
lookup country countryCurrency

test_findWithDefault :: Assertion
test_findWithDefault = do
findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) @?= 'x'
Expand Down
18 changes: 17 additions & 1 deletion containers/src/Data/IntMap/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ module Data.IntMap.Internal (
, member
, notMember
, lookup
, query
, findWithDefault
, lookupLT
, lookupGT
Expand Down Expand Up @@ -598,7 +599,22 @@ notMember k m = not $ member k m
lookup :: Key -> IntMap a -> Maybe a
lookup !k = go
where
go (Bin p m l r) | nomatch k p m = Nothing
go (Bin _p m l r)
| zero k m = go l
| otherwise = go r
go (Tip kx x) | k == kx = Just x
| otherwise = Nothing
go Nil = Nothing

-- | /O(min(n,W))/. Query has identical behaviour to 'Data.IntMap.Internal.lookup' but
-- will fail faster in the case that the key does not share is not present.

-- See Note: Local 'go' functions and capturing]
query :: Key -> IntMap a -> Maybe a
query !k = go
where
go (Bin p m l r)
| nomatch k p m = Nothing
| zero k m = go l
| otherwise = go r
go (Tip kx x) | k == kx = Just x
Expand Down
1 change: 1 addition & 0 deletions containers/src/Data/IntMap/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ module Data.IntMap.Lazy (
-- * Query
-- ** Lookup
, IM.lookup
, IM.query
, (!?)
, (!)
, findWithDefault
Expand Down
1 change: 1 addition & 0 deletions containers/src/Data/IntMap/Strict.hs
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,7 @@ module Data.IntMap.Strict (
-- * Query
-- ** Lookup
, lookup
, query
, (!?)
, (!)
, findWithDefault
Expand Down
2 changes: 2 additions & 0 deletions containers/src/Data/IntMap/Strict/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,7 @@ module Data.IntMap.Strict.Internal (
-- * Query
-- ** Lookup
, lookup
, query
, (!?)
, (!)
, findWithDefault
Expand Down Expand Up @@ -327,6 +328,7 @@ import Data.IntMap.Internal
, null
, partition
, partitionWithKey
, query
, restrictKeys
, size
, split
Expand Down

0 comments on commit 6fe267e

Please sign in to comment.