Rough matches for family instances
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
index 2c8780c..6bc1197 100644 (file)
@@ -30,7 +30,7 @@ module HscTypes (
        icPrintUnqual, mkPrintUnqualified,
 
        ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
-       emptyIfaceDepCache, 
+       emptyIfaceDepCache,
 
        Deprecs(..), IfaceDeprecs,
 
@@ -42,6 +42,7 @@ module HscTypes (
        TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
        extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
        typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
+       typeEnvDataCons,
 
        WhetherHasOrphans, IsBootInterface, Usage(..), 
        Dependencies(..), noDependencies,
@@ -77,14 +78,16 @@ import OccName              ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv,
                          extendOccEnv )
 import Module
 import InstEnv         ( InstEnv, Instance )
+import FamInstEnv      ( FamInstEnv, FamInst )
 import Rules           ( RuleBase )
 import CoreSyn         ( CoreBind )
 import Id              ( Id )
 import Type            ( TyThing(..) )
 
-import Class           ( Class, classSelIds, classTyCon )
-import TyCon           ( TyCon, tyConSelIds, tyConDataCons, isNewTyCon, newTyConCo )
-import DataCon         ( dataConImplicitIds )
+import Class           ( Class, classSelIds, classATs, classTyCon )
+import TyCon           ( TyCon, tyConSelIds, tyConDataCons, 
+                         newTyConCo_maybe, tyConFamilyCoercion_maybe )
+import DataCon         ( DataCon, dataConImplicitIds )
 import PrelNames       ( gHC_PRIM )
 import Packages                ( PackageId )
 import DynFlags                ( DynFlags(..), isOneShot, HscTarget (..) )
@@ -92,7 +95,8 @@ import DriverPhases   ( HscSource(..), isHsBoot, hscSourceString, Phase )
 import BasicTypes      ( Version, initialVersion, IPName, 
                          Fixity, defaultFixity, DeprecTxt )
 
-import IfaceSyn                ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
+import IfaceSyn                ( IfaceInst, IfaceFamInst, IfaceRule, 
+                         IfaceDecl(ifName) )
 
 import FiniteMap       ( FiniteMap )
 import CoreSyn         ( CoreRule )
@@ -105,6 +109,7 @@ import FastString   ( FastString )
 
 import DATA_IOREF      ( IORef, readIORef )
 import StringBuffer    ( StringBuffer )
+import Maybes           ( catMaybes, seqMaybe )
 import Time            ( ClockTime )
 \end{code}
 
@@ -242,12 +247,21 @@ lookupIfaceByModule
        -> Module
        -> Maybe ModIface
 lookupIfaceByModule dflags hpt pit mod
-  -- in one-shot, we don't use the HPT
-  | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
-  = fmap hm_iface (lookupUFM hpt (moduleName mod))
-  | otherwise
-  = lookupModuleEnv pit mod
-  where this_pkg = thisPackage dflags
+  | modulePackageId mod == thisPackage dflags
+  =    -- The module comes from the home package, so look first
+       -- in the HPT.  If it's not from the home package it's wrong to look
+       -- in the HPT, because the HPT is indexed by *ModuleName* not Module
+    fmap hm_iface (lookupUFM hpt (moduleName mod)) 
+    `seqMaybe` lookupModuleEnv pit mod
+
+  | otherwise = lookupModuleEnv pit mod                -- Look in PIT only 
+
+-- If the module does come from the home package, why do we look in the PIT as well?
+-- (a) In OneShot mode, even home-package modules accumulate in the PIT
+-- (b) Even in Batch (--make) mode, there is *one* case where a home-package
+--     module is in the PIT, namely GHC.Prim when compiling the base package.
+-- We could eliminate (b) if we wanted, by making GHC.Prim belong to a packake
+-- of its own, but it doesn't seem worth the bother.
 \end{code}
 
 
@@ -405,9 +419,11 @@ data ModIface
                -- HomeModInfo, but that leads to more plumbing.
 
                -- Instance declarations and rules
-       mi_insts     :: [IfaceInst],    -- Sorted
-       mi_rules     :: [IfaceRule],    -- Sorted
-       mi_rule_vers :: !Version,       -- Version number for rules and instances combined
+       mi_insts     :: [IfaceInst],                    -- Sorted
+       mi_fam_insts :: [IfaceFamInst],                 -- Sorted
+       mi_rules     :: [IfaceRule],                    -- Sorted
+       mi_rule_vers :: !Version,       -- Version number for rules and 
+                                       -- instances combined
 
                -- Cached environments for easy lookup
                -- These are computed (lazily) from other fields
@@ -424,16 +440,22 @@ data ModIface
 data ModDetails
    = ModDetails {
        -- The next three fields are created by the typechecker
-       md_exports  :: NameSet,
-        md_types    :: !TypeEnv,
-        md_insts    :: ![Instance],    -- Dfun-ids for the instances in this module
-        md_rules    :: ![CoreRule]     -- Domain may include Ids from other modules
+       md_exports   :: NameSet,
+        md_types     :: !TypeEnv,
+        md_fam_insts :: ![FamInst],    -- Cached value extracted from md_types
+        md_insts     :: ![Instance],    -- Dfun-ids for the instances in this 
+                                       -- module
+
+        md_rules     :: ![CoreRule]    -- Domain may include Ids from other 
+                                       -- modules
+
      }
 
 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
                               md_exports = emptyNameSet,
-                              md_insts = [],
-                              md_rules = [] }
+                              md_insts     = [],
+                              md_rules     = [],
+                              md_fam_insts = [] }
 
 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
 -- There is only one ModGuts at any time, the one for the module
