Skip to content

Commit f287120

Browse files
committed
Unboxing and streamlining Map maps
* Use an unboxed-sum version of `Maybe` to implement `mapMaybeWithKey`. This potentially (I suspect usually) allows all the `Maybe`s to be erased. * Comprehensive rewrite rules for both strict and lazy versions of `map`, `mapWithKey`, `mapMaybeWithKey`, and `filterWithKey` quickly get out of hand. Following `unordered-containers`, tame the mess by implementing both lazy and strict mapping functions in terms of versions that use unboxed results. Rewrite rules on these underlying functions will then apply uniformly. One concern: I found it a bit tricky to get the unfoldings I wanted; lots of things had to be marked `INLINABLE` explicitly.
1 parent 3db464d commit f287120

File tree

6 files changed

+279
-58
lines changed

6 files changed

+279
-58
lines changed

containers-tests/containers-tests.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,8 @@ library
104104
Utils.Containers.Internal.BitQueue
105105
Utils.Containers.Internal.BitUtil
106106
Utils.Containers.Internal.StrictPair
107+
Utils.Containers.Internal.UnboxedMaybe
108+
Utils.Containers.Internal.UnboxedSolo
107109
if impl(ghc >= 8.6.0)
108110
exposed-modules:
109111
Utils.NoThunks

containers/containers.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,8 @@ Library
6969
Utils.Containers.Internal.BitUtil
7070
Utils.Containers.Internal.BitQueue
7171
Utils.Containers.Internal.StrictPair
72+
Utils.Containers.Internal.UnboxedMaybe
73+
Utils.Containers.Internal.UnboxedSolo
7274

7375
other-modules:
7476
Prelude

containers/src/Data/Map/Internal.hs

