Basic set up for global family instance environment
[ghc-hetmet.git] / compiler / typecheck / TcRnTypes.lhs
index f16e9a8..30c922d 100644 (file)
@@ -21,7 +21,6 @@ module TcRnTypes(
 
        -- Typechecker types
        TcTyThing(..), pprTcTyThingCategory, 
-       GadtRefinement,
 
        -- Template Haskell
        ThStage(..), topStage, topSpliceStage,
@@ -44,28 +43,31 @@ module TcRnTypes(
 
 import HsSyn           ( PendingSplice, HsOverLit, LRuleDecl, LForeignDecl,
                          ArithSeqInfo, DictBinds, LHsBinds, LImportDecl, HsGroup,
-                          IE )
+                          ExprCoFn, IE )
 import HscTypes                ( FixityEnv,
                          HscEnv, TypeEnv, TyThing, 
                          GenAvailInfo(..), AvailInfo, HscSource(..),
                          availName, IsBootInterface, Deprecations )
-import Packages                ( PackageId, HomeModules )
+import Packages                ( PackageId )
 import Type            ( Type, pprTyThingCategory )
 import TcType          ( TcTyVarSet, TcType, TcThetaType, SkolemInfo, TvSubst,
-                         TcPredType, TcKind, tcCmpPred, tcCmpType, tcCmpTypes, pprSkolInfo )
+                         TcPredType, TcKind, tcCmpPred, tcCmpType,
+                         tcCmpTypes, pprSkolInfo )
 import InstEnv         ( Instance, InstEnv )
+import FamInstEnv      ( FamInst, FamInstEnv )
 import IOEnv
 import RdrName         ( GlobalRdrEnv, LocalRdrEnv )
 import Name            ( Name )
 import NameEnv
 import NameSet         ( NameSet, unionNameSets, DefUses )
-import OccName         ( OccEnv )
 import Var             ( Id, TyVar )
 import VarEnv          ( TidyEnv )
 import Module
+import UniqFM
 import SrcLoc          ( SrcSpan, SrcLoc, Located, srcSpanStart )
 import VarSet          ( IdSet )
 import ErrUtils                ( Messages, Message )
+import UniqFM           ( UniqFM )
 import UniqSupply      ( UniqSupply )
 import BasicTypes      ( IPName )
 import Util            ( thenCmp )
@@ -91,10 +93,9 @@ type TcId             = Id                   -- Type may be a TcType
 type TcIdSet    = IdSet
 type TcDictBinds = DictBinds TcId      -- Bag of dictionary bindings
 
-
-
 type TcRnIf a b c = IOEnv (Env a b) c
 type IfM lcl a  = TcRnIf IfGblEnv lcl a                -- Iface stuff
+
 type IfG a  = IfM () a                         -- Top level
 type IfL a  = IfM IfLclEnv a                   -- Nested
 type TcRn a = TcRnIf TcGblEnv TcLclEnv a
@@ -115,7 +116,8 @@ data Env gbl lcl    -- Changes as we move into an expression
        env_top  :: HscEnv,     -- Top-level stuff that never changes
                                -- Includes all info about imported things
 
-       env_us   :: TcRef UniqSupply,   -- Unique supply for local varibles
+       env_us   :: {-# UNPACK #-} !(IORef UniqSupply), 
+                               -- Unique supply for local varibles
 
        env_gbl  :: gbl,        -- Info about things defined at the top level
                                -- of the module being compiled
@@ -153,8 +155,11 @@ data TcGblEnv
                -- bound in this module when dealing with hi-boot recursions
                -- Updated at intervals (e.g. after dealing with types and classes)
        
-       tcg_inst_env :: InstEnv,        -- Instance envt for *home-package* modules
-                                       -- Includes the dfuns in tcg_insts
+       tcg_inst_env     :: InstEnv,    -- Instance envt for *home-package* 
+                                       -- modules; Includes the dfuns in 
+                                       -- tcg_insts
+       tcg_fam_inst_env :: FamInstEnv, -- Ditto for family instances
+
                -- Now a bunch of things about this module that are simply 
                -- accumulated, but never consulted until the end.  
                -- Nevertheless, it's convenient to accumulate them along 
@@ -164,10 +169,6 @@ data TcGblEnv
                                        --    from where, including things bound
                                        --    in this module
 
-       tcg_home_mods :: HomeModules,
-                               -- Calculated from ImportAvails, allows us to
-                               -- call Packages.isHomeModule
-
        tcg_dus :: DefUses,     -- What is defined in this module and what is used.
                                -- The latter is used to generate 
                                --      (a) version tracking; no need to recompile if these
@@ -266,8 +267,8 @@ data IfLclEnv
                --      .hi file, or GHCi state, or ext core
                -- plus which bit is currently being examined
 
-       if_tv_env  :: OccEnv TyVar,     -- Nested tyvar bindings
-       if_id_env  :: OccEnv Id         -- Nested id binding
+       if_tv_env  :: UniqFM TyVar,     -- Nested tyvar bindings
+       if_id_env  :: UniqFM Id         -- Nested id binding
     }
 \end{code}
 
@@ -327,7 +328,6 @@ data TcLclEnv               -- Changes as we move inside an expression
        tcl_lie   :: TcRef LIE          -- Place to accumulate type constraints
     }
 
