[project @ 1996-07-19 18:36:04 by partain]
[ghc-hetmet.git] / ghc / compiler / simplCore / SimplCore.lhs
index eea0443..0d3c544 100644 (file)
@@ -8,7 +8,8 @@
 
 module SimplCore ( core2core ) where
 
-import Ubiq{-uitous-}
+IMP_Ubiq(){-uitous-}
+IMPORT_1_3(IO(hPutStr,stderr))
 
 import AnalFBWW                ( analFBWW )
 import Bag             ( isEmptyBag, foldBag )
@@ -33,15 +34,16 @@ import CmdLineOpts  ( CoreToDo(..), SimplifierSwitch(..), switchIsOn,
 import CoreLint                ( lintCoreBindings )
 import CoreSyn
 import CoreUnfold
-import CoreUtils       ( substCoreBindings, manifestlyWHNF )
+import CoreUtils       ( substCoreBindings )
 import ErrUtils                ( ghcExit )
+import FiniteMap       ( FiniteMap )
 import FloatIn         ( floatInwards )
 import FloatOut                ( floatOutwards )
 import FoldrBuildWW    ( mkFoldrBuildWW )
 import Id              ( idType, toplevelishId, idWantsToBeINLINEd,
-                         unfoldingUnfriendlyId,
+                         unfoldingUnfriendlyId, isWrapperId,
                          nullIdEnv, addOneToIdEnv, delOneFromIdEnv,
-                         lookupIdEnv, IdEnv(..),
+                         lookupIdEnv, SYN_IE(IdEnv),
                          GenId{-instance Outputable-}
                        )
 import IdInfo          ( mkUnfolding )
@@ -49,15 +51,13 @@ import LiberateCase ( liberateCase )
 import MagicUFs                ( MagicUnfoldingFun )
 import Maybes          ( maybeToBool )
 import Outputable      ( Outputable(..){-instance * (,) -} )
-import PprCore         ( pprCoreBinding, GenCoreExpr{-instance Outputable-} )
+import PprCore
 import PprStyle                ( PprStyle(..) )
 import PprType         ( GenType{-instance Outputable-}, GenTyVar{-ditto-} )
 import Pretty          ( ppShow, ppAboves, ppAbove, ppCat, ppStr )
 import SAT             ( doStaticArgs )
-import SCCauto         ( addAutoCostCentres )
 import SimplMonad      ( zeroSimplCount, showSimplCount, SimplCount )
 import SimplPgm                ( simplifyPgm )
-import SimplVar                ( leastItCouldCost )
 import Specialise
 import SpecUtils       ( pprSpecErrs )
 import StrictAnal      ( saWwTopBinds )
@@ -72,7 +72,6 @@ import DefUtils               ( deforestable )
 #endif
 
 isWrapperFor = panic "SimplCore.isWrapperFor (ToDo)"
-isWrapperId = panic "SimplCore.isWrapperId (ToDo)"
 \end{code}
 
 \begin{code}
@@ -85,12 +84,11 @@ core2core :: [CoreToDo]                     -- spec of what core-to-core passes to do
          -> [CoreBinding]              -- input...
          -> IO
              ([CoreBinding],   -- results: program, plus...
-              IdEnv UnfoldingDetails,  --  unfoldings to be exported from here
+              IdEnv Unfolding, --  unfoldings to be exported from here
              SpecialiseData)           --  specialisation data
 
 core2core core_todos module_name ppr_style us local_tycons tycon_specs binds
-  = BSCC("Core2Core")
-    if null core_todos then -- very rare, I suspect...
+  = if null core_todos then -- very rare, I suspect...
        -- well, we still must do some renumbering
        return (
        (substCoreBindings nullIdEnv nullTyVarEnv binds us,
@@ -118,7 +116,6 @@ core2core core_todos module_name ppr_style us local_tycons tycon_specs binds
        ) >>
 
        return (processed_binds, inline_env, spec_data)
-    ESCC
   where
     init_specdata = initSpecData local_tycons tycon_specs
 
@@ -142,7 +139,7 @@ core2core core_todos module_name ppr_style us local_tycons tycon_specs binds
        in
        case to_do of
          CoreDoSimplify simpl_sw_chkr
-           -> BSCC("CoreSimplify")
+           -> _scc_ "CoreSimplify"
               begin_pass ("Simplify" ++ if switchIsOn simpl_sw_chkr SimplDoFoldrBuild
                                         then " (foldr/build)" else "") >>
               case (simplifyPgm binds simpl_sw_chkr simpl_stats us1) of
@@ -151,76 +148,66 @@ core2core core_todos module_name ppr_style us local_tycons tycon_specs binds
                               ("Simplify (" ++ show it_cnt ++ ")"
                                 ++ if switchIsOn simpl_sw_chkr SimplDoFoldrBuild
                                    then " foldr/build" else "")
-              ESCC
 
          CoreDoFoldrBuildWorkerWrapper
-           -> BSCC("CoreDoFoldrBuildWorkerWrapper")
+           -> _scc_ "CoreDoFoldrBuildWorkerWrapper"
               begin_pass "FBWW" >>
               case (mkFoldrBuildWW us1 binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "FBWW"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "FBWW" }
 
          CoreDoFoldrBuildWWAnal
-           -> BSCC("CoreDoFoldrBuildWWAnal")
+           -> _scc_ "CoreDoFoldrBuildWWAnal"
               begin_pass "AnalFBWW" >>
               case (analFBWW binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "AnalFBWW"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "AnalFBWW" }
 
          CoreLiberateCase
-           -> BSCC("LiberateCase")
+           -> _scc_ "LiberateCase"
               begin_pass "LiberateCase" >>
               case (liberateCase lib_case_threshold binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "LiberateCase"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "LiberateCase" }
 
          CoreDoCalcInlinings1  -- avoid inlinings w/ cost-centres
-           -> BSCC("CoreInlinings1")
+           -> _scc_ "CoreInlinings1"
               begin_pass "CalcInlinings" >>
               case (calcInlinings False inline_env binds) of { inline_env2 ->
-              end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings"
-              } ESCC
+              end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" }
 
          CoreDoCalcInlinings2  -- allow inlinings w/ cost-centres
-           -> BSCC("CoreInlinings2")
+           -> _scc_ "CoreInlinings2"
               begin_pass "CalcInlinings" >>
               case (calcInlinings True inline_env binds) of { inline_env2 ->
-              end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings"
-              } ESCC
+              end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" }
 
          CoreDoFloatInwards
-           -> BSCC("FloatInwards")
+           -> _scc_ "FloatInwards"
               begin_pass "FloatIn" >>
               case (floatInwards binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatIn"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatIn" }
 
          CoreDoFullLaziness
-           -> BSCC("CoreFloating")
+           -> _scc_ "CoreFloating"
               begin_pass "FloatOut" >>
               case (floatOutwards us1 binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatOut"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatOut" }
 
          CoreDoStaticArgs
-           -> BSCC("CoreStaticArgs")
+           -> _scc_ "CoreStaticArgs"
               begin_pass "StaticArgs" >>
               case (doStaticArgs binds us1) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "StaticArgs"
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "StaticArgs" }
                -- Binds really should be dependency-analysed for static-
                -- arg transformation... Not to worry, they probably are.
                -- (I don't think it *dies* if they aren't [WDP 94/04/15])
-              } ESCC
 
          CoreDoStrictness
