[GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks

GHC ghc-devs at haskell.org
Tue Jul 18 23:44:59 UTC 2017


#12150: Compile time performance degradation on code that uses undefined/error with
CallStacks
-------------------------------------+-------------------------------------
        Reporter:  thomie            |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.2.2
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #10844            |  Differential Rev(s):  Phab:D3753
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by dfeuer):

 * differential:   => Phab:D3753


Comment:

 I've made the changes Simon suggested to Phab:D3753. Unfortunately, the
 redundant cases still aren't removed until the simplification pass after
 float out, by which point we've already wasted a bunch of time. Consider

 {{{#!hs
 module Serialize where

 data Result a = Success a | Error String

 instance Functor Result where
     {-# INLINE fmap #-}
     fmap | bool = f
          | bool = f

       where
         bool = undefined
         f = undefined
 }}}

 We get

 {{{#!hs
 ==================== Simplifier ====================
 2017-07-18 23:33:20.811559426 UTC
   Max iterations = 4
   SimplMode {Phase = InitialPhase [Gentle],
              inline,
              rules,
              eta-expand,
              no case-of-case}

 ...

 bool_s2b7 :: forall a. a
 [LclId,
  Str=x,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
          WorkFree=True, Expandable=True, Guidance=NEVER}]
 bool_s2b7
   = \ (@ a_a1Xw) ->
       undefined
         @ 'GHC.Types.LiftedRep
         @ a_a1Xw
         ($dIP_s2b6
          `cast` (Sym
                    (GHC.Classes.N:IP[0] <"callStack">_N
 <GHC.Stack.Types.CallStack>_N)
                  :: (GHC.Stack.Types.CallStack :: *)
                     ~R# (?callStack::GHC.Stack.Types.CallStack ::
 Constraint)))
 }}}

 which looks great (there's an `x`!), but we still have

 {{{#!hs
 $cfmap_aU6 [InlPrag=INLINE (sat-args=0)]
   :: forall a b. (a -> b) -> Result a -> Result b
 [LclId,
  Str=x,  -- Yay for the x, of course
  Unf=...]
 $cfmap_aU6
   = \ (@ a_aUa) (@ b_aUb) ->
       case bool_s2b7 @ Bool of {
         False ->
           case bool_s2b7 @ Bool of {
             False ->
               Control.Exception.Base.patError
                 @ 'GHC.Types.LiftedRep
                 @ ((a_aUa -> b_aUb) -> Result a_aUa -> Result b_aUb)
                 "Serialize.hs:(7,5)-(21,21)|function fmap"#;
             True ->
               undefined
                 @ 'GHC.Types.LiftedRep
                 @ ((a_aUa -> b_aUb) -> Result a_aUa -> Result b_aUb)
                 ($dIP_s2aW
                  `cast` (Sym
                            (GHC.Classes.N:IP[0] <"callStack">_N
 <GHC.Stack.Types.CallStack>_N)
                          :: (GHC.Stack.Types.CallStack :: *)
                             ~R# (?callStack::GHC.Stack.Types.CallStack ::
 Constraint)))
           };
         True ->
           undefined
             @ 'GHC.Types.LiftedRep
             @ ((a_aUa -> b_aUb) -> Result a_aUa -> Result b_aUb)
             ($dIP_s2aW
              `cast` (Sym
                        (GHC.Classes.N:IP[0] <"callStack">_N
 <GHC.Stack.Types.CallStack>_N)
                      :: (GHC.Stack.Types.CallStack :: *)
                         ~R# (?callStack::GHC.Stack.Types.CallStack ::
 Constraint)))
       }
 }}}

 For some reason, we're not eliminating the two `case`s on `bool_s2b7 @
 Bool`. I'm not sure where to look next.

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


More information about the ghc-tickets mailing list