Use MD5 checksums for recompilation checking (fixes #1372, #1959)
[ghc-hetmet.git] / compiler / ghci / InteractiveUI.hs
index 8b1566a..a49109a 100644 (file)
@@ -11,12 +11,13 @@ module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where
 
 #include "HsVersions.h"
 
-import GhciMonad
+import qualified GhciMonad
+import GhciMonad hiding (runStmt)
 import GhciTags
 import Debugger
 
 -- The GHC interface
-import qualified GHC
+import qualified GHC hiding (resume, runStmt)
 import GHC              ( Session, LoadHowMuch(..), Target(..),  TargetId(..),
                           Module, ModuleName, TyThing(..), Phase,
                           BreakIndex, SrcSpan, Resume, SingleStep )
@@ -24,7 +25,7 @@ import PprTyThing
 import DynFlags
 
 import Packages
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 import PackageConfig
 import UniqFM
 #endif
@@ -56,9 +57,9 @@ import GHC.ConsoleHandler ( flushConsole )
 import qualified System.Win32
 #endif
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 import Control.Concurrent      ( yield )       -- Used in readline loop
-import System.Console.Readline as Readline
+import System.Console.Editline.Readline as Readline
 #endif
 
 --import SystemExts
@@ -89,7 +90,7 @@ import GHC.TopHandler
 
 import Data.IORef      ( IORef, readIORef, writeIORef )
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 import System.Posix.Internals ( setNonBlockingFD )
 #endif
 
@@ -102,7 +103,6 @@ ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++
 cmdName :: Command -> String
 cmdName (n,_,_,_) = n
 
-macros_ref :: IORef [Command]
 GLOBAL_VAR(macros_ref, [], [Command])
 
 builtin_commands :: [Command]
@@ -161,7 +161,7 @@ builtin_commands = [
 -- 
 -- NOTE: in order for us to override the default correctly, any custom entry
 -- must be a SUBSET of word_break_chars.
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 word_break_chars :: String
 word_break_chars = let symbols = "!#$%&*+/<=>?@\\^|-~"
                        specials = "(),;[]`{}"
@@ -229,6 +229,9 @@ helpText =
  "   :force <expr>               print <expr>, forcing unevaluated parts\n" ++
  "   :forward                    go forward in the history (after :back)\n" ++
  "   :history [<n>]              after :trace, show the execution history\n" ++
+ "   :list                       show the source code around current breakpoint\n" ++
+ "   :list identifier            show the source code for <identifier>\n" ++
+ "   :list [<module>] <line>     show the source code around line number <line>\n" ++
  "   :print [<name> ...]         prints a value without forcing its computation\n" ++
  "   :sprint [<name> ...]        simplifed version of :print\n" ++
  "   :step                       single-step after stopping at a breakpoint\n"++
@@ -312,7 +315,7 @@ interactiveUI session srcs maybe_exprs = do
         -- intended for the program, so unbuffer stdin.
         hSetBuffering stdin NoBuffering
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
         is_tty <- hIsTerminalDevice stdin
         when is_tty $ do
             Readline.initialize
@@ -336,6 +339,8 @@ interactiveUI session srcs maybe_exprs = do
 
    default_editor <- findEditor
 
+   cwd <- getCurrentDirectory
+
    startGHCi (runGHCi srcs maybe_exprs)
         GHCiState{ progname = "<interactive>",
                    args = [],
@@ -350,10 +355,12 @@ interactiveUI session srcs maybe_exprs = do
                    tickarrays = emptyModuleEnv,
                    last_command = Nothing,
                    cmdqueue = [],
-                   remembered_ctx = []
+                   remembered_ctx = [],
+                   virtual_path   = cwd,
+                   ghc_e = isJust maybe_exprs
                  }
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
    Readline.stifleHistory 100
    withGhcAppData (\dir -> Readline.writeHistory (dir </> "ghci_history"))
                   (return True)
@@ -447,12 +454,8 @@ runGHCi paths maybe_exprs = do
                                    -- current progname in the exception text:
                                    -- <progname>: <exception>
                               io $ withProgName (progname st)
-                                   -- The "fast exit" part just calls exit()
-                                   -- directly instead of doing an orderly
-                                   -- runtime shutdown, otherwise the main
-                                   -- GHCi thread will complain about being
-                                   -- interrupted.
-                                 $ topHandlerFastExit e
+                                   -- this used to be topHandlerFastExit, see #2228
+                                 $ topHandler e
             runCommands' handle (return Nothing)
 
   -- and finally, exit
@@ -473,7 +476,7 @@ interactiveLoop is_tty show_prompt =
                   -- exception handler above.
 
   -- read commands from stdin
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
   if (is_tty) 
        then runCommands readlineLoop
        else runCommands (fileLoop stdin show_prompt is_tty)
@@ -601,7 +604,7 @@ mkPrompt = do
   return (showSDoc (f (prompt st)))
 
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 readlineLoop :: GHCi (Maybe String)
 readlineLoop = do
    io yield
@@ -686,13 +689,9 @@ runStmt stmt step
  | null (filter (not.isSpace) stmt) = return False
  | ["import", mod] <- words stmt    = keepGoing setContext ('+':mod)
  | otherwise
- = do st <- getGHCiState
-      session <- getSession
-      result <- io $ withProgName (progname st) $ withArgs (args st) $
-                    GHC.runStmt session stmt step
+ = do result <- GhciMonad.runStmt stmt step
       afterRunStmt (const True) result
 
-
 --afterRunStmt :: GHC.RunResult -> GHCi Bool
                                  -- False <=> the statement failed to compile
 afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool
@@ -707,7 +706,7 @@ afterRunStmt step_here run_result = do
      GHC.RunBreak _ names mb_info 
          | isNothing  mb_info || 
            step_here (GHC.resumeSpan $ head resumes) -> do
-               printForUser $ ptext SLIT("Stopped at") <+> 
+               printForUser $ ptext (sLit "Stopped at") <+> 
                        ppr (GHC.resumeSpan $ head resumes)
 --               printTypeOfNames session names
                let namesSorted = sortBy compareNames names
@@ -720,14 +719,14 @@ afterRunStmt step_here run_result = do
                st <- getGHCiState
                enqueueCommands [stop st]
                return ()
-         | otherwise -> io(GHC.resume session GHC.SingleStep) >>= 
+         | otherwise -> resume GHC.SingleStep >>=
                         afterRunStmt step_here >> return ()
      _ -> return ()
 
   flushInterpBuffers
   io installSignalHandlers
   b <- isOptionSet RevertCAFs
-  io (when b revertCAFs)
+  when b revertCAFs
 
   return (case run_result of GHC.RunOk _ -> True; _ -> False)
 
@@ -897,7 +896,7 @@ doWithArgs args cmd = enqueueCommands ["System.Environment.withArgs " ++
 
 addModule :: [FilePath] -> GHCi ()
 addModule files = do
-  io (revertCAFs)                      -- always revert CAFs on load/add.
+  revertCAFs                   -- always revert CAFs on load/add.
   files <- mapM expandPath files
   targets <- mapM (\m -> io (GHC.guessTarget m Nothing)) files
   session <- getSession
@@ -1096,7 +1095,7 @@ doLoad session retain_context prev_context howmuch = do
 
 afterLoad :: SuccessFlag -> Session -> Bool -> ([Module],[Module]) -> GHCi ()
 afterLoad ok session retain_context prev_context = do
-  io (revertCAFs)  -- always revert CAFs on load.
+  revertCAFs  -- always revert CAFs on load.
   discardTickArrays
   loaded_mod_summaries <- getLoadedModules session
   let loaded_mods = map GHC.ms_mod loaded_mod_summaries
@@ -1624,8 +1623,8 @@ showContext = do
    printForUser $ vcat (map pp_resume (reverse resumes))
   where
    pp_resume resume =
-        ptext SLIT("--> ") <> text (GHC.resumeStmt resume)
-        $$ nest 2 (ptext SLIT("Stopped at") <+> ppr (GHC.resumeSpan resume))
+        ptext (sLit "--> ") <> text (GHC.resumeStmt resume)
+        $$ nest 2 (ptext (sLit "Stopped at") <+> ppr (GHC.resumeSpan resume))
 
 showPackages :: GHCi ()
 showPackages = do
@@ -1636,7 +1635,8 @@ showPackages = do
   pkg_ids <- fmap (preloadPackages . pkgState) getDynFlags
   io $ putStrLn $ showSDoc $ vcat $
     text "packages currently loaded:" 
-    : map (nest 2 . text . packageIdString) pkg_ids
+    : map (nest 2 . text . packageIdString) 
+               (sortBy (compare `on` packageIdFS) pkg_ids)
   where showFlag (ExposePackage p) = text $ "  -package " ++ p
         showFlag (HidePackage p)   = text $ "  -hide-package " ++ p
         showFlag (IgnorePackage p) = text $ "  -ignore-package " ++ p
@@ -1659,7 +1659,7 @@ completeMacro, completeIdentifier, completeModule,
     completeHomeModuleOrFile 
     :: String -> IO [String]
 
-#ifdef USE_READLINE
+#ifdef USE_EDITLINE
 completeWord :: String -> Int -> Int -> IO (Maybe (String, [String]))
 completeWord w start end = do
   line <- Readline.getLineBuffer
@@ -1947,8 +1947,7 @@ continueCmd = noArgs $ doContinue (const True) GHC.RunToCompletion
 -- doContinue :: SingleStep -> GHCi ()
 doContinue :: (SrcSpan -> Bool) -> SingleStep -> GHCi ()
 doContinue pred step = do 
-  session <- getSession
-  runResult <- io $ GHC.resume session step
+  runResult <- resume step
   afterRunStmt pred runResult
   return ()
 
@@ -2012,7 +2011,7 @@ backCmd :: String -> GHCi ()
 backCmd = noArgs $ do
   s <- getSession
   (names, _, span) <- io $ GHC.back s
-  printForUser $ ptext SLIT("Logged breakpoint at") <+> ppr span
+  printForUser $ ptext (sLit "Logged breakpoint at") <+> ppr span
   printTypeOfNames s names
    -- run the command set with ":set stop <cmd>"
   st <- getGHCiState
@@ -2023,8 +2022,8 @@ forwardCmd = noArgs $ do
   s <- getSession
   (names, ix, span) <- io $ GHC.forward s
   printForUser $ (if (ix == 0)
-                    then ptext SLIT("Stopped at")
-                    else ptext SLIT("Logged breakpoint at")) <+> ppr span
+                    then ptext (sLit "Stopped at")
+                    else ptext (sLit "Logged breakpoint at")) <+> ppr span
   printTypeOfNames s names
    -- run the command set with ":set stop <cmd>"
   st <- getGHCiState
@@ -2040,7 +2039,7 @@ breakSwitch :: Session -> [String] -> GHCi ()
 breakSwitch _session [] = do
    io $ putStrLn "The break command requires at least one argument."
 breakSwitch session (arg1:rest) 
-   | looksLikeModuleName arg1 = do
+   | looksLikeModuleName arg1 && not (null rest) = do
         mod <- wantInterpretedModule arg1
         breakByModule mod rest
    | all isDigit arg1 = do