[GHC] #14816: Missed Called Arity opportunity?

GHC ghc-devs at haskell.org
Fri Feb 16 18:57:14 UTC 2018


#14816: Missed Called Arity opportunity?
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Runtime
  Unknown/Multiple                   |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When I compile

 {{{#!hs
 test :: (a -> a -> a) -> Int -> a -> HashMap Int a -> HashMap Int a
 test f k a m = insertModifying a (blink (f a)) k m

 blink :: (a -> b) -> a -> (# b #)
 -- Or blink g = \a -> (# g a #) ; it makes no difference.
 blink g a = (# g a #)
 }}}

 I get

 {{{
 test
   = \ (@ a_a9o3)
       (f_a7iP :: a_a9o3 -> a_a9o3 -> a_a9o3)
       (k_a7iQ :: Int)
       (a1_a7iR :: a_a9o3)
       (m_a7iS :: HashMap Int a_a9o3) ->
       case k_a7iQ of { GHC.Types.I# ww1_sa1Z ->
       RULES.$w$sinsertModifying
         @ a_a9o3
         a1_a7iR
         (let {
            g_s9E1 [Dmd=<L,C(U)>] :: a_a9o3 -> a_a9o3
            [LclId]
            g_s9E1 = f_a7iP a1_a7iR } in
          \ (a2_a7iU :: a_a9o3) -> (# g_s9E1 a2_a7iU #))
         ww1_sa1Z
         m_a7iS
       }
 }}}

 We build `g_s9E1 = f_a7iP a1_a7iR` for no apparent reason. Trouble
 persists into STG:

 {{{
 RULES.test
   :: forall a.
      (a -> a -> a)
      -> GHC.Types.Int
      -> a
      -> Data.HashMap.Base.HashMap GHC.Types.Int a
      -> Data.HashMap.Base.HashMap GHC.Types.Int a
 [GblId,
  Arity=4,
  Str=<L,1*C1(C(U))><S(S),1*U(U)><L,U><S,1*U>,
  Unf=OtherCon []] =
     [] \r [f_saiX k_saiY a1_saiZ m_saj0]
         case k_saiY of {
           GHC.Types.I# ww1_saj2 [Occ=Once] ->
               let {
                 g_saj3 [Occ=OnceL!, Dmd=<L,C(U)>] :: a_a9o3 -> a_a9o3
                 [LclId] =
                     [f_saiX a1_saiZ] \u [] f_saiX a1_saiZ; } in
               let {
                 sat_saj6 [Occ=Once] :: a_a9o3 -> (# a_a9o3 #)
                 [LclId] =
                     [g_saj3] \r [a2_saj4]
                         let {
                           sat_saj5 [Occ=Once] :: a_a9o3
                           [LclId] =
                               [g_saj3 a2_saj4] \u [] g_saj3 a2_saj4;
                         } in  Unit# [sat_saj5];
               } in  RULES.$w$sinsertModifying a1_saiZ sat_saj6 ww1_saj2
 m_saj0;
         };
 }}}

 `insertModifying` uses its function argument at most once, so there is no
 possible benefit to this partial application.

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


More information about the ghc-tickets mailing list