summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2016-12-21 11:38:50 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2016-12-21 12:26:24 +0000
commitd250d493d1dbe0bcfb19122ab3444c9450babdca (patch)
tree5c9094ce20133bf6afe68078df39b12b7b7374f4
parentc66dd05c8d02e2b7df825ed2f13b79fb3a16ab58 (diff)
downloadhaskell-d250d493d1dbe0bcfb19122ab3444c9450babdca.tar.gz
Add INLINE pragamas on Traversable default methods
I discovered, when debugging a performance regression in the compiler, that the list instance of mapM was not being inlined at call sites, with terrible runtime costs. It turned out that this was a serious (but not entirely obvious) omission of an INLINE pragmas in the class declaration for Traversable. This patch fixes it. I reproduce below the Note [Inline default methods], which I wrote at some length. We may well want to apply the same fix in other class declarations whose default methods are often used. {- Note [Inline default methods] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) mapM = traverse -- Default method instance Traversable [] where {-# INLINE traverse #-} traverse = ...code for traverse on lists ... This gives rise to a list-instance of mapM looking like this $fTraversable[]_$ctaverse = ...code for traverse on lists... {-# INLINE $fTraversable[]_$ctaverse #-} $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/ that's all! We get $fTraversable[]_$cmapM = ...code for traverse on lists... with NO INLINE pragma! This happens even though 'traverse' had an INLINE pragma becuase the author knew it should be inlined pretty vigorously. Indeed, it turned out that the rhs of $cmapM was just too big to inline, so all uses of mapM on lists used a terribly inefficient dictionary-passing style, because of its 'Monad m =>' type. Disaster! Solution: add an INLINE pragma on the default method: class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) {-# INLINE mapM #-} -- VERY IMPORTANT! mapM = traverse
-rw-r--r--libraries/base/Data/Traversable.hs45
1 files changed, 45 insertions, 0 deletions
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 6f503b7dbe..635fcde4d9 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -157,26 +157,71 @@ class (Functor t, Foldable t) => Traversable t where
-- from left to right, and collect the results. For a version that ignores
-- the results see 'Data.Foldable.traverse_'.
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
+ {-# INLINE traverse #-} -- See Note [Inline default methods]
traverse f = sequenceA . fmap f
-- | Evaluate each action in the structure from left to right, and
-- and collect the results. For a version that ignores the results
-- see 'Data.Foldable.sequenceA_'.
sequenceA :: Applicative f => t (f a) -> f (t a)
+ {-# INLINE sequenceA #-} -- See Note [Inline default methods]
sequenceA = traverse id
-- | Map each element of a structure to a monadic action, evaluate
-- these actions from left to right, and collect the results. For
-- a version that ignores the results see 'Data.Foldable.mapM_'.
mapM :: Monad m => (a -> m b) -> t a -> m (t b)
+ {-# INLINE mapM #-} -- See Note [Inline default methods]
mapM = traverse
-- | Evaluate each monadic action in the structure from left to
-- right, and collect the results. For a version that ignores the
-- results see 'Data.Foldable.sequence_'.
sequence :: Monad m => t (m a) -> m (t a)
+ {-# INLINE sequence #-} -- See Note [Inline default methods]
sequence = sequenceA
+{- Note [Inline default methods]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider
+
+ class ... => Traversable t where
+ ...
+ mapM :: Monad m => (a -> m b) -> t a -> m (t b)
+ mapM = traverse -- Default method
+
+ instance Traversable [] where
+ {-# INLINE traverse #-}
+ traverse = ...code for traverse on lists ...
+
+This gives rise to a list-instance of mapM looking like this
+
+ $fTraversable[]_$ctaverse = ...code for traverse on lists...
+ {-# INLINE $fTraversable[]_$ctaverse #-}
+ $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse
+
+Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/
+that's all! We get
+
+ $fTraversable[]_$cmapM = ...code for traverse on lists...
+
+with NO INLINE pragma! This happens even though 'traverse' had an
+INLINE pragma becuase the author knew it should be inlined pretty
+vigorously.
+
+Indeed, it turned out that the rhs of $cmapM was just too big to
+inline, so all uses of mapM on lists used a terribly inefficient
+dictionary-passing style, because of its 'Monad m =>' type. Disaster!
+
+Solution: add an INLINE pragma on the default method:
+
+ class ... => Traversable t where
+ ...
+ mapM :: Monad m => (a -> m b) -> t a -> m (t b)
+ {-# INLINE mapM #-} -- VERY IMPORTANT!
+ mapM = traverse
+-}
+
-- instances for Prelude types
-- | @since 2.01