3
3
{-# LANGUAGE PatternGuards #-}
4
4
#if defined(__GLASGOW_HASKELL__)
5
5
{-# LANGUAGE DeriveLift #-}
6
+ {-# LANGUAGE UnboxedTuples #-}
6
7
{-# LANGUAGE RoleAnnotations #-}
7
8
{-# LANGUAGE StandaloneDeriving #-}
8
9
{-# LANGUAGE Trustworthy #-}
@@ -236,7 +237,9 @@ module Data.Map.Internal (
236
237
-- * Traversal
237
238
-- ** Map
238
239
, map
240
+ , mapU
239
241
, mapWithKey
242
+ , mapWithKeyU
240
243
, traverseWithKey
241
244
, traverseMaybeWithKey
242
245
, mapAccum
@@ -301,6 +304,7 @@ module Data.Map.Internal (
301
304
302
305
, mapMaybe
303
306
, mapMaybeWithKey
307
+ , mapMaybeWithKeyU
304
308
, mapEither
305
309
, mapEitherWithKey
306
310
@@ -407,6 +411,8 @@ import Data.Data
407
411
import qualified Control.Category as Category
408
412
import Data.Coerce
409
413
#endif
414
+ import Utils.Containers.Internal.UnboxedMaybe
415
+ import Utils.Containers.Internal.UnboxedSolo
410
416
411
417
412
418
{- -------------------------------------------------------------------
@@ -2849,6 +2855,7 @@ isProperSubmapOfBy f t1 t2
2849
2855
filter :: (a -> Bool ) -> Map k a -> Map k a
2850
2856
filter p m
2851
2857
= filterWithKey (\ _ x -> p x) m
2858
+ {-# INLINE filter #-}
2852
2859
2853
2860
-- | \(O(n)\). Filter all keys\/values that satisfy the predicate.
2854
2861
--
@@ -2863,6 +2870,32 @@ filterWithKey p t@(Bin _ kx x l r)
2863
2870
| otherwise = link2 pl pr
2864
2871
where ! pl = filterWithKey p l
2865
2872
! pr = filterWithKey p r
2873
+ {-# NOINLINE [1] filterWithKey #-}
2874
+
2875
+ {-# RULES
2876
+ "filterWK/filterWK" forall p q m. filterWithKey p (filterWithKey q m) =
2877
+ filterWithKey (\k x -> q k x && p k x) m
2878
+ "filterWK/mapU" forall p f m. filterWithKey p (mapU f m) =
2879
+ mapMaybeWithKeyU (\k x -> case f x of
2880
+ SoloU y
2881
+ | p k y -> JustU y
2882
+ | otherwise -> NothingU) m
2883
+ "filterWK/mapWK#" forall p f m. filterWithKey p (mapWithKeyU f m) =
2884
+ mapMaybeWithKeyU (\k x -> case f k x of
2885
+ SoloU y
2886
+ | p k y -> JustU y
2887
+ | otherwise -> NothingU) m
2888
+ "mapU/filterWK" forall f p m. mapU f (filterWithKey p m) =
2889
+ mapMaybeWithKeyU (\k x ->
2890
+ if p k x
2891
+ then case f x of SoloU y -> JustU y
2892
+ else NothingU) m
2893
+ "mapWK#/filterWK" forall f p m. mapWithKeyU f (filterWithKey p m) =
2894
+ mapMaybeWithKeyU (\k x ->
2895
+ if p k x
2896
+ then case f k x of SoloU y -> JustU y
2897
+ else NothingU) m
2898
+ #-}
2866
2899
2867
2900
-- | \(O(n)\). Filter keys and values using an 'Applicative'
2868
2901
-- predicate.
@@ -2977,17 +3010,54 @@ partitionWithKey p0 t0 = toPair $ go p0 t0
2977
3010
2978
3011
mapMaybe :: (a -> Maybe b ) -> Map k a -> Map k b
2979
3012
mapMaybe f = mapMaybeWithKey (\ _ x -> f x)
3013
+ {-# INLINE mapMaybe #-}
2980
3014
2981
3015
-- | \(O(n)\). Map keys\/values and collect the 'Just' results.
2982
3016
--
2983
3017
-- > let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
2984
3018
-- > mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
2985
3019
2986
3020
mapMaybeWithKey :: (k -> a -> Maybe b ) -> Map k a -> Map k b
2987
- mapMaybeWithKey _ Tip = Tip
2988
- mapMaybeWithKey f (Bin _ kx x l r) = case f kx x of
2989
- Just y -> link kx y (mapMaybeWithKey f l) (mapMaybeWithKey f r)
2990
- Nothing -> link2 (mapMaybeWithKey f l) (mapMaybeWithKey f r)
3021
+ mapMaybeWithKey f = \ m ->
3022
+ mapMaybeWithKeyU (\ k x -> toMaybeU (f k x)) m
3023
+ {-# INLINE mapMaybeWithKey #-}
3024
+
3025
+ mapMaybeWithKeyU :: (k -> a -> MaybeU b ) -> Map k a -> Map k b
3026
+ mapMaybeWithKeyU _ Tip = Tip
3027
+ mapMaybeWithKeyU f (Bin _ kx x l r) = case f kx x of
3028
+ JustU y -> link kx y (mapMaybeWithKeyU f l) (mapMaybeWithKeyU f r)
3029
+ NothingU -> link2 (mapMaybeWithKeyU f l) (mapMaybeWithKeyU f r)
3030
+ {-# NOINLINE [1] mapMaybeWithKeyU #-}
3031
+
3032
+ {-# RULES
3033
+ "mapMaybeWK#/mapU" forall f g m. mapMaybeWithKeyU f (mapU g m) =
3034
+ mapMaybeWithKeyU (\k x -> case g x of SoloU y -> f k y) m
3035
+ "mapU/mapMaybeWK#" forall f g m. mapU f (mapMaybeWithKeyU g m) =
3036
+ mapMaybeWithKeyU
3037
+ (\k x -> case g k x of
3038
+ NothingU -> NothingU
3039
+ JustU y -> case f y of SoloU z -> JustU z) m
3040
+ "mapMaybeWK#/mapWK#" forall f g m. mapMaybeWithKeyU f (mapWithKeyU g m) =
3041
+ mapMaybeWithKeyU (\k x -> case g k x of SoloU y -> f k y) m
3042
+ "mapWK#/mapMaybeWK#" forall f g m. mapWithKeyU f (mapMaybeWithKeyU g m) =
3043
+ mapMaybeWithKeyU
3044
+ (\k x -> case g k x of
3045
+ NothingU -> NothingU
3046
+ JustU y -> case f k y of SoloU z -> JustU z) m
3047
+ "mapMaybeWK#/mapMaybeWK#" forall f g m. mapMaybeWithKeyU f (mapMaybeWithKeyU g m) =
3048
+ mapMaybeWithKeyU
3049
+ (\k x -> case g k x of
3050
+ NothingU -> NothingU
3051
+ JustU y -> f k y) m
3052
+ "mapMaybeWK#/filterWK" forall f p m. mapMaybeWithKeyU f (filterWithKey p m) =
3053
+ mapMaybeWithKeyU (\k x -> if p k x then f k x else NothingU) m
3054
+ "filterWK/mapMaybeWK#" forall p f m. filterWithKey p (mapMaybeWithKeyU f m) =
3055
+ mapMaybeWithKeyU (\k x -> case f k x of
3056
+ NothingU -> NothingU
3057
+ JustU y
3058
+ | p k y -> JustU y
3059
+ | otherwise -> NothingU) m
3060
+ #-}
2991
3061
2992
3062
-- | \(O(n)\). Traverse keys\/values and collect the 'Just' results.
2993
3063
--
@@ -3045,17 +3115,38 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0
3045
3115
-- > map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
3046
3116
3047
3117
map :: (a -> b ) -> Map k a -> Map k b
3048
- map f = go where
3118
+ -- We define map using mapU solely to reduce the number of rewrite
3119
+ -- rules we need.
3120
+ map f = mapU (\ x -> SoloU (f x))
3121
+ -- We delay inlinability of map to support map/coerce. While a
3122
+ -- mapU/coerce rule seems to work when everything is done just so,
3123
+ -- it feels too brittle to me for now (GHC 9.4).
3124
+ #ifdef __GLASGOW_HASKELL__
3125
+ {-# INLINABLE [1] map #-}
3126
+ #endif
3127
+
3128
+ mapU :: (a -> SoloU b ) -> Map k a -> Map k b
3129
+ mapU f = go where
3049
3130
go Tip = Tip
3050
- go (Bin sx kx x l r) = Bin sx kx (f x) (go l) (go r)
3051
- -- We use a `go` function to allow `map` to inline. This makes
3052
- -- a big difference if someone uses `map (const x) m` instead
3053
- -- of `x <$ m`; it doesn't seem to do any harm.
3131
+ go (Bin sx kx x l r)
3132
+ | SoloU y <- f x
3133
+ = Bin sx kx y (go l) (go r)
3134
+ #if defined (__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ >= 806) && (__GLASGOW_HASKELL__ < 810)
3135
+ -- Something goes wrong checking SoloU completeness
3136
+ -- in these versions
3137
+ go _ = error " impossible"
3138
+ #endif
3139
+
3140
+ -- We use a `go` function to allow `mapU` to inline. Without this,
3141
+ -- we'd slow down both strict and lazy map, which wouldn't be great.
3142
+ -- This also lets us avoid a custom implementation of <$
3054
3143
3144
+ -- We don't let mapU inline until phase 0 because we need a step
3145
+ -- after map inlines.
3055
3146
#ifdef __GLASGOW_HASKELL__
3056
- {-# NOINLINE [1] map #-}
3147
+ {-# NOINLINE [0] mapU #-}
3057
3148
{-# RULES
3058
- "map/map " forall f g xs . map f (map g xs) = map (f . g ) xs
3149
+ "mapU/mapU " forall f g xs . mapU f (mapU g xs) = mapU (\x -> case g x of SoloU y -> f y ) xs
3059
3150
"map/coerce" map coerce = coerce
3060
3151
#-}
3061
3152
#endif
@@ -3066,21 +3157,35 @@ map f = go where
3066
3157
-- > mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
3067
3158
3068
3159
mapWithKey :: (k -> a -> b ) -> Map k a -> Map k b
3069
- mapWithKey _ Tip = Tip
3070
- mapWithKey f (Bin sx kx x l r) = Bin sx kx (f kx x) (mapWithKey f l) (mapWithKey f r)
3160
+ mapWithKey f = mapWithKeyU (\ k a -> SoloU (f k a))
3161
+ #ifdef __GLASGOW_HASKELL__
3162
+ {-# INLINABLE mapWithKey #-}
3163
+ #endif
3164
+
3165
+ -- | A version of 'mapWithKey' that takes a function producing a unary
3166
+ -- unboxed tuple.
3167
+ mapWithKeyU :: (k -> a -> SoloU b ) -> Map k a -> Map k b
3168
+ mapWithKeyU f = go where
3169
+ go Tip = Tip
3170
+ go (Bin sx kx x l r)
3171
+ | SoloU y <- f kx x
3172
+ = Bin sx kx y (go l) (go r)
3173
+ #if defined (__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ >= 806) && (__GLASGOW_HASKELL__ < 810)
3174
+ -- Something goes wrong checking SoloU completeness
3175
+ -- in these versions
3176
+ go _ = error " impossible"
3177
+ #endif
3071
3178
3072
3179
#ifdef __GLASGOW_HASKELL__
3073
- {-# NOINLINE [1] mapWithKey #-}
3180
+ {-# NOINLINE [1] mapWithKeyU #-}
3074
3181
{-# RULES
3075
- "mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) =
3076
- mapWithKey (\k a -> f k (g k a)) xs
3077
- "mapWithKey/map" forall f g xs . mapWithKey f (map g xs) =
3078
- mapWithKey (\k a -> f k (g a)) xs
3079
- "map/mapWithKey" forall f g xs . map f (mapWithKey g xs) =
3080
- mapWithKey (\k a -> f (g k a)) xs
3182
+ "mapWK#/mapWK#" forall f g xs. mapWithKeyU f (mapWithKeyU g xs) = mapWithKeyU (\k x -> case g k x of SoloU y -> f k y) xs
3183
+ "mapWK#/mapU" forall f g xs. mapWithKeyU f (mapU g xs) = mapWithKeyU (\k x -> case g x of SoloU y -> f k y) xs
3184
+ "mapU/mapWK#" forall f g xs. mapU f (mapWithKeyU g xs) = mapWithKeyU (\k x -> case g k x of SoloU y -> f y) xs
3081
3185
#-}
3082
3186
#endif
3083
3187
3188
+
3084
3189
-- | \(O(n)\).
3085
3190
-- @'traverseWithKey' f m == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@
3086
3191
-- That is, behaves exactly like a regular 'traverse' except that the traversing
@@ -4195,9 +4300,10 @@ instance (Ord k, Read k) => Read1 (Map k) where
4195
4300
--------------------------------------------------------------------}
4196
4301
instance Functor (Map k ) where
4197
4302
fmap f m = map f m
4303
+ a <$ m = map (const a) m
4198
4304
#ifdef __GLASGOW_HASKELL__
4199
- _ <$ Tip = Tip
4200
- a <$ ( Bin sx kx _ l r) = Bin sx kx a (a <$ l) (a <$ r)
4305
+ {-# INLINABLE fmap #-}
4306
+ {-# INLINABLE (<$) #-}
4201
4307
#endif
4202
4308
4203
4309
-- | Traverses in order of increasing key.
0 commit comments