Safe Haskell | None |
---|---|
Language | GHC2021 |
Tidying up Core
This module's purpose is to prepare the Core program for two distinct purposes: * To be serialised into the module's interface file * To feed to the code generator
The most important tasks are:
* Determine which Name
s should ultimately be Internal
and External
(which may differ to whether they were originally Internal
or External
).
See `Note [About the NameSorts]` in GHC.Types.Name.
For example, in:
module M where
f x = x + y
where y = factorial 4
could be optimized during the Core pass to:
module M where
y = factorial 4
f x = x + y
in which case y
would be changed from Internal
to External
.
- Rename local identifiers to avoid name clashes, so that unfoldings etc can be serialialised using the OccName, without Uniques.
For example (x_5
means x
with a Unique
of `5`):
f x_12 x_23 = x_12
would be changed to:
f x_12 x1_23 = x_12
Documentation
TidyOpts | |
|
data UnfoldingExposure Source #
ExposeNone | Don't expose unfoldings |
ExposeSome | Expose mandatory unfoldings and those meeting inlining thresholds. |
ExposeOverloaded | Expose unfoldings useful for inlinings and those which which might be specialised. See Note [Exposing overloaded functions] |
ExposeAll | Expose all unfoldings |
Instances
Show UnfoldingExposure Source # | |
Defined in GHC.Iface.Tidy showsPrec :: Int -> UnfoldingExposure -> ShowS # show :: UnfoldingExposure -> String # showList :: [UnfoldingExposure] -> ShowS # | |
Eq UnfoldingExposure Source # | |
Defined in GHC.Iface.Tidy (==) :: UnfoldingExposure -> UnfoldingExposure -> Bool # (/=) :: UnfoldingExposure -> UnfoldingExposure -> Bool # | |
Ord UnfoldingExposure Source # | |
Defined in GHC.Iface.Tidy compare :: UnfoldingExposure -> UnfoldingExposure -> Ordering # (<) :: UnfoldingExposure -> UnfoldingExposure -> Bool # (<=) :: UnfoldingExposure -> UnfoldingExposure -> Bool # (>) :: UnfoldingExposure -> UnfoldingExposure -> Bool # (>=) :: UnfoldingExposure -> UnfoldingExposure -> Bool # max :: UnfoldingExposure -> UnfoldingExposure -> UnfoldingExposure # min :: UnfoldingExposure -> UnfoldingExposure -> UnfoldingExposure # |
tidyProgram :: TidyOpts -> ModGuts -> IO (CgGuts, ModDetails) Source #
mkBootModDetailsTc :: Logger -> TcGblEnv -> IO ModDetails Source #