| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Core.Opt.Arity
Description
Arity and eta expansion
Synopsis
- manifestArity :: CoreExpr -> Arity
- joinRhsArity :: CoreExpr -> JoinArity
- exprArity :: CoreExpr -> Arity
- typeArity :: Type -> [OneShotInfo]
- exprEtaExpandArity :: DynFlags -> CoreExpr -> ArityType
- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType
- etaExpand :: Arity -> CoreExpr -> CoreExpr
- etaExpandAT :: InScopeSet -> ArityType -> CoreExpr -> CoreExpr
- exprBotStrictness_maybe :: CoreExpr -> Maybe (Arity, DmdSig)
- data ArityType = AT ![OneShotInfo] !Divergence
- mkBotArityType :: [OneShotInfo] -> ArityType
- mkTopArityType :: [OneShotInfo] -> ArityType
- expandableArityType :: ArityType -> Bool
- arityTypeArity :: ArityType -> Arity
- maxWithArity :: ArityType -> Arity -> ArityType
- idArityType :: Id -> ArityType
- etaExpandToJoinPoint :: JoinArity -> CoreExpr -> ([CoreBndr], CoreExpr)
- etaExpandToJoinPointRule :: JoinArity -> CoreRule -> CoreRule
- pushCoArg :: CoercionR -> CoreArg -> Maybe (CoreArg, MCoercion)
- pushCoArgs :: CoercionR -> [CoreArg] -> Maybe ([CoreArg], MCoercion)
- pushCoValArg :: CoercionR -> Maybe (MCoercionR, MCoercionR)
- pushCoTyArg :: CoercionR -> Type -> Maybe (Type, MCoercionR)
- pushCoercionIntoLambda :: HasDebugCallStack => InScopeSet -> Var -> CoreExpr -> CoercionR -> Maybe (Var, CoreExpr)
- pushCoDataCon :: DataCon -> [CoreExpr] -> Coercion -> Maybe (DataCon, [Type], [CoreExpr])
- collectBindersPushingCo :: CoreExpr -> ([Var], CoreExpr)
Documentation
manifestArity :: CoreExpr -> Arity Source #
manifestArity sees how many leading value lambdas there are, after looking through casts
joinRhsArity :: CoreExpr -> JoinArity Source #
typeArity :: Type -> [OneShotInfo] Source #
exprEtaExpandArity :: DynFlags -> CoreExpr -> ArityType Source #
The Arity returned is the number of value args the expression can be applied to without doing much work
etaExpand :: Arity -> CoreExpr -> CoreExpr Source #
etaExpand n e returns an expression with
 the same meaning as e, but with arity n.
Given:
e' = etaExpand n e
We should have that:
ty = exprType e = exprType e'
etaExpandAT :: InScopeSet -> ArityType -> CoreExpr -> CoreExpr Source #
ArityType
The analysis lattice of arity analysis. It is isomorphic to
   data ArityType'
     = AEnd Divergence
     | ALam OneShotInfo ArityType'
Which is easier to display the Hasse diagram for:
 ALam OneShotLam at
         |
     AEnd topDiv
         |
 ALam NoOneShotInfo at
         |
     AEnd exnDiv
         |
     AEnd botDiv
where the at fields of ALam are inductively subject to the same order.
 That is, ALam os at1 < ALam os at2 iff at1 < at2.
Why the strange Top element? See Note [Combining case branches].
We rely on this lattice structure for fixed-point iteration in
 findRhsArity. For the semantics of ArityType, see Note [ArityType].
Constructors
| AT ![OneShotInfo] !Divergence | 
 If  | 
Instances
| Outputable ArityType Source # | This is the BNF of the generated output: @ We format AT [o1,..,on] topDiv | 
| Eq ArityType Source # | |
mkBotArityType :: [OneShotInfo] -> ArityType Source #
mkTopArityType :: [OneShotInfo] -> ArityType Source #
arityTypeArity :: ArityType -> Arity Source #
The number of value args for the arity type
maxWithArity :: ArityType -> Arity -> ArityType Source #
Expand a non-bottoming arity type so that it has at least the given arity.
idArityType :: Id -> ArityType Source #
Join points
etaExpandToJoinPoint :: JoinArity -> CoreExpr -> ([CoreBndr], CoreExpr) Source #
Split an expression into the given number of binders and a body, eta-expanding if necessary. Counts value *and* type binders.
Coercions and casts
pushCoValArg :: CoercionR -> Maybe (MCoercionR, MCoercionR) Source #
pushCoTyArg :: CoercionR -> Type -> Maybe (Type, MCoercionR) Source #
pushCoercionIntoLambda :: HasDebugCallStack => InScopeSet -> Var -> CoreExpr -> CoercionR -> Maybe (Var, CoreExpr) Source #