[commit: ghc] master: Add INLINE pragamas on Traversable default methods (d250d49)

git at git.haskell.org git at git.haskell.org
Wed Dec 21 14:06:29 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/d250d493d1dbe0bcfb19122ab3444c9450babdca/ghc

>---------------------------------------------------------------

commit d250d493d1dbe0bcfb19122ab3444c9450babdca
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Dec 21 11:38:50 2016 +0000

    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


>---------------------------------------------------------------

d250d493d1dbe0bcfb19122ab3444c9450babdca
 libraries/base/Data/Traversable.hs | 45 ++++++++++++++++++++++++++++++++++++++
 1 file changed, 45 insertions(+)

diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 6f503b7..635fcde 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



More information about the ghc-commits mailing list