FIX #1970: ghci -hide-all-packages should work
[ghc-hetmet.git] / compiler / ghci / GhciMonad.hs
index dc16f25..2c5a0a5 100644 (file)
@@ -6,13 +6,6 @@
 --
 -----------------------------------------------------------------------------
 
-{-# OPTIONS -w #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and fix
--- any warnings in the module. See
---     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
--- for details
-
 module GhciMonad where
 
 #include "HsVersions.h"
@@ -27,6 +20,7 @@ import HscTypes
 import SrcLoc
 import Module
 import ObjLink
+import Linker
 import StaticFlags
 
 import Data.Maybe
@@ -77,7 +71,8 @@ data GHCiState = GHCiState
              -- were supposed to be in the context but currently had errors,
              -- but this was complicated.  Just replaying the :module commands
              -- seems to be the right thing.
-        virtual_path   :: FilePath
+        virtual_path   :: FilePath,
+        ghc_e :: Bool -- True if this is 'ghc -e' (or runghc)
      }
 
 data CtxtCmd
@@ -137,7 +132,7 @@ startGHCi g state = do ref <- newIORef state; unGHCi g ref
 
 instance Monad GHCi where
   (GHCi m) >>= k  =  GHCi $ \s -> m s >>= \a -> unGHCi (k a) s
-  return a  = GHCi $ \s -> return a
+  return a  = GHCi $ \_ -> return a
 
 instance Functor GHCi where
     fmap f m = m >>= return . f
@@ -146,22 +141,36 @@ ghciHandleDyn :: Typeable t => (t -> GHCi a) -> GHCi a -> GHCi a
 ghciHandleDyn h (GHCi m) = GHCi $ \s -> 
    Exception.catchDyn (m s) (\e -> unGHCi (h e) s)
 
+getGHCiState :: GHCi GHCiState
 getGHCiState   = GHCi $ \r -> readIORef r
+setGHCiState :: GHCiState -> GHCi ()
 setGHCiState s = GHCi $ \r -> writeIORef r s
 
 -- for convenience...
+getSession :: GHCi Session
 getSession = getGHCiState >>= return . session
+getPrelude :: GHCi Module
 getPrelude = getGHCiState >>= return . prelude
 
 GLOBAL_VAR(saved_sess, no_saved_sess, GHC.Session)
+
+no_saved_sess :: Session
 no_saved_sess = error "no saved_ses"
+
+saveSession :: GHCi ()
 saveSession = getSession >>= io . writeIORef saved_sess
+
+splatSavedSession :: GHCi ()
 splatSavedSession = io (writeIORef saved_sess no_saved_sess)
+
+restoreSession :: IO Session
 restoreSession = readIORef saved_sess
 
+getDynFlags :: GHCi DynFlags
 getDynFlags = do
   s <- getSession
   io (GHC.getSessionDynFlags s)
+setDynFlags :: DynFlags -> GHCi [PackageId]
 setDynFlags dflags = do 
   s <- getSession 
   io (GHC.setSessionDynFlags s dflags)
@@ -182,7 +191,7 @@ unsetOption opt
       setGHCiState (st{ options = filter (/= opt) (options st) })
 
 io :: IO a -> GHCi a
-io m = GHCi { unGHCi = \s -> m >>= return }
+io m = GHCi (\_ -> m)
 
 printForUser :: SDoc -> GHCi ()
 printForUser doc = do
@@ -251,10 +260,11 @@ printTimes allocs psecs
 -----------------------------------------------------------------------------
 -- reverting CAFs
        
-revertCAFs :: IO ()
+revertCAFs :: GHCi ()
 revertCAFs = do
-  rts_revertCAFs
-  turnOffBuffering
+  io $ rts_revertCAFs
+  s <- getGHCiState
+  when (not (ghc_e s)) $ io turnOffBuffering
        -- Have to turn off buffering again, because we just 
        -- reverted stdout, stderr & stdin to their defaults.
 
@@ -286,11 +296,8 @@ GLOBAL_VAR(stderr_ptr, error "no stderr_ptr", Ptr ())
 initInterpBuffering :: GHC.Session -> IO ()
 initInterpBuffering session
  = do -- make sure these are linked
-      mb_hval1 <- GHC.compileExpr session "System.IO.stdout"
-      mb_hval2 <- GHC.compileExpr session "System.IO.stderr"
-      mb_hval3 <- GHC.compileExpr session "System.IO.stdin"
-      when (any isNothing [mb_hval1,mb_hval2,mb_hval3]) $
-        panic "interactiveUI:setBuffering"
+      dflags <- GHC.getSessionDynFlags session
+      initDynLinker dflags
 
         -- ToDo: we should really look up these names properly, but
         -- it's a fiddle and not all the bits are exposed via the GHC
@@ -300,7 +307,7 @@ initInterpBuffering session
       mb_stderr_ptr <- ObjLink.lookupSymbol "base_GHCziHandle_stderr_closure"
 
       let f ref (Just ptr) = writeIORef ref ptr
-          f ref Nothing    = panic "interactiveUI:setBuffering2"
+          f _   Nothing    = panic "interactiveUI:setBuffering2"
       zipWithM f [stdin_ptr,stdout_ptr,stderr_ptr]
                  [mb_stdin_ptr,mb_stdout_ptr,mb_stderr_ptr]
       return ()