module GHC.Core.Opt.Pipeline.Types (
CorePluginPass, CoreToDo(..),
bindsOnlyPass, pprPassDetails,
) where
import GHC.Prelude
import GHC.Core ( CoreProgram )
import GHC.Core.Opt.Monad ( CoreM, FloatOutSwitches )
import GHC.Core.Opt.Simplify ( SimplifyOpts(..) )
import GHC.Types.Basic ( CompilerPhase(..) )
import GHC.Unit.Module.ModGuts
import GHC.Utils.Outputable as Outputable
type CorePluginPass = ModGuts -> CoreM ModGuts
bindsOnlyPass :: (CoreProgram -> CoreM CoreProgram) -> ModGuts -> CoreM ModGuts
bindsOnlyPass :: (CoreProgram -> CoreM CoreProgram) -> ModGuts -> CoreM ModGuts
bindsOnlyPass CoreProgram -> CoreM CoreProgram
pass ModGuts
guts
= do { CoreProgram
binds' <- CoreProgram -> CoreM CoreProgram
pass (ModGuts -> CoreProgram
mg_binds ModGuts
guts)
; forall (m :: * -> *) a. Monad m => a -> m a
return (ModGuts
guts { mg_binds :: CoreProgram
mg_binds = CoreProgram
binds' }) }
data CoreToDo
= CoreDoSimplify !SimplifyOpts
| CoreDoPluginPass String CorePluginPass
| CoreDoFloatInwards
| CoreDoFloatOutwards FloatOutSwitches
| CoreLiberateCase
| CoreDoPrintCore
| CoreDoStaticArgs
| CoreDoCallArity
| CoreDoExitify
| CoreDoDemand Bool
| CoreDoCpr
| CoreDoWorkerWrapper
| CoreDoSpecialising
| CoreDoSpecConstr
| CoreCSE
| CoreDoRuleCheck CompilerPhase String
| CoreDoNothing
| CoreDoPasses [CoreToDo]
| CoreDesugar
| CoreDesugarOpt
| CoreTidy
| CorePrep
| CoreAddCallerCcs
| CoreAddLateCcs
instance Outputable CoreToDo where
ppr :: CoreToDo -> SDoc
ppr (CoreDoSimplify SimplifyOpts
_) = forall doc. IsLine doc => String -> doc
text String
"Simplifier"
ppr (CoreDoPluginPass String
s ModGuts -> CoreM ModGuts
_) = forall doc. IsLine doc => String -> doc
text String
"Core plugin: " forall doc. IsLine doc => doc -> doc -> doc
<+> forall doc. IsLine doc => String -> doc
text String
s
ppr CoreToDo
CoreDoFloatInwards = forall doc. IsLine doc => String -> doc
text String
"Float inwards"
ppr (CoreDoFloatOutwards FloatOutSwitches
f) = forall doc. IsLine doc => String -> doc
text String
"Float out" forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => doc -> doc
parens (forall a. Outputable a => a -> SDoc
ppr FloatOutSwitches
f)
ppr CoreToDo
CoreLiberateCase = forall doc. IsLine doc => String -> doc
text String
"Liberate case"
ppr CoreToDo
CoreDoStaticArgs = forall doc. IsLine doc => String -> doc
text String
"Static argument"
ppr CoreToDo
CoreDoCallArity = forall doc. IsLine doc => String -> doc
text String
"Called arity analysis"
ppr CoreToDo
CoreDoExitify = forall doc. IsLine doc => String -> doc
text String
"Exitification transformation"
ppr (CoreDoDemand Bool
True) = forall doc. IsLine doc => String -> doc
text String
"Demand analysis (including Boxity)"
ppr (CoreDoDemand Bool
False) = forall doc. IsLine doc => String -> doc
text String
"Demand analysis"
ppr CoreToDo
CoreDoCpr = forall doc. IsLine doc => String -> doc
text String
"Constructed Product Result analysis"
ppr CoreToDo
CoreDoWorkerWrapper = forall doc. IsLine doc => String -> doc
text String
"Worker Wrapper binds"
ppr CoreToDo
CoreDoSpecialising = forall doc. IsLine doc => String -> doc
text String
"Specialise"
ppr CoreToDo
CoreDoSpecConstr = forall doc. IsLine doc => String -> doc
text String
"SpecConstr"
ppr CoreToDo
CoreCSE = forall doc. IsLine doc => String -> doc
text String
"Common sub-expression"
ppr CoreToDo
CoreDesugar = forall doc. IsLine doc => String -> doc
text String
"Desugar (before optimization)"
ppr CoreToDo
CoreDesugarOpt = forall doc. IsLine doc => String -> doc
text String
"Desugar (after optimization)"
ppr CoreToDo
CoreTidy = forall doc. IsLine doc => String -> doc
text String
"Tidy Core"
ppr CoreToDo
CoreAddCallerCcs = forall doc. IsLine doc => String -> doc
text String
"Add caller cost-centres"
ppr CoreToDo
CoreAddLateCcs = forall doc. IsLine doc => String -> doc
text String
"Add late core cost-centres"
ppr CoreToDo
CorePrep = forall doc. IsLine doc => String -> doc
text String
"CorePrep"
ppr CoreToDo
CoreDoPrintCore = forall doc. IsLine doc => String -> doc
text String
"Print core"
ppr (CoreDoRuleCheck {}) = forall doc. IsLine doc => String -> doc
text String
"Rule check"
ppr CoreToDo
CoreDoNothing = forall doc. IsLine doc => String -> doc
text String
"CoreDoNothing"
ppr (CoreDoPasses [CoreToDo]
passes) = forall doc. IsLine doc => String -> doc
text String
"CoreDoPasses" forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr [CoreToDo]
passes
pprPassDetails :: CoreToDo -> SDoc
pprPassDetails :: CoreToDo -> SDoc
pprPassDetails (CoreDoSimplify SimplifyOpts
cfg) = forall doc. IsDoc doc => [doc] -> doc
vcat [ forall doc. IsLine doc => String -> doc
text String
"Max iterations =" forall doc. IsLine doc => doc -> doc -> doc
<+> forall doc. IsLine doc => Int -> doc
int Int
n
, forall a. Outputable a => a -> SDoc
ppr SimplMode
md ]
where
n :: Int
n = SimplifyOpts -> Int
so_iterations SimplifyOpts
cfg
md :: SimplMode
md = SimplifyOpts -> SimplMode
so_mode SimplifyOpts
cfg
pprPassDetails CoreToDo
_ = forall doc. IsOutput doc => doc
Outputable.empty