Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Unfolding
- data UnfoldingGuidance
- noUnfolding :: Unfolding
- mkImplicitUnfolding :: DynFlags -> CoreExpr -> Unfolding
- mkUnfolding :: DynFlags -> UnfoldingSource -> Bool -> Bool -> CoreExpr -> Unfolding
- mkCoreUnfolding :: UnfoldingSource -> Bool -> CoreExpr -> UnfoldingGuidance -> Unfolding
- mkTopUnfolding :: DynFlags -> Bool -> CoreExpr -> Unfolding
- mkSimpleUnfolding :: DynFlags -> CoreExpr -> Unfolding
- mkWorkerUnfolding :: DynFlags -> (CoreExpr -> CoreExpr) -> Unfolding -> Unfolding
- mkInlineUnfolding :: CoreExpr -> Unfolding
- mkInlineUnfoldingWithArity :: Arity -> CoreExpr -> Unfolding
- mkInlinableUnfolding :: DynFlags -> CoreExpr -> Unfolding
- mkWwInlineRule :: DynFlags -> CoreExpr -> Arity -> Unfolding
- mkCompulsoryUnfolding :: CoreExpr -> Unfolding
- mkDFunUnfolding :: [Var] -> DataCon -> [CoreExpr] -> Unfolding
- specUnfolding :: DynFlags -> [Var] -> (CoreExpr -> CoreExpr) -> [CoreArg] -> Unfolding -> Unfolding
- data ArgSummary
- couldBeSmallEnoughToInline :: DynFlags -> Int -> CoreExpr -> Bool
- inlineBoringOk :: CoreExpr -> Bool
- certainlyWillInline :: DynFlags -> IdInfo -> Maybe Unfolding
- smallEnoughToInline :: DynFlags -> Unfolding -> Bool
- callSiteInline :: DynFlags -> Id -> Bool -> Bool -> [ArgSummary] -> CallCtxt -> Maybe CoreExpr
- data CallCtxt
- exprIsConApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (InScopeSet, [FloatBind], DataCon, [Type], [CoreExpr])
- exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal
Documentation
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 CoreUnfold
data UnfoldingGuidance Source #
UnfoldingGuidance
says when unfolding should take place
Instances
Eq UnfoldingGuidance # | |
Defined in CoreSyn (==) :: UnfoldingGuidance -> UnfoldingGuidance -> Bool # (/=) :: UnfoldingGuidance -> UnfoldingGuidance -> Bool # | |
Outputable UnfoldingGuidance # | |
noUnfolding :: Unfolding Source #
There is no known Unfolding
mkUnfolding :: DynFlags -> UnfoldingSource -> Bool -> Bool -> CoreExpr -> Unfolding Source #
mkCoreUnfolding :: UnfoldingSource -> Bool -> CoreExpr -> UnfoldingGuidance -> Unfolding Source #
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.
specUnfolding :: DynFlags -> [Var] -> (CoreExpr -> CoreExpr) -> [CoreArg] -> Unfolding -> Unfolding Source #
data ArgSummary Source #
Instances
Outputable ArgSummary # | |
Defined in CoreUnfold |
inlineBoringOk :: CoreExpr -> Bool Source #
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.
callSiteInline :: DynFlags -> Id -> Bool -> Bool -> [ArgSummary] -> CallCtxt -> Maybe CoreExpr Source #
exprIsConApp_maybe :: 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 MkId.
We also return the incoming InScopeSet, augmented with the binders from any [FloatBind] that we return
exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal Source #