ghc-9.0.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Core.Unfold

Synopsis

Documentation

data Unfolding Source #

Records the unfolding of an identifier, which is approximately the form the identifier would have if we substituted its definition in for the identifier. This type should be treated as abstract everywhere except in GHC.Core.Unfold

Instances

Instances details
Outputable Unfolding # 
Instance details

Defined in GHC.Core.Ppr

data UnfoldingGuidance Source #

UnfoldingGuidance says when unfolding should take place

Instances

Instances details
Eq UnfoldingGuidance # 
Instance details

Defined in GHC.Core

Outputable UnfoldingGuidance # 
Instance details

Defined in GHC.Core.Ppr

noUnfolding :: Unfolding Source #

There is no known Unfolding

mkInlineUnfolding :: CoreExpr -> Unfolding Source #

Make an unfolding that may be used unsaturated (ug_unsat_ok = unSaturatedOk) and that is reported as having its manifest arity (the number of outer lambdas applications will resolve before doing any work).

mkInlineUnfoldingWithArity :: Arity -> CoreExpr -> Unfolding Source #

Make an unfolding that will be used once the RHS has been saturated to the given arity.

data ArgSummary Source #

Constructors

TrivArg 
NonTrivArg 
ValueArg 

Instances

Instances details
Outputable ArgSummary # 
Instance details

Defined in GHC.Core.Unfold

certainlyWillInline :: DynFlags -> IdInfo -> Maybe Unfolding Source #

Sees if the unfolding is pretty certain to inline. If so, return a *stable* unfolding for it, that will always inline.

data CallCtxt Source #

Instances

Instances details
Outputable CallCtxt # 
Instance details

Defined in GHC.Core.Unfold

exprIsConApp_maybe :: HasDebugCallStack => InScopeEnv -> CoreExpr -> Maybe (InScopeSet, [FloatBind], DataCon, [Type], [CoreExpr]) Source #

Returns Just ([b1..bp], dc, [t1..tk], [x1..xn]) if the argument expression is a *saturated* constructor application of the form let b1 in .. let bp in dc t1..tk x1 .. xn, where t1..tk are the *universally-quantified* type args of dc. Floats can also be (and most likely are) single-alternative case expressions. Why does exprIsConApp_maybe return floats? We may have to look through lets and cases to detect that we are in the presence of a data constructor wrapper. In this case, we need to return the lets and cases that we traversed. See Note [exprIsConApp_maybe on data constructors with wrappers]. Data constructor wrappers are unfolded late, but we really want to trigger case-of-known-constructor as early as possible. See also Note [Activation for data constructor wrappers] in GHC.Types.Id.Make.

We also return the incoming InScopeSet, augmented with the binders from any [FloatBind] that we return