3
3
{-# LANGUAGE PatternGuards #-}
4
4
#if defined(__GLASGOW_HASKELL__)
5
5
{-# LANGUAGE DeriveLift #-}
6
+ {-# LANGUAGE MagicHash #-}
7
+ {-# LANGUAGE UnboxedTuples #-}
6
8
{-# LANGUAGE RoleAnnotations #-}
7
9
{-# LANGUAGE StandaloneDeriving #-}
8
10
{-# LANGUAGE Trustworthy #-}
9
11
{-# LANGUAGE TypeFamilies #-}
10
12
#endif
11
13
#define USE_MAGIC_PROXY 1
12
14
13
- #ifdef USE_MAGIC_PROXY
14
- {-# LANGUAGE MagicHash #-}
15
- #endif
16
-
17
15
{-# OPTIONS_HADDOCK not-home #-}
18
16
19
17
#include "containers.h"
@@ -236,7 +234,9 @@ module Data.Map.Internal (
236
234
-- * Traversal
237
235
-- ** Map
238
236
, map
237
+ , map #
239
238
, mapWithKey
239
+ , mapWithKey #
240
240
, traverseWithKey
241
241
, traverseMaybeWithKey
242
242
, mapAccum
@@ -301,6 +301,7 @@ module Data.Map.Internal (
301
301
302
302
, mapMaybe
303
303
, mapMaybeWithKey
304
+ , mapMaybeWithKey #
304
305
, mapEither
305
306
, mapEitherWithKey
306
307
@@ -407,6 +408,7 @@ import Data.Data
407
408
import qualified Control.Category as Category
408
409
import Data.Coerce
409
410
#endif
411
+ import Utils.Containers.Internal.UnboxedMaybe
410
412
411
413
412
414
{- -------------------------------------------------------------------
@@ -2849,6 +2851,7 @@ isProperSubmapOfBy f t1 t2
2849
2851
filter :: (a -> Bool ) -> Map k a -> Map k a
2850
2852
filter p m
2851
2853
= filterWithKey (\ _ x -> p x) m
2854
+ {-# INLINE filter #-}
2852
2855
2853
2856
-- | \(O(n)\). Filter all keys\/values that satisfy the predicate.
2854
2857
--
@@ -2863,6 +2866,32 @@ filterWithKey p t@(Bin _ kx x l r)
2863
2866
| otherwise = link2 pl pr
2864
2867
where ! pl = filterWithKey p l
2865
2868
! pr = filterWithKey p r
2869
+ {-# NOINLINE [1] filterWithKey #-}
2870
+
2871
+ {-# RULES
2872
+ "filterWK/filterWK" forall p q m. filterWithKey p (filterWithKey q m) =
2873
+ filterWithKey (\k x -> q k x && p k x) m
2874
+ "filterWK/map#" forall p f m. filterWithKey p (map# f m) =
2875
+ mapMaybeWithKey# (\k x -> case f x of
2876
+ (# y #)
2877
+ | p k y -> Just# y
2878
+ | otherwise -> Nothing#) m
2879
+ "filterWK/mapWK#" forall p f m. filterWithKey p (mapWithKey# f m) =
2880
+ mapMaybeWithKey# (\k x -> case f k x of
2881
+ (# y #)
2882
+ | p k y -> Just# y
2883
+ | otherwise -> Nothing#) m
2884
+ "map#/filterWK" forall f p m. map# f (filterWithKey p m) =
2885
+ mapMaybeWithKey# (\k x ->
2886
+ if p k x
2887
+ then case f x of (# y #) -> Just# y
2888
+ else Nothing#) m
2889
+ "mapWK#/filterWK" forall f p m. mapWithKey# f (filterWithKey p m) =
2890
+ mapMaybeWithKey# (\k x ->
2891
+ if p k x
2892
+ then case f k x of (# y #) -> Just# y
2893
+ else Nothing#) m
2894
+ #-}
2866
2895
2867
2896
-- | \(O(n)\). Filter keys and values using an 'Applicative'
2868
2897
-- predicate.
@@ -2977,17 +3006,60 @@ partitionWithKey p0 t0 = toPair $ go p0 t0
2977
3006
2978
3007
mapMaybe :: (a -> Maybe b ) -> Map k a -> Map k b
2979
3008
mapMaybe f = mapMaybeWithKey (\ _ x -> f x)
3009
+ {-# INLINE mapMaybe #-}
2980
3010
2981
3011
-- | \(O(n)\). Map keys\/values and collect the 'Just' results.
2982
3012
--
2983
3013
-- > let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
2984
3014
-- > mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
2985
3015
2986
3016
mapMaybeWithKey :: (k -> a -> Maybe b ) -> Map k a -> Map k b
3017
+ {-
2987
3018
mapMaybeWithKey _ Tip = Tip
2988
3019
mapMaybeWithKey f (Bin _ kx x l r) = case f kx x of
2989
3020
Just y -> link kx y (mapMaybeWithKey f l) (mapMaybeWithKey f r)
2990
3021
Nothing -> link2 (mapMaybeWithKey f l) (mapMaybeWithKey f r)
3022
+ -}
3023
+ mapMaybeWithKey f = \ m ->
3024
+ mapMaybeWithKey# (\ k x -> toMaybe# (f k x)) m
3025
+ {-# INLINE mapMaybeWithKey #-}
3026
+
3027
+ mapMaybeWithKey# :: (k -> a -> Maybe # b ) -> Map k a -> Map k b
3028
+ mapMaybeWithKey# _ Tip = Tip
3029
+ mapMaybeWithKey# f (Bin _ kx x l r) = case f kx x of
3030
+ Just # y -> link kx y (mapMaybeWithKey# f l) (mapMaybeWithKey# f r)
3031
+ Nothing # -> link2 (mapMaybeWithKey# f l) (mapMaybeWithKey# f r)
3032
+ {-# NOINLINE [1] mapMaybeWithKey# #-}
3033
+
3034
+ {-# RULES
3035
+ "mapMaybeWK#/map#" forall f g m. mapMaybeWithKey# f (map# g m) =
3036
+ mapMaybeWithKey# (\k x -> case g x of (# y #) -> f k y) m
3037
+ "map#/mapMaybeWK#" forall f g m. map# f (mapMaybeWithKey# g m) =
3038
+ mapMaybeWithKey#
3039
+ (\k x -> case g k x of
3040
+ Nothing# -> Nothing#
3041
+ Just# y -> case f y of (# z #) -> Just# z) m
3042
+ "mapMaybeWK#/mapWK#" forall f g m. mapMaybeWithKey# f (mapWithKey# g m) =
3043
+ mapMaybeWithKey# (\k x -> case g k x of (# y #) -> f k y) m
3044
+ "mapWK#/mapMaybeWK#" forall f g m. mapWithKey# f (mapMaybeWithKey# g m) =
3045
+ mapMaybeWithKey#
3046
+ (\k x -> case g k x of
3047
+ Nothing# -> Nothing#
3048
+ Just# y -> case f k y of (# z #) -> Just# z) m
3049
+ "mapMaybeWK#/mapMaybeWK#" forall f g m. mapMaybeWithKey# f (mapMaybeWithKey# g m) =
3050
+ mapMaybeWithKey#
3051
+ (\k x -> case g k x of
3052
+ Nothing# -> Nothing#
3053
+ Just# y -> f k y) m
3054
+ "mapMaybeWK#/filterWK" forall f p m. mapMaybeWithKey# f (filterWithKey p m) =
3055
+ mapMaybeWithKey# (\k x -> if p k x then f k x else Nothing#) m
3056
+ "filterWK/mapMaybeWK#" forall p f m. filterWithKey p (mapMaybeWithKey# f m) =
3057
+ mapMaybeWithKey# (\k x -> case f k x of
3058
+ Nothing# -> Nothing#
3059
+ Just# y
3060
+ | p k y -> Just# y
3061
+ | otherwise -> Nothing#) m
3062
+ #-}
2991
3063
2992
3064
-- | \(O(n)\). Traverse keys\/values and collect the 'Just' results.
2993
3065
--
@@ -3045,18 +3117,34 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0
3045
3117
-- > map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
3046
3118
3047
3119
map :: (a -> b ) -> Map k a -> Map k b
3120
+ #ifdef __GLASGOW_HASKELL__
3121
+ -- We define map using map# solely to reduce the number of rewrite
3122
+ -- rules we need.
3123
+ map f = map # (\ x -> (# f x # ))
3124
+ {-# INLINABLE map #-}
3125
+ #else
3048
3126
map f = go where
3049
3127
go Tip = Tip
3050
3128
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.
3129
+ #endif
3054
3130
3055
3131
#ifdef __GLASGOW_HASKELL__
3056
- {-# NOINLINE [1] map #-}
3132
+ map # :: (a -> (# b # )) -> Map k a -> Map k b
3133
+ map # f = go where
3134
+ go Tip = Tip
3135
+ go (Bin sx kx x l r)
3136
+ | (# y # ) <- f x
3137
+ = Bin sx kx y (go l) (go r)
3138
+ -- We use a `go` function to allow `map#` to inline. Without this,
3139
+ -- we'd slow down both strict and lazy map, which wouldn't be great.
3140
+ -- This also lets us avoid a custom implementation of <$
3141
+
3142
+ {-# NOINLINE [1] map# #-}
3143
+ -- Perhaps surprisingly, this map#/coerce rule seems to work. Hopefully,
3144
+ -- it will continue to do so.
3057
3145
{-# RULES
3058
- "map/map" forall f g xs . map f (map g xs) = map (f . g ) xs
3059
- "map/coerce" map coerce = coerce
3146
+ "map# /map# " forall f g xs . map# f (map# g xs) = map# (\x -> case g x of (# y #) -> f y ) xs
3147
+ "map# /coerce" map# (\x -> (# coerce x #)) = coerce
3060
3148
#-}
3061
3149
#endif
3062
3150
@@ -3066,21 +3154,33 @@ map f = go where
3066
3154
-- > mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
3067
3155
3068
3156
mapWithKey :: (k -> a -> b ) -> Map k a -> Map k b
3157
+ #ifdef __GLASGOW_HASKELL__
3158
+ mapWithKey f = mapWithKey# (\ k a -> (# f k a # ))
3159
+ {-# INLINABLE mapWithKey #-}
3160
+ #else
3069
3161
mapWithKey _ Tip = Tip
3070
3162
mapWithKey f (Bin sx kx x l r) = Bin sx kx (f kx x) (mapWithKey f l) (mapWithKey f r)
3163
+ #endif
3164
+
3165
+ -- | A version of 'mapWithKey' that takes a function producing a unary
3166
+ -- unboxed tuple.
3167
+ mapWithKey# :: (k -> a -> (# b # )) -> Map k a -> Map k b
3168
+ mapWithKey# f = go where
3169
+ go Tip = Tip
3170
+ go (Bin sx kx x l r)
3171
+ | (# y # ) <- f kx x
3172
+ = Bin sx kx y (go l) (go r)
3071
3173
3072
3174
#ifdef __GLASGOW_HASKELL__
3073
- {-# NOINLINE [1] mapWithKey #-}
3175
+ {-# NOINLINE [1] mapWithKey# #-}
3074
3176
{-# 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
3177
+ "mapWK#/mapWK#" forall f g xs. mapWithKey# f (mapWithKey# g xs) = mapWithKey# (\k x -> case g k x of (# y #) -> f k y) xs
3178
+ "mapWK#/map#" forall f g xs. mapWithKey# f (map# g xs) = mapWithKey# (\k x -> case g x of (# y #) -> f k y) xs
3179
+ "map#/mapWK#" forall f g xs. map# f (mapWithKey# g xs) = mapWithKey# (\k x -> case g k x of (# y #) -> f y) xs
3081
3180
#-}
3082
3181
#endif
3083
3182
3183
+
3084
3184
-- | \(O(n)\).
3085
3185
-- @'traverseWithKey' f m == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@
3086
3186
-- That is, behaves exactly like a regular 'traverse' except that the traversing
@@ -4195,10 +4295,12 @@ instance (Ord k, Read k) => Read1 (Map k) where
4195
4295
--------------------------------------------------------------------}
4196
4296
instance Functor (Map k ) where
4197
4297
fmap f m = map f m
4198
- #ifdef __GLASGOW_HASKELL__
4199
- _ <$ Tip = Tip
4200
- a <$ (Bin sx kx _ l r) = Bin sx kx a (a <$ l) (a <$ r)
4201
- #endif
4298
+ {-# INLINABLE fmap #-}
4299
+ a <$ m = map (const a) m
4300
+ -- For some reason, we need an explicit INLINE or INLINABLE pragma to
4301
+ -- get the unfolding to use map rather than expanding into a recursive
4302
+ -- function that RULES will never match. Hmm....
4303
+ {-# INLINABLE (<$) #-}
4202
4304
4203
4305
-- | Traverses in order of increasing key.
4204
4306
instance Traversable (Map k ) where
0 commit comments