-type GadtRefinement = TvSubst
 
 {- Note [Given Insts]
    ~~~~~~~~~~~~~~~~~~
@@ -422,9 +422,15 @@ escapeArrowScope
 data TcTyThing
   = AGlobal TyThing            -- Used only in the return type of a lookup
 
-  | ATcId   TcId               -- Ids defined in this module; may not be fully zonked
-           ThLevel 
-           Bool                -- True <=> apply the type refinement to me
+  | ATcId   {          -- Ids defined in this module; may not be fully zonked
+       tct_id :: TcId,         
+       tct_co :: Maybe ExprCoFn,       -- Nothing <=>  Do not apply a GADT type refinement
+                                       --              I am wobbly, or have no free
+                                       --              type variables
+                                       -- Just co <=>  Apply any type refinement to me,
+                                       --              and record it in the coercion
+       tct_type  :: TcType,    -- Type of (coercion applied to id)
+       tct_level :: ThLevel }
 
   | ATyVar  Name TcType                -- The type to which the lexically scoped type vaiable
                                -- is currently refined. We only need the Name
@@ -435,8 +441,9 @@ data TcTyThing
 
 instance Outputable TcTyThing where    -- Debugging only
    ppr (AGlobal g)      = ppr g
-   ppr (ATcId g tl rig) = text "Identifier" <> 
-                         ifPprDebug (brackets (ppr g <> comma <> ppr tl <+> ppr rig))
+   ppr elt@(ATcId {})   = text "Identifier" <> 
+                         ifPprDebug (brackets (ppr (tct_id elt) <> dcolon <> ppr (tct_type elt) <> comma
+                                <+> ppr (tct_level elt) <+> ppr (tct_co elt)))
    ppr (ATyVar tv _)    = text "Type variable" <+> quotes (ppr tv)
    ppr (AThing k)       = text "AThing" <+> ppr k
 
@@ -472,7 +479,7 @@ It is used  * when processing the export list
 \begin{code}
 data ImportAvails 
    = ImportAvails {
-       imp_env :: ModuleEnv NameSet,
+       imp_env :: ModuleNameEnv NameSet,
                -- All the things imported, classified by 
                -- the *module qualifier* for its import
                --   e.g.        import List as Foo
@@ -501,7 +508,7 @@ data ImportAvails
                --       need to recompile if the export version changes
                --   (b) to specify what child modules to initialise
 
-       imp_dep_mods :: ModuleEnv (Module, IsBootInterface),
+       imp_dep_mods :: ModuleNameEnv (ModuleName, IsBootInterface),
                -- Home-package modules needed by the module being compiled
                --
                -- It doesn't matter whether any of these dependencies
@@ -520,16 +527,16 @@ data ImportAvails
                -- Orphan modules below us in the import tree
       }
 
-mkModDeps :: [(Module, IsBootInterface)]
-         -> ModuleEnv (Module, IsBootInterface)
-mkModDeps deps = foldl add emptyModuleEnv deps
+mkModDeps :: [(ModuleName, IsBootInterface)]
+         -> ModuleNameEnv (ModuleName, IsBootInterface)
+mkModDeps deps = foldl add emptyUFM deps
               where
-                add env elt@(m,_) = extendModuleEnv env m elt
+                add env elt@(m,_) = addToUFM env m elt
 
 emptyImportAvails :: ImportAvails
-emptyImportAvails = ImportAvails { imp_env     = emptyModuleEnv, 
+emptyImportAvails = ImportAvails { imp_env     = emptyUFM, 
                                   imp_mods     = emptyModuleEnv,
-                                  imp_dep_mods = emptyModuleEnv,
+                                  imp_dep_mods = emptyUFM,
                                   imp_dep_pkgs = [],
                                   imp_orphs    = [] }
 
@@ -539,9 +546,9 @@ plusImportAvails
                  imp_dep_mods = dmods1, imp_dep_pkgs = dpkgs1, imp_orphs = orphs1 })
   (ImportAvails { imp_env = env2, imp_mods = mods2,
                  imp_dep_mods = dmods2, imp_dep_pkgs = dpkgs2, imp_orphs = orphs2 })
-  = ImportAvails { imp_env      = plusModuleEnv_C unionNameSets env1 env2, 
+  = ImportAvails { imp_env      = plusUFM_C unionNameSets env1 env2, 
                   imp_mods     = mods1  `plusModuleEnv` mods2, 
-                  imp_dep_mods = plusModuleEnv_C plus_mod_dep dmods1 dmods2,   
+                  imp_dep_mods = plusUFM_C plus_mod_dep dmods1 dmods2, 
                   imp_dep_pkgs = dpkgs1 `unionLists` dpkgs2,
                   imp_orphs    = orphs1 `unionLists` orphs2 }
   where
@@ -801,7 +808,8 @@ data InstOrigin
 \begin{code}
 pprInstLoc :: InstLoc -> SDoc
 pprInstLoc (InstLoc orig locn _)
-  = hsep [text "arising from", pp_orig orig, text "at", ppr locn]
+  = sep [text "arising from" <+> pp_orig orig, 
+        text "at" <+> ppr locn]
   where
     pp_orig (OccurrenceOf name)  = hsep [ptext SLIT("use of"), quotes (ppr name)]
     pp_orig (IPOccOrigin name)   = hsep [ptext SLIT("use of implicit parameter"), quotes (ppr name)]