Lines changed: 128 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE PatternGuards #-}
44
#if defined(__GLASGOW_HASKELL__)
55
{-# LANGUAGE DeriveLift #-}
6+
{-# LANGUAGE UnboxedTuples #-}
67
{-# LANGUAGE RoleAnnotations #-}
78
{-# LANGUAGE StandaloneDeriving #-}
89
{-# LANGUAGE Trustworthy #-}
@@ -236,7 +237,9 @@ module Data.Map.Internal (
236237
-- * Traversal
237238
-- ** Map
238239
, map
240+
, mapU
239241
, mapWithKey
242+
, mapWithKeyU
240243
, traverseWithKey
241244
, traverseMaybeWithKey
242245
, mapAccum
@@ -301,6 +304,7 @@ module Data.Map.Internal (
301304

302305
, mapMaybe
303306
, mapMaybeWithKey
307+
, mapMaybeWithKeyU
304308
, mapEither
305309
, mapEitherWithKey
306310

@@ -407,6 +411,8 @@ import Data.Data
407411
import qualified Control.Category as Category
408412
import Data.Coerce
409413
#endif
414+
import Utils.Containers.Internal.UnboxedMaybe
415+
import Utils.Containers.Internal.UnboxedSolo
410416

411417

412418
{--------------------------------------------------------------------
@@ -2849,6 +2855,7 @@ isProperSubmapOfBy f t1 t2
28492855
filter :: (a -> Bool) -> Map k a -> Map k a
28502856
filter p m
28512857
= filterWithKey (\_ x -> p x) m
2858+
{-# INLINE filter #-}
28522859

28532860
-- | \(O(n)\). Filter all keys\/values that satisfy the predicate.
28542861
--
@@ -2863,6 +2870,32 @@ filterWithKey p t@(Bin _ kx x l r)
28632870
| otherwise = link2 pl pr
28642871
where !pl = filterWithKey p l
28652872
!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+
#-}
28662899

28672900
-- | \(O(n)\). Filter keys and values using an 'Applicative'
28682901
-- predicate.
@@ -2977,17 +3010,54 @@ partitionWithKey p0 t0 = toPair $ go p0 t0
29773010

29783011
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b
29793012
mapMaybe f = mapMaybeWithKey (\_ x -> f x)
3013+
{-# INLINE mapMaybe #-}
29803014

29813015
-- | \(O(n)\). Map keys\/values and collect the 'Just' results.
29823016
--
29833017
-- > let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
29843018
-- > mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
29853019

29863020
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+
#-}
29913061

29923062
-- | \(O(n)\). Traverse keys\/values and collect the 'Just' results.
29933063
--
@@ -3045,17 +3115,38 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0
30453115
-- > map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
30463116

30473117
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
30493130
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 <$
30543143

3144+
-- We don't let mapU inline until phase 0 because we need a step
3145+
-- after map inlines.
30553146
#ifdef __GLASGOW_HASKELL__
3056-
{-# NOINLINE [1] map #-}
3147+
{-# NOINLINE [0] mapU #-}
30573148
{-# 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
30593150
"map/coerce" map coerce = coerce
30603151
#-}
30613152
#endif
@@ -3066,21 +3157,35 @@ map f = go where
30663157
-- > mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
30673158

30683159
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
30713178

30723179
#ifdef __GLASGOW_HASKELL__
3073-
{-# NOINLINE [1] mapWithKey #-}
3180+
{-# NOINLINE [1] mapWithKeyU #-}
30743181
{-# 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
30813185
#-}
30823186
#endif
30833187

3188+
30843189
-- | \(O(n)\).
30853190
-- @'traverseWithKey' f m == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@
30863191
-- 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
41954300
--------------------------------------------------------------------}
41964301
instance Functor (Map k) where
41974302
fmap f m = map f m
4303+
a <$ m = map (const a) m
41984304
#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 (<$) #-}
42014307
#endif
42024308

42034309
-- | Traverses in order of increasing key.

containers/src/Data/Map/Strict/Internal.hs

Lines changed: 15 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,10 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE BangPatterns #-}
33
#if defined(__GLASGOW_HASKELL__)
4+
{-# LANGUAGE MagicHash #-}
5+
{-# LANGUAGE PatternSynonyms #-}
46
{-# LANGUAGE Trustworthy #-}
7+
{-# LANGUAGE UnboxedTuples #-}
58
#endif
69
{-# OPTIONS_HADDOCK not-home #-}
710

@@ -420,6 +423,8 @@ import Data.Semigroup (Arg (..))
420423
import qualified Data.Set.Internal as Set
421424
import qualified Data.Map.Internal as L
422425
import Utils.Containers.Internal.StrictPair
426+
import Utils.Containers.Internal.UnboxedMaybe (pattern NothingU, pattern JustU)
427+
import Utils.Containers.Internal.UnboxedSolo (pattern SoloU)
423428

424429
import Data.Bits (shiftL, shiftR)
425430
#ifdef __GLASGOW_HASKELL__
@@ -1271,17 +1276,19 @@ mergeWithKey f g1 g2 = go
12711276

12721277
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b
12731278
mapMaybe f = mapMaybeWithKey (\_ x -> f x)
1279+
{-# INLINABLE mapMaybe #-}
12741280

12751281
-- | \(O(n)\). Map keys\/values and collect the 'Just' results.
12761282
--
12771283
-- > let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
12781284
-- > mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
12791285

12801286
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b
1281-
mapMaybeWithKey _ Tip = Tip
1282-
mapMaybeWithKey f (Bin _ kx x l r) = case f kx x of
1283-
Just y -> y `seq` link kx y (mapMaybeWithKey f l) (mapMaybeWithKey f r)
1284-
Nothing -> link2 (mapMaybeWithKey f l) (mapMaybeWithKey f r)
1287+
mapMaybeWithKey f = \m ->
1288+
L.mapMaybeWithKeyU (\k x -> case f k x of
1289+
Nothing -> NothingU
1290+
Just !a -> JustU a) m
1291+
{-# INLINABLE mapMaybeWithKey #-}
12851292

12861293
-- | \(O(n)\). Traverse keys\/values and collect the 'Just' results.
12871294
--
@@ -1340,19 +1347,9 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0
13401347
-- > map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
13411348

13421349
map :: (a -> b) -> Map k a -> Map k b
1343-
map f = go
1344-
where
1345-
go Tip = Tip
1346-
go (Bin sx kx x l r) = let !x' = f x in Bin sx kx x' (go l) (go r)
1347-
-- We use `go` to let `map` inline. This is important if `f` is a constant
1348-
-- function.
1349-
1350+
map f = L.mapU (\x -> let !y = f x in SoloU y)
13501351
#ifdef __GLASGOW_HASKELL__
1351-
{-# NOINLINE [1] map #-}
1352-
{-# RULES
1353-
"map/map" forall f g xs . map f (map g xs) = map (\x -> f $! g x) xs
1354-
"map/mapL" forall f g xs . map f (L.map g xs) = map (\x -> f (g x)) xs
1355-
#-}
1352+
{-# INLINABLE map #-}
13561353
#endif
13571354

13581355
-- | \(O(n)\). Map a function over all values in the map.
@@ -1361,27 +1358,9 @@ map f = go
13611358
-- > mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
13621359

13631360
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b
1364-
mapWithKey _ Tip = Tip
1365-
mapWithKey f (Bin sx kx x l r) =
1366-
let x' = f kx x
1367-
in x' `seq` Bin sx kx x' (mapWithKey f l) (mapWithKey f r)
1368-
1361+
mapWithKey f = L.mapWithKeyU (\k x -> let !y = f k x in SoloU y)
13691362
#ifdef __GLASGOW_HASKELL__
1370-
{-# NOINLINE [1] mapWithKey #-}
1371-
{-# RULES
1372-
"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) =
1373-
mapWithKey (\k a -> f k $! g k a) xs
1374-
"mapWithKey/mapWithKeyL" forall f g xs . mapWithKey f (L.mapWithKey g xs) =
1375-
mapWithKey (\k a -> f k (g k a)) xs
1376-
"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) =
1377-
mapWithKey (\k a -> f k $! g a) xs
1378-
"mapWithKey/mapL" forall f g xs . mapWithKey f (L.map g xs) =
1379-
mapWithKey (\k a -> f k (g a)) xs
1380-
"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) =
1381-
mapWithKey (\k a -> f $! g k a) xs
1382-
"map/mapWithKeyL" forall f g xs . map f (L.mapWithKey g xs) =
1383-
mapWithKey (\k a -> f (g k a)) xs
1384-
#-}
1363+
{-# INLINABLE mapWithKey #-}
13851364
#endif
13861365

13871366
-- | \(O(n)\).

0 commit comments

Comments
 (0)