[project @ 2005-04-13 13:30:42 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / GHC.hs
index 301db13..d907884 100644 (file)
@@ -33,6 +33,7 @@ module GHC (
        -- * Loading\/compiling the program
        depanal,
        load, LoadHowMuch(..), SuccessFlag(..), -- also does depanal
+       loadMsgs,
        workingDirectoryChanged,
        checkModule, CheckedModule(..),
 
@@ -46,13 +47,14 @@ module GHC (
        ModuleInfo,
        getModuleInfo,
        modInfoTyThings,
-       modInfoInstances,
+       modInfoTopLevelScope,
        lookupName,
 
        -- * Interactive evaluation
        getBindings, getPrintUnqual,
 #ifdef GHCI
        setContext, getContext, 
+       getNamesInScope,
        moduleIsInterpreted,
        getInfo, GetInfoResult,
        exprType,
@@ -70,21 +72,28 @@ module GHC (
        -- ** Modules
        Module, mkModule, pprModule,
 
-       -- ** Identifiers
+       -- ** Names
        Name,
+       
+       -- ** Identifiers
        Id, idType,
+       isImplicitId, isDeadBinder,
+       isSpecPragmaId, isExportedId, isLocalId, isGlobalId,
+       isRecordSelector,
+       isPrimOpId, isFCallId,
+       isDataConWorkId, idDataCon,
+       isBottomingId, isDictonaryId,
 
        -- ** Type constructors
        TyCon, 
+       isClassTyCon, isSynTyCon, isNewTyCon,
 
        -- ** Data constructors
        DataCon,
 
        -- ** Classes
        Class, 
-
-       -- ** Instances
-       Instance,
+       classSCTheta, classTvsFds,
 
        -- ** Types and Kinds
        Type, dropForAlls,
@@ -130,15 +139,21 @@ import IfaceSyn           ( IfaceDecl )
 #endif
 
 import Packages                ( initPackages )
+import NameSet         ( NameSet, nameSetToList )
 import RdrName         ( GlobalRdrEnv )
 import HsSyn           ( HsModule, LHsBinds )
 import Type            ( Kind, Type, dropForAlls )
-import Id              ( Id, idType )
-import TyCon           ( TyCon )
-import Class           ( Class )
+import Id              ( Id, idType, isImplicitId, isDeadBinder,
+                          isSpecPragmaId, isExportedId, isLocalId, isGlobalId,
+                          isRecordSelector,
+                          isPrimOpId, isFCallId,
+                          isDataConWorkId, idDataCon,
+                          isBottomingId )
+import TyCon           ( TyCon, isClassTyCon, isSynTyCon, isNewTyCon )
+import Class           ( Class, classSCTheta, classTvsFds )
 import DataCon         ( DataCon )
-import Name            ( Name )
-import RdrName         ( RdrName )
+import Name            ( Name, getName, nameModule_maybe )
+import RdrName         ( RdrName, gre_name, globalRdrEnvElts )
 import NameEnv         ( nameEnvElts )
 import SrcLoc          ( Located(..) )
 import DriverPipeline
@@ -163,9 +178,10 @@ import Outputable
 import SysTools                ( cleanTempFilesExcept )
 import BasicTypes      ( SuccessFlag(..), succeeded, failed )
 import Maybes          ( orElse, expectJust, mapCatMaybes )
+import TcType           ( tcSplitSigmaTy, isDictTy )
 
 import Directory        ( getModificationTime, doesFileExist )
-import Maybe           ( isJust, isNothing, fromJust )
+import Maybe           ( isJust, isNothing, fromJust, fromMaybe, catMaybes )
 import Maybes          ( expectJust )
 import List            ( partition, nub )
 import qualified List
@@ -386,7 +402,13 @@ data LoadHowMuch
 -- attempt to load up to this target.  If no Module is supplied,
 -- then try to load all targets.
 load :: Session -> LoadHowMuch -> IO SuccessFlag
-load s@(Session ref) how_much
+load session how_much = 
+   loadMsgs session how_much ErrUtils.printErrorsAndWarnings
+
+-- | Version of 'load' that takes a callback function to be invoked
+-- on compiler errors and warnings as they occur during compilation.
+loadMsgs :: Session -> LoadHowMuch -> (Messages-> IO ()) -> IO SuccessFlag
+loadMsgs s@(Session ref) how_much msg_act
    = do 
        -- Dependency analysis first.  Note that this fixes the module graph:
        -- even if we don't get a fully successful upsweep, the full module
@@ -480,7 +502,7 @@ load s@(Session ref) how_much
                  List.init partial_mg0
                | otherwise
                = partial_mg0
-
+  
            stable_mg = 
                [ AcyclicSCC ms
                | AcyclicSCC ms <- full_mg,
@@ -496,7 +518,7 @@ load s@(Session ref) how_much
 
         (upsweep_ok, hsc_env1, modsUpswept)
            <- upsweep (hsc_env { hsc_HPT = emptyHomePackageTable })
-                          pruned_hpt stable_mods cleanup mg
+                          pruned_hpt stable_mods cleanup msg_act mg
 
        -- Make modsDone be the summaries for each home module now
        -- available; this should equal the domain of hpt3.
@@ -606,11 +628,12 @@ ppFilesFromSummaries summaries = [ fn | Just fn <- map ms_hspp_file summaries ]
 data CheckedModule = 
   CheckedModule { parsedSource      :: ParsedSource,
                -- ToDo: renamedSource
-                 typecheckedSource :: Maybe TypecheckedSource
+                 typecheckedSource :: Maybe TypecheckedSource,
+                 checkedModuleInfo :: Maybe ModuleInfo
                }
 
 type ParsedSource  = Located (HsModule RdrName)
-type TypecheckedSource = (LHsBinds Id, GlobalRdrEnv)
+type TypecheckedSource = LHsBinds Id
 
 -- | This is the way to get access to parsed and typechecked source code
 -- for a module.  'checkModule' loads all the dependencies of the specified
@@ -620,7 +643,7 @@ checkModule :: Session -> Module -> (Messages -> IO ())
        -> IO (Maybe CheckedModule)
 checkModule session@(Session ref) mod msg_act = do
        -- load up the dependencies first
-   r <- load session (LoadDependenciesOf mod)
+   r <- loadMsgs session (LoadDependenciesOf mod) msg_act
    if (failed r) then return Nothing else do
 
        -- now parse & typecheck the module
@@ -633,10 +656,19 @@ checkModule session@(Session ref) mod msg_act = do
           case r of
                HscFail -> 
                   return Nothing
-               HscChecked parsed tcd -> 
-                  return (Just (CheckedModule parsed tcd)   )
+               HscChecked parsed Nothing ->
+                  return (Just (CheckedModule parsed Nothing Nothing))
+               HscChecked parsed (Just (tc_binds, rdr_env, details)) -> do
+                  let minf = ModuleInfo {
+                               minf_details  = details,
+                               minf_rdr_env  = Just rdr_env
+                             }
+                  return (Just (CheckedModule {
+                                       parsedSource = parsed,
+                                       typecheckedSource = Just tc_binds,
+                                       checkedModuleInfo = Just minf }))
 
------------------------------------------------------------------------------
+-- ---------------------------------------------------------------------------
 -- Unloading
 
 unload :: HscEnv -> [Linkable] -> IO ()
@@ -834,27 +866,28 @@ upsweep
     -> HomePackageTable                -- HPT from last time round (pruned)
     -> ([Module],[Module])     -- stable modules (see checkStability)
     -> IO ()                   -- How to clean up unwanted tmp files
+    -> (Messages -> IO ())     -- Compiler error message callback
     -> [SCC ModSummary]                -- Mods to do (the worklist)
     -> IO (SuccessFlag,
            HscEnv,             -- With an updated HPT
            [ModSummary])       -- Mods which succeeded
 
-upsweep hsc_env old_hpt stable_mods cleanup
+upsweep hsc_env old_hpt stable_mods cleanup msg_act
      []
    = return (Succeeded, hsc_env, [])
 
-upsweep hsc_env old_hpt stable_mods cleanup
+upsweep hsc_env old_hpt stable_mods cleanup msg_act
      (CyclicSCC ms:_)
    = do putMsg (showSDoc (cyclicModuleErr ms))
         return (Failed, hsc_env, [])
 
-upsweep hsc_env old_hpt stable_mods cleanup
+upsweep hsc_env old_hpt stable_mods cleanup msg_act
      (AcyclicSCC mod:mods)
    = do -- putStrLn ("UPSWEEP_MOD: hpt = " ++ 
        --           show (map (moduleUserString.moduleName.mi_module.hm_iface) 
        --                     (moduleEnvElts (hsc_HPT hsc_env)))
 
-        mb_mod_info <- upsweep_mod hsc_env old_hpt stable_mods mod 
+        mb_mod_info <- upsweep_mod hsc_env old_hpt stable_mods msg_act mod 
 
        cleanup         -- Remove unwanted tmp files between compilations
 
@@ -878,7 +911,8 @@ upsweep hsc_env old_hpt stable_mods cleanup
                               | otherwise = delModuleEnv old_hpt this_mod
 
                ; (restOK, hsc_env2, modOKs) 
-                       <- upsweep hsc_env1 old_hpt1 stable_mods cleanup mods
+                       <- upsweep hsc_env1 old_hpt1 stable_mods cleanup 
+                               msg_act mods
                ; return (restOK, hsc_env2, mod:modOKs)
                }
 
@@ -888,10 +922,11 @@ upsweep hsc_env old_hpt stable_mods cleanup
 upsweep_mod :: HscEnv
             -> HomePackageTable
            -> ([Module],[Module])
+           -> (Messages -> IO ())
             -> ModSummary
             -> IO (Maybe HomeModInfo)  -- Nothing => Failed
 
-upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary
+upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) msg_act summary
    = do 
         let 
            this_mod    = ms_mod summary
@@ -900,7 +935,8 @@ upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary
            hs_date     = ms_hs_date summary
 
            compile_it :: Maybe Linkable -> IO (Maybe HomeModInfo)
-           compile_it  = upsweep_compile hsc_env old_hpt this_mod summary
+           compile_it  = upsweep_compile hsc_env old_hpt this_mod 
+                               msg_act summary
 
        case ghcMode (hsc_dflags hsc_env) of
            BatchCompile ->
@@ -953,7 +989,7 @@ upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary
                    old_hmi = lookupModuleEnv old_hpt this_mod
 
 -- Run hsc to compile a module
-upsweep_compile hsc_env old_hpt this_mod summary mb_old_linkable = do
+upsweep_compile hsc_env old_hpt this_mod msg_act summary mb_old_linkable = do
   let
        -- The old interface is ok if it's in the old HPT 
        --      a) we're compiling a source file, and the old HPT
@@ -973,7 +1009,7 @@ upsweep_compile hsc_env old_hpt this_mod summary mb_old_linkable = do
                                   where 
                                     iface = hm_iface hm_info
 
-  compresult <- compile hsc_env summary mb_old_linkable mb_old_iface
+  compresult <- compile hsc_env msg_act summary mb_old_linkable mb_old_iface
 
   case compresult of
         -- Compilation failed.  Compile may still have updated the PCS, tho.
@@ -1463,9 +1499,11 @@ lookupName s name = withSession s $ \hsc_env -> do
            eps <- readIORef (hsc_EPS hsc_env)
            return $! lookupType (hsc_HPT hsc_env) (eps_PTE eps) name
 
-
 -- | Container for information about a 'Module'.
-newtype ModuleInfo = ModuleInfo ModDetails
+data ModuleInfo = ModuleInfo {
+       minf_details  :: ModDetails,
+       minf_rdr_env  :: Maybe GlobalRdrEnv
+  }
        -- ToDo: this should really contain the ModIface too
        -- We don't want HomeModInfo here, because a ModuleInfo applies
        -- to package modules too.
@@ -1475,20 +1513,29 @@ getModuleInfo :: Session -> Module -> IO (Maybe ModuleInfo)
 getModuleInfo s mdl = withSession s $ \hsc_env -> do
   case lookupModuleEnv (hsc_HPT hsc_env) mdl of
     Nothing  -> return Nothing
-    Just hmi -> return (Just (ModuleInfo (hm_details hmi)))
+    Just hmi -> 
+       return (Just (ModuleInfo {
+                       minf_details = hm_details hmi,
+                       minf_rdr_env = mi_globals $! hm_iface hmi
+                       }))
+
        -- ToDo: we should be able to call getModuleInfo on a package module,
        -- even one that isn't loaded yet.
 
 -- | The list of top-level entities defined in a module
 modInfoTyThings :: ModuleInfo -> [TyThing]
-modInfoTyThings (ModuleInfo md) = typeEnvElts (md_types md)
+modInfoTyThings minf = typeEnvElts (md_types (minf_details minf))
+
+modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
+modInfoTopLevelScope minf
+  = fmap (map gre_name . globalRdrEnvElts) (minf_rdr_env minf)
 
--- | An instance of a class
-newtype Instance = Instance DFunId
+modInfoExports :: ModuleInfo -> [Name]
+modInfoExports minf = nameSetToList $! (md_exports $! minf_details minf)
 
--- | The list of 'Instance's defined in a module
-modInfoInstances :: ModuleInfo -> [Instance]
-modInfoInstances (ModuleInfo md) = map Instance (md_insts md)
+isDictonaryId :: Id -> Bool
+isDictonaryId id
+  = case tcSplitSigmaTy (idType id) of { (tvs, theta, tau) -> isDictTy tau }
 
 #if 0
 
@@ -1617,6 +1664,11 @@ moduleIsInterpreted s modl = withSession s $ \h ->
 getInfo :: Session -> String -> IO [GetInfoResult]
 getInfo s id = withSession s $ \hsc_env -> hscGetInfo hsc_env id
 
+-- | Returns all names in scope in the current interactive context
+getNamesInScope :: Session -> IO [Name]
+getNamesInScope s = withSession s $ \hsc_env -> do
+  return (map gre_name (globalRdrEnvElts (ic_rn_gbl_env (hsc_IC hsc_env))))
+
 -- -----------------------------------------------------------------------------
 -- Getting the type of an expression