Force the result of user-defined commands
[ghc-hetmet.git] / compiler / ghci / GhciMonad.hs
index dc16f25..8374491 100644 (file)
@@ -1,3 +1,6 @@
+{-# OPTIONS -fno-cse #-}
+-- -fno-cse is needed for GLOBAL_VAR's to behave properly
+
 -----------------------------------------------------------------------------
 --
 -- Monadery code used in InteractiveUI
@@ -6,13 +9,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,19 +23,19 @@ import HscTypes
 import SrcLoc
 import Module
 import ObjLink
+import Linker
 import StaticFlags
+import MonadUtils       ( MonadIO, liftIO )
 
+import Exception
 import Data.Maybe
 import Numeric
-import Control.Exception as Exception
 import Data.Array
 import Data.Char
 import Data.Int         ( Int64 )
 import Data.IORef
 import Data.List
-import Data.Typeable
 import System.CPUTime
-import System.Directory
 import System.Environment
 import System.IO
 import Control.Monad as Monad
@@ -57,7 +53,6 @@ data GHCiState = GHCiState
         prompt         :: String,
        editor         :: String,
         stop           :: String,
-       session        :: GHC.Session,
        options        :: [GHCiOption],
         prelude        :: GHC.Module,
         break_ctr      :: !Int,
@@ -73,11 +68,11 @@ data GHCiState = GHCiState
         remembered_ctx :: [(CtxtCmd, [String], [String])],
              -- we remember the :module commands between :loads, so that
              -- on a :reload we can replay them.  See bugs #2049,
-             -- #1873, #1360. Previously we tried to remember modules that
+             -- \#1873, #1360. Previously we tried to remember modules that
              -- 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
+        ghc_e :: Bool -- True if this is 'ghc -e' (or runghc)
      }
 
 data CtxtCmd
@@ -130,41 +125,89 @@ recordBreak brkLoc = do
                         }
       return (False, oldCounter)
 
-newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> IO a }
+newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> Ghc a }
+
+reflectGHCi :: (Session, IORef GHCiState) -> GHCi a -> IO a
+reflectGHCi (s, gs) m = unGhc (unGHCi m gs) s
 
-startGHCi :: GHCi a -> GHCiState -> IO a
-startGHCi g state = do ref <- newIORef state; unGHCi g ref
+reifyGHCi :: ((Session, IORef GHCiState) -> IO a) -> GHCi a
+reifyGHCi f = GHCi f'
+  where
+    -- f' :: IORef GHCiState -> Ghc a
+    f' gs = reifyGhc (f'' gs)
+    -- f'' :: IORef GHCiState -> Session -> IO a
+    f'' gs s = f (s, gs)
+
+startGHCi :: GHCi a -> GHCiState -> Ghc a
+startGHCi g state = do ref <- liftIO $ 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
 
-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)
+ghciHandleGhcException :: (GhcException -> GHCi a) -> GHCi a -> GHCi a
+ghciHandleGhcException = handleGhcException
+
+getGHCiState :: GHCi GHCiState
+getGHCiState   = GHCi $ \r -> liftIO $ readIORef r
+setGHCiState :: GHCiState -> GHCi ()
+setGHCiState s = GHCi $ \r -> liftIO $ writeIORef r s
+
+liftGhc :: Ghc a -> GHCi a
+liftGhc m = GHCi $ \_ -> m
+
+instance MonadIO GHCi where
+  liftIO m = liftGhc $ liftIO m
+
+instance GhcMonad GHCi where
+  setSession s' = liftGhc $ setSession s'
+  getSession    = liftGhc $ getSession
+
+instance ExceptionMonad GHCi where
+  gcatch m h = GHCi $ \r -> unGHCi m r `gcatch` (\e -> unGHCi (h e) r)
+  gblock (GHCi m)   = GHCi $ \r -> gblock (m r)
+  gunblock (GHCi m) = GHCi $ \r -> gunblock (m r)
 
-getGHCiState   = GHCi $ \r -> readIORef r
-setGHCiState s = GHCi $ \r -> writeIORef r s
+instance WarnLogMonad GHCi where
+  setWarnings warns = liftGhc $ setWarnings warns
+  getWarnings = liftGhc $ getWarnings
 
 -- for convenience...
-getSession = getGHCiState >>= return . session
+getPrelude :: GHCi Module
 getPrelude = getGHCiState >>= return . prelude
 
-GLOBAL_VAR(saved_sess, no_saved_sess, GHC.Session)
+GLOBAL_VAR(saved_sess, no_saved_sess, Session)
+
+no_saved_sess :: Session
 no_saved_sess = error "no saved_ses"
