Don't import FastString in HsVersions.h
[ghc-hetmet.git] / compiler / coreSyn / CoreUnfold.lhs
index 841e2a7..8da91ed 100644 (file)
@@ -27,7 +27,7 @@ module CoreUnfold (
        couldBeSmallEnoughToInline, 
        certainlyWillInline, smallEnoughToInline,
 
-       callSiteInline, CallContInfo(..)
+       callSiteInline, CallCtxt(..)
 
     ) where
 
@@ -48,6 +48,7 @@ import Type
 import PrelNames
 import Bag
 import FastTypes
+import FastString
 import Outputable
 
 \end{code}
@@ -503,7 +504,7 @@ If the thing is in WHNF, there's no danger of duplicating work,
 so we can inline if it occurs once, or is small
 
 NOTE: we don't want to inline top-level functions that always diverge.
-It just makes the code bigger.  It turns out that the convenient way to prevent
+It just makes the code bigger.  Tt turns out that the convenient way to prevent
 them inlining is to give them a NOINLINE pragma, which we do in 
 StrictAnal.addStrictnessInfoToTopId
 
@@ -513,19 +514,25 @@ callSiteInline :: DynFlags
               -> Id                    -- The Id
               -> Bool                  -- True if there are are no arguments at all (incl type args)
               -> [Bool]                -- One for each value arg; True if it is interesting
-              -> CallContInfo          -- True <=> continuation is interesting
+              -> CallCtxt              -- True <=> continuation is interesting
               -> Maybe CoreExpr        -- Unfolding, if any
 
 
-data CallContInfo = BoringCont         
-                 | InterestingCont     -- Somewhat interesting
-                 | CaseCont            -- Very interesting; the argument of a case
-                                       -- that decomposes its scrutinee
+data CallCtxt = BoringCtxt
 
-instance Outputable CallContInfo where
-  ppr BoringCont      = ptext SLIT("BoringCont")
-  ppr InterestingCont = ptext SLIT("InterestingCont")
-  ppr CaseCont               = ptext SLIT("CaseCont")
+             | ArgCtxt Bool    -- We're somewhere in the RHS of function with rules
+                               --      => be keener to inline
+                       Int     -- We *are* the argument of a function with this arg discount
+                               --      => be keener to inline
+               -- INVARIANT: ArgCtxt False 0 ==> BoringCtxt
+
+             | CaseCtxt        -- We're the scrutinee of a case
+                               -- that decomposes its scrutinee
+
+instance Outputable CallCtxt where
+  ppr BoringCtxt    = ptext SLIT("BoringCtxt")
+  ppr (ArgCtxt _ _) = ptext SLIT("ArgCtxt")
+  ppr CaseCtxt             = ptext SLIT("CaseCtxt")
 
 callSiteInline dflags active_inline id lone_variable arg_infos cont_info
   = case idUnfolding id of {
@@ -569,10 +576,10 @@ callSiteInline dflags active_inline id lone_variable arg_infos cont_info
                  -> True
 
                  | otherwise
-                 -> some_benefit && small_enough 
+                 -> some_benefit && small_enough
+
                  where
                    enough_args = n_val_args >= n_vals_wanted
-                       -- Note [Enough args] 
 
                    some_benefit = or arg_infos || really_interesting_cont
                                -- There must be something interesting
@@ -588,17 +595,18 @@ callSiteInline dflags active_inline id lone_variable arg_infos cont_info
 
                    interesting_saturated_call 
                        = case cont_info of
-                           BoringCont -> not is_top && n_vals_wanted > 0       -- Note [Nested functions] 
-                           CaseCont   -> not lone_variable || not is_value     -- Note [Lone variables]
-                           InterestingCont -> True     -- Something else interesting about continuation
+                           BoringCtxt -> not is_top && n_vals_wanted > 0       -- Note [Nested functions] 
+                           CaseCtxt   -> not lone_variable || not is_value     -- Note [Lone variables]
+                           ArgCtxt {} -> True
+                               -- Was: n_vals_wanted > 0; but see test eyeball/inline1.hs
 
                    small_enough = (size - discount) <= opt_UF_UseThreshold
                    discount = computeDiscount n_vals_wanted arg_discounts 
                                               res_discount' arg_infos
                    res_discount' = case cont_info of
-                                       BoringCont      -> 0
-                                       CaseCont        -> res_discount
-                                       InterestingCont -> 4 `min` res_discount
+                                       BoringCtxt  -> 0
+                                       CaseCtxt    -> res_discount
+                                       ArgCtxt _ _ -> 4 `min` res_discount
                        -- res_discount can be very large when a function returns
                        -- construtors; but we only want to invoke that large discount
                        -- when there's a case continuation.
@@ -611,8 +619,7 @@ callSiteInline dflags active_inline id lone_variable arg_infos cont_info
        pprTrace "Considering inlining"
                 (ppr id <+> vcat [text "active:" <+> ppr active_inline,
                                   text "arg infos" <+> ppr arg_infos,
-                                  text "interesting continuation" <+> ppr cont_info <+> 
-                                       ppr n_val_args,
+                                  text "interesting continuation" <+> ppr cont_info,
                                   text "is value:" <+> ppr is_value,
                                   text "is cheap:" <+> ppr is_cheap,
                                   text "guidance" <+> ppr guidance,
@@ -623,16 +630,6 @@ callSiteInline dflags active_inline id lone_variable arg_infos cont_info
     }
 \end{code}
 
-Note [Enough args]
-~~~~~~~~~~~~~~~~~~
-At one stage we considered only inlining a function that has enough
-arguments to saturate its arity.  But we can lose from this. For
-example (f . g) might not be a saturated application of (.), but
-nevertheless f and g might usefully optimise with each other if we
-inlined (.) and f and g.  
-
-Current story (Jan08): inline even if not saturated.
-
 Note [Nested functions]
 ~~~~~~~~~~~~~~~~~~~~~~~
 If a function has a nested defn we also record some-benefit, on the
@@ -646,7 +643,7 @@ increase the chance that the constructor won't be allocated at all in
 the branches that don't use it.
 
 Note [Lone variables]
-~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 The "lone-variable" case is important.  I spent ages messing about
 with unsatisfactory varaints, but this is nice.  The idea is that if a
 variable appears all alone