Understanding the core2core simplifier <-> occurence-analysis interaction

Herbert Valerio Riedel hvr at gnu.org
Mon Oct 22 09:59:00 CEST 2012


Hello GHC HQ,

I've been trying to improve/fix a minor optimization sub-optimality
w.r.t to the following code (code like that results from the
generics-based NFData deriver[1]):

    data Foo = Foo1 | Foo2 | Foo3 !Int
    
    rnf1 :: Foo -> ()
    rnf1 x = case x of
               Foo1 -> ()
               Foo2 -> ()
               Foo3 {} -> ()
    
which the current GHC 7.6.1 translates to the following core
expression:

    NFDataTest2.rnf1 =
      \ x_aeG ->
        case x_aeG of _ {
          __DEFAULT -> GHC.Tuple.();
          NFDataTest2.Foo3 ds_deT -> GHC.Tuple.()
        }

...whereas I'd have expected it to to compile it to a collapsed
'__DEFAULT'-only case, i.e.

    NFDataTest2.rnf1 =
      \ x_aeG -> case x_aeG of _ { __DEFAULT -> GHC.Tuple.() }


Now I've been hunting it down to the function SimplUtils.mkCase1 [2],
which according to the source-code comments, is supposed to merge
identical alternatives, i.e.:

| 3.  Merge identical alternatives.
|     If several alternatives are identical, merge them into
|     a single DEFAULT alternative.  I've occasionally seen this
|     making a big difference:
| 
|         case e of               =====>     case e of
|           C _ -> f x                         D v -> ....v....
|           D v -> ....v....                   DEFAULT -> f x
|           DEFAULT -> f x


...and the 'mkCase1' function itself reads as follows:

    mkCase1 dflags scrut case_bndr alts_ty ((_con1,bndrs1,rhs1) : con_alts)
      | all isDeadBinder bndrs1                     -- Remember the default
      , length filtered_alts < length con_alts      -- alternative comes first
            -- Also Note [Dead binders]
      = do  { tick (AltMerge case_bndr)
            ; mkCase2 dflags scrut case_bndr alts_ty alts' }
      where
        alts' = (DEFAULT, [], rhs1) : filtered_alts
        filtered_alts         = filter keep con_alts
        keep (_con,bndrs,rhs) = not (all isDeadBinder bndrs && rhs `cheapEqExpr` rhs1)
    


...now the problem seems to be, that 'isDeadBinder' returns 'False'; so
I hacked up 'mkCase1' and inserted a 'occurAnalyseExpr' on artificially
constructed single-alternative 'Case' values before applying
'isDeadBinder', and then it would return 'True' and simplify the case
expression as expected.



So now my question is, why isn't the occurrence information available
for the case-alternative's binders (the occInfo is set to 'NoOccInfo')
at 'mkCase1'-time?  When is occurence analysis performed relative to the
simplifier?


 [1]: http://hackage.haskell.org/package/deepseq-generics
 [2]: http://www.haskell.org/ghc/docs/7.6.1/html/libraries/ghc-7.6.1/src/SimplUtils.html#mkCase1

cheers,
  hvr
--



More information about the Glasgow-haskell-users mailing list