@@ -442,23 +464,26 @@ emptyModDetails = ModDetails { md_types = emptyTypeEnv,
 
 data ModGuts
   = ModGuts {
-        mg_module   :: !Module,
-       mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
-       mg_exports  :: !NameSet,        -- What it exports
-       mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
-       mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
-                                       --      generate initialisation code
-       mg_usages   :: ![Usage],        -- Version info for what it needed
-
-        mg_rdr_env  :: !GlobalRdrEnv,  -- Top-level lexical environment
-       mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
-       mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
-
-       mg_types    :: !TypeEnv,
-       mg_insts    :: ![Instance],     -- Instances 
-        mg_rules    :: ![CoreRule],    -- Rules from this module
-       mg_binds    :: ![CoreBind],     -- Bindings for this module
-       mg_foreign  :: !ForeignStubs
+        mg_module    :: !Module,
+       mg_boot      :: IsBootInterface, -- Whether it's an hs-boot module
+       mg_exports   :: !NameSet,        -- What it exports
+       mg_deps      :: !Dependencies,   -- What is below it, directly or
+                                        --   otherwise 
+       mg_dir_imps  :: ![Module],       -- Directly-imported modules; used to
+                                        --     generate initialisation code
+       mg_usages    :: ![Usage],        -- Version info for what it needed
+
+        mg_rdr_env   :: !GlobalRdrEnv,  -- Top-level lexical environment
+       mg_fix_env   :: !FixityEnv,      -- Fixity env, for things declared in
+                                        --   this module 
+       mg_deprecs   :: !Deprecations,   -- Deprecations declared in the module
+
+       mg_types     :: !TypeEnv,
+       mg_insts     :: ![Instance],     -- Instances 
+       mg_fam_insts :: ![FamInst],      -- Instances 
+        mg_rules     :: ![CoreRule],    -- Rules from this module
+       mg_binds     :: ![CoreBind],     -- Bindings for this module
+       mg_foreign   :: !ForeignStubs
     }
 
 -- The ModGuts takes on several slightly different forms:
@@ -537,10 +562,11 @@ emptyModIface mod
               mi_exp_vers = initialVersion,
               mi_fixities = [],
               mi_deprecs  = NoDeprecs,
-              mi_insts = [],
-              mi_rules = [],
-              mi_decls = [],
-              mi_globals  = Nothing,
+              mi_insts     = [],
+              mi_fam_insts = [],
+              mi_rules     = [],
+              mi_decls     = [],
+              mi_globals   = Nothing,
               mi_rule_vers = initialVersion,
               mi_dep_fn = emptyIfaceDepCache,
               mi_fix_fn = emptyIfaceFixCache,
@@ -626,23 +652,25 @@ implicitTyThings (AnId id)   = []
        -- and the selectors and generic-programming Ids too
        --
        -- Newtypes don't have a worker Id, so don't generate that?
-implicitTyThings (ATyCon tc) = implicitNewCoTyCon tc ++
+implicitTyThings (ATyCon tc) = implicitCoTyCon tc ++
                               map AnId (tyConSelIds tc) ++ 
-                              concatMap (extras_plus . ADataCon) (tyConDataCons tc)
+                              concatMap (extras_plus . ADataCon) 
+                                        (tyConDataCons tc)
                     
        -- For classes, add the class TyCon too (and its extras)
-       -- and the class selector Ids
+       -- and the class selector Ids and the associated types (they don't
+       -- have extras as these are only the family decls)
 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
+                              map ATyCon (classATs cl) ++
                               extras_plus (ATyCon (classTyCon cl))
-                        
 
        -- For data cons add the worker and wrapper (if any)
 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
 
-       -- For newtypes, add the implicit coercion tycon
-implicitNewCoTyCon tc 
-  | isNewTyCon tc, Just co_con <- newTyConCo tc = [ATyCon co_con]
-  | otherwise = []
+       -- For newtypes and indexed data types, add the implicit coercion tycon
+implicitCoTyCon tc 
+  = map ATyCon . catMaybes $ [newTyConCo_maybe tc, 
+                             tyConFamilyCoercion_maybe tc]
 
 extras_plus thing = thing : implicitTyThings thing
 
@@ -660,18 +688,20 @@ extendTypeEnvWithIds env ids
 \begin{code}
 type TypeEnv = NameEnv TyThing
 
-emptyTypeEnv   :: TypeEnv
-typeEnvElts    :: TypeEnv -> [TyThing]
-typeEnvClasses :: TypeEnv -> [Class]
-typeEnvTyCons  :: TypeEnv -> [TyCon]
-typeEnvIds     :: TypeEnv -> [Id]
-lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
-
-emptyTypeEnv      = emptyNameEnv
-typeEnvElts    env = nameEnvElts env
-typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
-typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
-typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
+emptyTypeEnv    :: TypeEnv
+typeEnvElts     :: TypeEnv -> [TyThing]
+typeEnvClasses  :: TypeEnv -> [Class]
+typeEnvTyCons   :: TypeEnv -> [TyCon]
+typeEnvIds      :: TypeEnv -> [Id]
+typeEnvDataCons :: TypeEnv -> [DataCon]
+lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
+
+emptyTypeEnv       = emptyNameEnv
+typeEnvElts     env = nameEnvElts env
+typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
+typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
+typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
+typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
 
 mkTypeEnv :: [TyThing] -> TypeEnv
 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
@@ -704,7 +734,6 @@ lookupType dflags hpt pte name
        this_pkg = thisPackage dflags
 \end{code}
 
-
 \begin{code}
 tyThingTyCon (ATyCon tc) = tc
 tyThingTyCon other      = pprPanic "tyThingTyCon" (ppr other)
@@ -913,9 +942,10 @@ data Usage
 %************************************************************************
 
 \begin{code}
-type PackageTypeEnv  = TypeEnv
-type PackageRuleBase = RuleBase
-type PackageInstEnv  = InstEnv
+type PackageTypeEnv    = TypeEnv
+type PackageRuleBase   = RuleBase
+type PackageInstEnv    = InstEnv
+type PackageFamInstEnv = FamInstEnv
 
 data ExternalPackageState
   = EPS {
@@ -936,8 +966,8 @@ data ExternalPackageState
                -- The ModuleIFaces for modules in external packages
                -- whose interfaces we have opened
                -- The declarations in these interface files are held in
-               -- eps_decls, eps_inst_env, eps_rules (below), not in the 
-               -- mi_decls fields of the iPIT.  
+               -- eps_decls, eps_inst_env, eps_fam_inst_env, eps_rules
+               -- (below), not in the mi_decls fields of the iPIT.  
                -- What _is_ in the iPIT is:
                --      * The Module 
                --      * Version info
@@ -945,11 +975,13 @@ data ExternalPackageState
                --      * Fixities
                --      * Deprecations
 
-       eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
+       eps_PTE :: !PackageTypeEnv,        -- Domain = external-package modules
 
-       eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
-                                               --   all the external-package modules
-       eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
+       eps_inst_env     :: !PackageInstEnv,   -- The total InstEnv accumulated
+                                              -- from all the external-package
+                                              -- modules 
+       eps_fam_inst_env :: !PackageFamInstEnv,-- Ditto FamInstEnv
+       eps_rule_base    :: !PackageRuleBase,  -- Ditto RuleEnv
 
        eps_stats :: !EpsStats
   }