Trim redundant import
[ghc-hetmet.git] / compiler / specialise / Rules.lhs
index 0303833..39a9f05 100644 (file)
@@ -29,7 +29,7 @@ module Rules (
        addIdSpecialisations, 
        
        -- * Misc. CoreRule helpers
-        rulesOfBinds,
+        rulesOfBinds, getRules, pprRulesForUser,
         
         lookupRule, mkLocalRule, roughTopNames
     ) where
@@ -39,7 +39,6 @@ module Rules (
 import CoreSyn         -- All of it
 import OccurAnal       ( occurAnalyseExpr )
 import CoreFVs         ( exprFreeVars, exprsFreeVars, bindFreeVars, rulesFreeVars )
-import CoreUnfold      ( isCheapUnfolding, unfoldingTemplate )
 import CoreUtils       ( tcEqExprX, exprType )
 import PprCore         ( pprRules )
 import Type            ( Type, TvSubstEnv )
@@ -54,7 +53,7 @@ import VarSet
 import Name            ( Name, NamedThing(..) )
 import NameEnv
 import Unify           ( ruleMatchTyX, MatchEnv(..) )
-import BasicTypes      ( Activation, CompilerPhase, isActive )
+import BasicTypes      ( Activation )
 import StaticFlags     ( opt_PprStyle_Debug )
 import Outputable
 import FastString
@@ -152,6 +151,22 @@ ruleCantMatch (t       : ts) (a       : as) = ruleCantMatch ts as
 ruleCantMatch ts            as             = False
 \end{code}
 
+\begin{code}
+pprRulesForUser :: [CoreRule] -> SDoc
+-- (a) tidy the rules
+-- (b) sort them into order based on the rule name
+-- (c) suppress uniques (unless -dppr-debug is on)
+-- This combination makes the output stable so we can use in testing
+-- It's here rather than in PprCore because it calls tidyRules
+pprRulesForUser rules
+  = withPprStyle defaultUserStyle $
+    pprRules $
+    sortLe le_rule  $
+    tidyRules emptyTidyEnv rules
+  where 
+    le_rule r1 r2 = ru_name r1 <= ru_name r2
+\end{code}
+
 
 %************************************************************************
 %*                                                                     *
@@ -181,6 +196,18 @@ addIdSpecialisations id rules
 -- | Gather all the rules for locally bound identifiers from the supplied bindings
 rulesOfBinds :: [CoreBind] -> [CoreRule]
 rulesOfBinds binds = concatMap (concatMap idCoreRules . bindersOf) binds
+
+getRules :: RuleBase -> Id -> [CoreRule]
+       -- The rules for an Id come from two places:
+       --      (a) the ones it is born with (idCoreRules fn)
+       --      (b) rules added in subsequent modules (extra_rules)
+       -- PrimOps, for example, are born with a bunch of rules under (a)
+getRules rule_base fn
+  | isLocalId fn  = idCoreRules fn
+  | otherwise     = WARN( not (isPrimOpId fn) && notNull (idCoreRules fn), 
+                         ppr fn <+> ppr (idCoreRules fn) )
+                   idCoreRules fn ++ (lookupNameEnv rule_base (idName fn) `orElse` [])
+       -- Only PrimOpIds have rules inside themselves, and perhaps more besides
 \end{code}
 
 
@@ -241,37 +268,17 @@ in the Simplifier works better as it is.  Reason: the 'args' passed
 to lookupRule are the result of a lazy substitution
 
 \begin{code}
--- | The main rule matching function. Attempts to apply all the active
--- rules in a given 'RuleBase' to this instance of an application
--- in a given context, returning the rule applied and the resulting
--- expression if successful.
-lookupRule :: (Activation -> Bool)  -- ^ Activation test
-           -> InScopeSet                -- ^ Variables that are in scope at this point
-          -> RuleBase                  -- ^ Imported rules
-          -> Id                        -- ^ Function 'Id' to lookup a rule by
-          -> [CoreExpr]                -- ^ Arguments to function
-          -> Maybe (CoreRule, CoreExpr)
--- See Note [Extra argsin rule matching]
-lookupRule is_active in_scope rule_base fn args
-  = matchRules is_active in_scope fn args (getRules rule_base fn)
-
-getRules :: RuleBase -> Id -> [CoreRule]
-       -- The rules for an Id come from two places:
-       --      (a) the ones it is born with (idCoreRules fn)
-       --      (b) rules added in subsequent modules (extra_rules)
-       -- PrimOps, for example, are born with a bunch of rules under (a)
-getRules rule_base fn
-  | isLocalId fn  = idCoreRules fn
-  | otherwise     = WARN( not (isPrimOpId fn) && notNull (idCoreRules fn), 
-                         ppr fn <+> ppr (idCoreRules fn) )
-                   idCoreRules fn ++ (lookupNameEnv rule_base (idName fn) `orElse` [])
-       -- Only PrimOpIds have rules inside themselves, and perhaps more besides
-
-matchRules :: (Activation -> Bool) -> InScopeSet
-          -> Id -> [CoreExpr]
-          -> [CoreRule] -> Maybe (CoreRule, CoreExpr)
+-- | 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.
+lookupRule :: (Activation -> Bool) -> InScopeSet
+           -> Id -> [CoreExpr]
+           -> [CoreRule] -> Maybe (CoreRule, CoreExpr)
+
+-- See Note [Extra args in rule matching]
 -- See comments on matchRule
-matchRules is_active in_scope fn args rules
+lookupRule is_active in_scope fn args rules
   = -- pprTrace "matchRules" (ppr fn <+> ppr rules) $
     case go [] rules of
        []     -> Nothing
@@ -284,7 +291,7 @@ matchRules is_active in_scope fn args rules
     go ms (r:rs) = case (matchRule is_active in_scope args rough_args r) of
                        Just e  -> go ((r,e):ms) rs
                        Nothing -> -- pprTrace "match failed" (ppr r $$ ppr args $$ 
-                                  --   ppr [(arg_id, unfoldingTemplate unf) | Var arg_id <- args, let unf = idUnfolding arg_id, isCheapUnfolding unf] )
+                                  --   ppr [(arg_id, unfoldingTemplate unf) | Var arg_id <- args, let unf = idUnfolding arg_id, isCheapUnfolding unf] )
                                   go ms         rs
 
 findBest :: (Id, [CoreExpr])
