[GHC] #9441: Merge identical top-level expressions following simplification when it is safe to do so

GHC ghc-devs at haskell.org
Thu Aug 14 07:00:52 UTC 2014


#9441: Merge identical top-level expressions following simplification when it is
safe to do so
-------------------------------------+-------------------------------------
       Reporter:  dfeuer             |                   Owner:
           Type:  feature request    |                  Status:  new
       Priority:  normal             |               Milestone:
      Component:  Compiler           |                 Version:  7.8.2
       Keywords:                     |        Operating System:
   Architecture:  Unknown/Multiple   |  Unknown/Multiple
     Difficulty:  Unknown            |         Type of failure:
     Blocked By:                     |  None/Unknown
Related Tickets:                     |               Test Case:
                                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------
 If I redefine

 {{{#!hs
 {-# INLINE reverse #-}
 reverse :: [a] -> [a]
 reverse xs = build $ \c n -> foldl (\a x -> x `c` a) n xs
 }}}

 and then write a couple test cases:

 {{{#!hs
 appRev xs ys = xs ++ reverse ys
 revAppRev xs ys = reverse xs ++ reverse ys
 }}}

 I end up getting some rather annoying code duplication (lots of stuff
 omitted from the following):

 {{{#!hs
 Rec {
 poly_go_r2v3
 poly_go_r2v3 =
   \ @ a_a2nF ds_a2zc eta_Xl ->
     case ds_a2zc of _ {
       [] -> eta_Xl;
       : y_a2zh ys_a2zi -> poly_go_r2v3 ys_a2zi (: y_a2zh eta_Xl)
     }
 end Rec }

 reverse
 reverse = \ @ a_a2nF eta_B1 -> poly_go_r2v3 eta_B1 ([])

 Rec {
 revAppRev2
 revAppRev2 =
   \ @ a_a2y7 ds_a2zc eta_B1 ->
     case ds_a2zc of _ {
       [] -> eta_B1;
       : y_a2zh ys_a2zi -> revAppRev2 ys_a2zi (: y_a2zh eta_B1)
     }
 end Rec }

 Rec {
 revAppRev1
 revAppRev1 =
   \ @ a_a2y7 ds_a2zc eta_B1 ->
     case ds_a2zc of _ {
       [] -> eta_B1;
       : y_a2zh ys_a2zi -> revAppRev1 ys_a2zi (: y_a2zh eta_B1)
     }
 end Rec }

 Rec {
 appRev1
 appRev1 =
   \ @ a_a2xE ds_a2zc eta_B1 ->
     case ds_a2zc of _ {
       [] -> eta_B1;
       : y_a2zh ys_a2zi -> appRev1 ys_a2zi (: y_a2zh eta_B1)
     }
 end Rec }
 }}}

 The `reverse` function was inlined three times. In each case, there was no
 fusion, so `build` was inlined and the resulting copy of the `reverse`
 worker lifted to the top level. It would seem to me that once
 simplification is complete, it should be safe to merge all these copies
 into one. They are all `Rec {\ ... -> ...}` forms, so I don't think this
 has any potential to introduce undesirable sharing.

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


More information about the ghc-tickets mailing list