Tidy up the ic_exports field of the InteractiveContext. Previously
[ghc-hetmet.git] / ghc / GhciMonad.hs
index 82f2aa7..52b28ef 100644 (file)
@@ -56,7 +56,8 @@ data GHCiState = GHCiState
        editor         :: String,
         stop           :: String,
        options        :: [GHCiOption],
-        prelude        :: GHC.Module,
+        prelude        :: GHC.ModuleName,
+        line_number    :: !Int,         -- input line
         break_ctr      :: !Int,
         breaks         :: ![(Int, BreakLocation)],
         tickarrays     :: ModuleEnv TickArray,
@@ -77,7 +78,8 @@ data GHCiState = GHCiState
         ghc_e :: Bool -- True if this is 'ghc -e' (or runghc)
      }
 
-data CtxtCmd
+data CtxtCmd    -- In each case, the first [String] are the starred modules
+               -- and the second are the unstarred ones
   = SetContext [String] [String]
   | AddModules [String] [String]
   | RemModules [String] [String]
@@ -89,6 +91,7 @@ data GHCiOption
        = ShowTiming            -- show time/allocs after evaluation
        | ShowType              -- show the type of expressions
        | RevertCAFs            -- revert CAFs after every evaluation
+        | Multiline             -- use multiline commands
        deriving Eq
 
 data BreakLocation
@@ -191,7 +194,7 @@ instance ExceptionMonad GHCi where
                                 unGHCi (f g_restore) s
 
 instance MonadIO GHCi where
-  liftIO = io
+  liftIO = MonadUtils.liftIO
 
 instance Haskeline.MonadException GHCi where
   catch = gcatch
@@ -207,7 +210,7 @@ instance ExceptionMonad (InputT GHCi) where
   gunblock = Haskeline.unblock
 
 -- for convenience...
-getPrelude :: GHCi Module
+getPrelude :: GHCi ModuleName
 getPrelude = getGHCiState >>= return . prelude
 
 getDynFlags :: GhcMonad m => m DynFlags
@@ -233,9 +236,6 @@ unsetOption opt
  = do st <- getGHCiState
       setGHCiState (st{ options = filter (/= opt) (options st) })
 
-io :: IO a -> GHCi a
-io = MonadUtils.liftIO
-
 printForUser :: GhcMonad m => SDoc -> m ()
 printForUser doc = do
   unqual <- GHC.getPrintUnqual
@@ -244,7 +244,7 @@ printForUser doc = do
 printForUserPartWay :: SDoc -> GHCi ()
 printForUserPartWay doc = do
   unqual <- GHC.getPrintUnqual
-  io $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc
+  liftIO $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc
 
 runStmt :: String -> GHC.SingleStep -> GHCi GHC.RunResult
 runStmt expr step = do
@@ -255,7 +255,7 @@ runStmt expr step = do
       reflectGHCi x $ do
         GHC.handleSourceError (\e -> do GHC.printException e
                                         return GHC.RunFailed) $ do
-          GHC.runStmt expr step
+          GHC.runStmtWithLocation (progname st) (line_number st) expr step 
 
 resume :: (SrcSpan -> Bool) -> GHC.SingleStep -> GHCi GHC.RunResult
 resume canLogSpan step = do
@@ -299,9 +299,9 @@ printTimes allocs psecs
        
 revertCAFs :: GHCi ()
 revertCAFs = do
-  io $ rts_revertCAFs
+  liftIO rts_revertCAFs
   s <- getGHCiState
-  when (not (ghc_e s)) $ io turnOffBuffering
+  when (not (ghc_e s)) $ liftIO turnOffBuffering
        -- Have to turn off buffering again, because we just 
        -- reverted stdout, stderr & stdin to their defaults.
 
@@ -350,8 +350,8 @@ initInterpBuffering = do -- make sure these are linked
 
 flushInterpBuffers :: GHCi ()
 flushInterpBuffers
- = io $ do getHandle stdout_ptr >>= hFlush
-           getHandle stderr_ptr >>= hFlush
+ = liftIO $ do getHandle stdout_ptr >>= hFlush
+               getHandle stderr_ptr >>= hFlush
 
 turnOffBuffering :: IO ()
 turnOffBuffering