[GHC] #9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to Typeable

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to Typeable ------------------------------+-------------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | ------------------------------+-------------------------------------------- {{{ $ git clone http://github.com/facebook/Haxl.git Cloning into 'Haxl'... remote: Counting objects: 77, done. remote: Compressing objects: 100% (65/65), done. remote: Total 77 (delta 17), reused 69 (delta 9) Unpacking objects: 100% (77/77), done. $ cd Haxl $ ghc-7.6.3 -O2 tests/Bench.hs -main-is Bench -o tests/Bench-76 [1 of 6] Compiling Haxl.Core.StateStore ( Haxl/Core/StateStore.hs, Haxl/Core/StateStore.o ) [2 of 6] Compiling Haxl.Core.Show1 ( Haxl/Core/Show1.hs, Haxl/Core/Show1.o ) [3 of 6] Compiling Haxl.Core.Util ( Haxl/Core/Util.hs, Haxl/Core/Util.o ) [4 of 6] Compiling Haxl.Core.Types ( Haxl/Core/Types.hs, Haxl/Core/Types.o ) [5 of 6] Compiling Haxl.Core.DataCache ( Haxl/Core/DataCache.hs, Haxl/Core/DataCache.o ) [6 of 6] Compiling Bench ( tests/Bench.hs, tests/Bench.o ) Linking tests/Bench-76 ... $ ./tests/Bench-76 500000 Just (Right 0) insert: 0.87s 500000 lookup: 0.24s $ ./tests/Bench-76 500000 Just (Right 0) insert: 0.87s 500000 lookup: 0.26s $ ghc-7.8.2 -O2 tests/Bench.hs -main-is Bench -o tests/Bench-78 [1 of 5] Compiling Haxl.Core.StateStore ( Haxl/Core/StateStore.hs, Haxl/Core/StateStore.o ) [2 of 5] Compiling Haxl.Core.Show1 ( Haxl/Core/Show1.hs, Haxl/Core/Show1.o ) [3 of 5] Compiling Haxl.Core.Types ( Haxl/Core/Types.hs, Haxl/Core/Types.o ) [4 of 5] Compiling Haxl.Core.DataCache ( Haxl/Core/DataCache.hs, Haxl/Core/DataCache.o ) [5 of 5] Compiling Bench ( tests/Bench.hs, tests/Bench.o ) Linking tests/Bench-78 ... $ ./tests/Bench-78 500000 Just (Right 0) insert: 1.09s 500000 lookup: 0.44s $ ./tests/Bench-78 500000 Just (Right 0) insert: 1.08s 500000 lookup: 0.44s }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to Typeable --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonmar): * cc: tibbe (added) Comment: I've narrowed this down further. It seems to be something to do with `HashMap`. With the following source file: {{{ {-# LANGUAGE RankNTypes, GADTs, BangPatterns, DeriveDataTypeable, StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-unused-do-bind -fno-warn-type-defaults #-} module Bench where import Prelude hiding (mapM) import Control.Concurrent import Data.Hashable import Data.Time.Clock import Data.Traversable import Data.Typeable import System.Environment import Text.Printf import qualified Data.HashMap.Strict as HashMap import Data.HashMap.Strict (HashMap) import Unsafe.Coerce data TestReq a where ReqInt :: {-# UNPACK #-} !Int -> TestReq Int deriving Typeable deriving instance Eq (TestReq a) deriving instance Show (TestReq a) instance Hashable (TestReq a) where hashWithSalt salt (ReqInt i) = hashWithSalt salt (0::Int, i) main = do [n] <- fmap (fmap read) getArgs t0 <- getCurrentTime let f 0 !cache = cache f !n !cache = f (n-1) (dcinsert (ReqInt n) 0 cache) -- let !cache = f n dcempty let m = dclookup (ReqInt (n `div` 2)) cache print m t1 <- getCurrentTime printf "insert: %.2fs\n" (realToFrac (t1 `diffUTCTime` t0) :: Double) t0 <- getCurrentTime let f 0 !m = m f !n !m = case dclookup (ReqInt n) cache of Nothing -> f (n-1) m Just _ -> f (n-1) (m+1) print (f n 0) t1 <- getCurrentTime printf "lookup: %.2fs\n" (realToFrac (t1 `diffUTCTime` t0) :: Double) newtype DataCache = DataCache (HashMap TypeRep SubCache) -- | The implementation is a two-level map: the outer level maps the -- types of requests to 'SubCache', which maps actual requests to their -- results. So each 'SubCache' contains requests of the same type. -- This works well because we only have to store the dictionaries for -- 'Hashable' and 'Eq' once per request type. data SubCache = forall req a . (Hashable (req a), Eq (req a)) => SubCache ! (HashMap (req a) a) -- NB. the inner HashMap is strict, to avoid building up -- a chain of thunks during repeated insertions. -- | A new, empty 'DataCache'. dcempty :: DataCache dcempty = DataCache HashMap.empty -- | Inserts a request-result pair into the 'DataCache'. dcinsert :: (Hashable (r a), Typeable (r a), Eq (r a)) => r a -- ^ Request -> a -- ^ Result -> DataCache -> DataCache dcinsert req result (DataCache m) = DataCache $ HashMap.insertWith fn (typeOf req) (SubCache (HashMap.singleton req result)) m where fn (SubCache new) (SubCache old) = SubCache (unsafeCoerce new `HashMap.union` old) -- | Looks up the cached result of a request. dclookup :: Typeable (r a) => r a -- ^ Request -> DataCache -> Maybe a dclookup req (DataCache m) = case HashMap.lookup (typeOf req) m of Nothing -> Nothing Just (SubCache sc) -> unsafeCoerce (HashMap.lookup (unsafeCoerce req) sc) }}} GHC 7.6.3: {{{ Just 0 insert: 0.73s 500000 lookup: 0.23s }}} GHC 7.8.2: {{{ Just 0 insert: 1.01s 500000 lookup: 0.53s }}} `insert` is a bit slower, but `lookup` is more than twice as slow with 7.8.2. Looking at the Core, at lookup in particular, the code in 7.8.2 looks reasonable. But in both cases we end up calling `Data.HashMap.Base.lookup` for the inner lookup, and I'm guessing that is where the inefficiency lies. @tibbe, want to take a look? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonmar): Hang on, I'm just doing some more investigation in `TypeRep`, I think it might be in there after all. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonmar): * priority: normal => high Comment: Fix: https://phabricator.haskell.org/D19 It would be nice to get this into 7.8.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: new Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Yes, great fix, let's get it in as soon as poss. I've added Phab comment thought. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * status: new => merge Comment: I'm going to change the status to 'merge' even though it's not in HEAD, so that Austin doesn't miss it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap
--------------------------------------------+------------------------------
Reporter: simonmar | Owner:
Type: bug | Status: merge
Priority: high | Milestone: 7.8.3
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime performance bug | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Marlow

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonmar): Simon: I don't think you added a comment on Phabricator (you probably need to click the big button at the bottom of the page). I've been digging a bit more into this: it turns out we had fixed this once before, see #3245, and there was even a big Note in the code that was *removed* by Pedro in 3d53407f9c6e87bcff30d51f0a048e92b2745a32. There's also a perf test (`testsuite/tests/perf/should_run/T3245.hs`), but that didn't trigger because (a) there are no bounds defined for it in all.T, and (b) that test doesn't trigger the bug any more anyway. I'm going to add a new perf test, and some comments to `Internal.hs`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Ha ha! My attempt to use Phab fails at the first fence. I'm jolly glad I only wrote one short comment, not a whole lot!! Anyway you read my mind: I was suggesting a clear Note to explain the issue, but I see you are already on it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap
--------------------------------------------+------------------------------
Reporter: simonmar | Owner:
Type: bug | Status: merge
Priority: high | Milestone: 7.8.3
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime performance bug | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Iavor S. Diatchki

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonmar): Simon - you didn't lose your comment, if you go back to Phabricator it will still be there ready to submit. Phabricator auto-saves comments (unlike Trac). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9203: Perf regression in 7.8.2 relative to 7.6.3, possibly related to HashMap --------------------------------------------+------------------------------ Reporter: simonmar | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by jstolarek): Perhaps it's also worth to resurrect the deleted Note? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9203#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC