Repository : ssh://darcs.haskell.org//srv/darcs/packages/containers

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d95988c2fc7f920b3d6ec2f28166f06ec56be255

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

commit d95988c2fc7f920b3d6ec2f28166f06ec56be255
Author: Milan Straka <[email protected]>
Date:   Wed Mar 14 18:30:43 2012 +0100

    Mark Data.Map.(!) as INLINABLE instead of INLINE.
    
    This should have been done in commit 3f798e33. As mentioned in the
    commit log, the chain
      m ! k = find k m
      {-# INLINE (!) #-}
      find k m = ...
      {-# INLINABLE find #-}
    results in find not being specialized at the call site of (!).

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

 Data/Map/Base.hs |    2 +-
 1 files changed, 1 insertions(+), 1 deletions(-)

diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 78d4a79..d9cf4ce 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -254,7 +254,7 @@ infixl 9 !,\\ --
 
 (!) :: Ord k => Map k a -> k -> a
 m ! k    = find k m
-{-# INLINE (!) #-}
+{-# INLINABLE (!) #-}
 
 -- | Same as 'difference'.
 (\\) :: Ord k => Map k a -> Map k b -> Map k a



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to