| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Core.Rules
Description
Functions for collecting together and applying rewrite rules to a module.
 The CoreRule datatype itself is declared elsewhere.
Synopsis
- lookupRule :: RuleOpts -> InScopeEnv -> (Activation -> Bool) -> Id -> [CoreExpr] -> [CoreRule] -> Maybe (CoreRule, CoreExpr)
 - type RuleBase = NameEnv [CoreRule]
 - data RuleEnv = RuleEnv {}
 - mkRuleEnv :: ModGuts -> RuleBase -> RuleBase -> RuleEnv
 - emptyRuleEnv :: RuleEnv
 - updExternalPackageRules :: RuleEnv -> RuleBase -> RuleEnv
 - addLocalRules :: RuleEnv -> [CoreRule] -> RuleEnv
 - updLocalRules :: RuleEnv -> [CoreRule] -> RuleEnv
 - emptyRuleBase :: RuleBase
 - mkRuleBase :: [CoreRule] -> RuleBase
 - extendRuleBaseList :: RuleBase -> [CoreRule] -> RuleBase
 - pprRuleBase :: RuleBase -> SDoc
 - ruleCheckProgram :: RuleOpts -> CompilerPhase -> String -> (Id -> [CoreRule]) -> CoreProgram -> SDoc
 - extendRuleInfo :: RuleInfo -> [CoreRule] -> RuleInfo
 - addRuleInfo :: RuleInfo -> RuleInfo -> RuleInfo
 - addIdSpecialisations :: Id -> [CoreRule] -> Id
 - addRulesToId :: RuleBase -> Id -> Id
 - rulesOfBinds :: [CoreBind] -> [CoreRule]
 - getRules :: RuleEnv -> Id -> [CoreRule]
 - pprRulesForUser :: [CoreRule] -> SDoc
 - mkRule :: Module -> Bool -> Bool -> RuleName -> Activation -> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule
 - mkSpecRule :: DynFlags -> Module -> Bool -> Activation -> SDoc -> Id -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule
 - roughTopNames :: [CoreExpr] -> [Maybe Name]
 
Looking up rules
lookupRule :: RuleOpts -> InScopeEnv -> (Activation -> Bool) -> Id -> [CoreExpr] -> [CoreRule] -> Maybe (CoreRule, CoreExpr) Source #
The main rule matching function. Attempts to apply all (active) supplied rules to this instance of an application in a given context, returning the rule applied and the resulting expression if successful.
RuleBase, RuleEnv
A full rule environment which we can apply rules from.  Like a RuleBase,
 but it also includes the set of visible orphans we use to filter out orphan
 rules which are not visible (even though we can see them...)
 See Note [Orphans] in GHC.Core
Constructors
| RuleEnv | |
Fields 
  | |
mkRuleBase :: [CoreRule] -> RuleBase Source #
pprRuleBase :: RuleBase -> SDoc Source #
Checking rule applications
Arguments
| :: RuleOpts | Rule options  | 
| -> CompilerPhase | Rule activation test  | 
| -> String | Rule pattern  | 
| -> (Id -> [CoreRule]) | Rules for an Id  | 
| -> CoreProgram | Bindings to check in  | 
| -> SDoc | Resulting check message  | 
Report partial matches for rules beginning with the specified string for the purposes of error reporting
Manipulating RuleInfo rules
RuleBase and RuleEnv
Misc. CoreRule helpers
rulesOfBinds :: [CoreBind] -> [CoreRule] Source #
Gather all the rules for locally bound identifiers from the supplied bindings
pprRulesForUser :: [CoreRule] -> SDoc Source #
Making rules
mkRule :: Module -> Bool -> Bool -> RuleName -> Activation -> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule Source #
mkSpecRule :: DynFlags -> Module -> Bool -> Activation -> SDoc -> Id -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule Source #
roughTopNames :: [CoreExpr] -> [Maybe Name] Source #
Find the "top" free names of several expressions. Such names are either:
- The function finally being applied to in an application chain (if that name is a GlobalId: see GHC.Types.Var), or
 - The 
TyConif the expression is aType 
This is used for the fast-match-check for rules; if the top names don't match, the rest can't