-           -> BSCC("CoreStranal")
+           -> _scc_ "CoreStranal"
               begin_pass "StrAnal" >>
               case (saWwTopBinds us1 binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "StrAnal"
-              } ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "StrAnal" }
 
          CoreDoSpecialising
-           -> BSCC("Specialise")
+           -> _scc_ "Specialise"
               begin_pass "Specialise" >>
               case (specProgram us1 binds spec_data) of {
                 (p, spec_data2@(SpecData _ spec_noerrs _ _ _
@@ -242,32 +229,20 @@ core2core core_todos module_name ppr_style us local_tycons tycon_specs binds
 
                   end_pass False us2 p inline_env spec_data2 simpl_stats "Specialise"
               }
-              ESCC
 
          CoreDoDeforest
 #if OMIT_DEFORESTER
            -> error "ERROR: CoreDoDeforest: not built into compiler\n"
 #else
-           -> BSCC("Deforestation")
+           -> _scc_ "Deforestation"
               begin_pass "Deforestation" >>
               case (deforestProgram binds us1) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "Deforestation"
-              }
-              ESCC
+              end_pass False us2 binds2 inline_env spec_data simpl_stats "Deforestation" }
 #endif
 
-         CoreDoAutoCostCentres
-           -> BSCC("AutoSCCs")
-              begin_pass "AutoSCCs" >>
-              case (addAutoCostCentres module_name binds) of { binds2 ->
-              end_pass False us2 binds2 inline_env spec_data simpl_stats "AutoSCCs"
-              }
-              ESCC
-
          CoreDoPrintCore       -- print result of last pass
            -> end_pass True us2 binds inline_env spec_data simpl_stats "Print"
 
