summaryrefslogtreecommitdiff
path: root/ghc/compiler/compMan/CompManager.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2000-11-20 14:48:59 +0000
committersimonpj <unknown>2000-11-20 14:48:59 +0000
commitc271b64780a6504e7ccd4cc422dfc90678ea966f (patch)
treee75f7b6abaa149d0fb1ce80e0bbb891ea355f806 /ghc/compiler/compMan/CompManager.lhs
parent9a094a5c6dd79e33224aa7eff496d7b9aa180c39 (diff)
downloadhaskell-c271b64780a6504e7ccd4cc422dfc90678ea966f.tar.gz
[project @ 2000-11-20 14:48:52 by simonpj]
When renaming, typechecking an expression from the user interface, we may suck in declarations from interface files (e.g. the Prelude). This commit takes account of that. To do so, I did some significant restructuring in TcModule, with consequential changes and tidy ups elsewhere in the type checker. I think there should be fewer lines in total than before.
Diffstat (limited to 'ghc/compiler/compMan/CompManager.lhs')
-rw-r--r--ghc/compiler/compMan/CompManager.lhs17
1 files changed, 12 insertions, 5 deletions
diff --git a/ghc/compiler/compMan/CompManager.lhs b/ghc/compiler/compMan/CompManager.lhs
index a853f1f675..9e78ee0d9e 100644
--- a/ghc/compiler/compMan/CompManager.lhs
+++ b/ghc/compiler/compMan/CompManager.lhs
@@ -5,7 +5,9 @@
\begin{code}
module CompManager ( cmInit, cmLoadModule,
+#ifdef GHCI
cmGetExpr, cmRunExpr,
+#endif
CmState, emptyCmState -- abstract
)
where
@@ -15,8 +17,6 @@ where
import CmLink
import CmTypes
import HscTypes
-import HscMain ( hscExpr )
-import Interpreter ( HValue )
import Module ( ModuleName, moduleName,
isModuleInThisPackage, moduleEnvElts,
moduleNameUserString )
@@ -26,7 +26,6 @@ import GetImports
import HscTypes ( HomeSymbolTable, HomeIfaceTable,
PersistentCompilerState, ModDetails(..) )
import Name ( lookupNameEnv )
-import RdrName
import Module
import PrelNames ( mainName )
import HscMain ( initPersistentCompilerState )
@@ -36,11 +35,18 @@ import UniqFM ( emptyUFM, lookupUFM, addToUFM, delListFromUFM,
import Unique ( Uniquable )
import Digraph ( SCC(..), stronglyConnComp )
import DriverUtil ( BarfKind(..), splitFilename3 )
-import CmdLineOpts ( DynFlags )
import Util
import Outputable
import Panic ( panic )
+#ifdef GHCI
+import CmdLineOpts ( DynFlags )
+import Interpreter ( HValue )
+import HscMain ( hscExpr )
+import RdrName
+import PrelGHC ( unsafeCoerce# )
+#endif
+
-- lang
import Exception ( throwDyn )
@@ -50,7 +56,6 @@ import Directory ( getModificationTime, doesFileExist )
import IO
import List ( nub )
import Maybe ( catMaybes, fromMaybe, isJust )
-import PrelGHC ( unsafeCoerce# )
\end{code}
@@ -59,6 +64,7 @@ cmInit :: PackageConfigInfo -> GhciMode -> IO CmState
cmInit raw_package_info gmode
= emptyCmState raw_package_info gmode
+#ifdef GHCI
cmGetExpr :: CmState
-> DynFlags
-> ModuleName
@@ -83,6 +89,7 @@ cmRunExpr :: HValue -> IO ()
cmRunExpr hval
= do unsafeCoerce# hval :: IO ()
-- putStrLn "done."
+#endif
-- Persistent state just for CM, excluding link & compile subsystems
data PersistentCMState