@@ -800,12 +807,12 @@ This pass runs over the tree (without changing it) and reports such.
 \begin{code}
 -- | Report partial matches for rules beginning with the specified
 -- string for the purposes of error reporting
-ruleCheckProgram :: CompilerPhase               -- ^ Phase to check in
+ruleCheckProgram :: (Activation -> Bool)    -- ^ Rule activation test
                  -> String                      -- ^ Rule pattern
                  -> RuleBase                    -- ^ Database of rules
                  -> [CoreBind]                  -- ^ Bindings to check in
                  -> SDoc                        -- ^ Resulting check message
-ruleCheckProgram phase rule_pat rule_base binds 
+ruleCheckProgram is_active rule_pat rule_base binds 
   | isEmptyBag results
   = text "Rule check results: no rule application sites"
   | otherwise
@@ -814,10 +821,14 @@ ruleCheckProgram phase rule_pat rule_base binds
          vcat [ p $$ line | p <- bagToList results ]
         ]
   where
-    results = unionManyBags (map (ruleCheckBind (phase, rule_pat, rule_base)) binds)
+    results = unionManyBags (map (ruleCheckBind (RuleCheckEnv is_active rule_pat rule_base)) binds)
     line = text (replicate 20 '-')
          
-type RuleCheckEnv = (CompilerPhase, String, RuleBase)  -- Phase and Pattern
+data RuleCheckEnv = RuleCheckEnv {
+    rc_is_active :: Activation -> Bool, 
+    rc_pattern :: String, 
+    rc_rule_base :: RuleBase
+}
 
 ruleCheckBind :: RuleCheckEnv -> CoreBind -> Bag SDoc
    -- The Bag returned has one SDoc for each call site found
@@ -846,15 +857,15 @@ ruleCheckFun :: RuleCheckEnv -> Id -> [CoreExpr] -> Bag SDoc
 -- Produce a report for all rules matching the predicate
 -- saying why it doesn't match the specified application
 
-ruleCheckFun (phase, pat, rule_base) fn args
+ruleCheckFun env fn args
   | null name_match_rules = emptyBag
-  | otherwise            = unitBag (ruleAppCheck_help phase fn args name_match_rules)
+  | otherwise            = unitBag (ruleAppCheck_help (rc_is_active env) fn args name_match_rules)
   where
-    name_match_rules = filter match (getRules rule_base fn)
-    match rule = pat `isPrefixOf` unpackFS (ruleName rule)
+    name_match_rules = filter match (getRules (rc_rule_base env) fn)
+    match rule = (rc_pattern env) `isPrefixOf` unpackFS (ruleName rule)
 
-ruleAppCheck_help :: CompilerPhase -> Id -> [CoreExpr] -> [CoreRule] -> SDoc
-ruleAppCheck_help phase fn args rules
+ruleAppCheck_help :: (Activation -> Bool) -> Id -> [CoreExpr] -> [CoreRule] -> SDoc
+ruleAppCheck_help is_active fn args rules
   =    -- The rules match the pattern, so we want to print something
     vcat [text "Expression:" <+> ppr (mkApps (Var fn) args),
          vcat (map check_rule rules)]
@@ -878,7 +889,7 @@ ruleAppCheck_help phase fn args rules
 
     rule_info (Rule { ru_name = name, ru_act = act, 
                      ru_bndrs = rule_bndrs, ru_args = rule_args})
-       | not (isActive phase act)    = text "active only in later phase"
+       | not (is_active act)    = text "active only in later phase"
        | n_args < n_rule_args        = text "too few arguments"
        | n_mismatches == n_rule_args = text "no arguments match"
        | n_mismatches == 0           = text "all arguments match (considered individually), but rule as a whole does not"