Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- simpleOptPgm :: DynFlags -> Module -> CoreProgram -> [CoreRule] -> IO (CoreProgram, [CoreRule])
- simpleOptExpr :: DynFlags -> CoreExpr -> CoreExpr
- simpleOptExprWith :: DynFlags -> Subst -> InExpr -> OutExpr
- joinPointBinding_maybe :: InBndr -> InExpr -> Maybe (InBndr, InExpr)
- joinPointBindings_maybe :: [(InBndr, InExpr)] -> Maybe [(InBndr, InExpr)]
- exprIsConApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (InScopeSet, [FloatBind], DataCon, [Type], [CoreExpr])
- exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal
- exprIsLambda_maybe :: InScopeEnv -> CoreExpr -> Maybe (Var, CoreExpr, [Tickish Id])
- pushCoArg :: CoercionR -> CoreArg -> Maybe (CoreArg, MCoercion)
- pushCoValArg :: CoercionR -> Maybe (Coercion, MCoercion)
- pushCoTyArg :: CoercionR -> Type -> Maybe (Type, MCoercionR)
- collectBindersPushingCo :: CoreExpr -> ([Var], CoreExpr)
Simple expression optimiser
simpleOptPgm :: DynFlags -> Module -> CoreProgram -> [CoreRule] -> IO (CoreProgram, [CoreRule]) Source #
Join points
joinPointBinding_maybe :: InBndr -> InExpr -> Maybe (InBndr, InExpr) Source #
Returns Just (bndr,rhs) if the binding is a join point: If it's a JoinId, just return it If it's not yet a JoinId but is always tail-called, make it into a JoinId and return it. In the latter case, eta-expand the RHS if necessary, to make the lambdas explicit, as is required for join points
Precondition: the InBndr has been occurrence-analysed, so its OccInfo is valid
Predicates on expressions
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 #
exprIsLambda_maybe :: InScopeEnv -> CoreExpr -> Maybe (Var, CoreExpr, [Tickish Id]) Source #
Coercions and casts
pushCoTyArg :: CoercionR -> Type -> Maybe (Type, MCoercionR) Source #