#6047: GHC retains unnecessary binding
---------------------------------+------------------------------------------
    Reporter:  simonmar          |       Owner:  simonpj         
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Milestone:  7.6.1           
   Component:  Compiler          |     Version:  7.4.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------
 milan posted this example on #6042, I'm making a separate ticket for it.
 He says:

 ----------

 BTW, when I preparing for the advanced functional programming course, I
 found out that the following code

 {{{
 module Test where
 factorial :: Int -> Int
 factorial n | n > 0 = f n 1
   where f 0 acc = acc
         f n acc = f (n-1) (n * acc)
 }}}

 produces the following STG, on both GHC 7.0.4 and 7.4.1, with unused
 method `factorial_f`:

 {{{
 Test.factorial2 =
     \u srt:(0,*bitmap*) []
         Control.Exception.Base.patError
             "a.hs:(4,1)-(6,35)|function factorial";
 SRT(Test.factorial2): [Control.Exception.Base.patError]
 Test.$wf =
     \r [ww_srk ww1_sro]
         case ww_srk of wild_srm {
           __DEFAULT ->
               case *# [wild_srm ww1_sro] of sat_srK {
                 __DEFAULT ->
                     case -# [wild_srm 1] of sat_srL {
                       __DEFAULT -> Test.$wf sat_srL sat_srK;
                     };
               };
           0 -> ww1_sro;
         };
 SRT(Test.$wf): []
 Test.factorial_f =
     \r [w_srs w1_srv]
         case w_srs of w2_srN {
           GHC.Types.I# ww_sry ->
               case w1_srv of w3_srM {
                 GHC.Types.I# ww1_srz ->
                     case Test.$wf ww_sry ww1_srz of ww2_srB {
                       __DEFAULT -> GHC.Types.I# [ww2_srB];
                     };
               };
         };
 SRT(Test.factorial_f): []
 Test.factorial1 = NO_CCS GHC.Types.I#! [1];
 SRT(Test.factorial1): []
 Test.factorial =
     \r srt:(0,*bitmap*) [n_srD]
         case n_srD of wild_srP {
           GHC.Types.I# x_srG ->
               case ># [x_srG 0] of wild1_srO {
                 GHC.Types.False -> Test.factorial2;
                 GHC.Types.True ->
                     case Test.$wf x_srG 1 of ww_srJ {
                       __DEFAULT -> GHC.Types.I# [ww_srJ];
                     };
               };
         };
 SRT(Test.factorial): [Test.factorial2]
 }}}

 The `Test.factorial_f` appears also in asm and in the object file.
 ----------

 simonpj explained to me why this is happening: `factorial_f` is being
 retained because it is referenced in an INLINE pragma for `factorial`.  In
 fact it will never be used, because `factorial_f` itself is also INLINE.

 We're going to investigate possible workarounds/solutions.

 Note it's only a code size issue, performance is not affected (compile
 time is affected a little though).  We're not sure how much it happens.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to