Merge remote branch 'working/master'
authorSimon Marlow <marlowsd@gmail.com>
Mon, 6 Jun 2011 10:39:00 +0000 (11:39 +0100)
committerSimon Marlow <marlowsd@gmail.com>
Mon, 6 Jun 2011 10:39:00 +0000 (11:39 +0100)
1  2 
compiler/main/HscTypes.lhs

@@@ -100,7 -100,7 +100,7 @@@ module HscTypes 
  #include "HsVersions.h"
  
  #ifdef GHCI
 -import ByteCodeAsm    ( CompiledByteCode )
 +import ByteCodeAsm      ( CompiledByteCode )
  import {-# SOURCE #-}  InteractiveEval ( Resume )
  #endif
  
@@@ -108,17 -108,16 +108,17 @@@ import HsSy
  import RdrName
  import Name
  import NameEnv
 -import NameSet        
 +import NameSet  
  import Module
 -import InstEnv                ( InstEnv, Instance )
 -import FamInstEnv     ( FamInstEnv, FamInst )
 -import Rules          ( RuleBase )
 -import CoreSyn                ( CoreBind )
 +import InstEnv          ( InstEnv, Instance )
 +import FamInstEnv       ( FamInstEnv, FamInst )
 +import Rules            ( RuleBase )
 +import CoreSyn          ( CoreBind )
  import VarEnv
 +import VarSet
  import Var
  import Id
 -import Type           
 +import Type             
  
  import Annotations
  import Class          ( Class, classAllSelIds, classATs, classTyCon )
@@@ -864,37 -863,47 +864,47 @@@ emptyModIface mo
  %************************************************************************
  
  \begin{code}
- -- | Interactive context, recording information relevant to GHCi
+ -- | Interactive context, recording information about the state of the
+ -- context in which statements are executed in a GHC session.
+ --
  data InteractiveContext 
    = InteractiveContext { 
-           ic_toplev_scope :: [Module]   -- ^ The context includes the "top-level" scope of
-                                       -- these modules
-         , ic_exports :: [(Module, Maybe (ImportDecl RdrName))]    -- ^ The context includes just the exported parts of these
-                                       -- modules
-         , ic_rn_gbl_env :: GlobalRdrEnv -- ^ The contexts' cached 'GlobalRdrEnv', built from
-                                       -- 'ic_toplev_scope' and 'ic_exports'
-         , ic_tmp_ids :: [Id]   -- ^ Names bound during interaction with the user.
-                                -- Later Ids shadow earlier ones with the same OccName
-                                -- Expressions are typed with these Ids in the envt
-                                -- For runtime-debugging, these Ids may have free
-                                -- TcTyVars of RuntimUnkSkol flavour, but no free TyVars
-                                -- (because the typechecker doesn't expect that)
+          -- These two fields are only stored here so that the client
+          -- can retrieve them with GHC.getContext.  GHC itself doesn't
+          -- use them, but it does reset them to empty sometimes (such
+          -- as before a GHC.load).  The context is set with GHC.setContext.
+          ic_toplev_scope :: [Module],
+              -- ^ The context includes the "top-level" scope of
+              -- these modules
+          ic_imports :: [ImportDecl RdrName],
+              -- ^ The context is extended with these import declarations
+          ic_rn_gbl_env :: GlobalRdrEnv,
+              -- ^ The contexts' cached 'GlobalRdrEnv', built by
+              -- 'InteractiveEval.setContext'
+          ic_tmp_ids :: [Id],
+              -- ^ Names bound during interaction with the user.  Later
+              -- Ids shadow earlier ones with the same OccName
+              -- Expressions are typed with these Ids in the envt For
+              -- runtime-debugging, these Ids may have free TcTyVars of
+              -- RuntimUnkSkol flavour, but no free TyVars (because the
+              -- typechecker doesn't expect that)
  
  #ifdef GHCI
-         , ic_resume :: [Resume]         -- ^ The stack of breakpoint contexts
+          ic_resume :: [Resume],
+              -- ^ The stack of breakpoint contexts
  #endif
  
-         , ic_cwd :: Maybe FilePath      -- virtual CWD of the program
+          ic_cwd :: Maybe FilePath
+              -- virtual CWD of the program
      }
  
  
  emptyInteractiveContext :: InteractiveContext
  emptyInteractiveContext
    = InteractiveContext { ic_toplev_scope = [],
-                        ic_exports = [],
+                          ic_imports = [],
                         ic_rn_gbl_env = emptyGlobalRdrEnv,
                         ic_tmp_ids = []
  #ifdef GHCI
@@@ -1713,9 -1722,9 +1723,9 @@@ isHpcUsed (NoHpcInfo { hpcUsed = used }
  \end{code}
  
  %************************************************************************
 -%*                                                                    *
 +%*                                                                      *
  \subsection{Vectorisation Support}
 -%*                                                                    *
 +%*                                                                      *
  %************************************************************************
  
  The following information is generated and consumed by the vectorisation
@@@ -1728,58 -1737,49 +1738,58 @@@ vectorisation, we need to know `f_v', w
  on just the OccName easily in a Core pass.
  
  \begin{code}
 --- | Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'.
 +-- |Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'; see also
 +-- documentation at 'Vectorise.Env.GlobalEnv'.
  data VectInfo      
 -  = VectInfo {
 -      vectInfoVar     :: VarEnv  (Var    , Var  ),   -- ^ @(f, f_v)@ keyed on @f@
 -      vectInfoTyCon   :: NameEnv (TyCon  , TyCon),   -- ^ @(T, T_v)@ keyed on @T@
 -      vectInfoDataCon :: NameEnv (DataCon, DataCon), -- ^ @(C, C_v)@ keyed on @C@
 -      vectInfoPADFun  :: NameEnv (TyCon  , Var),     -- ^ @(T_v, paT)@ keyed on @T_v@
 -      vectInfoIso     :: NameEnv (TyCon  , Var)      -- ^ @(T, isoT)@ keyed on @T@
 +  = VectInfo
 +    { vectInfoVar          :: VarEnv  (Var    , Var  )    -- ^ @(f, f_v)@ keyed on @f@
 +    , vectInfoTyCon        :: NameEnv (TyCon  , TyCon)    -- ^ @(T, T_v)@ keyed on @T@
 +    , vectInfoDataCon      :: NameEnv (DataCon, DataCon)  -- ^ @(C, C_v)@ keyed on @C@
 +    , vectInfoPADFun       :: NameEnv (TyCon  , Var)      -- ^ @(T_v, paT)@ keyed on @T_v@
 +    , vectInfoIso          :: NameEnv (TyCon  , Var)      -- ^ @(T, isoT)@ keyed on @T@
 +    , vectInfoScalarVars   :: VarSet                      -- ^ set of purely scalar variables
 +    , vectInfoScalarTyCons :: NameSet                     -- ^ set of scalar type constructors
      }
  
 --- | Vectorisation information for 'ModIface': a slightly less low-level view
 +-- |Vectorisation information for 'ModIface'; i.e, the vectorisation information propagated 
 +-- across module boundaries.
 +--
  data IfaceVectInfo 
 -  = IfaceVectInfo {
 -      ifaceVectInfoVar        :: [Name],
 -        -- ^ All variables in here have a vectorised variant
 -      ifaceVectInfoTyCon      :: [Name],
 -        -- ^ All 'TyCon's in here have a vectorised variant;
 -        -- the name of the vectorised variant and those of its
 -        -- data constructors are determined by 'OccName.mkVectTyConOcc'
 -        -- and 'OccName.mkVectDataConOcc'; the names of
 -        -- the isomorphisms are determined by 'OccName.mkVectIsoOcc'
 -      ifaceVectInfoTyConReuse :: [Name]              
 -        -- ^ The vectorised form of all the 'TyCon's in here coincides with
 -        -- the unconverted form; the name of the isomorphisms is determined
 -        -- by 'OccName.mkVectIsoOcc'
 +  = IfaceVectInfo 
 +    { ifaceVectInfoVar          :: [Name]  -- ^ All variables in here have a vectorised variant
 +    , ifaceVectInfoTyCon        :: [Name]  -- ^ All 'TyCon's in here have a vectorised variant;
 +                                           -- the name of the vectorised variant and those of its
 +                                           -- data constructors are determined by
 +                                           -- 'OccName.mkVectTyConOcc' and 
 +                                           -- 'OccName.mkVectDataConOcc'; the names of the
 +                                           -- isomorphisms are determined by 'OccName.mkVectIsoOcc'
 +    , ifaceVectInfoTyConReuse   :: [Name]  -- ^ The vectorised form of all the 'TyCon's in here
 +                                           -- coincides with the unconverted form; the name of the
 +                                           -- isomorphisms is determined by 'OccName.mkVectIsoOcc'
 +    , ifaceVectInfoScalarVars   :: [Name]  -- iface version of 'vectInfoScalarVar'
 +    , ifaceVectInfoScalarTyCons :: [Name]  -- iface version of 'vectInfoScalarTyCon'
      }
  
  noVectInfo :: VectInfo
 -noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyNameEnv
 +noVectInfo 
 +  = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyVarSet
 +             emptyNameSet
  
  plusVectInfo :: VectInfo -> VectInfo -> VectInfo
  plusVectInfo vi1 vi2 = 
 -  VectInfo (vectInfoVar     vi1 `plusVarEnv`  vectInfoVar     vi2)
 -           (vectInfoTyCon   vi1 `plusNameEnv` vectInfoTyCon   vi2)
 -           (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
 -           (vectInfoPADFun  vi1 `plusNameEnv` vectInfoPADFun  vi2)
 -           (vectInfoIso     vi1 `plusNameEnv` vectInfoIso     vi2)
 +  VectInfo (vectInfoVar          vi1 `plusVarEnv`    vectInfoVar          vi2)
 +           (vectInfoTyCon        vi1 `plusNameEnv`   vectInfoTyCon        vi2)
 +           (vectInfoDataCon      vi1 `plusNameEnv`   vectInfoDataCon      vi2)
 +           (vectInfoPADFun       vi1 `plusNameEnv`   vectInfoPADFun       vi2)
 +           (vectInfoIso          vi1 `plusNameEnv`   vectInfoIso          vi2)
 +           (vectInfoScalarVars   vi1 `unionVarSet`   vectInfoScalarVars   vi2)
 +           (vectInfoScalarTyCons vi1 `unionNameSets` vectInfoScalarTyCons vi2)
  
  concatVectInfo :: [VectInfo] -> VectInfo
  concatVectInfo = foldr plusVectInfo noVectInfo
  
  noIfaceVectInfo :: IfaceVectInfo
 -noIfaceVectInfo = IfaceVectInfo [] [] []
 +noIfaceVectInfo = IfaceVectInfo [] [] [] [] []
  \end{code}
  
  %************************************************************************