[project @ 2001-11-26 09:20:25 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
index a490730..762e315 100644 (file)
@@ -5,6 +5,8 @@
 
 \begin{code}
 module HscTypes ( 
+       GhciMode(..),
+
        ModuleLocation(..),
 
        ModDetails(..), ModIface(..), 
@@ -24,11 +26,11 @@ module HscTypes (
 
        TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
        extendTypeEnvList, extendTypeEnvWithIds,
-       typeEnvClasses, typeEnvTyCons, typeEnvIds,
+       typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
 
        ImportedModuleInfo, WhetherHasOrphans, ImportVersion, WhatsImported(..),
        PersistentRenamerState(..), IsBootInterface, DeclsMap,
-       IfaceInsts, IfaceRules, GatedDecl, GatedDecls, IsExported,
+       IfaceInsts, IfaceRules, GatedDecl, GatedDecls, GateFn, IsExported,
        NameSupply(..), OrigNameCache, OrigIParamCache,
        Avails, AvailEnv, GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
        PersistentCompilerState(..),
@@ -50,7 +52,8 @@ module HscTypes (
 
 #include "HsVersions.h"
 
-import RdrName         ( RdrNameEnv, addListToRdrEnv, emptyRdrEnv, mkRdrUnqual, rdrEnvToList )
+import RdrName         ( RdrName, RdrNameEnv, addListToRdrEnv, emptyRdrEnv, 
+                         mkRdrUnqual, rdrEnvToList )
 import Name            ( Name, NamedThing, getName, nameOccName, nameModule, nameSrcLoc )
 import NameEnv
 import OccName         ( OccName )
@@ -61,8 +64,9 @@ import InstEnv                ( InstEnv, ClsInstEnv, DFunId )
 import Rules           ( RuleBase )
 import CoreSyn         ( CoreBind )
 import Id              ( Id )
+import Type            ( IPName )
 import Class           ( Class, classSelIds )
-import TyCon           ( TyCon, tyConGenIds, tyConSelIds, tyConDataConsIfAvailable )
+import TyCon           ( TyCon, isNewTyCon, tyConGenIds, tyConSelIds, tyConDataConsIfAvailable )
 import DataCon         ( dataConId, dataConWrapId )
 
 import BasicTypes      ( Version, initialVersion, Fixity )
@@ -84,6 +88,18 @@ import UniqSupply    ( UniqSupply )
 
 %************************************************************************
 %*                                                                     *
+\subsection{Which mode we're in
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+data GhciMode = Batch | Interactive | OneShot 
+     deriving Eq
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
 \subsection{Module locations}
 %*                                                                     *
 %************************************************************************
@@ -125,26 +141,26 @@ linking; it is the "linked" form of the mi_decls field.
 \begin{code}
 data ModIface 
    = ModIface {
-        mi_module   :: Module,                 -- Complete with package info
-        mi_version  :: VersionInfo,            -- Module version number
-        mi_orphan   :: WhetherHasOrphans,       -- Whether this module has orphans
-       mi_boot     :: IsBootInterface,         -- Whether this interface was read from an hi-boot file
+        mi_module   :: !Module,                    -- Complete with package info
+        mi_version  :: !VersionInfo,       -- Module version number
+        mi_orphan   :: WhetherHasOrphans,   -- Whether this module has orphans
+       mi_boot     :: !IsBootInterface,    -- read from an hi-boot file?
 
-        mi_usages   :: [ImportVersion Name],   -- Usages; kept sorted so that it's easy
-                                               -- to decide whether to write a new iface file
-                                               -- (changing usages doesn't affect the version of
-                                               --  this module)
+        mi_usages   :: ![ImportVersion Name],  
+               -- Usages; kept sorted so that it's easy to decide
+               -- whether to write a new iface file (changing usages
+               -- doesn't affect the version of this module)
 
-        mi_exports  :: [(ModuleName,Avails)],  -- What it exports
-                                               -- Kept sorted by (mod,occ),
-                                               -- to make version comparisons easier
+        mi_exports  :: ![(ModuleName,Avails)],
+               -- What it exports Kept sorted by (mod,occ), to make
+               -- version comparisons easier
 
-        mi_globals  :: GlobalRdrEnv,           -- Its top level environment
+        mi_globals  :: !GlobalRdrEnv,      -- Its top level environment
 
-        mi_fixities :: NameEnv Fixity,         -- Fixities
-       mi_deprecs  :: Deprecations,            -- Deprecations
+        mi_fixities :: !(NameEnv Fixity),   -- Fixities
+       mi_deprecs  :: !Deprecations,       -- Deprecations
 
-       mi_decls    :: IfaceDecls               -- The RnDecls form of ModDetails
+       mi_decls    :: IfaceDecls           -- The RnDecls form of ModDetails
      }
 
 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl], -- Sorted
@@ -166,16 +182,16 @@ mkIfaceDecls tycls rules insts
 data ModDetails
    = ModDetails {
        -- The next three fields are created by the typechecker
-        md_types    :: TypeEnv,
-        md_insts    :: [DFunId],       -- Dfun-ids for the instances in this module
-        md_rules    :: [IdCoreRule],   -- Domain may include Ids from other modules
-       md_binds    :: [CoreBind]
+        md_types    :: !TypeEnv,
+        md_insts    :: ![DFunId],      -- Dfun-ids for the instances in this module
+        md_rules    :: ![IdCoreRule],  -- Domain may include Ids from other modules
+       md_binds    :: ![CoreBind]
      }
 
 -- The ModDetails takes on several slightly different forms:
 --
 -- After typecheck + desugar
---     md_types        Contains TyCons, Classes, and hasNoBinding Ids
+--     md_types        Contains TyCons, Classes, and implicit Ids
 --     md_insts        All instances from this module (incl derived ones)
 --     md_rules        All rules from this module
 --     md_binds        Desugared bindings
@@ -303,9 +319,16 @@ instance Outputable TyThing where
   ppr (ATyCon tc) = ptext SLIT("ATyCon") <+> ppr tc
   ppr (AClass cl) = ptext SLIT("AClass") <+> ppr cl
 
-typeEnvClasses env = [cl | AClass cl <- nameEnvElts env]
-typeEnvTyCons  env = [tc | ATyCon tc <- nameEnvElts env] 
-typeEnvIds     env = [id | AnId id   <- nameEnvElts env] 
+
+typeEnvElts    :: TypeEnv -> [TyThing]
+typeEnvClasses :: TypeEnv -> [Class]
+typeEnvTyCons  :: TypeEnv -> [TyCon]
+typeEnvIds     :: TypeEnv -> [Id]
+
+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] 
 
 implicitTyThingIds :: [TyThing] -> [Id]
 -- Add the implicit data cons and selectors etc 
@@ -317,8 +340,13 @@ implicitTyThingIds things
     go (ATyCon tc) = tyConGenIds tc ++
                     tyConSelIds tc ++
                     [ n | dc <- tyConDataConsIfAvailable tc, 
-                          n  <- [dataConId dc, dataConWrapId dc] ] 
+                          n  <- implicitConIds tc dc]
                -- Synonyms return empty list of constructors and selectors
+
+    implicitConIds tc dc       -- Newtypes have a constructor wrapper,
+                               -- but no worker
+       | isNewTyCon tc = [dataConWrapId dc]
+       | otherwise     = [dataConId dc, dataConWrapId dc]
 \end{code}
 
 
@@ -486,18 +514,18 @@ type IsExported = Name -> Bool            -- True for names that are exported from this mo
 \begin{code}
 data PersistentCompilerState 
    = PCS {
-        pcs_PIT :: PackageIfaceTable,  -- Domain = non-home-package modules
+        pcs_PIT :: !PackageIfaceTable, -- Domain = non-home-package modules
                                        --   the mi_decls component is empty
 
-        pcs_PTE :: PackageTypeEnv,     -- Domain = non-home-package modules
+        pcs_PTE :: !PackageTypeEnv,    -- Domain = non-home-package modules
                                        --   except that the InstEnv components is empty
 
-       pcs_insts :: PackageInstEnv,    -- The total InstEnv accumulated from all
+       pcs_insts :: !PackageInstEnv,   -- The total InstEnv accumulated from all
                                        --   the non-home-package modules
 
-       pcs_rules :: PackageRuleBase,   -- Ditto RuleEnv
+       pcs_rules :: !PackageRuleBase,  -- Ditto RuleEnv
 
-        pcs_PRS :: PersistentRenamerState
+        pcs_PRS :: !PersistentRenamerState
      }
 \end{code}
 
@@ -528,11 +556,11 @@ type PackageRuleBase = RuleBase
 type PackageInstEnv  = InstEnv
 
 data PersistentRenamerState
-  = PRS { prsOrig    :: NameSupply,
-         prsImpMods :: ImportedModuleInfo,
-         prsDecls   :: DeclsMap,
-         prsInsts   :: IfaceInsts,
-         prsRules   :: IfaceRules
+  = PRS { prsOrig    :: !NameSupply,
+         prsImpMods :: !ImportedModuleInfo,
+         prsDecls   :: !DeclsMap,
+         prsInsts   :: !IfaceInsts,
+         prsRules   :: !IfaceRules
     }
 \end{code}
 
@@ -559,7 +587,7 @@ data NameSupply
    }
 
 type OrigNameCache   = FiniteMap (ModuleName,OccName) Name
-type OrigIParamCache = FiniteMap OccName Name
+type OrigIParamCache = FiniteMap (IPName RdrName) (IPName Name)
 \end{code}
 
 @ImportedModuleInfo@ contains info ONLY about modules that have not yet 
@@ -585,7 +613,13 @@ type IfaceInsts = GatedDecls RdrNameInstDecl
 type IfaceRules = GatedDecls RdrNameRuleDecl
 
 type GatedDecls d = (Bag (GatedDecl d), Int)   -- The Int says how many have been sucked in
-type GatedDecl  d = ([Name], (Module, d))
+type GatedDecl  d = (GateFn, (Module, d))
+type GateFn       = (Name -> Bool) -> Bool     -- Returns True <=> gate is open
+                                               -- The (Name -> Bool) fn returns True for visible Names
+       -- For example, suppose this is in an interface file
+       --      instance C T where ...
+       -- We want to slurp this decl if both C and T are "visible" in 
+       -- the importing module.  See "The gating story" in RnIfaces for details.
 \end{code}