Fixed warnings in coreSyn/CoreSubst
[ghc-hetmet.git] / compiler / coreSyn / CoreUnfold.lhs
index 9d71b73..d8e0cb0 100644 (file)
@@ -57,7 +57,6 @@ import Bag
 import FastTypes
 import Outputable
 
-import GHC.Exts                ( Int# )
 \end{code}
 
 
@@ -182,7 +181,7 @@ calcUnfoldingGuidance bOMB_OUT_SIZE expr
 \end{code}
 
 \begin{code}
-sizeExpr :: Int#           -- Bomb out if it gets bigger than this
+sizeExpr :: FastInt        -- Bomb out if it gets bigger than this
         -> [Id]            -- Arguments; we're interested in which of these
                            -- get case'd
         -> CoreExpr
@@ -242,7 +241,7 @@ sizeExpr bOMB_OUT_SIZE top_args expr
 
            case alts of
 
-               [alt] -> size_up_alt alt `addSize` SizeIs 0# (unitBag (v, 1)) 0#
+               [alt] -> size_up_alt alt `addSize` SizeIs (_ILIT(0)) (unitBag (v, 1)) (_ILIT(0))
                -- We want to make wrapper-style evaluation look cheap, so that
                -- when we inline a wrapper it doesn't make call site (much) bigger
                -- Otherwise we get nasty phase ordering stuff: 
@@ -270,7 +269,7 @@ sizeExpr bOMB_OUT_SIZE top_args expr
                -- the case when we are scrutinising an argument variable
          alts_size (SizeIs tot tot_disc tot_scrut)             -- Size of all alternatives
                    (SizeIs max max_disc max_scrut)             -- Size of biggest alternative
-               = SizeIs tot (unitBag (v, iBox (_ILIT 1 +# tot -# max)) `unionBags` max_disc) max_scrut
+               = SizeIs tot (unitBag (v, iBox (_ILIT(1) +# tot -# max)) `unionBags` max_disc) max_scrut
                        -- If the variable is known, we produce a discount that
                        -- will take us back to 'max', the size of rh largest alternative
                        -- The 1+ is a little discount for reduced allocation in the caller
@@ -335,7 +334,7 @@ sizeExpr bOMB_OUT_SIZE top_args expr
 
     ------------
        -- We want to record if we're case'ing, or applying, an argument
-    fun_discount v | v `elem` top_args = SizeIs 0# (unitBag (v, opt_UF_FunAppDiscount)) 0#
+    fun_discount v | v `elem` top_args = SizeIs (_ILIT(0)) (unitBag (v, opt_UF_FunAppDiscount)) (_ILIT(0))
     fun_discount other                = sizeZero
 
     ------------
@@ -373,12 +372,12 @@ maxSize _              TooBig                               = TooBig
 maxSize s1@(SizeIs n1 _ _) s2@(SizeIs n2 _ _) | n1 ># n2  = s1
                                              | otherwise = s2
 
-sizeZero       = SizeIs (_ILIT 0)  emptyBag (_ILIT 0)
-sizeOne        = SizeIs (_ILIT 1)  emptyBag (_ILIT 0)
-sizeN n        = SizeIs (iUnbox n) emptyBag (_ILIT 0)
+sizeZero       = SizeIs (_ILIT(0))  emptyBag (_ILIT(0))
+sizeOne        = SizeIs (_ILIT(1))  emptyBag (_ILIT(0))
+sizeN n        = SizeIs (iUnbox n) emptyBag (_ILIT(0))
 conSizeN dc n   
-  | isUnboxedTupleCon dc = SizeIs (_ILIT 0) emptyBag (iUnbox n +# _ILIT 1)
-  | otherwise           = SizeIs (_ILIT 1) emptyBag (iUnbox n +# _ILIT 1)
+  | isUnboxedTupleCon dc = SizeIs (_ILIT(0)) emptyBag (iUnbox n +# _ILIT(1))
+  | otherwise           = SizeIs (_ILIT(1)) emptyBag (iUnbox n +# _ILIT(1))
        -- Treat constructors as size 1; we are keen to expose them
        -- (and we charge separately for their args).  We can't treat
        -- them as size zero, else we find that (iBox x) has size 1,
@@ -404,7 +403,7 @@ primOpSize op n_args
        -- and there's a good chance it'll get inlined back into C's RHS. Urgh!
  | otherwise               = sizeOne
 
-buildSize = SizeIs (-2#) emptyBag 4#
+buildSize = SizeIs (_ILIT(-2)) emptyBag (_ILIT(4))
        -- We really want to inline applications of build
        -- build t (\cn -> e) should cost only the cost of e (because build will be inlined later)
        -- Indeed, we should add a result_discount becuause build is 
@@ -412,11 +411,11 @@ buildSize = SizeIs (-2#) emptyBag 4#
        -- build is saturated (it usually is).  The "-2" discounts for the \c n, 
        -- The "4" is rather arbitrary.
 
-augmentSize = SizeIs (-2#) emptyBag 4#
+augmentSize = SizeIs (_ILIT(-2)) emptyBag (_ILIT(4))
        -- Ditto (augment t (\cn -> e) ys) should cost only the cost of
        -- e plus ys. The -2 accounts for the \cn 
                                                
-nukeScrutDiscount (SizeIs n vs d) = SizeIs n vs 0#
+nukeScrutDiscount (SizeIs n vs d) = SizeIs n vs (_ILIT(0))
 nukeScrutDiscount TooBig         = TooBig
 
 -- When we return a lambda, give a discount if it's used (applied)
@@ -497,7 +496,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.  Tt turns out that the convenient way to prevent
+It just makes the code bigger.  It turns out that the convenient way to prevent
 them inlining is to give them a NOINLINE pragma, which we do in 
 StrictAnal.addStrictnessInfoToTopId
 
@@ -563,10 +562,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
@@ -584,7 +583,7 @@ callSiteInline dflags active_inline id lone_variable arg_infos cont_info
                        = 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 -> n_vals_wanted > 0
+                           InterestingCont -> True     -- Something else interesting about continuation
 
                    small_enough = (size - discount) <= opt_UF_UseThreshold
                    discount = computeDiscount n_vals_wanted arg_discounts 
@@ -605,7 +604,8 @@ 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,
+                                  text "interesting continuation" <+> ppr cont_info <+> 
+                                       ppr n_val_args,
                                   text "is value:" <+> ppr is_value,
                                   text "is cheap:" <+> ppr is_cheap,
                                   text "guidance" <+> ppr guidance,
@@ -616,6 +616,16 @@ 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
@@ -629,7 +639,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