[project @ 2004-04-02 16:46:57 by simonpj]
[ghc-hetmet.git] / ghc / compiler / typecheck / TcRnDriver.lhs
index 8df2efc..6af188c 100644 (file)
@@ -35,7 +35,7 @@ import TcType         ( tidyTopType )
 import Inst            ( showLIE )
 import TcBinds         ( tcTopBinds )
 import TcDefaults      ( tcDefaults )
-import TcEnv           ( tcExtendGlobalValEnv, tcLookupGlobal )
+import TcEnv           ( tcExtendGlobalValEnv )
 import TcRules         ( tcRules )
 import TcForeign       ( tcForeignImports, tcForeignExports )
 import TcInstDcls      ( tcInstDecls1, tcInstDecls2 )
@@ -62,7 +62,6 @@ import Outputable
 import HscTypes                ( ModGuts(..), HscEnv(..),
                          GhciMode(..), noDependencies,
                          Deprecs( NoDeprecs ), plusDeprecs,
-                         GenAvailInfo(Avail), availsToNameSet, availName,
                          ForeignStubs(NoStubs), TypeEnv, typeEnvTyCons, 
                          extendTypeEnvWithIds, typeEnvIds, typeEnvTyCons,
                          emptyFixityEnv
@@ -81,13 +80,13 @@ import TcMType              ( zonkTcType )
 import TcMatches       ( tcStmtsAndThen, TcStmtCtxt(..) )
 import TcSimplify      ( tcSimplifyInteractive, tcSimplifyInfer )
 import TcType          ( Type, mkForAllTys, mkFunTys, mkTyConApp, tyVarsOfType )
-import TcEnv           ( tcLookupTyCon, tcLookupId )
-import TyCon           ( DataConDetails(..) )
+import TcEnv           ( tcLookupTyCon, tcLookupId, tcLookupGlobal )
 import Inst            ( tcStdSyntaxName )
 import RnExpr          ( rnStmts, rnLExpr )
 import RnNames         ( exportsToAvails )
 import LoadIface       ( loadSrcInterface )
-import IfaceSyn                ( IfaceDecl(..), IfaceClassOp(..), IfaceConDecl(..), IfaceExtName(..),
+import IfaceSyn                ( IfaceDecl(..), IfaceClassOp(..), IfaceConDecl(..), 
+                         IfaceExtName(..), IfaceConDecls(..),
                          tyThingToIfaceDecl )
 import RnEnv           ( lookupOccRn, dataTcOccs, lookupFixityRn )
 import Id              ( Id, isImplicitId )
@@ -102,7 +101,7 @@ import PrelNames    ( iNTERACTIVE, ioTyConName, printName, monadNames, itName, retu
 import Module          ( ModuleName, lookupModuleEnvByName )
 import HscTypes                ( InteractiveContext(..),
                          HomeModInfo(..), typeEnvElts, 
-                         TyThing(..), availNames, icPrintUnqual,
+                         TyThing(..), availName, availNames, icPrintUnqual,
                          ModIface(..), ModDetails(..) )
 import BasicTypes      ( RecFlag(..), Fixity )
 import Bag             ( unitBag )
@@ -228,7 +227,7 @@ tcRnStmt :: HscEnv
                -- a list of the bound values, coerced to ().
 
 tcRnStmt hsc_env ictxt rdr_stmt
-  = initTc hsc_env iNTERACTIVE $ 
+  = initTcPrintErrors hsc_env iNTERACTIVE $ 
     setInteractiveContext ictxt $ do {
 
     -- Rename; use CmdLineMode because tcRnStmt is only used interactively
@@ -400,7 +399,7 @@ tcRnExpr :: HscEnv
         -> LHsExpr RdrName
         -> IO (Maybe Type)
 tcRnExpr hsc_env ictxt rdr_expr
-  = initTc hsc_env iNTERACTIVE $ 
+  = initTcPrintErrors hsc_env iNTERACTIVE $ 
     setInteractiveContext ictxt $ do {
 
     (rn_expr, fvs) <- rnLExpr rdr_expr ;
@@ -433,7 +432,7 @@ tcRnThing :: HscEnv
 -- *and* as a type or class constructor; 
 -- hence the call to dataTcOccs, and we return up to two results
 tcRnThing hsc_env ictxt rdr_name
-  = initTc hsc_env iNTERACTIVE $ 
+  = initTcPrintErrors hsc_env iNTERACTIVE $ 
     setInteractiveContext ictxt $ do {
 
        -- If the identifier is a constructor (begins with an
@@ -804,7 +803,7 @@ mkExportEnv :: HscEnv -> [ModuleName]       -- Expose these modules' exports only
            -> IO GlobalRdrEnv
 
 mkExportEnv hsc_env exports
-  = do { mb_envs <- initTc hsc_env iNTERACTIVE $
+  = do { mb_envs <- initTcPrintErrors hsc_env iNTERACTIVE $
                     mappM getModuleExports exports 
        ; case mb_envs of
             Just envs -> return (foldr plusGlobalRdrEnv emptyGlobalRdrEnv envs)
@@ -836,7 +835,7 @@ getModuleContents
   -> IO (Maybe [IfaceDecl])
 
 getModuleContents hsc_env ictxt mod exports_only
- = initTc hsc_env iNTERACTIVE (get_mod_contents exports_only)
+ = initTcPrintErrors hsc_env iNTERACTIVE (get_mod_contents exports_only)
  where
    get_mod_contents exports_only
       | not exports_only       -- We want the whole top-level type env
@@ -864,8 +863,11 @@ getModuleContents hsc_env ictxt mod exports_only
 ---------------------
 filter_decl occs decl@(IfaceClass {ifSigs = sigs})
   = decl { ifSigs = filter (keep_sig occs) sigs }
-filter_decl occs decl@(IfaceData {ifCons = DataCons cons})
-  = decl { ifCons = DataCons (filter (keep_con occs) cons) }
+filter_decl occs decl@(IfaceData {ifCons = IfDataTyCon cons})
+  = decl { ifCons = IfDataTyCon (filter (keep_con occs) cons) }
+filter_decl occs decl@(IfaceData {ifCons = IfNewTyCon con})
+  | keep_con occs con = decl
+  | otherwise        = decl {ifCons = IfAbstractTyCon} -- Hmm?
 filter_decl occs decl
   = decl