-
     -------------------------------------------------
 
     begin_pass
@@ -328,9 +303,9 @@ will be visible on the other side of an interface, too.
 
 \begin{code}
 calcInlinings :: Bool  -- True => inlinings with _scc_s are OK
-             -> IdEnv UnfoldingDetails
+             -> IdEnv Unfolding
              -> [CoreBinding]
-             -> IdEnv UnfoldingDetails
+             -> IdEnv Unfolding
 
 calcInlinings scc_s_OK inline_env_so_far top_binds
   = let
@@ -342,9 +317,9 @@ calcInlinings scc_s_OK inline_env_so_far top_binds
     pp_item (binder, details)
       = ppCat [ppr PprDebug binder, ppStr "=>", pp_det details]
       where
-       pp_det NoUnfoldingDetails   = ppStr "_N_"
+       pp_det NoUnfolding   = ppStr "_N_"
 --LATER:       pp_det (IWantToBeINLINEd _) = ppStr "INLINE"
-       pp_det (GenForm _ _ expr guide)
+       pp_det (CoreUnfolding (SimpleUnfolding _ guide expr))
          = ppAbove (ppr PprDebug guide) (ppr PprDebug expr)
        pp_det other                = ppStr "???"
 
@@ -385,7 +360,7 @@ calcInlinings scc_s_OK inline_env_so_far top_binds
 
       | rhs_mentions_an_unmentionable
       || (not explicit_INLINE_requested
-         && (rhs_looks_like_a_caf || guidance_says_don't || guidance_size_too_big))
+         && (rhs_looks_like_a_caf || guidance_size_too_big))
       = let
            my_my_trace
              = if explicit_INLINE_requested
@@ -452,38 +427,16 @@ calcInlinings scc_s_OK inline_env_so_far top_binds
        guidance_size
          = case guidance of
              UnfoldAlways                -> 0 -- *extremely* small
-             EssentialUnfolding          -> 0 -- ditto
              UnfoldIfGoodArgs _ _ _ size -> size
 
-       guidance_says_don't = case guidance of { UnfoldNever -> True; _ -> False }
-
        guidance_size_too_big
            -- Does the guidance suggest that this unfolding will
            -- be of no use *no matter* the arguments given to it?
            -- Could be more sophisticated...
-         = case guidance of
-             UnfoldAlways       -> False
-             EssentialUnfolding -> False
-             UnfoldIfGoodArgs _ no_val_args arg_info_vec size
-
-               -> if explicit_creation_threshold then
-                     False     -- user set threshold; don't second-guess...
-
-                  else if no_val_args == 0 && rhs_looks_like_a_data_val then
-                     False     -- we'd like a top-level data constr to be
-                               -- visible even if it is never unfolded
-                  else
-                     let
-                         cost
-                           = leastItCouldCost con_discount_weight size no_val_args
-                               arg_info_vec rhs_arg_tys
-                     in
---                   (if (unfold_use_threshold < cost) then (pprTrace "cost:" (ppInt cost)) else \x->x ) (
-                     unfold_use_threshold < cost
---                   )
+         = not (couldBeSmallEnoughToInline con_discount_weight unfold_use_threshold guidance)
 
 
-       rhs_looks_like_a_caf = not (manifestlyWHNF rhs)
+       rhs_looks_like_a_caf = not (whnfOrBottom rhs)
 
        rhs_looks_like_a_data_val
          = case (collectBinders rhs) of