-saveSession = getSession >>= io . writeIORef saved_sess
+
+saveSession :: GHCi ()
+saveSession =
+    liftGhc $ do
+      reifyGhc $ \s ->
+        writeIORef saved_sess s
+
+splatSavedSession :: GHCi ()
 splatSavedSession = io (writeIORef saved_sess no_saved_sess)
-restoreSession = readIORef saved_sess
 
+-- restoreSession :: IO Session
+-- restoreSession = readIORef saved_sess
+
+withRestoredSession :: Ghc a -> IO a
+withRestoredSession ghc = do
+    s <- readIORef saved_sess
+    reflectGhc ghc s
+
+getDynFlags :: GHCi DynFlags
 getDynFlags = do
-  s <- getSession
-  io (GHC.getSessionDynFlags s)
+  GHC.getSessionDynFlags
+
+setDynFlags :: DynFlags -> GHCi [PackageId]
 setDynFlags dflags = do 
-  s <- getSession 
-  io (GHC.setSessionDynFlags s dflags)
+  GHC.setSessionDynFlags dflags
 
 isOptionSet :: GHCiOption -> GHCi Bool
 isOptionSet opt
@@ -182,43 +225,31 @@ unsetOption opt
       setGHCiState (st{ options = filter (/= opt) (options st) })
 
 io :: IO a -> GHCi a
-io m = GHCi { unGHCi = \s -> m >>= return }
+io = liftIO
 
 printForUser :: SDoc -> GHCi ()
 printForUser doc = do
-  session <- getSession
-  unqual <- io (GHC.getPrintUnqual session)
+  unqual <- GHC.getPrintUnqual
   io $ Outputable.printForUser stdout unqual doc
 
 printForUserPartWay :: SDoc -> GHCi ()
 printForUserPartWay doc = do
-  session <- getSession
-  unqual <- io (GHC.getPrintUnqual session)
+  unqual <- GHC.getPrintUnqual
   io $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc
 
-withVirtualPath :: GHCi a -> GHCi a
-withVirtualPath m = do
-  ghci_wd <- io getCurrentDirectory                -- Store the cwd of GHCi
-  st  <- getGHCiState
-  io$ setCurrentDirectory (virtual_path st)
-  result <- m                                  -- Evaluate in the virtual wd..
-  vwd <- io getCurrentDirectory
-  setGHCiState (st{ virtual_path = vwd})       -- Update the virtual path
-  io$ setCurrentDirectory ghci_wd                  -- ..and restore GHCi wd
-  return result
-
 runStmt :: String -> GHC.SingleStep -> GHCi GHC.RunResult
-runStmt expr step = withVirtualPath$ do
-  session <- getSession
-  st      <- getGHCiState
-  io$ withProgName (progname st) $ withArgs (args st) $
-                    GHC.runStmt session expr step
+runStmt expr step = do
+  st <- getGHCiState
+  reifyGHCi $ \x ->
+    withProgName (progname st) $
+    withArgs (args st) $
+      reflectGHCi x $ do
+        GHC.handleSourceError (\e -> do GHC.printExceptionAndWarnings e
+                                        return GHC.RunFailed) $ do
+          GHC.runStmt expr step
 
 resume :: GHC.SingleStep -> GHCi GHC.RunResult
-resume step = withVirtualPath$ do
-  session <- getSession
-  io$ GHC.resume session step
-
+resume step = GHC.resume step
 
 -- --------------------------------------------------------------------------
 -- timing & statistics
@@ -242,7 +273,7 @@ foreign import ccall unsafe "getAllocations" getAllocations :: IO Int64
 
 printTimes :: Integer -> Integer -> IO ()
 printTimes allocs psecs
-   = do let secs = (fromIntegral psecs / (10^12)) :: Float
+   = do let secs = (fromIntegral psecs / (10^(12::Integer))) :: Float
            secs_str = showFFloat (Just 2) secs
        putStrLn (showSDoc (
                 parens (text (secs_str "") <+> text "secs" <> comma <+> 
@@ -251,10 +282,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.
 
@@ -283,14 +315,11 @@ GLOBAL_VAR(stderr_ptr, error "no stderr_ptr", Ptr ())
 -- of the Handle rather than referring to it from its static address
 -- each time.  There's no safe workaround for this.
 
-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"
+initInterpBuffering :: Ghc ()
+initInterpBuffering = do -- make sure these are linked
+    dflags <- GHC.getSessionDynFlags
+    liftIO $ do
+      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 +329,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 ()