| ||||||||||||
| ||||||||||||
| ||||||||||||
Description | ||||||||||||
Commonly useful utilites for manipulating the Core language | ||||||||||||
Synopsis | ||||||||||||
Constructing expressions | ||||||||||||
mkInlineMe :: CoreExpr -> CoreExpr | ||||||||||||
Wraps the given expression in an inlining hint unless the expression is trivial in some sense, so that doing so would usually hurt us | ||||||||||||
mkSCC :: CostCentre -> Expr b -> Expr b | ||||||||||||
Wraps the given expression in the cost centre unless in a way that maximises their utility to the user | ||||||||||||
mkCoerce :: Coercion -> CoreExpr -> CoreExpr | ||||||||||||
Wrap the given expression in the coercion safely, coalescing nested coercions | ||||||||||||
mkCoerceI :: CoercionI -> CoreExpr -> CoreExpr | ||||||||||||
Wrap the given expression in the coercion, dropping identity coercions and coalescing nested coercions | ||||||||||||
bindNonRec :: Id -> CoreExpr -> CoreExpr -> CoreExpr | ||||||||||||
bindNonRec x r b produces either: let x = r in b or: case r of x { _DEFAULT_ -> b } depending on whether we have to use a case or let binding for the expression (see needsCaseBinding). It's used by the desugarer to avoid building bindings that give Core Lint a heart attack, although actually the simplifier deals with them perfectly well. See also MkCore.mkCoreLet | ||||||||||||
needsCaseBinding :: Type -> CoreExpr -> Bool | ||||||||||||
Tests whether we have to use a case rather than let binding for this expression as per the invariants of CoreExpr: see CoreSyn | ||||||||||||
mkIfThenElse :: CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr | ||||||||||||
mkAltExpr | ||||||||||||
| ||||||||||||
mkPiType :: Var -> Type -> Type | ||||||||||||
Makes a (->) type or a forall type, depending on whether it is given a type variable or a term variable. | ||||||||||||
mkPiTypes :: [Var] -> Type -> Type | ||||||||||||
mkPiType for multiple type or value arguments | ||||||||||||
Taking expressions apart | ||||||||||||
findDefault :: [CoreAlt] -> ([CoreAlt], Maybe CoreExpr) | ||||||||||||
Extract the default case alternative | ||||||||||||
findAlt :: AltCon -> [CoreAlt] -> CoreAlt | ||||||||||||
Find the case alternative corresponding to a particular constructor: panics if no such constructor exists | ||||||||||||
isDefaultAlt :: CoreAlt -> Bool | ||||||||||||
mergeAlts :: [CoreAlt] -> [CoreAlt] -> [CoreAlt] | ||||||||||||
Merge alternatives preserving order; alternatives in the first argument shadow ones in the second | ||||||||||||
trimConArgs :: AltCon -> [CoreArg] -> [CoreArg] | ||||||||||||
Given: case (C a b x y) of C b x y -> ... We want to drop the leading type argument of the scrutinee leaving the arguments to match agains the pattern | ||||||||||||
Properties of expressions | ||||||||||||
exprType :: CoreExpr -> Type | ||||||||||||
Recover the type of a well-typed Core expression. Fails when applied to the actual Type expression as it cannot really be said to have a type | ||||||||||||
coreAltType :: CoreAlt -> Type | ||||||||||||
Returns the type of the alternatives right hand side | ||||||||||||
coreAltsType :: [CoreAlt] -> Type | ||||||||||||
Returns the type of the first alternative, which should be the same as for all alternatives | ||||||||||||
exprIsDupable :: CoreExpr -> Bool | ||||||||||||
exprIsTrivial :: CoreExpr -> Bool | ||||||||||||
exprIsCheap :: CoreExpr -> Bool | ||||||||||||
exprIsHNF :: CoreExpr -> Bool | ||||||||||||
This returns true for expressions that are certainly already evaluated to head normal form. This is used to decide whether it's ok to change: case x of _ -> e into: e and to decide whether it's safe to discard a seq. So, it does not treat variables as evaluated, unless they say they are. However, it does treat partial applications and constructor applications as values, even if their arguments are non-trivial, provided the argument type is lifted. For example, both of these are values: (:) (f x) (map f xs) map (...redex...) Because seq on such things completes immediately. For unlifted argument types, we have to be careful: C (f x :: Int#) Suppose f x diverges; then C (f x) is not a value. However this can't happen: see CoreSyn. This invariant states that arguments of unboxed type must be ok-for-speculation (or trivial). | ||||||||||||
exprOkForSpeculation :: CoreExpr -> Bool | ||||||||||||
exprOkForSpeculation returns True of an expression that is:
Precisely, it returns True iff:
Note that if exprIsHNF e, then exprOkForSpecuation e. As an example of the considerations in this test, consider: let x = case y# +# 1# of { r# -> I# r# } in E being translated to: case y# +# 1# of { r# -> let x = I# r# in E } We can only do this if the y + 1 is ok for speculation: it has no side effects, and can't diverge or raise an exception. | ||||||||||||
exprIsBig :: Expr b -> Bool | ||||||||||||
Returns True of expressions that are too big to be compared by cheapEqExpr | ||||||||||||
exprIsConApp_maybe :: CoreExpr -> Maybe (DataCon, [CoreExpr]) | ||||||||||||
Returns Just (dc, [x1..xn]) if the argument expression is a constructor application of the form dc x1 .. xn The Arity returned is the number of value args the expression can be applied to without doing much work | ||||||||||||
exprIsBottom :: CoreExpr -> Bool | ||||||||||||
True of expressions that are guaranteed to diverge upon execution | ||||||||||||
rhsIsStatic :: PackageId -> CoreExpr -> Bool | ||||||||||||
This function is called only on *top-level* right-hand sides. Returns True if the RHS can be allocated statically in the output, with no thunks involved at all. | ||||||||||||
Arity and eta expansion | ||||||||||||
manifestArity :: CoreExpr -> Arity | ||||||||||||
exprArity :: CoreExpr -> Arity | ||||||||||||
An approximate, fast, version of exprEtaExpandArity | ||||||||||||
exprEtaExpandArity :: DynFlags -> CoreExpr -> Arity | ||||||||||||
etaExpand | ||||||||||||
| ||||||||||||
Expression and bindings size | ||||||||||||
coreBindsSize :: [CoreBind] -> Int | ||||||||||||
exprSize :: CoreExpr -> Int | ||||||||||||
A measure of the size of the expressions, strictly greater than 0 It also forces the expression pretty drastically as a side effect | ||||||||||||
Hashing | ||||||||||||
hashExpr :: CoreExpr -> Int | ||||||||||||
Two expressions that hash to the same Int may be equal (but may not be) Two expressions that hash to the different Ints are definitely unequal. The emphasis is on a crude, fast hash, rather than on high precision. But unequal here means "not identical"; two alpha-equivalent expressions may hash to the different Ints. We must be careful that \x.x and \y.y map to the same hash code, (at least if we want the above invariant to be true). | ||||||||||||
Equality | ||||||||||||
cheapEqExpr :: Expr b -> Expr b -> Bool | ||||||||||||
A cheap equality test which bales out fast! If it returns True the arguments are definitely equal, otherwise, they may or may not be equal. See also exprIsBig | ||||||||||||
tcEqExpr :: CoreExpr -> CoreExpr -> Bool | ||||||||||||
A kind of shallow equality used in rule matching, so does not look through newtypes or predicate types | ||||||||||||
tcEqExprX :: RnEnv2 -> CoreExpr -> CoreExpr -> Bool | ||||||||||||
Manipulating data constructors and types | ||||||||||||
applyTypeToArgs :: CoreExpr -> Type -> [CoreExpr] -> Type | ||||||||||||
A more efficient version of applyTypeToArg when we have several arguments. The first argument is just for debugging, and gives some context | ||||||||||||
applyTypeToArg :: Type -> CoreExpr -> Type | ||||||||||||
Determines the type resulting from applying an expression to a function with the given type | ||||||||||||
dataConOrigInstPat :: [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) | ||||||||||||
dataConRepInstPat :: [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) | ||||||||||||
dataConRepFSInstPat :: [FastString] -> [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) | ||||||||||||
Produced by Haddock version 2.4.2 |