Safe Haskell | None |
---|---|
Language | Haskell2010 |
- simpleOptPgm :: DynFlags -> Module -> CoreProgram -> [CoreRule] -> [CoreVect] -> IO (CoreProgram, [CoreRule], [CoreVect])
- simpleOptExpr :: CoreExpr -> CoreExpr
- simpleOptExprWith :: Subst -> InExpr -> OutExpr
- joinPointBinding_maybe :: InBndr -> InExpr -> Maybe (InBndr, InExpr)
- joinPointBindings_maybe :: [(InBndr, InExpr)] -> Maybe [(InBndr, InExpr)]
- exprIsConApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (DataCon, [Type], [CoreExpr])
- exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal
- exprIsLambda_maybe :: InScopeEnv -> CoreExpr -> Maybe (Var, CoreExpr, [Tickish Id])
- pushCoArg :: Coercion -> CoreArg -> Maybe (CoreArg, Coercion)
- pushCoValArg :: Coercion -> Maybe (Coercion, Coercion)
- pushCoTyArg :: Coercion -> Type -> Maybe (Type, Coercion)
- collectBindersPushingCo :: CoreExpr -> ([Var], CoreExpr)
Simple expression optimiser
simpleOptPgm :: DynFlags -> Module -> CoreProgram -> [CoreRule] -> [CoreVect] -> IO (CoreProgram, [CoreRule], [CoreVect]) Source #
simpleOptExpr :: CoreExpr -> CoreExpr 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 (DataCon, [Type], [CoreExpr]) Source #
Returns Just (dc, [t1..tk], [x1..xn])
if the argument expression is
a *saturated* constructor application of the form dc t1..tk x1 .. xn
,
where t1..tk are the *universally-qantified* type args of dc
exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal Source #
exprIsLambda_maybe :: InScopeEnv -> CoreExpr -> Maybe (Var, CoreExpr, [Tickish Id]) Source #