ghc-6.12.2: The GHC APISource codeContentsIndex
Rules
Contents
RuleBase
Constructing
Checking rule applications
Manipulating SpecInfo rules
Misc. CoreRule helpers
Description
Functions for collecting together and applying rewrite rules to a module. The CoreRule datatype itself is declared elsewhere.
Synopsis
type RuleBase = NameEnv [CoreRule]
emptyRuleBase :: RuleBase
mkRuleBase :: [CoreRule] -> RuleBase
extendRuleBaseList :: RuleBase -> [CoreRule] -> RuleBase
unionRuleBase :: RuleBase -> RuleBase -> RuleBase
pprRuleBase :: RuleBase -> SDoc
ruleCheckProgram :: (Activation -> Bool) -> String -> RuleBase -> [CoreBind] -> SDoc
mkSpecInfo :: [CoreRule] -> SpecInfo
extendSpecInfo :: SpecInfo -> [CoreRule] -> SpecInfo
addSpecInfo :: SpecInfo -> SpecInfo -> SpecInfo
addIdSpecialisations :: Id -> [CoreRule] -> Id
rulesOfBinds :: [CoreBind] -> [CoreRule]
getRules :: RuleBase -> Id -> [CoreRule]
pprRulesForUser :: [CoreRule] -> SDoc
lookupRule :: (Activation -> Bool) -> InScopeSet -> Id -> [CoreExpr] -> [CoreRule] -> Maybe (CoreRule, CoreExpr)
mkLocalRule :: RuleName -> Activation -> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule
roughTopNames :: [CoreExpr] -> [Maybe Name]
RuleBase
type RuleBase = NameEnv [CoreRule]Source
Gathers a collection of CoreRules. Maps (the name of) an Id to its rules
Constructing
emptyRuleBase :: RuleBaseSource
mkRuleBase :: [CoreRule] -> RuleBaseSource
extendRuleBaseList :: RuleBase -> [CoreRule] -> RuleBaseSource
unionRuleBase :: RuleBase -> RuleBase -> RuleBaseSource
pprRuleBase :: RuleBase -> SDocSource
Checking rule applications
ruleCheckProgramSource
:: Activation -> BoolRule activation test
-> StringRule pattern
-> RuleBaseDatabase of rules
-> [CoreBind]Bindings to check in
-> SDocResulting check message
Report partial matches for rules beginning with the specified string for the purposes of error reporting
Manipulating SpecInfo rules
mkSpecInfo :: [CoreRule] -> SpecInfoSource
Make a SpecInfo containing a number of CoreRules, suitable for putting into an IdInfo
extendSpecInfo :: SpecInfo -> [CoreRule] -> SpecInfoSource
addSpecInfo :: SpecInfo -> SpecInfo -> SpecInfoSource
addIdSpecialisations :: Id -> [CoreRule] -> IdSource
Misc. CoreRule helpers
rulesOfBinds :: [CoreBind] -> [CoreRule]Source
Gather all the rules for locally bound identifiers from the supplied bindings
getRules :: RuleBase -> Id -> [CoreRule]Source
pprRulesForUser :: [CoreRule] -> SDocSource
lookupRule :: (Activation -> Bool) -> InScopeSet -> 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.
mkLocalRule :: RuleName -> Activation -> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRuleSource
Used to make CoreRule for an Id defined in the module being compiled. See also CoreRule
roughTopNames :: [CoreExpr] -> [Maybe Name]Source

Find the "top" free names of several expressions. Such names are either:

1. The function finally being applied to in an application chain (if that name is a GlobalId: see Var), or

2. The TyCon if the expression is a Type

This is used for the fast-match-check for rules; if the top names don't match, the rest can't

Produced by Haddock version 2.6.1