| Safe Haskell | None |
|---|---|
| Language | GHC2024 |
GHC.Types.InlinePragma
Synopsis
- data InlinePragma pass
- = InlinePragma {
- inl_ext :: !(XInlinePragma pass)
- inl_inline :: !InlineSpec
- inl_act :: !(Activation pass)
- inl_rule :: !RuleMatchInfo
- | XInlinePragma !(XXInlinePragma pass)
- = InlinePragma {
- type InlinePragmaInfo = InlinePragma GhcTc
- defaultInlinePragma :: IsPass p => InlinePragma (GhcPass p)
- alwaysConLikePragma :: IsPass p => InlinePragma (GhcPass p)
- alwaysInlinePragma :: IsPass p => InlinePragma (GhcPass p)
- alwaysInlineConLikePragma :: IsPass p => InlinePragma (GhcPass p)
- dfunInlinePragma :: IsPass p => InlinePragma (GhcPass p)
- neverInlinePragma :: IsPass p => InlinePragma (GhcPass p)
- inlinePragmaActivation :: InlinePragma (GhcPass p) -> ActivationGhc
- inlinePragmaSaturation :: XInlinePragma (GhcPass p) ~ XInlinePragmaGhc => InlinePragma (GhcPass p) -> InlineSaturation
- inlinePragmaName :: InlineSpec -> SDoc
- inlinePragmaRuleMatchInfo :: InlinePragma (GhcPass p) -> RuleMatchInfo
- inlinePragmaSource :: IsPass p => InlinePragma (GhcPass p) -> SourceText
- inlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec
- isAnyInlinePragma :: InlinePragma p -> Bool
- isDefaultInlinePragma :: InlinePragma (GhcPass p) -> Bool
- isInlinablePragma :: InlinePragma p -> Bool
- isInlinePragma :: InlinePragma p -> Bool
- isNoInlinePragma :: InlinePragma p -> Bool
- isOpaquePragma :: InlinePragma p -> Bool
- setInlinePragmaSource :: IsPass p => InlinePragma (GhcPass p) -> SourceText -> InlinePragma (GhcPass p)
- setInlinePragmaSaturation :: (IsPass p, XInlinePragma (GhcPass q) ~ XInlinePragmaGhc) => InlinePragma (GhcPass p) -> InlineSaturation -> InlinePragma (GhcPass q)
- setInlinePragmaActivation :: InlinePragma (GhcPass p) -> ActivationGhc -> InlinePragma (GhcPass p)
- setInlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec -> InlinePragma (GhcPass p)
- setInlinePragmaRuleMatchInfo :: InlinePragma (GhcPass p) -> RuleMatchInfo -> InlinePragma (GhcPass p)
- tcInlinePragma :: InlinePragma GhcRn -> InlinePragma GhcTc
- pprInline :: IsPass p => InlinePragma (GhcPass p) -> SDoc
- pprInlineDebug :: IsPass p => InlinePragma (GhcPass p) -> SDoc
- data XInlinePragmaGhc = XInlinePragmaGhc {}
- data InlineSaturation
- data InlineSpec
- noUserInlineSpec :: InlineSpec -> Bool
- data RuleMatchInfo
- isConLike :: RuleMatchInfo -> Bool
- isFunLike :: RuleMatchInfo -> Bool
- type ActivationGhc = ActivationX XXActivationGhc
- data ActivationX e
- pattern ActiveFinal :: Activation (GhcPass p)
- type PhaseNum = Int
- activeAfter :: CompilerPhase -> ActivationGhc
- activateAfterInitial :: ActivationGhc
- activateDuringFinal :: ActivationGhc
- activeInFinalPhase :: ActivationGhc -> Bool
- activeInInitialPhase :: ActivationGhc -> Bool
- activeInPhase :: PhaseNum -> ActivationGhc -> Bool
- competesWith :: ActivationGhc -> ActivationGhc -> Bool
- isAlwaysActive :: ActivationGhc -> Bool
- isNeverActive :: ActivationGhc -> Bool
- data CompilerPhase
- beginPhase :: ActivationGhc -> CompilerPhase
- endPhase :: ActivationGhc -> CompilerPhase
- isActiveInPhase :: CompilerPhase -> ActivationGhc -> Bool
- laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase
- laterThanPhase :: CompilerPhase -> CompilerPhase -> Bool
- nextPhase :: CompilerPhase -> CompilerPhase
Inline Pragma Encoding
InlinePragma
Data-type
data InlinePragma pass Source #
Constructors
| InlinePragma | |
Fields
| |
| XInlinePragma !(XXInlinePragma pass) | |
Instances
type InlinePragmaInfo = InlinePragma GhcTc Source #
Inline Pragma Information
Tells when the inlining is active. When it is active the thing may be inlined, depending on how big it is.
If there was an INLINE pragma, then as a separate matter, the
RHS will have been made to look small with a Core inline Note
The default InlinePragInfo is AlwaysActive, so the info serves
entirely as a way to inhibit inlining until we want it
Constants
defaultInlinePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for GHC.
The type and value of inl_ext provided will differ
between the passes of GHC. Consequently, it may be
necessary to apply type annotation at the call site
to help the type checker disambiguate the correct
type of inl_ext.
alwaysConLikePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for the "parser pass" of GHC.
alwaysInlinePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for the "parser pass" of GHC.
alwaysInlineConLikePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for the "parser pass" of GHC.
dfunInlinePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for the "parser pass" of GHC.
neverInlinePragma :: IsPass p => InlinePragma (GhcPass p) Source #
The default InlinePragma definition for the "parser pass" of GHC.
Field accessors
inlinePragmaSaturation :: XInlinePragma (GhcPass p) ~ XInlinePragmaGhc => InlinePragma (GhcPass p) -> InlineSaturation Source #
inlinePragmaName :: InlineSpec -> SDoc Source #
Outputs string for pragma name for any of INLINEINLINABLENOINLINE. This differs from the Outputable instance for the InlineSpec type where the pragma name string as well as the accompanying SourceText (if any) is printed.
inlinePragmaSource :: IsPass p => InlinePragma (GhcPass p) -> SourceText Source #
inlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec Source #
Queries
isAnyInlinePragma :: InlinePragma p -> Bool Source #
isDefaultInlinePragma :: InlinePragma (GhcPass p) -> Bool Source #
isInlinablePragma :: InlinePragma p -> Bool Source #
isInlinePragma :: InlinePragma p -> Bool Source #
isNoInlinePragma :: InlinePragma p -> Bool Source #
isOpaquePragma :: InlinePragma p -> Bool Source #
Mutators
setInlinePragmaSource :: IsPass p => InlinePragma (GhcPass p) -> SourceText -> InlinePragma (GhcPass p) infixl 1 Source #
setInlinePragmaSaturation :: (IsPass p, XInlinePragma (GhcPass q) ~ XInlinePragmaGhc) => InlinePragma (GhcPass p) -> InlineSaturation -> InlinePragma (GhcPass q) infixl 1 Source #
setInlinePragmaActivation :: InlinePragma (GhcPass p) -> ActivationGhc -> InlinePragma (GhcPass p) infixl 1 Source #
setInlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec -> InlinePragma (GhcPass p) infixl 1 Source #
setInlinePragmaRuleMatchInfo :: InlinePragma (GhcPass p) -> RuleMatchInfo -> InlinePragma (GhcPass p) infixl 1 Source #
GHC pass conversions
Pretty-printing
pprInline :: IsPass p => InlinePragma (GhcPass p) -> SDoc Source #
Pretty-print without displaying the user-specified InlineSpec.
pprInlineDebug :: IsPass p => InlinePragma (GhcPass p) -> SDoc Source #
Pretty-print including the user-specified InlineSpec.
Extensible record type for GhcRn & GhcTc
data XInlinePragmaGhc Source #
Constructors
| XInlinePragmaGhc | |
Fields
| |
Instances
data InlineSaturation Source #
The arity at which to inline a function. This may differ from the function's syntactic arity.
Constructors
| AppliedToAtLeast !Arity | Inline only when applied to That is, |
| AnySaturation | There does not exist an explicit number of arguments that the inlining process should be applied to. |
Instances
InlineSpec
Data-type
data InlineSpec Source #
Inline Specification
Constructors
| Inline | |
| Inlinable | |
| NoInline | |
| Opaque | |
| NoUserInlinePrag |
Instances
Queries
noUserInlineSpec :: InlineSpec -> Bool Source #
RuleMatchInfo
Data-type
data RuleMatchInfo Source #
Rule Match Information
Instances
Queries
isConLike :: RuleMatchInfo -> Bool Source #
isFunLike :: RuleMatchInfo -> Bool Source #
Phase Activation
Activation
Data-type
type ActivationGhc = ActivationX XXActivationGhc Source #
data ActivationX e Source #
An activation is a range of phases throughout which something is active (like an INLINE pragma, SPECIALISE pragma, or RULE).
Constructors
| AlwaysActive | |
| ActiveBefore PhaseNum | Active only *strictly before* this phase |
| ActiveAfter PhaseNum | Active in this phase and later phases |
| NeverActive | Active in the final phase only |
Instances
pattern ActiveFinal :: Activation (GhcPass p) Source #
Compilation phase number, as can be written by users in INLINE pragmas, SPECIALISE pragmas, and RULES.
- phases decrease towards zero
- zero is the last phase
Does not include GHC internal "initial" and "final" phases; see CompilerPhase.
Construction
Constants
activateAfterInitial :: ActivationGhc Source #
Active in the first phase after the initial phase
activateDuringFinal :: ActivationGhc Source #
Active in the final simplification phase (which is repeated)
Queries
activeInPhase :: PhaseNum -> ActivationGhc -> Bool Source #
competesWith :: ActivationGhc -> ActivationGhc -> Bool Source #
act1 returns whether competesWith act2act1 is active in the phase
when act2 becomes active.
This answers the question: might act1 fire first?
NB: this is not the same as computing whether act1 and act2 are
ever active at the same time.
See Note [Competing activations]
isAlwaysActive :: ActivationGhc -> Bool Source #
isNeverActive :: ActivationGhc -> Bool Source #
CompilerPhase
Data-type
data CompilerPhase Source #
Compilation phase number, including the user-specifiable PhaseNum
and the GHC internal "initial" and "final" phases.
Constructors
| InitialPhase | The first phase; number = infinity! |
| Phase PhaseNum | User-specifiable phases |
| FinalPhase | The last phase; number = -infinity! |
Instances
Constructors
beginPhase :: ActivationGhc -> CompilerPhase Source #
First phase in which the Activation is active,
or FinalPhase if it is never active
endPhase :: ActivationGhc -> CompilerPhase Source #
Last phase in which the Activation is active,
or InitialPhase if it is never active
Queries
isActiveInPhase :: CompilerPhase -> ActivationGhc -> Bool Source #
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase Source #
Returns the later of two phases
laterThanPhase :: CompilerPhase -> CompilerPhase -> Bool Source #
p1 computes whether laterThanOrEqualPhase p2p1 happens (strictly)
after p2.
nextPhase :: CompilerPhase -> CompilerPhase Source #
Tells you the next phase after this one
Currently we have just phases [2,1,0,FinalPhase,FinalPhase,...],
where FinalPhase means GHC's internal simplification steps
after all rules have run
Orphan instances
| IsPass p => Binary (InlinePragma (GhcPass p)) Source # | |
Methods put_ :: WriteBinHandle -> InlinePragma (GhcPass p) -> IO () Source # put :: WriteBinHandle -> InlinePragma (GhcPass p) -> IO (Bin (InlinePragma (GhcPass p))) Source # get :: ReadBinHandle -> IO (InlinePragma (GhcPass p)) Source # | |
| IsPass p => Outputable (InlinePragma (GhcPass p)) Source # | |