summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorsewardj <unknown>2001-02-13 17:13:39 +0000
committersewardj <unknown>2001-02-13 17:13:39 +0000
commit04be746b439b8c470a4c12a3ea5b63d6e81a0241 (patch)
treebb29479615604e65242b1b33a4a405cdb0a88a16 /ghc/compiler
parenta4cce3da12d8bbb40596ac35840ef894f504af8a (diff)
downloadhaskell-04be746b439b8c470a4c12a3ea5b63d6e81a0241.tar.gz
[project @ 2001-02-13 17:13:39 by sewardj]
* Turn off -O when --interactive is engaged. * Check and abort if --interactive is used together with any non-std Way.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/ghci/InteractiveUI.hs5
-rw-r--r--ghc/compiler/main/Main.hs52
2 files changed, 37 insertions, 20 deletions
diff --git a/ghc/compiler/ghci/InteractiveUI.hs b/ghc/compiler/ghci/InteractiveUI.hs
index 707b278500..83061acf06 100644
--- a/ghc/compiler/ghci/InteractiveUI.hs
+++ b/ghc/compiler/ghci/InteractiveUI.hs
@@ -1,5 +1,5 @@
-----------------------------------------------------------------------------
--- $Id: InteractiveUI.hs,v 1.46 2001/02/13 15:51:57 sewardj Exp $
+-- $Id: InteractiveUI.hs,v 1.47 2001/02/13 17:13:39 sewardj Exp $
--
-- GHC Interactive User Interface
--
@@ -8,7 +8,7 @@
-----------------------------------------------------------------------------
{-# OPTIONS -#include "Linker.h" #-}
-module InteractiveUI (interactiveUI) where
+module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where
#include "HsVersions.h"
@@ -109,7 +109,6 @@ helpText = "\
interactiveUI :: CmState -> Maybe FilePath -> [String] -> IO ()
interactiveUI cmstate mod cmdline_libs = do
- hPutStrLn stdout ghciWelcomeMsg
hFlush stdout
hSetBuffering stdout NoBuffering
diff --git a/ghc/compiler/main/Main.hs b/ghc/compiler/main/Main.hs
index 9790e1dc66..6e14950835 100644
--- a/ghc/compiler/main/Main.hs
+++ b/ghc/compiler/main/Main.hs
@@ -1,6 +1,6 @@
{-# OPTIONS -fno-warn-incomplete-patterns #-}
-----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.51 2001/02/13 15:51:57 sewardj Exp $
+-- $Id: Main.hs,v 1.52 2001/02/13 17:13:39 sewardj Exp $
--
-- GHC Driver program
--
@@ -164,9 +164,26 @@ main =
(flags2, mode, stop_flag) <- getGhcMode argv'
writeIORef v_GhcMode mode
+ -- Show the GHCi banner?
+# ifdef GHCI
+ when (mode == DoInteractive) $
+ hPutStrLn stdout ghciWelcomeMsg
+# endif
+
-- process all the other arguments, and get the source files
non_static <- processArgs static_flags flags2 []
+ -- -O and --interactive are not a good combination
+ -- ditto with any kind of way selection
+ orig_opt_level <- readIORef v_OptLevel
+ when (orig_opt_level > 0 && mode == DoInteractive) $
+ do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
+ writeIORef v_OptLevel 0
+ orig_ways <- readIORef v_Ways
+ when (not (null orig_ways) && mode == DoInteractive) $
+ do throwDyn (OtherError
+ "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
+
-- Find the build tag, and re-process the build-specific options.
-- Also add in flags for unregisterised compilation, if
-- GhcUnregisterised=YES.
@@ -188,8 +205,8 @@ main =
W_all -> minusWallOpts
W_not -> []
- -- build the default DynFlags (these may be adjusted on a per
- -- module basis by OPTIONS pragmas and settings in the interpreter).
+ -- build the default DynFlags (these may be adjusted on a per
+ -- module basis by OPTIONS pragmas and settings in the interpreter).
core_todo <- buildCoreToDo
stg_todo <- buildStgToDo
@@ -198,6 +215,8 @@ main =
-- by module basis, using only the -fvia-C and -fasm flags. If the global
-- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
opt_level <- readIORef v_OptLevel
+
+
let lang = case mode of
StopBefore HCc -> HscC
DoInteractive -> HscInterpreted
@@ -315,19 +334,18 @@ beginInteractive :: [String] -> IO ()
beginInteractive = throwDyn (OtherError "not built for interactive use")
#else
beginInteractive fileish_args
- = let is_libraryish nm
- = let nmr = map toLower (reverse nm)
- in take 2 nmr == "o." ||
- take 3 nmr == "os." ||
- take 4 nmr == "lld."
- libs = filter is_libraryish fileish_args
- mods = filter (not.is_libraryish) fileish_args
- mod = case mods of
- [] -> Nothing
- [mod] -> Just mod
- _ -> throwDyn (UsageError
- "only one module allowed with --interactive")
- in
- do state <- cmInit Interactive
+ = do let is_libraryish nm
+ = let nmr = map toLower (reverse nm)
+ in take 2 nmr == "o." ||
+ take 3 nmr == "os." ||
+ take 4 nmr == "lld."
+ libs = filter is_libraryish fileish_args
+ mods = filter (not.is_libraryish) fileish_args
+ mod = case mods of
+ [] -> Nothing
+ [mod] -> Just mod
+ _ -> throwDyn (UsageError
+ "only one module allowed with --interactive")
+ state <- cmInit Interactive
interactiveUI state mod libs
#endif