[commit: ghc] master: Move declaration of Rulebase from Rules to CoreSyn (dbd9299)

git at git.haskell.org git at git.haskell.org
Tue Mar 17 12:38:20 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/dbd929971c05b5a05129029657a354ddfb658e61/ghc

>---------------------------------------------------------------

commit dbd929971c05b5a05129029657a354ddfb658e61
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Mar 17 00:00:31 2015 +0000

    Move declaration of Rulebase from Rules to CoreSyn
    
    This allow HscTypes to import CoreSyn rather than Rules, which makes
    module loops easier to avoid.  At one point in my recent travels this
    was important; I'm not sure it's so important now, but it's a good
    thing anyway.
    
    In any case CoreRule is defined in CoreSyn, so this move make sense.


>---------------------------------------------------------------

dbd929971c05b5a05129029657a354ddfb658e61
 compiler/coreSyn/CoreSyn.hs      | 8 +++++++-
 compiler/main/HscTypes.hs        | 3 +--
 compiler/simplCore/CoreMonad.hs  | 1 -
 compiler/simplCore/SimplCore.hs  | 9 +++++++--
 compiler/simplCore/SimplMonad.hs | 2 +-
 compiler/specialise/Rules.hs     | 8 +-------
 6 files changed, 17 insertions(+), 14 deletions(-)

diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs
index 32ebd8a..86939bd 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/coreSyn/CoreSyn.hs
@@ -71,7 +71,7 @@ module CoreSyn (
         deAnnotate, deAnnotate', deAnnAlt, collectAnnBndrs,
 
         -- * Core rule data types
-        CoreRule(..),   -- CoreSubst, CoreTidy, CoreFVs, PprCore only
+        CoreRule(..), RuleBase,
         RuleName, RuleFun, IdUnfoldingFun, InScopeEnv,
 
         -- ** Operations on 'CoreRule's
@@ -91,6 +91,7 @@ import Var
 import Type
 import Coercion
 import Name
+import NameEnv( NameEnv )
 import Literal
 import DataCon
 import Module
@@ -708,6 +709,11 @@ The CoreRule type and its friends are dealt with mainly in CoreRules,
 but CoreFVs, Subst, PprCore, CoreTidy also inspect the representation.
 -}
 
+-- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules
+type RuleBase = NameEnv [CoreRule]
+        -- The rules are are unordered;
+        -- we sort out any overlaps on lookup
+
 -- | A 'CoreRule' is:
 --
 -- * \"Local\" if the function it is a rule for is defined in the
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index 09f643c..90ed559 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -140,8 +140,7 @@ import Avail
 import Module
 import InstEnv          ( InstEnv, ClsInst, identicalClsInstHead )
 import FamInstEnv
-import Rules            ( RuleBase )
-import CoreSyn          ( CoreProgram )
+import CoreSyn          ( CoreProgram, RuleBase )
 import Name
 import NameEnv
 import NameSet
diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs
index e9c828d..dec41bb 100644
--- a/compiler/simplCore/CoreMonad.hs
+++ b/compiler/simplCore/CoreMonad.hs
@@ -62,7 +62,6 @@ import HscTypes
 import Module
 import DynFlags
 import StaticFlags
-import Rules            ( RuleBase )
 import BasicTypes       ( CompilerPhase(..) )
 import Annotations
 
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index 3e82084..0fd929a 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -15,7 +15,7 @@ import CoreSyn
 import CoreSubst
 import HscTypes
 import CSE              ( cseProgram )
-import Rules            ( RuleBase, emptyRuleBase, mkRuleBase, unionRuleBase,
+import Rules            ( emptyRuleBase, mkRuleBase, unionRuleBase,
                           extendRuleBaseList, ruleCheckProgram, addSpecInfo, )
 import PprCore          ( pprCoreBindings, pprCoreExpr )
 import OccurAnal        ( occurAnalysePgm, occurAnalyseExpr )
@@ -625,7 +625,8 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode)
                        InitialPhase -> (mg_vect_decls guts, vectVars)
                        _            -> ([], vectVars)
                ; tagged_binds = {-# SCC "OccAnal" #-}
-                     occurAnalysePgm this_mod active_rule rules maybeVects maybeVectVars binds
+                     occurAnalysePgm this_mod active_rule rules
+                                     maybeVects maybeVectVars binds
                } ;
            Err.dumpIfSet_dyn dflags Opt_D_dump_occur_anal "Occurrence analysis"
                      (pprCoreBindings tagged_binds);
@@ -646,6 +647,10 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode)
                 -- Simplify the program
            (env1, counts1) <- initSmpl dflags rule_base2 fam_envs us1 sz simpl_binds ;
 
+                -- Apply the substitution to rules defined in this module
+                -- for imported Ids.  Eg  RULE map my_f = blah
+                -- If we have a substitution my_f :-> other_f, we'd better
+                -- apply it to the rule to, or it'll never match
            let  { binds1 = getFloatBinds env1
                 ; rules1 = substRulesForImportedIds (mkCoreSubst (text "imp-rules") env1) rules
                 } ;
diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs
index 0069106..fbf23d7 100644
--- a/compiler/simplCore/SimplMonad.hs
+++ b/compiler/simplCore/SimplMonad.hs
@@ -22,7 +22,7 @@ module SimplMonad (
 import Id               ( Id, mkSysLocal )
 import Type             ( Type )
 import FamInstEnv       ( FamInstEnv )
-import Rules            ( RuleBase )
+import CoreSyn          ( RuleBase )
 import UniqSupply
 import DynFlags
 import CoreMonad
diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs
index b66d973..e6e5359 100644
--- a/compiler/specialise/Rules.hs
+++ b/compiler/specialise/Rules.hs
@@ -9,9 +9,6 @@
 -- | Functions for collecting together and applying rewrite rules to a module.
 -- The 'CoreRule' datatype itself is declared elsewhere.
 module Rules (
-        -- * RuleBase
-        RuleBase,
-
         -- ** Constructing
         emptyRuleBase, mkRuleBase, extendRuleBaseList,
         unionRuleBase, pprRuleBase,
@@ -315,10 +312,7 @@ but that isn't quite right:
 ************************************************************************
 -}
 
--- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules
-type RuleBase = NameEnv [CoreRule]
-        -- The rules are are unordered;
-        -- we sort out any overlaps on lookup
+-- RuleBase itself is defined in CoreSyn, along with CoreRule
 
 emptyRuleBase :: RuleBase
 emptyRuleBase = emptyNameEnv



More information about the ghc-commits mailing list