[GHC] #10528: compile time performance regression with OverloadedStrings and Text

GHC ghc-devs at haskell.org
Tue Aug 4 10:01:40 UTC 2015


#10528: compile time performance regression with OverloadedStrings and Text
-------------------------------------+-------------------------------------
        Reporter:  jakewheat         |                   Owner:
            Type:  bug               |                  Status:  merge
        Priority:  high              |               Milestone:  7.10.3
       Component:  Compiler          |                 Version:  7.10.2-rc2
      Resolution:                    |                Keywords:
Operating System:  Linux             |            Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  performance bug                    |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by afarmer):

 Proposed patch that implements Option 3 in my list above... which I think
 is the best short term solution.

 {{{
 diff --git a/compiler/simplCore/Simplify.hs
 b/compiler/simplCore/Simplify.hs
 index d816d3f..0e4ca50 100644
 --- a/compiler/simplCore/Simplify.hs
 +++ b/compiler/simplCore/Simplify.hs
 @@ -38,7 +38,7 @@ import CoreArity
  --import PrimOp           ( tagToEnumKey ) -- temporalily commented out.
 See #8326
  import Rules            ( mkSpecInfo, lookupRule, getRules )
  import TysPrim          ( voidPrimTy ) --, intPrimTy ) -- temporalily
 commented out. See #8326
 -import BasicTypes       ( TopLevelFlag(..), isTopLevel, RecFlag(..) )
 +import BasicTypes       ( TopLevelFlag(..), isTopLevel, RecFlag(..),
 Activation(..) )
  import MonadUtils       ( foldlM, mapAccumLM, liftIO )
  import Maybes           ( orElse )
  --import Unique           ( hasKey ) -- temporalily commented out. See
 #8326
 @@ -2970,7 +2970,9 @@ simplRules env mb_new_nm rules
                            , ru_act = act })
        = do { (env, bndrs') <- simplBinders env bndrs
             ; let lhs_env = updMode updModeForRuleLHS env
 -                 rhs_env = updMode (updModeForStableUnfoldings act) env
 +                 rhs_env = case act of
 +                            NeverActive -> lhs_env
 +                            _ -> updMode (updModeForStableUnfoldings act)
 env
             ; args' <- mapM (simplExpr lhs_env) args
             ; rhs'  <- simplExpr rhs_env rhs
             ; return (rule { ru_bndrs = bndrs'
 }}}

 Since NeverActive rules are not actually applied by GHC, not rewriting
 their RHSs shouldn't change anything for real libraries, while still
 offering HERMIT access to the original rule without the extra
 inlining/rule application. This patch also allows our test suite to pass.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10528#comment:39>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list