Cheng Shao pushed to branch wip/ghci-no-simpl at Glasgow Haskell Compiler / GHC
Commits:
-
5d35dc97
by Cheng Shao at 2025-09-14T12:35:55+02:00
-
c307ec77
by Cheng Shao at 2025-09-14T12:35:55+02:00
4 changed files:
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Main.hs
Changes:
| ... | ... | @@ -6,7 +6,7 @@ |
| 6 | 6 | |
| 7 | 7 | {-# LANGUAGE CPP #-}
|
| 8 | 8 | |
| 9 | -module GHC.Core.Opt.Pipeline ( core2core, simplifyExpr ) where
|
|
| 9 | +module GHC.Core.Opt.Pipeline ( core2core ) where
|
|
| 10 | 10 | |
| 11 | 11 | import GHC.Prelude
|
| 12 | 12 | |
| ... | ... | @@ -27,7 +27,7 @@ import GHC.Core.Ppr ( pprCoreBindings ) |
| 27 | 27 | import GHC.Core.Utils ( dumpIdInfoOfProgram )
|
| 28 | 28 | import GHC.Core.Lint ( lintAnnots )
|
| 29 | 29 | import GHC.Core.Lint.Interactive ( interactiveInScope )
|
| 30 | -import GHC.Core.Opt.Simplify ( simplifyExpr, simplifyPgm )
|
|
| 30 | +import GHC.Core.Opt.Simplify ( simplifyPgm )
|
|
| 31 | 31 | import GHC.Core.Opt.Simplify.Monad
|
| 32 | 32 | import GHC.Core.Opt.Monad
|
| 33 | 33 | import GHC.Core.Opt.Pipeline.Types
|
| 1 | 1 | {-# LANGUAGE CPP #-}
|
| 2 | 2 | |
| 3 | 3 | module GHC.Core.Opt.Simplify
|
| 4 | - ( SimplifyExprOpts(..), SimplifyOpts(..)
|
|
| 5 | - , simplifyExpr, simplifyPgm
|
|
| 4 | + ( SimplifyOpts(..)
|
|
| 5 | + , simplifyPgm
|
|
| 6 | 6 | ) where
|
| 7 | 7 | |
| 8 | 8 | import GHC.Prelude
|
| ... | ... | @@ -11,20 +11,18 @@ import GHC.Driver.Flags |
| 11 | 11 | |
| 12 | 12 | import GHC.Core
|
| 13 | 13 | import GHC.Core.Rules
|
| 14 | -import GHC.Core.Ppr ( pprCoreBindings, pprCoreExpr )
|
|
| 15 | -import GHC.Core.Opt.OccurAnal ( occurAnalysePgm, occurAnalyseExpr )
|
|
| 16 | -import GHC.Core.Stats ( coreBindsSize, coreBindsStats, exprSize )
|
|
| 14 | +import GHC.Core.Ppr ( pprCoreBindings )
|
|
| 15 | +import GHC.Core.Opt.OccurAnal ( occurAnalysePgm )
|
|
| 16 | +import GHC.Core.Stats ( coreBindsSize, coreBindsStats )
|
|
| 17 | 17 | import GHC.Core.Utils ( mkTicks, stripTicksTop )
|
| 18 | 18 | import GHC.Core.Lint ( LintPassResultConfig, dumpPassResult, lintPassResult )
|
| 19 | -import GHC.Core.Opt.Simplify.Iteration ( simplTopBinds, simplExpr, simplImpRules )
|
|
| 19 | +import GHC.Core.Opt.Simplify.Iteration ( simplTopBinds, simplImpRules )
|
|
| 20 | 20 | import GHC.Core.Opt.Simplify.Utils ( activeRule )
|
| 21 | 21 | import GHC.Core.Opt.Simplify.Inline ( activeUnfolding )
|
| 22 | 22 | import GHC.Core.Opt.Simplify.Env
|
| 23 | 23 | import GHC.Core.Opt.Simplify.Monad
|
| 24 | 24 | import GHC.Core.Opt.Stats ( simplCountN )
|
| 25 | -import GHC.Core.FamInstEnv
|
|
| 26 | 25 | |
| 27 | -import GHC.Utils.Error ( withTiming )
|
|
| 28 | 26 | import GHC.Utils.Logger as Logger
|
| 29 | 27 | import GHC.Utils.Outputable
|
| 30 | 28 | import GHC.Utils.Constants (debugIsOn)
|
| ... | ... | @@ -44,72 +42,6 @@ import GHC.Types.Unique.FM |
| 44 | 42 | import Control.Monad
|
| 45 | 43 | import Data.Foldable ( for_ )
|
| 46 | 44 | |
| 47 | -{-
|
|
| 48 | -************************************************************************
|
|
| 49 | -* *
|
|
| 50 | - Gentle simplification
|
|
| 51 | -* *
|
|
| 52 | -************************************************************************
|
|
| 53 | --}
|
|
| 54 | - |
|
| 55 | --- | Configuration record for `simplifyExpr`.
|
|
| 56 | --- The values of this datatype are /only/ driven by the demands of that function.
|
|
| 57 | -data SimplifyExprOpts = SimplifyExprOpts
|
|
| 58 | - { se_fam_inst :: ![FamInst]
|
|
| 59 | - , se_mode :: !SimplMode
|
|
| 60 | - , se_top_env_cfg :: !TopEnvConfig
|
|
| 61 | - }
|
|
| 62 | - |
|
| 63 | -simplifyExpr :: Logger
|
|
| 64 | - -> ExternalUnitCache
|
|
| 65 | - -> SimplifyExprOpts
|
|
| 66 | - -> CoreExpr
|
|
| 67 | - -> IO CoreExpr
|
|
| 68 | --- ^ Simplify an expression using 'simplExprGently'.
|
|
| 69 | ---
|
|
| 70 | --- See 'simplExprGently' for details.
|
|
| 71 | -simplifyExpr logger euc opts expr
|
|
| 72 | - = withTiming logger (text "Simplify [expr]") (const ()) $
|
|
| 73 | - do { eps <- eucEPS euc ;
|
|
| 74 | - ; let fam_envs = ( eps_fam_inst_env eps
|
|
| 75 | - , extendFamInstEnvList emptyFamInstEnv $ se_fam_inst opts
|
|
| 76 | - )
|
|
| 77 | - simpl_env = mkSimplEnv (se_mode opts) fam_envs
|
|
| 78 | - top_env_cfg = se_top_env_cfg opts
|
|
| 79 | - read_eps_rules = eps_rule_base <$> eucEPS euc
|
|
| 80 | - read_ruleenv = updExternalPackageRules emptyRuleEnv <$> read_eps_rules
|
|
| 81 | - |
|
| 82 | - ; let sz = exprSize expr
|
|
| 83 | - |
|
| 84 | - ; (expr', counts) <- initSmpl logger read_ruleenv top_env_cfg sz $
|
|
| 85 | - simplExprGently simpl_env expr
|
|
| 86 | - |
|
| 87 | - ; Logger.putDumpFileMaybe logger Opt_D_dump_simpl_stats
|
|
| 88 | - "Simplifier statistics" FormatText (pprSimplCount counts)
|
|
| 89 | - |
|
| 90 | - ; Logger.putDumpFileMaybe logger Opt_D_dump_simpl "Simplified expression"
|
|
| 91 | - FormatCore
|
|
| 92 | - (pprCoreExpr expr')
|
|
| 93 | - |
|
| 94 | - ; return expr'
|
|
| 95 | - }
|
|
| 96 | - |
|
| 97 | -simplExprGently :: SimplEnv -> CoreExpr -> SimplM CoreExpr
|
|
| 98 | --- ^ Simplifies an expression by doing occurrence analysis, then simplification,
|
|
| 99 | --- and repeating (twice currently), because one pass alone leaves tons of crud.
|
|
| 100 | ---
|
|
| 101 | --- Used only:
|
|
| 102 | ---
|
|
| 103 | --- 1. for user expressions typed in at the interactive prompt (see 'GHC.Driver.Main.hscStmt'),
|
|
| 104 | --- 2. for Template Haskell splices (see 'GHC.Tc.Gen.Splice.runMeta').
|
|
| 105 | ---
|
|
| 106 | --- The name 'Gently' suggests that the SimplMode is InitialPhase,
|
|
| 107 | --- and in fact that is so.... but the 'Gently' in 'simplExprGently' doesn't
|
|
| 108 | --- enforce that; it just simplifies the expression twice.
|
|
| 109 | -simplExprGently env expr = do
|
|
| 110 | - expr1 <- simplExpr env (occurAnalyseExpr expr)
|
|
| 111 | - simplExpr env (occurAnalyseExpr expr1)
|
|
| 112 | - |
|
| 113 | 45 | {-
|
| 114 | 46 | ************************************************************************
|
| 115 | 47 | * *
|
| 1 | 1 | module GHC.Driver.Config.Core.Opt.Simplify
|
| 2 | - ( initSimplifyExprOpts
|
|
| 3 | - , initSimplifyOpts
|
|
| 2 | + ( initSimplifyOpts
|
|
| 4 | 3 | , initSimplMode
|
| 5 | 4 | , initGentleSimplMode
|
| 6 | 5 | ) where
|
| ... | ... | @@ -9,7 +8,7 @@ import GHC.Prelude |
| 9 | 8 | |
| 10 | 9 | import GHC.Core.Rules ( RuleBase )
|
| 11 | 10 | import GHC.Core.Opt.Pipeline.Types ( CoreToDo(..) )
|
| 12 | -import GHC.Core.Opt.Simplify ( SimplifyExprOpts(..), SimplifyOpts(..) )
|
|
| 11 | +import GHC.Core.Opt.Simplify ( SimplifyOpts(..) )
|
|
| 13 | 12 | import GHC.Core.Opt.Simplify.Env ( FloatEnable(..), SimplMode(..), SimplPhase(..) )
|
| 14 | 13 | import GHC.Core.Opt.Simplify.Monad ( TopEnvConfig(..) )
|
| 15 | 14 | |
| ... | ... | @@ -19,26 +18,9 @@ import GHC.Driver.Config.Core.Rules ( initRuleOpts ) |
| 19 | 18 | import GHC.Driver.Config.Core.Opt.Arity ( initArityOpts )
|
| 20 | 19 | import GHC.Driver.DynFlags ( DynFlags(..), GeneralFlag(..), gopt )
|
| 21 | 20 | |
| 22 | -import GHC.Runtime.Context ( InteractiveContext(..) )
|
|
| 23 | - |
|
| 24 | 21 | import GHC.Types.Basic ( CompilerPhase(..) )
|
| 25 | 22 | import GHC.Types.Var ( Var )
|
| 26 | 23 | |
| 27 | -initSimplifyExprOpts :: DynFlags -> InteractiveContext -> SimplifyExprOpts
|
|
| 28 | -initSimplifyExprOpts dflags ic = SimplifyExprOpts
|
|
| 29 | - { se_fam_inst = snd $ ic_instances ic
|
|
| 30 | - , se_mode = (initSimplMode dflags InitialPhase "GHCi")
|
|
| 31 | - { sm_inline = False
|
|
| 32 | - -- Do not do any inlining, in case we expose some
|
|
| 33 | - -- unboxed tuple stuff that confuses the bytecode
|
|
| 34 | - -- interpreter
|
|
| 35 | - }
|
|
| 36 | - , se_top_env_cfg = TopEnvConfig
|
|
| 37 | - { te_history_size = historySize dflags
|
|
| 38 | - , te_tick_factor = simplTickFactor dflags
|
|
| 39 | - }
|
|
| 40 | - }
|
|
| 41 | - |
|
| 42 | 24 | initSimplifyOpts :: DynFlags -> [Var] -> Int -> SimplMode -> RuleBase -> SimplifyOpts
|
| 43 | 25 | initSimplifyOpts dflags extra_vars iterations mode hpt_rule_base = let
|
| 44 | 26 | -- This is a particularly ugly construction, but we will get rid of it in !8341.
|
| ... | ... | @@ -2709,28 +2709,35 @@ hscCompileCoreExpr hsc_env loc expr = |
| 2709 | 2709 | Just h -> h hsc_env loc expr
|
| 2710 | 2710 | |
| 2711 | 2711 | hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO (ForeignHValue, [Linkable], PkgsLoaded)
|
| 2712 | -hscCompileCoreExpr' hsc_env srcspan ds_expr = do
|
|
| 2713 | - {- Simplify it -}
|
|
| 2714 | - let dflags = hsc_dflags hsc_env
|
|
| 2712 | +hscCompileCoreExpr' hsc_env' srcspan ds_expr = do
|
|
| 2713 | + -- Use modified `dflags` and session that sets -O0 and do less work
|
|
| 2714 | + -- throughout the Core -> ByteCode pipeline under
|
|
| 2715 | + -- `-funoptimized-core-for-interpreter`, even if current session
|
|
| 2716 | + -- enables `-O1` or above.
|
|
| 2717 | + let dflags' = hsc_dflags hsc_env'
|
|
| 2718 | + unopt = gopt Opt_UnoptimizedCoreForInterpreter dflags'
|
|
| 2719 | + dflags
|
|
| 2720 | + | unopt = updOptLevel 0 dflags'
|
|
| 2721 | + | otherwise = dflags'
|
|
| 2722 | + hsc_env
|
|
| 2723 | + | unopt = hsc_env' {hsc_dflags = dflags}
|
|
| 2724 | + | otherwise = hsc_env'
|
|
| 2715 | 2725 | let logger = hsc_logger hsc_env
|
| 2716 | 2726 | |
| 2727 | + {- Simplify it -}
|
|
| 2717 | 2728 | let simpl_expr
|
| 2718 | - -- Do less work under `-funoptimized-core-for-interpreter`,
|
|
| 2719 | - -- use modified `dflags` that sets `-O0` here even if current
|
|
| 2720 | - -- session enables `-O1` or above.
|
|
| 2721 | - --
|
|
| 2722 | 2729 | -- When generating bytecode for ghci via `hscParsedStmt`, we
|
| 2723 | 2730 | -- still need to enable inlining! For `let foo = Foo ...`, the
|
| 2724 | 2731 | -- ghci debugger expects `:print foo` to show `foo = <Foo> ...`
|
| 2725 | 2732 | -- without forcing `foo` first, without inlining `foo`
|
| 2726 | 2733 | -- would remain a top-level thunk instead of a datacon
|
| 2727 | 2734 | -- closure. We can skip inlining for TH splices though.
|
| 2728 | - | gopt Opt_UnoptimizedCoreForInterpreter dflags =
|
|
| 2735 | + | unopt =
|
|
| 2729 | 2736 | ( if srcspan == interactiveSrcSpan
|
| 2730 | 2737 | then simpleOptExpr
|
| 2731 | 2738 | else simpleOptExprNoInline
|
| 2732 | 2739 | )
|
| 2733 | - (initSimpleOpts $ updOptLevel 0 dflags)
|
|
| 2740 | + (initSimpleOpts dflags)
|
|
| 2734 | 2741 | ds_expr
|
| 2735 | 2742 | | otherwise =
|
| 2736 | 2743 | simpleOptExpr (initSimpleOpts dflags) ds_expr
|