ghc-9.15: The GHC API
Safe HaskellNone
LanguageGHC2024

GHC.Types.InlinePragma

Synopsis

Inline Pragma Encoding

InlinePragma

Data-type

data InlinePragma pass Source #

Instances

Instances details
(NFData (XInlinePragma p), NFData (XXInlinePragma p), NFData (XXActivation p)) => NFData (InlinePragma p) Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

rnf :: InlinePragma p -> () Source #

IsPass p => Binary (InlinePragma (GhcPass p)) Source # 
Instance details

Defined in GHC.Types.InlinePragma

IsPass p => Outputable (InlinePragma (GhcPass p)) Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

ppr :: InlinePragma (GhcPass p) -> SDoc Source #

(Eq (XXActivation pass), Eq (XInlinePragma pass), Eq (XXInlinePragma pass)) => Eq (InlinePragma pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

(==) :: InlinePragma pass -> InlinePragma pass -> Bool Source #

(/=) :: InlinePragma pass -> InlinePragma pass -> Bool Source #

Data (InlinePragma GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma GhcPs -> c (InlinePragma GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InlinePragma GhcPs) Source #

toConstr :: InlinePragma GhcPs -> Constr Source #

dataTypeOf :: InlinePragma GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InlinePragma GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InlinePragma GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> InlinePragma GhcPs -> InlinePragma GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InlinePragma GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma GhcPs -> m (InlinePragma GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcPs -> m (InlinePragma GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcPs -> m (InlinePragma GhcPs) Source #

Data (InlinePragma GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma GhcRn -> c (InlinePragma GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InlinePragma GhcRn) Source #

toConstr :: InlinePragma GhcRn -> Constr Source #

dataTypeOf :: InlinePragma GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InlinePragma GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InlinePragma GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> InlinePragma GhcRn -> InlinePragma GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InlinePragma GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma GhcRn -> m (InlinePragma GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcRn -> m (InlinePragma GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcRn -> m (InlinePragma GhcRn) Source #

Data (InlinePragma GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma GhcTc -> c (InlinePragma GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InlinePragma GhcTc) Source #

toConstr :: InlinePragma GhcTc -> Constr Source #

dataTypeOf :: InlinePragma GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InlinePragma GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InlinePragma GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> InlinePragma GhcTc -> InlinePragma GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InlinePragma GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma GhcTc -> m (InlinePragma GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcTc -> m (InlinePragma GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma GhcTc -> m (InlinePragma GhcTc) Source #

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

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.

Queries

Mutators

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

  • xinl_src :: SourceText

    See Note [Pragma source text]

  • xinl_sat :: InlineSaturation

    Inline only when applied to n explicit (non-type, non-dictionary) arguments.

    That is, xinl_sat describes the number of *source-code* arguments the thing must be applied to. We add on the number of implicit, dictionary arguments when making the Unfolding, and don't look at inl_sat further

Instances

Instances details
NFData XInlinePragmaGhc Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

rnf :: XInlinePragmaGhc -> () Source #

Binary XInlinePragmaGhc Source # 
Instance details

Defined in GHC.Types.InlinePragma

Eq XInlinePragmaGhc Source # 
Instance details

Defined in GHC.Types.InlinePragma

Data XInlinePragmaGhc Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XInlinePragmaGhc -> c XInlinePragmaGhc Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XInlinePragmaGhc Source #

toConstr :: XInlinePragmaGhc -> Constr Source #

dataTypeOf :: XInlinePragmaGhc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XInlinePragmaGhc) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XInlinePragmaGhc) Source #

gmapT :: (forall b. Data b => b -> b) -> XInlinePragmaGhc -> XInlinePragmaGhc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XInlinePragmaGhc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XInlinePragmaGhc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> XInlinePragmaGhc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XInlinePragmaGhc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XInlinePragmaGhc -> m XInlinePragmaGhc Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XInlinePragmaGhc -> m XInlinePragmaGhc Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XInlinePragmaGhc -> m XInlinePragmaGhc Source #

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 n explicit (non-type, non-dictionary) arguments.

That is, AppliedToAtLeast describes the number of *source-code* arguments the thing must be applied to.

AnySaturation

There does not exist an explicit number of arguments that the inlining process should be applied to.

Instances

Instances details
NFData InlineSaturation Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

rnf :: InlineSaturation -> () Source #

Binary InlineSaturation Source # 
Instance details

Defined in GHC.Types.InlinePragma

Eq InlineSaturation Source # 
Instance details

Defined in GHC.Types.InlinePragma

Data InlineSaturation Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSaturation -> c InlineSaturation Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSaturation Source #

toConstr :: InlineSaturation -> Constr Source #

dataTypeOf :: InlineSaturation -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSaturation) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSaturation) Source #

gmapT :: (forall b. Data b => b -> b) -> InlineSaturation -> InlineSaturation Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSaturation -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSaturation -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InlineSaturation -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSaturation -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSaturation -> m InlineSaturation Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSaturation -> m InlineSaturation Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSaturation -> m InlineSaturation Source #

InlineSpec

Data-type

data InlineSpec Source #

Inline Specification

Instances

Instances details
NFData InlineSpec Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

rnf :: InlineSpec -> () Source #

Binary InlineSpec Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable InlineSpec Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: InlineSpec -> SDoc Source #

Eq InlineSpec Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Data InlineSpec Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSpec -> c InlineSpec Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec Source #

toConstr :: InlineSpec -> Constr Source #

dataTypeOf :: InlineSpec -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) Source #

gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source #

Show InlineSpec Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Queries

RuleMatchInfo

Data-type

data RuleMatchInfo Source #

Rule Match Information

Constructors

ConLike 
FunLike 

Instances

Instances details
NFData RuleMatchInfo Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

rnf :: RuleMatchInfo -> () Source #

Binary RuleMatchInfo Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable RuleMatchInfo Source # 
Instance details

Defined in GHC.Utils.Outputable

Eq RuleMatchInfo Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Data RuleMatchInfo Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatchInfo Source #

toConstr :: RuleMatchInfo -> Constr Source #

dataTypeOf :: RuleMatchInfo -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatchInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleMatchInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo Source #

Show RuleMatchInfo Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Queries

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

Instances details
Binary ActivationGhc Source # 
Instance details

Defined in GHC.Types.InlinePragma

Data ActivationGhc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActivationGhc -> c ActivationGhc Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActivationGhc Source #

toConstr :: ActivationGhc -> Constr Source #

dataTypeOf :: ActivationGhc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ActivationGhc) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActivationGhc) Source #

gmapT :: (forall b. Data b => b -> b) -> ActivationGhc -> ActivationGhc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActivationGhc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActivationGhc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ActivationGhc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActivationGhc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActivationGhc -> m ActivationGhc Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivationGhc -> m ActivationGhc Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivationGhc -> m ActivationGhc Source #

NFData e => NFData (ActivationX e) Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

Methods

rnf :: ActivationX e -> () Source #

Outputable (ActivationX p) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: ActivationX p -> SDoc Source #

Eq e => Eq (ActivationX e) Source # 
Instance details

Defined in Language.Haskell.Syntax.Binds.InlinePragma

type PhaseNum = Int 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

competesWith :: ActivationGhc -> ActivationGhc -> Bool Source #

act1 competesWith act2 returns whether act1 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]

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

Instances details
NFData CompilerPhase Source #

activeAfter p makes an Activation that is active in phase p and after

Invariant: beginPhase (activeAfter p) = p

Instance details

Defined in GHC.Types.InlinePragma

Methods

rnf :: CompilerPhase -> () Source #

Binary CompilerPhase Source # 
Instance details

Defined in GHC.Types.InlinePragma

Outputable CompilerPhase Source # 
Instance details

Defined in GHC.Types.InlinePragma

Eq CompilerPhase Source # 
Instance details

Defined in GHC.Types.InlinePragma

Data CompilerPhase Source # 
Instance details

Defined in GHC.Types.InlinePragma

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompilerPhase -> c CompilerPhase Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompilerPhase Source #

toConstr :: CompilerPhase -> Constr Source #

dataTypeOf :: CompilerPhase -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompilerPhase) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompilerPhase) Source #

gmapT :: (forall b. Data b => b -> b) -> CompilerPhase -> CompilerPhase Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompilerPhase -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompilerPhase -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CompilerPhase -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompilerPhase -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompilerPhase -> m CompilerPhase Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerPhase -> m CompilerPhase Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerPhase -> m CompilerPhase Source #

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

laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase Source #

Returns the later of two phases

laterThanPhase :: CompilerPhase -> CompilerPhase -> Bool Source #

p1 laterThanOrEqualPhase p2 computes whether p1 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