From 4d9315dde69ec48b59e7639826514472da4b0701 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Sun, 7 Sep 2025 19:33:03 +0100 Subject: [PATCH 01/11] Add Data.Set.{catMaybe,mapMaybes}. --- containers-tests/tests/set-properties.hs | 39 +++++++++++++++++++++++- containers/src/Data/Set.hs | 2 ++ containers/src/Data/Set/Internal.hs | 22 +++++++++++++ 3 files changed, 62 insertions(+), 1 deletion(-) diff --git a/containers-tests/tests/set-properties.hs b/containers-tests/tests/set-properties.hs index aeb4e65c3..7f96ff399 100644 --- a/containers-tests/tests/set-properties.hs +++ b/containers-tests/tests/set-properties.hs @@ -2,7 +2,8 @@ import qualified Data.IntSet as IntSet import Data.List (nub, sort, sortBy) import qualified Data.List as List -import Data.Maybe +import Data.Maybe (isJust, fromJust) +import qualified Data.Maybe as Maybe import Data.Set import Data.Set.Internal (link, merge) import Prelude hiding (lookup, null, map, filter, foldr, foldl, foldl', all, take, drop, splitAt) @@ -98,6 +99,8 @@ main = defaultMain $ testGroup "set-properties" , testProperty "prop_splitRoot" prop_splitRoot , testProperty "prop_partition" prop_partition , testProperty "prop_filter" prop_filter + , testProperty "prop_catMaybes" prop_catMaybes + , testProperty "prop_mapMaybe" prop_mapMaybe , testProperty "takeWhileAntitone" prop_takeWhileAntitone , testProperty "dropWhileAntitone" prop_dropWhileAntitone , testProperty "spanAntitone" prop_spanAntitone @@ -241,6 +244,32 @@ instance IsInt a => Arbitrary (Set a) where put i' pure (fromInt i') +newtype MaybeIntSet = MaybeIntSet (Set (Maybe Int)) deriving (Show) +instance Arbitrary MaybeIntSet where + arbitrary = sized $ \sz0 -> do + sz <- choose (0, sz0) + middle <- choose (-positionFactor * (sz + 1), positionFactor * (sz + 1)) + let shift = (sz * (gapRange) + 1) `quot` 2 + start = middle - shift + hasNothing <- arbitrary + t <- evalStateT (mkArbSet (step start) sz) + (if hasNothing then Nothing else Just start) + if valid t + then pure $ MaybeIntSet t + else error "Test generated invalid tree!" + where + step start = do + mi <- get + case mi of + Nothing -> do + put $ Just start + pure Nothing + Just i -> do + diff <- lift $ choose (1, gapRange) + let i' = i + diff + put $ Just i' + pure $ Just i' + data TwoSets = TwoSets (Set Int) (Set Int) deriving (Show) data TwoLists a = TwoLists [a] [a] @@ -618,6 +647,14 @@ prop_partition s i = case partition odd s of prop_filter :: Set Int -> Int -> Bool prop_filter s i = partition odd s == (filter odd s, filter even s) +prop_catMaybes :: MaybeIntSet -> Bool +prop_catMaybes (MaybeIntSet s) = + toList (catMaybes s) == Maybe.catMaybes (toList s) + +prop_mapMaybe :: Set Int -> Bool +prop_mapMaybe s = toList (mapMaybe f s) == Maybe.mapMaybe f (toList s) + where f n = if odd n then Just n else Nothing + prop_take :: Int -> Set Int -> Property prop_take n xs = valid taken .&&. taken === fromDistinctAscList (List.take n (toList xs)) diff --git a/containers/src/Data/Set.hs b/containers/src/Data/Set.hs index 7eaf80622..dc1f9d203 100644 --- a/containers/src/Data/Set.hs +++ b/containers/src/Data/Set.hs @@ -137,6 +137,8 @@ module Data.Set ( , takeWhileAntitone , dropWhileAntitone , spanAntitone + , catMaybes + , mapMaybe , partition , split , splitMember diff --git a/containers/src/Data/Set/Internal.hs b/containers/src/Data/Set/Internal.hs index 4682abc8c..e6f7ee028 100644 --- a/containers/src/Data/Set/Internal.hs +++ b/containers/src/Data/Set/Internal.hs @@ -162,6 +162,8 @@ module Data.Set.Internal ( , takeWhileAntitone , dropWhileAntitone , spanAntitone + , catMaybes + , mapMaybe , partition , split , splitMember @@ -239,6 +241,7 @@ import Data.Functor.Identity (Identity) import qualified Data.Foldable as Foldable import Control.DeepSeq (NFData(rnf),NFData1(liftRnf)) import Data.List.NonEmpty (NonEmpty(..)) +import qualified Data.Maybe as Maybe import Utils.Containers.Internal.StrictPair import Utils.Containers.Internal.PtrEquality @@ -993,6 +996,25 @@ partition p0 t0 = toPair $ go p0 t0 then t else link x l2 r2) +{-------------------------------------------------------------------- + Maybes +--------------------------------------------------------------------} + +-- | \(O(n)\). Drop 'Nothing' if it's in the set, and retain the 'Just' values. +-- +-- @since FIXME +catMaybes :: Set (Maybe a) -> Set a +catMaybes = mapMonotonic Maybe.fromJust . dropWhileAntitone Maybe.isNothing + +-- | \(O(n \log n)\). Map values and collect the 'Just' results. +-- +-- If the function is monotonically non-decreasing, this function takes \(O(n)\) +-- time. +-- +-- @since FIXME +mapMaybe :: Ord b => (a -> Maybe b) -> Set a -> Set b +mapMaybe f = fromList . Maybe.mapMaybe f . toList + {---------------------------------------------------------------------- Map ----------------------------------------------------------------------} From 68b8a741b5e7cb15bb83db93307d55ab68f67305 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Sun, 7 Sep 2025 20:34:01 +0100 Subject: [PATCH 02/11] Add Data.Sequence.{catMaybe,mapMaybes}. --- containers-tests/tests/seq-properties.hs | 14 +++++++++++++- containers/src/Data/Sequence.hs | 2 ++ containers/src/Data/Sequence/Internal.hs | 18 ++++++++++++++++++ 3 files changed, 33 insertions(+), 1 deletion(-) diff --git a/containers-tests/tests/seq-properties.hs b/containers-tests/tests/seq-properties.hs index 06e2f48c5..a8b18d576 100644 --- a/containers-tests/tests/seq-properties.hs +++ b/containers-tests/tests/seq-properties.hs @@ -24,7 +24,8 @@ import Data.Array (listArray) import Data.Coerce (coerce) import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, fold), toList, all, sum, foldl', foldr') import Data.Functor ((<$>), (<$)) -import Data.Maybe +import Data.Maybe (listToMaybe) +import qualified Data.Maybe as Maybe import Data.Function (on) import Data.Monoid (Monoid(..), All(..), Endo(..), Dual(..)) import Data.Semigroup (stimes, stimesMonoid) @@ -100,6 +101,8 @@ main = defaultMain $ testGroup "seq-properties" , testProperty "breakr" prop_breakr , testProperty "partition" prop_partition , testProperty "filter" prop_filter + , testProperty "catMaybes" prop_catMaybes + , testProperty "mapMaybe" prop_mapMaybe , testProperty "sort" prop_sort , testProperty "sortStable" prop_sortStable , testProperty "sortBy" prop_sortBy @@ -553,6 +556,15 @@ prop_filter (Positive n) xs = toList' (filter p xs) ~= Prelude.filter p (toList xs) where p x = x `mod` n == 0 +prop_catMaybes :: Seq (Maybe Int) -> Bool +prop_catMaybes xs = + toList' (catMaybes xs) ~= Maybe.catMaybes (toList xs) + +prop_mapMaybe :: Positive Int -> Seq Int -> Bool +prop_mapMaybe (Positive n) xs = + toList' (mapMaybe f xs) ~= Maybe.mapMaybe f (toList xs) + where f x = if x `mod` n == 0 then Just x else Nothing + -- * Sorting prop_sort :: Seq OrdA -> Bool diff --git a/containers/src/Data/Sequence.hs b/containers/src/Data/Sequence.hs index 9c9c52973..ea23f29b6 100644 --- a/containers/src/Data/Sequence.hs +++ b/containers/src/Data/Sequence.hs @@ -192,6 +192,8 @@ module Data.Sequence ( breakr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) partition, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) filter, -- :: (a -> Bool) -> Seq a -> Seq a + catMaybes, -- :: Seq (Maybe a) -> Seq a + mapMaybe, -- :: (a -> Maybe b) -> Seq a -> Seq b -- * Sorting sort, -- :: Ord a => Seq a -> Seq a sortBy, -- :: (a -> a -> Ordering) -> Seq a -> Seq a diff --git a/containers/src/Data/Sequence/Internal.hs b/containers/src/Data/Sequence/Internal.hs index ac9796ab3..27d8aa33d 100644 --- a/containers/src/Data/Sequence/Internal.hs +++ b/containers/src/Data/Sequence/Internal.hs @@ -128,6 +128,8 @@ module Data.Sequence.Internal ( breakr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) partition, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) filter, -- :: (a -> Bool) -> Seq a -> Seq a + catMaybes, -- :: Seq (Maybe a) -> Seq a + mapMaybe, -- :: (a -> Maybe b) -> Seq a -> Seq b -- * Indexing lookup, -- :: Int -> Seq a -> Maybe a (!?), -- :: Seq a -> Int -> Maybe a @@ -4199,6 +4201,22 @@ partition p = toPair . foldl' part (empty :*: empty) filter :: (a -> Bool) -> Seq a -> Seq a filter p = foldl' (\ xs x -> if p x then xs `snoc'` x else xs) empty +-- | \( O(n) \). Take a sequence of 'Maybe's and return a sequence of all the +-- 'Just' values. +-- +-- @since FIXME +catMaybes :: Seq (Maybe a) -> Seq a +catMaybes = mapMaybe id + +-- | \( O(n) \). Map values and collect the 'Just' results. +-- +-- @since FIXME +mapMaybe :: (a -> Maybe b) -> Seq a -> Seq b +mapMaybe f = foldl' go empty + where go xs x = case f x of + Nothing -> xs + Just x' -> xs `snoc'` x' + -- Indexing sequences -- | 'elemIndexL' finds the leftmost index of the specified element, From 5eb6d2e59f528b3d1fabc11ba00d5db419124889 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Mon, 8 Sep 2025 21:05:19 +0100 Subject: [PATCH 03/11] Add Data.IntSet.mapMaybe. --- containers-tests/tests/intset-properties.hs | 8 ++++++++ containers/src/Data/IntSet.hs | 2 ++ containers/src/Data/IntSet/Internal.hs | 14 ++++++++++++++ 3 files changed, 24 insertions(+) diff --git a/containers-tests/tests/intset-properties.hs b/containers-tests/tests/intset-properties.hs index 76b5813b4..e218fbdf1 100644 --- a/containers-tests/tests/intset-properties.hs +++ b/containers-tests/tests/intset-properties.hs @@ -6,6 +6,7 @@ import Data.IntSet import Data.List (nub,sort) import qualified Data.List as List import Data.Maybe (listToMaybe) +import qualified Data.Maybe as Maybe import Data.Monoid (mempty) import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NE @@ -79,6 +80,7 @@ main = defaultMain $ testGroup "intset-properties" , testProperty "prop_splitRoot" prop_splitRoot , testProperty "prop_partition" prop_partition , testProperty "prop_filter" prop_filter + , testProperty "prop_mapMaybe" prop_mapMaybe , testProperty "takeWhileAntitone" prop_takeWhileAntitone , testProperty "dropWhileAntitone" prop_dropWhileAntitone , testProperty "spanAntitone" prop_spanAntitone @@ -457,6 +459,12 @@ prop_filter s i = valid evens .&&. parts === (odds, evens) +prop_mapMaybe :: IntSet -> Property +prop_mapMaybe s = + let f n = if odd n then Just n else Nothing + odds = mapMaybe f s + in valid odds .&&. toList odds === Maybe.mapMaybe f (toList s) + prop_takeWhileAntitone :: Int -> [Int] -> Property prop_takeWhileAntitone x ys = let l = takeWhileAntitone ( Maybe Key) -> IntSet -> IntSet +mapMaybe f t = finishB (foldl' go emptyB t) + where go b x = case f x of + Nothing -> b + Just x' -> insertB x' b + -- | \(O(n)\). partition the set according to some predicate. partition :: (Key -> Bool) -> IntSet -> (IntSet,IntSet) partition predicate0 t0 = toPair $ go predicate0 t0 From d52fb9bdf6a951fb3903004e3cb47895f5e73000 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Mon, 8 Sep 2025 23:36:13 +0100 Subject: [PATCH 04/11] Add `catMaybes` to Data.Map.Strict and Data.Map.Lazy. --- containers-tests/tests/map-properties.hs | 14 +++++++++++++- containers-tests/tests/map-strictness.hs | 7 +++++++ containers/src/Data/Map/Internal.hs | 10 ++++++++++ containers/src/Data/Map/Lazy.hs | 1 + containers/src/Data/Map/Strict.hs | 1 + containers/src/Data/Map/Strict/Internal.hs | 10 ++++++++++ 6 files changed, 42 insertions(+), 1 deletion(-) diff --git a/containers-tests/tests/map-properties.hs b/containers-tests/tests/map-properties.hs index a585391c4..a86188a2e 100644 --- a/containers-tests/tests/map-properties.hs +++ b/containers-tests/tests/map-properties.hs @@ -18,7 +18,7 @@ import Control.Monad ((<=<)) import qualified Data.Either as Either import Data.Functor.Identity (Identity(Identity, runIdentity)) import Data.Monoid -import Data.Maybe hiding (mapMaybe) +import Data.Maybe hiding (catMaybes, mapMaybe) import qualified Data.Maybe as Maybe (mapMaybe) import Data.Ord import Data.Semigroup (Arg(..)) @@ -124,6 +124,7 @@ main = defaultMain $ testGroup "map-properties" , testCase "filterWithKey" test_filterWithKey , testCase "partition" test_partition , testCase "partitionWithKey" test_partitionWithKey + , testCase "catMaybes" test_catMaybes , testCase "mapMaybe" test_mapMaybe , testCase "mapMaybeWithKey" test_mapMaybeWithKey , testCase "mapEither" test_mapEither @@ -296,6 +297,7 @@ main = defaultMain $ testGroup "map-properties" , testProperty "differenceWith" prop_differenceWith , testProperty "differenceWithKey" prop_differenceWithKey , testProperty "partitionWithKey" prop_partitionWithKey + , testProperty "catMaybes" prop_catMaybes , testProperty "mapMaybe" prop_mapMaybe , testProperty "mapMaybeWithKey" prop_mapMaybeWithKey , testProperty "traverseMaybeWithKey" prop_traverseMaybeWithKey @@ -862,6 +864,9 @@ test_partitionWithKey = do partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) @?= (fromList [(3, "b"), (5, "a")], empty) partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) @?= (empty, fromList [(3, "b"), (5, "a")]) +test_catMaybes :: Assertion +test_catMaybes = catMaybes (fromList [(5,Just "a"), (3,Nothing)]) @?= singleton 5 "a" + test_mapMaybe :: Assertion test_mapMaybe = mapMaybe f (fromList [(5,"a"), (3,"b")]) @?= singleton 5 "new a" where @@ -1960,6 +1965,13 @@ prop_partitionWithKey f m = where (m1, m2) = partitionWithKey (applyFun2 f) m +prop_catMaybes :: Map Int (Maybe A) -> Property +prop_catMaybes m = + valid m' .&&. + toList m' === Maybe.mapMaybe (\(k,x) -> (,) k <$> x) (toList m) + where + m' = catMaybes m + prop_mapMaybe :: Fun A (Maybe B) -> Map Int A -> Property prop_mapMaybe f m = valid m' .&&. diff --git a/containers-tests/tests/map-strictness.hs b/containers-tests/tests/map-strictness.hs index f6e4630c8..3107936a4 100644 --- a/containers-tests/tests/map-strictness.hs +++ b/containers-tests/tests/map-strictness.hs @@ -755,6 +755,12 @@ prop_lazyMapKeysWith fun kfun m = isNotBottomProp (L.mapKeysWith f kf m) f = coerce (applyFunc2 fun) :: A -> A -> A kf = applyFunc kfun +prop_strictCatMaybes :: Map OrdA (Maybe (Bot A)) -> Property +prop_strictCatMaybes m = isBottom (M.catMaybes m) === isBottom (M.mapMaybe id m) + +prop_lazyCatMaybes :: Map OrdA (Maybe (Bot A)) -> Property +prop_lazyCatMaybes m = isNotBottomProp (L.catMaybes m) + prop_strictMapMaybe :: Func A (Maybe (Bot B)) -> Map OrdA A -> Property prop_strictMapMaybe fun m = isBottom (M.mapMaybe f m) === isBottom (M.mapMaybeWithKey (const f) m) @@ -1193,6 +1199,7 @@ tests = , testPropStrictLazy "mapAccumWithKey" prop_strictMapAccumWithKey prop_lazyMapAccumWithKey , testPropStrictLazy "mapAccumRWithKey" prop_strictMapAccumRWithKey prop_lazyMapAccumRWithKey , testPropStrictLazy "mapKeysWith" prop_strictMapKeysWith prop_lazyMapKeysWith + , testPropStrictLazy "catMaybes" prop_strictCatMaybes prop_lazyCatMaybes , testPropStrictLazy "mapMaybe" prop_strictMapMaybe prop_lazyMapMaybe , testPropStrictLazy "mapMaybeWithKey" prop_strictMapMaybeWithKey prop_lazyMapMaybeWithKey , testPropStrictLazy "mapEither" prop_strictMapEither prop_lazyMapEither diff --git a/containers/src/Data/Map/Internal.hs b/containers/src/Data/Map/Internal.hs index 40181416f..5a5da2a32 100644 --- a/containers/src/Data/Map/Internal.hs +++ b/containers/src/Data/Map/Internal.hs @@ -304,6 +304,7 @@ module Data.Map.Internal ( , partition , partitionWithKey + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -3114,6 +3115,15 @@ partitionWithKey p0 t0 = toPair $ go p0 t0 (l1 :*: l2) = go p l (r1 :*: r2) = go p r +-- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. +-- +-- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" +-- +-- @since FIXME + +catMaybes :: Map k (Maybe a) -> Map k a +catMaybes = mapMaybe id + -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing diff --git a/containers/src/Data/Map/Lazy.hs b/containers/src/Data/Map/Lazy.hs index 56ca3c536..408467410 100644 --- a/containers/src/Data/Map/Lazy.hs +++ b/containers/src/Data/Map/Lazy.hs @@ -247,6 +247,7 @@ module Data.Map.Lazy ( , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/Map/Strict.hs b/containers/src/Data/Map/Strict.hs index de0fb18c4..4ff221893 100644 --- a/containers/src/Data/Map/Strict.hs +++ b/containers/src/Data/Map/Strict.hs @@ -262,6 +262,7 @@ module Data.Map.Strict , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/Map/Strict/Internal.hs b/containers/src/Data/Map/Strict/Internal.hs index d70977e38..7c60eb8f8 100644 --- a/containers/src/Data/Map/Strict/Internal.hs +++ b/containers/src/Data/Map/Strict/Internal.hs @@ -246,6 +246,7 @@ module Data.Map.Strict.Internal , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -1246,6 +1247,15 @@ mergeWithKey f g1 g2 = go Filter and partition --------------------------------------------------------------------} +-- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. +-- +-- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" +-- +-- @since FIXME + +catMaybes :: Map k (Maybe a) -> Map k a +catMaybes = mapMaybe id + -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing From a44f68685c74f80d98310f7baee9864926aa49f0 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Mon, 8 Sep 2025 23:59:18 +0100 Subject: [PATCH 05/11] Add `catMaybes` to Data.IntMap.Strict and Data.IntMap.Lazy. --- containers-tests/tests/intmap-properties.hs | 23 ++++++++++++++++++- containers-tests/tests/intmap-strictness.hs | 7 ++++++ containers/src/Data/IntMap/Internal.hs | 10 ++++++++ containers/src/Data/IntMap/Lazy.hs | 1 + containers/src/Data/IntMap/Strict.hs | 1 + containers/src/Data/IntMap/Strict/Internal.hs | 10 ++++++++ 6 files changed, 51 insertions(+), 1 deletion(-) diff --git a/containers-tests/tests/intmap-properties.hs b/containers-tests/tests/intmap-properties.hs index ec198d929..bed771ee9 100644 --- a/containers-tests/tests/intmap-properties.hs +++ b/containers-tests/tests/intmap-properties.hs @@ -18,7 +18,7 @@ import Control.Monad ((<=<)) import qualified Data.Either as Either import qualified Data.Foldable as Foldable import Data.Monoid -import Data.Maybe hiding (mapMaybe) +import Data.Maybe hiding (catMaybes, mapMaybe) import qualified Data.Maybe as Maybe (mapMaybe) import Data.Ord import Data.Foldable (foldMap) @@ -110,6 +110,7 @@ main = defaultMain $ testGroup "intmap-properties" , testCase "filterWithKey" test_filterWithKey , testCase "partition" test_partition , testCase "partitionWithKey" test_partitionWithKey + , testCase "catMaybes" test_catMaybes , testCase "mapMaybe" test_mapMaybe , testCase "mapMaybeWithKey" test_mapMaybeWithKey , testCase "mapEither" test_mapEither @@ -189,6 +190,8 @@ main = defaultMain $ testGroup "intmap-properties" , testProperty "filterKeys" prop_filterKeys , testProperty "filterWithKey" prop_filterWithKey , testProperty "partition" prop_partition + , testProperty "catMaybes" prop_catMaybes + , testProperty "mapMaybe" prop_mapMaybe , testProperty "takeWhileAntitone" prop_takeWhileAntitone , testProperty "dropWhileAntitone" prop_dropWhileAntitone , testProperty "spanAntitone" prop_spanAntitone @@ -940,6 +943,10 @@ test_partitionWithKey = do partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (-3,"b")]) @?= (fromList [(-3, "b"), (5, "a")], empty) partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (-3,"b")]) @?= (empty, fromList [(-3, "b"), (5, "a")]) +test_catMaybes :: Assertion +test_catMaybes = do + catMaybes (fromList [(5,Just "a"), (3,Nothing)]) @?= singleton 5 "a" + test_mapMaybe :: Assertion test_mapMaybe = do mapMaybe f (fromList [(5,"a"), (3,"b")]) @?= singleton 5 "new a" @@ -1552,6 +1559,20 @@ prop_filterWithKey fun m = where m' = filterWithKey (applyFun2 fun) m +prop_catMaybes :: IntMap (Maybe A) -> Property +prop_catMaybes m = + valid m' .&&. + toList m' === Maybe.mapMaybe (\(k,x) -> (,) k <$> x) (toList m) + where + m' = catMaybes m + +prop_mapMaybe :: Fun Int (Maybe Bool) -> IMap -> Property +prop_mapMaybe f m = + valid m' .&&. + toList m' === Maybe.mapMaybe (\(k,x) -> (,) k <$> applyFun f x) (toList m) + where + m' = mapMaybe (applyFun f) m + prop_partition :: Fun Int Bool -> [(Int, Int)] -> Property prop_partition p ys = length ys > 0 ==> let xs = List.nubBy ((==) `on` fst) ys diff --git a/containers-tests/tests/intmap-strictness.hs b/containers-tests/tests/intmap-strictness.hs index 90a189c8e..2a557f740 100644 --- a/containers-tests/tests/intmap-strictness.hs +++ b/containers-tests/tests/intmap-strictness.hs @@ -618,6 +618,12 @@ prop_lazyMapKeysWith fun kfun m = isNotBottomProp (L.mapKeysWith f kf m) f = coerce (applyFunc2 fun) :: A -> A -> A kf = applyFunc kfun +prop_strictCatMaybes :: IntMap (Maybe (Bot A)) -> Property +prop_strictCatMaybes m = isBottom (M.catMaybes m) === isBottom (M.mapMaybe id m) + +prop_lazyCatMaybes :: IntMap (Maybe (Bot A)) -> Property +prop_lazyCatMaybes m = isNotBottomProp (L.catMaybes m) + prop_strictMapMaybe :: Func A (Maybe (Bot B)) -> IntMap A -> Property prop_strictMapMaybe fun m = isBottom (M.mapMaybe f m) === isBottom (M.mapMaybeWithKey (const f) m) @@ -1050,6 +1056,7 @@ tests = , testPropStrictLazy "mapAccumWithKey" prop_strictMapAccumWithKey prop_lazyMapAccumWithKey , testPropStrictLazy "mapAccumRWithKey" prop_strictMapAccumRWithKey prop_lazyMapAccumRWithKey , testPropStrictLazy "mapKeysWith" prop_strictMapKeysWith prop_lazyMapKeysWith + , testPropStrictLazy "catMaybes" prop_strictCatMaybes prop_lazyCatMaybes , testPropStrictLazy "mapMaybe" prop_strictMapMaybe prop_lazyMapMaybe , testPropStrictLazy "mapMaybeWithKey" prop_strictMapMaybeWithKey prop_lazyMapMaybeWithKey , testPropStrictLazy "mapEither" prop_strictMapEither prop_lazyMapEither diff --git a/containers/src/Data/IntMap/Internal.hs b/containers/src/Data/IntMap/Internal.hs index 6cd047625..e4368cc3f 100644 --- a/containers/src/Data/IntMap/Internal.hs +++ b/containers/src/Data/IntMap/Internal.hs @@ -250,6 +250,7 @@ module Data.IntMap.Internal ( , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -2877,6 +2878,15 @@ spanAntitone predicate t = | otherwise = (Nil :*: t') go _ Nil = (Nil :*: Nil) +-- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. +-- +-- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" +-- +-- @since FIXME + +catMaybes :: IntMap (Maybe a) -> IntMap a +catMaybes = mapMaybe id + -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing diff --git a/containers/src/Data/IntMap/Lazy.hs b/containers/src/Data/IntMap/Lazy.hs index e6be3148e..cead95b81 100644 --- a/containers/src/Data/IntMap/Lazy.hs +++ b/containers/src/Data/IntMap/Lazy.hs @@ -234,6 +234,7 @@ module Data.IntMap.Lazy ( , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/IntMap/Strict.hs b/containers/src/Data/IntMap/Strict.hs index 91c083152..45b3c6329 100644 --- a/containers/src/Data/IntMap/Strict.hs +++ b/containers/src/Data/IntMap/Strict.hs @@ -252,6 +252,7 @@ module Data.IntMap.Strict ( , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/IntMap/Strict/Internal.hs b/containers/src/Data/IntMap/Strict/Internal.hs index 85dd7d63f..c5df91f3c 100644 --- a/containers/src/Data/IntMap/Strict/Internal.hs +++ b/containers/src/Data/IntMap/Strict/Internal.hs @@ -195,6 +195,7 @@ module Data.IntMap.Strict.Internal ( , dropWhileAntitone , spanAntitone + , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -989,6 +990,15 @@ mapKeysWith c f t = {-------------------------------------------------------------------- Filter --------------------------------------------------------------------} +-- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. +-- +-- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" +-- +-- @since FIXME + +catMaybes :: IntMap (Maybe a) -> IntMap a +catMaybes = mapMaybe id + -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing From 98ea59e234d8a67817e01580b436b1ff2560c7b1 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Tue, 9 Sep 2025 20:53:14 +0100 Subject: [PATCH 06/11] Update changelog. --- containers/changelog.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/containers/changelog.md b/containers/changelog.md index 1e3632985..0445f51c4 100644 --- a/containers/changelog.md +++ b/containers/changelog.md @@ -7,6 +7,10 @@ * Add `compareSize` for `IntSet` and `IntMap`. (Soumik Sarkar) ([#1135](https://github.com/haskell/containers/pull/1135)) +* Add `catMaybes` for `Seq`, `Set`, `Map` and `IntMap`; and `mapMaybe` for + `Seq`, `Set` and `IntSet`. (Phil Hazelden) + ([#1159](https://github.com/haskell/containers/pull/1159) + ### Performance improvements * Improved performance for `Data.IntMap.restrictKeys` and From 2ada724e92d7677ba28bb393463e7f5dae03445a Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Tue, 16 Sep 2025 23:30:59 +0100 Subject: [PATCH 07/11] Update comments. --- containers/src/Data/IntSet/Internal.hs | 2 +- containers/src/Data/Sequence/Internal.hs | 4 ++-- containers/src/Data/Set/Internal.hs | 5 +++-- 3 files changed, 6 insertions(+), 5 deletions(-) diff --git a/containers/src/Data/IntSet/Internal.hs b/containers/src/Data/IntSet/Internal.hs index 324076cf6..bfa2b7083 100644 --- a/containers/src/Data/IntSet/Internal.hs +++ b/containers/src/Data/IntSet/Internal.hs @@ -882,7 +882,7 @@ filter predicate t | otherwise = bm {-# INLINE bitPred #-} --- | \( O(n \log n) \). Map values and collect the 'Just' results. +-- | \(O(n \min(n,W))\). Map elements and collect the 'Just' results. -- -- If the function is monotonically non-decreasing or monotonically -- non-increasing, 'mapMaybe' takes \(O(n)\) time. diff --git a/containers/src/Data/Sequence/Internal.hs b/containers/src/Data/Sequence/Internal.hs index 27d8aa33d..dd60f0057 100644 --- a/containers/src/Data/Sequence/Internal.hs +++ b/containers/src/Data/Sequence/Internal.hs @@ -4202,13 +4202,13 @@ filter :: (a -> Bool) -> Seq a -> Seq a filter p = foldl' (\ xs x -> if p x then xs `snoc'` x else xs) empty -- | \( O(n) \). Take a sequence of 'Maybe's and return a sequence of all the --- 'Just' values. +-- 'Just' elements. -- -- @since FIXME catMaybes :: Seq (Maybe a) -> Seq a catMaybes = mapMaybe id --- | \( O(n) \). Map values and collect the 'Just' results. +-- | \( O(n) \). Map elements and collect the 'Just' results. -- -- @since FIXME mapMaybe :: (a -> Maybe b) -> Seq a -> Seq b diff --git a/containers/src/Data/Set/Internal.hs b/containers/src/Data/Set/Internal.hs index e6f7ee028..d71cad0e6 100644 --- a/containers/src/Data/Set/Internal.hs +++ b/containers/src/Data/Set/Internal.hs @@ -1000,13 +1000,14 @@ partition p0 t0 = toPair $ go p0 t0 Maybes --------------------------------------------------------------------} --- | \(O(n)\). Drop 'Nothing' if it's in the set, and retain the 'Just' values. +-- | \(O(n)\). Drop 'Nothing' if it's in the set, and retain the 'Just' +-- elements. -- -- @since FIXME catMaybes :: Set (Maybe a) -> Set a catMaybes = mapMonotonic Maybe.fromJust . dropWhileAntitone Maybe.isNothing --- | \(O(n \log n)\). Map values and collect the 'Just' results. +-- | \(O(n \log n)\). Map elements and collect the 'Just' results. -- -- If the function is monotonically non-decreasing, this function takes \(O(n)\) -- time. From 27a48b9e34363bf1b34c6e293da77f5e7dbfd719 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Mon, 22 Sep 2025 08:52:02 +0100 Subject: [PATCH 08/11] Use an arbitrary Fun for mapMaybe property tests. --- containers-tests/tests/intset-properties.hs | 10 +++++----- containers-tests/tests/seq-properties.hs | 7 +++---- containers-tests/tests/set-properties.hs | 8 +++++--- 3 files changed, 13 insertions(+), 12 deletions(-) diff --git a/containers-tests/tests/intset-properties.hs b/containers-tests/tests/intset-properties.hs index e218fbdf1..d889976e1 100644 --- a/containers-tests/tests/intset-properties.hs +++ b/containers-tests/tests/intset-properties.hs @@ -459,11 +459,11 @@ prop_filter s i = valid evens .&&. parts === (odds, evens) -prop_mapMaybe :: IntSet -> Property -prop_mapMaybe s = - let f n = if odd n then Just n else Nothing - odds = mapMaybe f s - in valid odds .&&. toList odds === Maybe.mapMaybe f (toList s) +prop_mapMaybe :: Fun Int (Maybe Int) -> IntSet -> Property +prop_mapMaybe f s = + let mapped = mapMaybe (applyFun f) s + in valid mapped .&&. + mapped === fromList (Maybe.mapMaybe (applyFun f) $ toList s) prop_takeWhileAntitone :: Int -> [Int] -> Property prop_takeWhileAntitone x ys = diff --git a/containers-tests/tests/seq-properties.hs b/containers-tests/tests/seq-properties.hs index a8b18d576..cbc172c89 100644 --- a/containers-tests/tests/seq-properties.hs +++ b/containers-tests/tests/seq-properties.hs @@ -560,10 +560,9 @@ prop_catMaybes :: Seq (Maybe Int) -> Bool prop_catMaybes xs = toList' (catMaybes xs) ~= Maybe.catMaybes (toList xs) -prop_mapMaybe :: Positive Int -> Seq Int -> Bool -prop_mapMaybe (Positive n) xs = - toList' (mapMaybe f xs) ~= Maybe.mapMaybe f (toList xs) - where f x = if x `mod` n == 0 then Just x else Nothing +prop_mapMaybe :: Fun Int (Maybe Int) -> Seq Int -> Bool +prop_mapMaybe f xs = + toList' (mapMaybe (applyFun f) xs) ~= Maybe.mapMaybe (applyFun f) (toList xs) -- * Sorting diff --git a/containers-tests/tests/set-properties.hs b/containers-tests/tests/set-properties.hs index 7f96ff399..abf569b4b 100644 --- a/containers-tests/tests/set-properties.hs +++ b/containers-tests/tests/set-properties.hs @@ -651,9 +651,11 @@ prop_catMaybes :: MaybeIntSet -> Bool prop_catMaybes (MaybeIntSet s) = toList (catMaybes s) == Maybe.catMaybes (toList s) -prop_mapMaybe :: Set Int -> Bool -prop_mapMaybe s = toList (mapMaybe f s) == Maybe.mapMaybe f (toList s) - where f n = if odd n then Just n else Nothing +prop_mapMaybe :: Fun Int (Maybe Int) -> Set Int -> Property +prop_mapMaybe f s = + let mapped = mapMaybe (applyFun f) s + in valid mapped .&&. + mapped === fromList (Maybe.mapMaybe (applyFun f) $ toList s) prop_take :: Int -> Set Int -> Property prop_take n xs = valid taken .&&. From af0b16962b7a018341c5cb12ab4eabf35248172a Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Tue, 23 Sep 2025 00:23:16 +0100 Subject: [PATCH 09/11] Better mapMaybe for Set. --- containers/src/Data/Set/Internal.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/containers/src/Data/Set/Internal.hs b/containers/src/Data/Set/Internal.hs index d71cad0e6..c8036e306 100644 --- a/containers/src/Data/Set/Internal.hs +++ b/containers/src/Data/Set/Internal.hs @@ -1014,7 +1014,11 @@ catMaybes = mapMonotonic Maybe.fromJust . dropWhileAntitone Maybe.isNothing -- -- @since FIXME mapMaybe :: Ord b => (a -> Maybe b) -> Set a -> Set b -mapMaybe f = fromList . Maybe.mapMaybe f . toList +mapMaybe f t = finishB (foldl' go emptyB t) + where go b x = case f x of + Nothing -> b + Just x' -> insertB x' b +{-# INLINABLE mapMaybe #-} {---------------------------------------------------------------------- Map From 763ba83af5e3abc9a3eed370a96038bc8c9ec702 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Tue, 23 Sep 2025 23:06:00 +0100 Subject: [PATCH 10/11] Remove `catMaybes`. --- containers-tests/tests/intmap-properties.hs | 15 +-------------- containers-tests/tests/intmap-strictness.hs | 7 ------- containers-tests/tests/map-properties.hs | 14 +------------- containers-tests/tests/map-strictness.hs | 7 ------- containers-tests/tests/seq-properties.hs | 5 ----- containers-tests/tests/set-properties.hs | 5 ----- containers/changelog.md | 3 +-- containers/src/Data/IntMap/Internal.hs | 10 ---------- containers/src/Data/IntMap/Lazy.hs | 1 - containers/src/Data/IntMap/Strict.hs | 1 - containers/src/Data/IntMap/Strict/Internal.hs | 9 --------- containers/src/Data/Map/Internal.hs | 10 ---------- containers/src/Data/Map/Lazy.hs | 1 - containers/src/Data/Map/Strict.hs | 1 - containers/src/Data/Map/Strict/Internal.hs | 10 ---------- containers/src/Data/Sequence.hs | 1 - containers/src/Data/Sequence/Internal.hs | 8 -------- containers/src/Data/Set.hs | 1 - containers/src/Data/Set/Internal.hs | 9 --------- 19 files changed, 3 insertions(+), 115 deletions(-) diff --git a/containers-tests/tests/intmap-properties.hs b/containers-tests/tests/intmap-properties.hs index bed771ee9..613ed1eb2 100644 --- a/containers-tests/tests/intmap-properties.hs +++ b/containers-tests/tests/intmap-properties.hs @@ -18,7 +18,7 @@ import Control.Monad ((<=<)) import qualified Data.Either as Either import qualified Data.Foldable as Foldable import Data.Monoid -import Data.Maybe hiding (catMaybes, mapMaybe) +import Data.Maybe hiding (mapMaybe) import qualified Data.Maybe as Maybe (mapMaybe) import Data.Ord import Data.Foldable (foldMap) @@ -110,7 +110,6 @@ main = defaultMain $ testGroup "intmap-properties" , testCase "filterWithKey" test_filterWithKey , testCase "partition" test_partition , testCase "partitionWithKey" test_partitionWithKey - , testCase "catMaybes" test_catMaybes , testCase "mapMaybe" test_mapMaybe , testCase "mapMaybeWithKey" test_mapMaybeWithKey , testCase "mapEither" test_mapEither @@ -190,7 +189,6 @@ main = defaultMain $ testGroup "intmap-properties" , testProperty "filterKeys" prop_filterKeys , testProperty "filterWithKey" prop_filterWithKey , testProperty "partition" prop_partition - , testProperty "catMaybes" prop_catMaybes , testProperty "mapMaybe" prop_mapMaybe , testProperty "takeWhileAntitone" prop_takeWhileAntitone , testProperty "dropWhileAntitone" prop_dropWhileAntitone @@ -943,10 +941,6 @@ test_partitionWithKey = do partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (-3,"b")]) @?= (fromList [(-3, "b"), (5, "a")], empty) partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (-3,"b")]) @?= (empty, fromList [(-3, "b"), (5, "a")]) -test_catMaybes :: Assertion -test_catMaybes = do - catMaybes (fromList [(5,Just "a"), (3,Nothing)]) @?= singleton 5 "a" - test_mapMaybe :: Assertion test_mapMaybe = do mapMaybe f (fromList [(5,"a"), (3,"b")]) @?= singleton 5 "new a" @@ -1559,13 +1553,6 @@ prop_filterWithKey fun m = where m' = filterWithKey (applyFun2 fun) m -prop_catMaybes :: IntMap (Maybe A) -> Property -prop_catMaybes m = - valid m' .&&. - toList m' === Maybe.mapMaybe (\(k,x) -> (,) k <$> x) (toList m) - where - m' = catMaybes m - prop_mapMaybe :: Fun Int (Maybe Bool) -> IMap -> Property prop_mapMaybe f m = valid m' .&&. diff --git a/containers-tests/tests/intmap-strictness.hs b/containers-tests/tests/intmap-strictness.hs index 2a557f740..90a189c8e 100644 --- a/containers-tests/tests/intmap-strictness.hs +++ b/containers-tests/tests/intmap-strictness.hs @@ -618,12 +618,6 @@ prop_lazyMapKeysWith fun kfun m = isNotBottomProp (L.mapKeysWith f kf m) f = coerce (applyFunc2 fun) :: A -> A -> A kf = applyFunc kfun -prop_strictCatMaybes :: IntMap (Maybe (Bot A)) -> Property -prop_strictCatMaybes m = isBottom (M.catMaybes m) === isBottom (M.mapMaybe id m) - -prop_lazyCatMaybes :: IntMap (Maybe (Bot A)) -> Property -prop_lazyCatMaybes m = isNotBottomProp (L.catMaybes m) - prop_strictMapMaybe :: Func A (Maybe (Bot B)) -> IntMap A -> Property prop_strictMapMaybe fun m = isBottom (M.mapMaybe f m) === isBottom (M.mapMaybeWithKey (const f) m) @@ -1056,7 +1050,6 @@ tests = , testPropStrictLazy "mapAccumWithKey" prop_strictMapAccumWithKey prop_lazyMapAccumWithKey , testPropStrictLazy "mapAccumRWithKey" prop_strictMapAccumRWithKey prop_lazyMapAccumRWithKey , testPropStrictLazy "mapKeysWith" prop_strictMapKeysWith prop_lazyMapKeysWith - , testPropStrictLazy "catMaybes" prop_strictCatMaybes prop_lazyCatMaybes , testPropStrictLazy "mapMaybe" prop_strictMapMaybe prop_lazyMapMaybe , testPropStrictLazy "mapMaybeWithKey" prop_strictMapMaybeWithKey prop_lazyMapMaybeWithKey , testPropStrictLazy "mapEither" prop_strictMapEither prop_lazyMapEither diff --git a/containers-tests/tests/map-properties.hs b/containers-tests/tests/map-properties.hs index a86188a2e..a585391c4 100644 --- a/containers-tests/tests/map-properties.hs +++ b/containers-tests/tests/map-properties.hs @@ -18,7 +18,7 @@ import Control.Monad ((<=<)) import qualified Data.Either as Either import Data.Functor.Identity (Identity(Identity, runIdentity)) import Data.Monoid -import Data.Maybe hiding (catMaybes, mapMaybe) +import Data.Maybe hiding (mapMaybe) import qualified Data.Maybe as Maybe (mapMaybe) import Data.Ord import Data.Semigroup (Arg(..)) @@ -124,7 +124,6 @@ main = defaultMain $ testGroup "map-properties" , testCase "filterWithKey" test_filterWithKey , testCase "partition" test_partition , testCase "partitionWithKey" test_partitionWithKey - , testCase "catMaybes" test_catMaybes , testCase "mapMaybe" test_mapMaybe , testCase "mapMaybeWithKey" test_mapMaybeWithKey , testCase "mapEither" test_mapEither @@ -297,7 +296,6 @@ main = defaultMain $ testGroup "map-properties" , testProperty "differenceWith" prop_differenceWith , testProperty "differenceWithKey" prop_differenceWithKey , testProperty "partitionWithKey" prop_partitionWithKey - , testProperty "catMaybes" prop_catMaybes , testProperty "mapMaybe" prop_mapMaybe , testProperty "mapMaybeWithKey" prop_mapMaybeWithKey , testProperty "traverseMaybeWithKey" prop_traverseMaybeWithKey @@ -864,9 +862,6 @@ test_partitionWithKey = do partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) @?= (fromList [(3, "b"), (5, "a")], empty) partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) @?= (empty, fromList [(3, "b"), (5, "a")]) -test_catMaybes :: Assertion -test_catMaybes = catMaybes (fromList [(5,Just "a"), (3,Nothing)]) @?= singleton 5 "a" - test_mapMaybe :: Assertion test_mapMaybe = mapMaybe f (fromList [(5,"a"), (3,"b")]) @?= singleton 5 "new a" where @@ -1965,13 +1960,6 @@ prop_partitionWithKey f m = where (m1, m2) = partitionWithKey (applyFun2 f) m -prop_catMaybes :: Map Int (Maybe A) -> Property -prop_catMaybes m = - valid m' .&&. - toList m' === Maybe.mapMaybe (\(k,x) -> (,) k <$> x) (toList m) - where - m' = catMaybes m - prop_mapMaybe :: Fun A (Maybe B) -> Map Int A -> Property prop_mapMaybe f m = valid m' .&&. diff --git a/containers-tests/tests/map-strictness.hs b/containers-tests/tests/map-strictness.hs index 3107936a4..f6e4630c8 100644 --- a/containers-tests/tests/map-strictness.hs +++ b/containers-tests/tests/map-strictness.hs @@ -755,12 +755,6 @@ prop_lazyMapKeysWith fun kfun m = isNotBottomProp (L.mapKeysWith f kf m) f = coerce (applyFunc2 fun) :: A -> A -> A kf = applyFunc kfun -prop_strictCatMaybes :: Map OrdA (Maybe (Bot A)) -> Property -prop_strictCatMaybes m = isBottom (M.catMaybes m) === isBottom (M.mapMaybe id m) - -prop_lazyCatMaybes :: Map OrdA (Maybe (Bot A)) -> Property -prop_lazyCatMaybes m = isNotBottomProp (L.catMaybes m) - prop_strictMapMaybe :: Func A (Maybe (Bot B)) -> Map OrdA A -> Property prop_strictMapMaybe fun m = isBottom (M.mapMaybe f m) === isBottom (M.mapMaybeWithKey (const f) m) @@ -1199,7 +1193,6 @@ tests = , testPropStrictLazy "mapAccumWithKey" prop_strictMapAccumWithKey prop_lazyMapAccumWithKey , testPropStrictLazy "mapAccumRWithKey" prop_strictMapAccumRWithKey prop_lazyMapAccumRWithKey , testPropStrictLazy "mapKeysWith" prop_strictMapKeysWith prop_lazyMapKeysWith - , testPropStrictLazy "catMaybes" prop_strictCatMaybes prop_lazyCatMaybes , testPropStrictLazy "mapMaybe" prop_strictMapMaybe prop_lazyMapMaybe , testPropStrictLazy "mapMaybeWithKey" prop_strictMapMaybeWithKey prop_lazyMapMaybeWithKey , testPropStrictLazy "mapEither" prop_strictMapEither prop_lazyMapEither diff --git a/containers-tests/tests/seq-properties.hs b/containers-tests/tests/seq-properties.hs index cbc172c89..a3db6bca1 100644 --- a/containers-tests/tests/seq-properties.hs +++ b/containers-tests/tests/seq-properties.hs @@ -101,7 +101,6 @@ main = defaultMain $ testGroup "seq-properties" , testProperty "breakr" prop_breakr , testProperty "partition" prop_partition , testProperty "filter" prop_filter - , testProperty "catMaybes" prop_catMaybes , testProperty "mapMaybe" prop_mapMaybe , testProperty "sort" prop_sort , testProperty "sortStable" prop_sortStable @@ -556,10 +555,6 @@ prop_filter (Positive n) xs = toList' (filter p xs) ~= Prelude.filter p (toList xs) where p x = x `mod` n == 0 -prop_catMaybes :: Seq (Maybe Int) -> Bool -prop_catMaybes xs = - toList' (catMaybes xs) ~= Maybe.catMaybes (toList xs) - prop_mapMaybe :: Fun Int (Maybe Int) -> Seq Int -> Bool prop_mapMaybe f xs = toList' (mapMaybe (applyFun f) xs) ~= Maybe.mapMaybe (applyFun f) (toList xs) diff --git a/containers-tests/tests/set-properties.hs b/containers-tests/tests/set-properties.hs index abf569b4b..0127aba59 100644 --- a/containers-tests/tests/set-properties.hs +++ b/containers-tests/tests/set-properties.hs @@ -99,7 +99,6 @@ main = defaultMain $ testGroup "set-properties" , testProperty "prop_splitRoot" prop_splitRoot , testProperty "prop_partition" prop_partition , testProperty "prop_filter" prop_filter - , testProperty "prop_catMaybes" prop_catMaybes , testProperty "prop_mapMaybe" prop_mapMaybe , testProperty "takeWhileAntitone" prop_takeWhileAntitone , testProperty "dropWhileAntitone" prop_dropWhileAntitone @@ -647,10 +646,6 @@ prop_partition s i = case partition odd s of prop_filter :: Set Int -> Int -> Bool prop_filter s i = partition odd s == (filter odd s, filter even s) -prop_catMaybes :: MaybeIntSet -> Bool -prop_catMaybes (MaybeIntSet s) = - toList (catMaybes s) == Maybe.catMaybes (toList s) - prop_mapMaybe :: Fun Int (Maybe Int) -> Set Int -> Property prop_mapMaybe f s = let mapped = mapMaybe (applyFun f) s diff --git a/containers/changelog.md b/containers/changelog.md index 0445f51c4..8f53bbbce 100644 --- a/containers/changelog.md +++ b/containers/changelog.md @@ -7,8 +7,7 @@ * Add `compareSize` for `IntSet` and `IntMap`. (Soumik Sarkar) ([#1135](https://github.com/haskell/containers/pull/1135)) -* Add `catMaybes` for `Seq`, `Set`, `Map` and `IntMap`; and `mapMaybe` for - `Seq`, `Set` and `IntSet`. (Phil Hazelden) +* Add `mapMaybe` for `Seq`, `Set` and `IntSet`. (Phil Hazelden) ([#1159](https://github.com/haskell/containers/pull/1159) ### Performance improvements diff --git a/containers/src/Data/IntMap/Internal.hs b/containers/src/Data/IntMap/Internal.hs index e4368cc3f..6cd047625 100644 --- a/containers/src/Data/IntMap/Internal.hs +++ b/containers/src/Data/IntMap/Internal.hs @@ -250,7 +250,6 @@ module Data.IntMap.Internal ( , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -2878,15 +2877,6 @@ spanAntitone predicate t = | otherwise = (Nil :*: t') go _ Nil = (Nil :*: Nil) --- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. --- --- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" --- --- @since FIXME - -catMaybes :: IntMap (Maybe a) -> IntMap a -catMaybes = mapMaybe id - -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing diff --git a/containers/src/Data/IntMap/Lazy.hs b/containers/src/Data/IntMap/Lazy.hs index cead95b81..e6be3148e 100644 --- a/containers/src/Data/IntMap/Lazy.hs +++ b/containers/src/Data/IntMap/Lazy.hs @@ -234,7 +234,6 @@ module Data.IntMap.Lazy ( , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/IntMap/Strict.hs b/containers/src/Data/IntMap/Strict.hs index 45b3c6329..91c083152 100644 --- a/containers/src/Data/IntMap/Strict.hs +++ b/containers/src/Data/IntMap/Strict.hs @@ -252,7 +252,6 @@ module Data.IntMap.Strict ( , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/IntMap/Strict/Internal.hs b/containers/src/Data/IntMap/Strict/Internal.hs index c5df91f3c..49d8b331f 100644 --- a/containers/src/Data/IntMap/Strict/Internal.hs +++ b/containers/src/Data/IntMap/Strict/Internal.hs @@ -195,7 +195,6 @@ module Data.IntMap.Strict.Internal ( , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -990,14 +989,6 @@ mapKeysWith c f t = {-------------------------------------------------------------------- Filter --------------------------------------------------------------------} --- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. --- --- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" --- --- @since FIXME - -catMaybes :: IntMap (Maybe a) -> IntMap a -catMaybes = mapMaybe id -- | \(O(n)\). Map values and collect the 'Just' results. -- diff --git a/containers/src/Data/Map/Internal.hs b/containers/src/Data/Map/Internal.hs index 5a5da2a32..40181416f 100644 --- a/containers/src/Data/Map/Internal.hs +++ b/containers/src/Data/Map/Internal.hs @@ -304,7 +304,6 @@ module Data.Map.Internal ( , partition , partitionWithKey - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -3115,15 +3114,6 @@ partitionWithKey p0 t0 = toPair $ go p0 t0 (l1 :*: l2) = go p l (r1 :*: r2) = go p r --- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. --- --- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" --- --- @since FIXME - -catMaybes :: Map k (Maybe a) -> Map k a -catMaybes = mapMaybe id - -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing diff --git a/containers/src/Data/Map/Lazy.hs b/containers/src/Data/Map/Lazy.hs index 408467410..56ca3c536 100644 --- a/containers/src/Data/Map/Lazy.hs +++ b/containers/src/Data/Map/Lazy.hs @@ -247,7 +247,6 @@ module Data.Map.Lazy ( , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/Map/Strict.hs b/containers/src/Data/Map/Strict.hs index 4ff221893..de0fb18c4 100644 --- a/containers/src/Data/Map/Strict.hs +++ b/containers/src/Data/Map/Strict.hs @@ -262,7 +262,6 @@ module Data.Map.Strict , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither diff --git a/containers/src/Data/Map/Strict/Internal.hs b/containers/src/Data/Map/Strict/Internal.hs index 7c60eb8f8..d70977e38 100644 --- a/containers/src/Data/Map/Strict/Internal.hs +++ b/containers/src/Data/Map/Strict/Internal.hs @@ -246,7 +246,6 @@ module Data.Map.Strict.Internal , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , mapMaybeWithKey , mapEither @@ -1247,15 +1246,6 @@ mergeWithKey f g1 g2 = go Filter and partition --------------------------------------------------------------------} --- | \(O(n)\). Remove 'Nothing's and retain the 'Just' values. --- --- > catMaybes (fromList [(5,Just "a"), (3,Nothing)]) == singleton 5 "a" --- --- @since FIXME - -catMaybes :: Map k (Maybe a) -> Map k a -catMaybes = mapMaybe id - -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing diff --git a/containers/src/Data/Sequence.hs b/containers/src/Data/Sequence.hs index ea23f29b6..0adaeb2e0 100644 --- a/containers/src/Data/Sequence.hs +++ b/containers/src/Data/Sequence.hs @@ -192,7 +192,6 @@ module Data.Sequence ( breakr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) partition, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) filter, -- :: (a -> Bool) -> Seq a -> Seq a - catMaybes, -- :: Seq (Maybe a) -> Seq a mapMaybe, -- :: (a -> Maybe b) -> Seq a -> Seq b -- * Sorting sort, -- :: Ord a => Seq a -> Seq a diff --git a/containers/src/Data/Sequence/Internal.hs b/containers/src/Data/Sequence/Internal.hs index dd60f0057..59e13e84e 100644 --- a/containers/src/Data/Sequence/Internal.hs +++ b/containers/src/Data/Sequence/Internal.hs @@ -128,7 +128,6 @@ module Data.Sequence.Internal ( breakr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) partition, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) filter, -- :: (a -> Bool) -> Seq a -> Seq a - catMaybes, -- :: Seq (Maybe a) -> Seq a mapMaybe, -- :: (a -> Maybe b) -> Seq a -> Seq b -- * Indexing lookup, -- :: Int -> Seq a -> Maybe a @@ -4201,13 +4200,6 @@ partition p = toPair . foldl' part (empty :*: empty) filter :: (a -> Bool) -> Seq a -> Seq a filter p = foldl' (\ xs x -> if p x then xs `snoc'` x else xs) empty --- | \( O(n) \). Take a sequence of 'Maybe's and return a sequence of all the --- 'Just' elements. --- --- @since FIXME -catMaybes :: Seq (Maybe a) -> Seq a -catMaybes = mapMaybe id - -- | \( O(n) \). Map elements and collect the 'Just' results. -- -- @since FIXME diff --git a/containers/src/Data/Set.hs b/containers/src/Data/Set.hs index dc1f9d203..096420907 100644 --- a/containers/src/Data/Set.hs +++ b/containers/src/Data/Set.hs @@ -137,7 +137,6 @@ module Data.Set ( , takeWhileAntitone , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , partition , split diff --git a/containers/src/Data/Set/Internal.hs b/containers/src/Data/Set/Internal.hs index c8036e306..0af7eb150 100644 --- a/containers/src/Data/Set/Internal.hs +++ b/containers/src/Data/Set/Internal.hs @@ -162,7 +162,6 @@ module Data.Set.Internal ( , takeWhileAntitone , dropWhileAntitone , spanAntitone - , catMaybes , mapMaybe , partition , split @@ -241,7 +240,6 @@ import Data.Functor.Identity (Identity) import qualified Data.Foldable as Foldable import Control.DeepSeq (NFData(rnf),NFData1(liftRnf)) import Data.List.NonEmpty (NonEmpty(..)) -import qualified Data.Maybe as Maybe import Utils.Containers.Internal.StrictPair import Utils.Containers.Internal.PtrEquality @@ -1000,13 +998,6 @@ partition p0 t0 = toPair $ go p0 t0 Maybes --------------------------------------------------------------------} --- | \(O(n)\). Drop 'Nothing' if it's in the set, and retain the 'Just' --- elements. --- --- @since FIXME -catMaybes :: Set (Maybe a) -> Set a -catMaybes = mapMonotonic Maybe.fromJust . dropWhileAntitone Maybe.isNothing - -- | \(O(n \log n)\). Map elements and collect the 'Just' results. -- -- If the function is monotonically non-decreasing, this function takes \(O(n)\) From c311f3160d2ef8012e5c4d4034116a4f37d6a833 Mon Sep 17 00:00:00 2001 From: Phil Hazelden Date: Mon, 13 Oct 2025 08:58:20 +0100 Subject: [PATCH 11/11] Revert unnecessary changes. --- containers-tests/tests/set-properties.hs | 26 ------------------- containers/src/Data/IntMap/Strict/Internal.hs | 1 - 2 files changed, 27 deletions(-) diff --git a/containers-tests/tests/set-properties.hs b/containers-tests/tests/set-properties.hs index 0127aba59..29bd94ca8 100644 --- a/containers-tests/tests/set-properties.hs +++ b/containers-tests/tests/set-properties.hs @@ -243,32 +243,6 @@ instance IsInt a => Arbitrary (Set a) where put i' pure (fromInt i') -newtype MaybeIntSet = MaybeIntSet (Set (Maybe Int)) deriving (Show) -instance Arbitrary MaybeIntSet where - arbitrary = sized $ \sz0 -> do - sz <- choose (0, sz0) - middle <- choose (-positionFactor * (sz + 1), positionFactor * (sz + 1)) - let shift = (sz * (gapRange) + 1) `quot` 2 - start = middle - shift - hasNothing <- arbitrary - t <- evalStateT (mkArbSet (step start) sz) - (if hasNothing then Nothing else Just start) - if valid t - then pure $ MaybeIntSet t - else error "Test generated invalid tree!" - where - step start = do - mi <- get - case mi of - Nothing -> do - put $ Just start - pure Nothing - Just i -> do - diff <- lift $ choose (1, gapRange) - let i' = i + diff - put $ Just i' - pure $ Just i' - data TwoSets = TwoSets (Set Int) (Set Int) deriving (Show) data TwoLists a = TwoLists [a] [a] diff --git a/containers/src/Data/IntMap/Strict/Internal.hs b/containers/src/Data/IntMap/Strict/Internal.hs index 49d8b331f..85dd7d63f 100644 --- a/containers/src/Data/IntMap/Strict/Internal.hs +++ b/containers/src/Data/IntMap/Strict/Internal.hs @@ -989,7 +989,6 @@ mapKeysWith c f t = {-------------------------------------------------------------------- Filter --------------------------------------------------------------------} - -- | \(O(n)\). Map values and collect the 'Just' results. -- -- > let f x = if x == "a" then Just "new a" else Nothing