[project @ 2001-03-30 14:50:18 by rrt]
[ghc-hetmet.git] / ghc / compiler / coreSyn / CoreUnfold.lhs
index 102d8bc..7db6f2d 100644 (file)
@@ -42,14 +42,14 @@ import CoreSyn
 import PprCore         ( pprCoreExpr )
 import OccurAnal       ( occurAnalyseGlobalExpr )
 import CoreUtils       ( exprIsValue, exprIsCheap, exprIsTrivial )
-import Id              ( Id, idType, idFlavour, isId,
+import Id              ( Id, idType, isId,
                          idSpecialisation, idInlinePragma, idUnfolding,
-                         isPrimOpId_maybe
+                         isPrimOpId_maybe, globalIdDetails
                        )
 import VarSet
-import Literal         ( isLitLitLit, litIsDupable )
+import Literal         ( isLitLitLit, litSize )
 import PrimOp          ( PrimOp(..), primOpIsDupable, primOpOutOfLine, ccallIsCasm )
-import IdInfo          ( InlinePragInfo(..), OccInfo(..), IdFlavour(..),
+import IdInfo          ( InlinePragInfo(..), OccInfo(..), GlobalIdDetails(..),
                          isNeverInlinePrag
                        )
 import Type            ( isUnLiftedType )
@@ -188,13 +188,20 @@ sizeExpr bOMB_OUT_SIZE top_args expr
     size_up (Type t)         = sizeZero        -- Types cost nothing
     size_up (Var v)           = sizeOne
 
-    size_up (Note _ body)     = size_up body   -- Notes cost nothing
+    size_up (Note InlineMe body) = sizeOne     -- Inline notes make it look very small
+       -- This can be important.  If you have an instance decl like this:
+       --      instance Foo a => Foo [a] where
+       --         {-# INLINE op1, op2 #-}
+       --         op1 = ...
+       --         op2 = ...
+       -- then we'll get a dfun which is a pair of two INLINE lambdas
+
+    size_up (Note _        body) = size_up body        -- Other notes cost nothing
 
     size_up (App fun (Type t)) = size_up fun
     size_up (App fun arg)      = size_up_app fun [arg]
 
-    size_up (Lit lit) | litIsDupable lit = sizeOne
-                     | otherwise        = sizeN opt_UF_DearOp  -- For lack of anything better
+    size_up (Lit lit)         = sizeN (litSize lit)
 
     size_up (Lam b e) | isId b    = lamScrutDiscount (size_up e `addSizeN` 1)
                      | otherwise = size_up e
@@ -289,7 +296,7 @@ sizeExpr bOMB_OUT_SIZE top_args expr
       | fun `hasKey` buildIdKey   = buildSize
       | fun `hasKey` augmentIdKey = augmentSize
       | otherwise 
-      = case idFlavour fun of
+      = case globalIdDetails fun of
          DataConId dc -> conSizeN (valArgCount args)
 
          PrimOpId op  -> primOpSize op (valArgCount args)
@@ -572,7 +579,9 @@ callSiteInline dflags black_listed inline_call occ id arg_infos interesting_cont
                -- Note: there used to be a '&& not top_level' in the guard above,
                --       but that stopped us inlining top-level functions used only once,
                --       which is stupid
-         = not in_lam || not (null arg_infos) || interesting_cont
+         = WARN( not in_lam, ppr id )  -- If (not in_lam) && one_br then PreInlineUnconditionally
+                                       -- should have caught it, shouldn't it?
+           not (null arg_infos) || interesting_cont
 
          | otherwise
          = case guidance of
@@ -615,7 +624,6 @@ callSiteInline dflags black_listed inline_call occ id arg_infos interesting_cont
                                                 arg_infos really_interesting_cont
                
     in    
-#ifdef DEBUG
     if dopt Opt_D_dump_inlinings dflags then
        pprTrace "Considering inlining"
                 (ppr id <+> vcat [text "black listed:" <+> ppr black_listed,
@@ -631,7 +639,6 @@ callSiteInline dflags black_listed inline_call occ id arg_infos interesting_cont
                                   else empty])
                  result
     else
-#endif
     result
     }