Skip to content

Commit d5fbab7

Browse files
committed
Add mapMaybe and mapMaybeWithKey (issue #59)
They share the implementation with filterWithKey, without affecting the former's structure reuse.
1 parent 2d984fe commit d5fbab7

File tree

4 files changed

+59
-9
lines changed

4 files changed

+59
-9
lines changed

Data/HashMap/Base.hs

Lines changed: 44 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, MagicHash #-}
22
{-# LANGUAGE ScopedTypeVariables #-}
3+
{-# LANGUAGE PatternGuards #-}
34
#if __GLASGOW_HASKELL__ >= 708
45
{-# LANGUAGE TypeFamilies #-}
56
#endif
@@ -52,6 +53,8 @@ module Data.HashMap.Base
5253
, foldrWithKey
5354

5455
-- * Filter
56+
, mapMaybe
57+
, mapMaybeWithKey
5558
, filter
5659
, filterWithKey
5760

@@ -855,14 +858,46 @@ trim mary n = do
855858
A.unsafeFreeze mary2
856859
{-# INLINE trim #-}
857860

861+
-- | /O(n)/ Transform this map by applying a function to every value
862+
-- and retaining only some of them.
863+
mapMaybeWithKey :: (k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
864+
mapMaybeWithKey f = filterMapAux onLeaf onColl
865+
where onLeaf (Leaf h (L k v)) | Just v' <- f k v = Just (Leaf h (L k v'))
866+
onLeaf _ = Nothing
867+
868+
onColl (L k v) | Just v' <- f k v = Just (L k v')
869+
| otherwise = Nothing
870+
{-# INLINE mapMaybeWithKey #-}
871+
872+
-- | /O(n)/ Transform this map by applying a function to every value
873+
-- and retaining only some of them.
874+
mapMaybe :: (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
875+
mapMaybe f = mapMaybeWithKey (const f)
876+
{-# INLINE mapMaybe #-}
877+
858878
-- | /O(n)/ Filter this map by retaining only elements satisfying a
859879
-- predicate.
860880
filterWithKey :: forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
861-
filterWithKey pred = go
881+
filterWithKey pred = filterMapAux onLeaf onColl
882+
where onLeaf t@(Leaf _ (L k v)) | pred k v = Just t
883+
onLeaf _ = Nothing
884+
885+
onColl el@(L k v) | pred k v = Just el
886+
onColl _ = Nothing
887+
888+
889+
-- | Common implementation for 'filterWithKey' and 'mapMaybeWithKey',
890+
-- allowing the former to former to reuse terms.
891+
filterMapAux :: forall k v1 v2
892+
. (HashMap k v1 -> Maybe (HashMap k v2))
893+
-> (Leaf k v1 -> Maybe (Leaf k v2))
894+
-> HashMap k v1
895+
-> HashMap k v2
896+
filterMapAux onLeaf onColl = go
862897
where
863898
go Empty = Empty
864-
go t@(Leaf _ (L k v))
865-
| pred k v = t
899+
go t@Leaf{}
900+
| Just t' <- onLeaf t = t'
866901
| otherwise = Empty
867902
go (BitmapIndexed b ary) = filterA ary b
868903
go (Full ary) = filterA ary fullNodeMask
@@ -874,9 +909,9 @@ filterWithKey pred = go
874909
mary <- A.new_ n
875910
step ary0 mary b0 0 0 1 n
876911
where
877-
step :: A.Array (HashMap k v) -> A.MArray s (HashMap k v)
912+
step :: A.Array (HashMap k v1) -> A.MArray s (HashMap k v2)
878913
-> Bitmap -> Int -> Int -> Bitmap -> Int
879-
-> ST s (HashMap k v)
914+
-> ST s (HashMap k v2)
880915
step !ary !mary !b i !j !bi n
881916
| i >= n = case j of
882917
0 -> return Empty
@@ -903,9 +938,9 @@ filterWithKey pred = go
903938
mary <- A.new_ n
904939
step ary0 mary 0 0 n
905940
where
906-
step :: A.Array (Leaf k v) -> A.MArray s (Leaf k v)
941+
step :: A.Array (Leaf k v1) -> A.MArray s (Leaf k v2)
907942
-> Int -> Int -> Int
908-
-> ST s (HashMap k v)
943+
-> ST s (HashMap k v2)
909944
step !ary !mary i !j n
910945
| i >= n = case j of
911946
0 -> return Empty
@@ -915,9 +950,9 @@ filterWithKey pred = go
915950
return $! Collision h ary2
916951
| otherwise -> do ary2 <- trim mary j
917952
return $! Collision h ary2
918-
| pred k v = A.write mary j el >> step ary mary (i+1) (j+1) n
953+
| Just el <- onColl (A.index ary i)
954+
= A.write mary j el >> step ary mary (i+1) (j+1) n
919955
| otherwise = step ary mary (i+1) j n
920-
where el@(L k v) = A.index ary i
921956
{-# INLINE filterWithKey #-}
922957

923958
-- | /O(n)/ Filter this map by retaining only elements which values

Data/HashMap/Lazy.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,8 @@ module Data.HashMap.Lazy
7373
, foldrWithKey
7474

7575
-- * Filter
76+
, mapMaybe
77+
, mapMaybeWithKey
7678
, HM.filter
7779
, filterWithKey
7880

Data/HashMap/Strict.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,8 @@ module Data.HashMap.Strict
7373
, foldrWithKey
7474

7575
-- * Filter
76+
, mapMaybe
77+
, mapMaybeWithKey
7678
, HM.filter
7779
, filterWithKey
7880

tests/HashMapProperties.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55

66
module Main (main) where
77

8+
import Control.Monad ( guard )
89
import qualified Data.Foldable as Foldable
910
import Data.Function (on)
1011
import Data.Hashable (Hashable(hashWithSalt))
@@ -173,6 +174,14 @@ foldlWithKey'Map = M.foldlWithKey
173174
------------------------------------------------------------------------
174175
-- ** Filter
175176

177+
pMapMaybeWithKey :: [(Key, Int)] -> Bool
178+
pMapMaybeWithKey = M.mapMaybeWithKey f `eq_` HM.mapMaybeWithKey f
179+
where f k v = guard (odd (unK k + v)) >> Just (v + 1)
180+
181+
pMapMaybe :: [(Key, Int)] -> Bool
182+
pMapMaybe = M.mapMaybe f `eq_` HM.mapMaybe f
183+
where f v = guard (odd v) >> Just (v + 1)
184+
176185
pFilter :: [(Key, Int)] -> Bool
177186
pFilter = M.filter odd `eq_` HM.filter odd
178187

@@ -251,6 +260,8 @@ tests =
251260
, testGroup "filter"
252261
[ testProperty "filter" pFilter
253262
, testProperty "filterWithKey" pFilterWithKey
263+
, testProperty "mapMaybe" pMapMaybe
264+
, testProperty "mapMaybeWithKey" pMapMaybeWithKey
254265
]
255266
-- Conversions
256267
, testGroup "conversions"

0 commit comments

Comments
 (0)