Bugfix in completion code for :set and :unset.
[ghc-hetmet.git] / ghc / compiler / ghci / InteractiveUI.hs
index 76a80b5..c5edfa6 100644 (file)
@@ -15,21 +15,27 @@ module InteractiveUI (
 
 -- The GHC interface
 import qualified GHC
-import GHC             ( Session, verbosity, dopt, DynFlag(..),
-                         mkModule, pprModule, Type, Module, SuccessFlag(..),
+import GHC             ( Session, verbosity, dopt, DynFlag(..), Target(..),
+                         TargetId(..), DynFlags(..),
+                         pprModule, Type, Module, SuccessFlag(..),
                          TyThing(..), Name, LoadHowMuch(..), Phase,
                          GhcException(..), showGhcException,
                          CheckedModule(..), SrcLoc )
+import DynFlags         ( allFlags )
+import Packages                ( PackageState(..) )
+import PackageConfig   ( InstalledPackageInfo(..) )
+import UniqFM          ( eltsUFM )
 import PprTyThing
 import Outputable
 
 -- for createtags (should these come via GHC?)
-import Module( moduleUserString )
-import Name( nameSrcLoc, nameModule, nameOccName )
-import OccName( pprOccName )
-import SrcLoc( isGoodSrcLoc, srcLocFile, srcLocLine, srcLocCol )
+import Module          ( moduleString )
+import Name            ( nameSrcLoc, nameModule, nameOccName )
+import OccName         ( pprOccName )
+import SrcLoc          ( isGoodSrcLoc, srcLocFile, srcLocLine, srcLocCol )
 
 -- Other random utilities
+import Digraph         ( flattenSCCs )
 import BasicTypes      ( failed, successIf )
 import Panic           ( panic, installSignalHandlers )
 import Config
@@ -37,7 +43,6 @@ import StaticFlags    ( opt_IgnoreDotGhci )
 import Linker          ( showLinkerState )
 import Util            ( removeSpaces, handle, global, toArgs,
                          looksLikeModuleName, prefixMatch, sortLe )
-import ErrUtils                ( printErrorsAndWarnings )
 
 #ifndef mingw32_HOST_OS
 import System.Posix
@@ -73,6 +78,7 @@ import System.IO.Error as IO
 import Data.Char
 import Control.Monad as Monad
 import Foreign.StablePtr       ( newStablePtr )
+import Text.Printf
 
 import GHC.Exts                ( unsafeCoerce# )
 import GHC.IOBase      ( IOErrorType(InvalidArgument) )
@@ -90,29 +96,34 @@ ghciWelcomeMsg =
  "/ /_\\\\/ __  / /___| |      http://www.haskell.org/ghc/\n"++
  "\\____/\\/ /_/\\____/|_|      Type :? for help.\n"
 
-GLOBAL_VAR(commands, builtin_commands, [(String, String -> GHCi Bool)])
+type Command = (String, String -> GHCi Bool, Bool, String -> IO [String])
+cmdName (n,_,_,_) = n
 
-builtin_commands :: [(String, String -> GHCi Bool)]
+GLOBAL_VAR(commands, builtin_commands, [Command])
+
+builtin_commands :: [Command]
 builtin_commands = [
-  ("add",      keepGoingPaths addModule),
-  ("browse",    keepGoing browseCmd),
-  ("cd",       keepGoing changeDirectory),
-  ("def",      keepGoing defineMacro),
-  ("help",     keepGoing help),
-  ("?",                keepGoing help),
-  ("info",      keepGoing info),
-  ("load",     keepGoingPaths loadModule_),
-  ("module",   keepGoing setContext),
-  ("reload",   keepGoing reloadModule),
-  ("check",    keepGoing checkModule),
-  ("set",      keepGoing setCmd),
-  ("show",     keepGoing showCmd),
-  ("tags",     keepGoing createTagsFileCmd),
-  ("type",     keepGoing typeOfExpr),
-  ("kind",     keepGoing kindOfType),
-  ("unset",    keepGoing unsetOptions),
-  ("undef",     keepGoing undefineMacro),
-  ("quit",     quit)
+  ("add",      keepGoingPaths addModule,       False, completeFilename),
+  ("browse",    keepGoing browseCmd,           False, completeModule),
+  ("cd",       keepGoing changeDirectory,      False, completeFilename),
+  ("def",      keepGoing defineMacro,          False, completeIdentifier),
+  ("help",     keepGoing help,                 False, completeNone),
+  ("?",                keepGoing help,                 False, completeNone),
+  ("info",      keepGoing info,                        False, completeIdentifier),
+  ("load",     keepGoingPaths loadModule_,     False, completeHomeModuleOrFile),
+  ("module",   keepGoing setContext,           False, completeModule),
+  ("main",     keepGoing runMain,              False, completeIdentifier),
+  ("reload",   keepGoing reloadModule,         False, completeNone),
+  ("check",    keepGoing checkModule,          False, completeHomeModule),
+  ("set",      keepGoing setCmd,               True,  completeSetOptions),
+  ("show",     keepGoing showCmd,              False, completeNone),
+  ("etags",    keepGoing createETagsFileCmd,   False, completeFilename),
+  ("ctags",    keepGoing createCTagsFileCmd,   False, completeFilename),
+  ("type",     keepGoing typeOfExpr,           False, completeIdentifier),
+  ("kind",     keepGoing kindOfType,           False, completeIdentifier),
+  ("unset",    keepGoing unsetOptions,         True,  completeSetOptions),
+  ("undef",     keepGoing undefineMacro,       False, completeMacro),
+  ("quit",     quit,                           False, completeNone)
   ]
 
 keepGoing :: (String -> GHCi ()) -> (String -> GHCi Bool)
@@ -136,6 +147,7 @@ helpText =
  "   :info [<name> ...]          display information about the given names\n" ++
  "   :load <filename> ...        load module(s) and their dependents\n" ++
  "   :module [+/-] [*]<mod> ...  set the context for expression evaluation\n" ++
+ "   :main [<arguments> ...]     run the main function with the given arguments\n" ++
  "   :reload                     reload the current module set\n" ++
  "\n" ++
  "   :set <option> ...           set options\n" ++
@@ -145,7 +157,8 @@ helpText =
  "   :show modules               show the currently loaded modules\n" ++
  "   :show bindings              show the current bindings made at the prompt\n" ++
  "\n" ++
- "   :tags -e|-c                 create tags file for Vi (-c) or Emacs (-e)\n" ++
+ "   :ctags [<file>]             create tags file for Vi (default: \"tags\")\n" ++
+ "   :etags [<file>]                    create tags file for Emacs (defauilt: \"TAGS\")\n" ++
  "   :type <expr>                show the type of <expr>\n" ++
  "   :kind <type>                show the kind of <type>\n" ++
  "   :undef <cmd>                undefine user-defined command :<cmd>\n" ++
@@ -192,15 +205,18 @@ interactiveUI session srcs maybe_expr = do
 
 #ifdef USE_READLINE
    Readline.initialize
-#endif
+   Readline.setAttemptedCompletionFunction (Just completeWord)
+   --Readline.parseAndBind "set show-all-if-ambiguous 1"
 
-#if defined(mingw32_HOST_OS)
-    -- The win32 Console API mutates the first character of 
-    -- type-ahead when reading from it in a non-buffered manner. Work
-    -- around this by flushing the input buffer of type-ahead characters.
-    -- 
-   GHC.ConsoleHandler.flushConsole stdin
+   let symbols = "!#$%&*+/<=>?@\\^|-~"
+       specials = "(),;[]`{}"
+       spaces = " \t\n"
+       word_break_chars = spaces ++ specials ++ symbols
+
+   Readline.setBasicWordBreakCharacters word_break_chars
+   Readline.setCompleterWordBreakCharacters word_break_chars
 #endif
+
    startGHCi (runGHCi srcs maybe_expr)
        GHCiState{ progname = "<interactive>",
                   args = [],
@@ -263,6 +279,18 @@ runGHCi paths maybe_expr = do
 
   case maybe_expr of
        Nothing -> 
+#if defined(mingw32_HOST_OS)
+          do
+            -- The win32 Console API mutates the first character of 
+            -- type-ahead when reading from it in a non-buffered manner. Work
+            -- around this by flushing the input buffer of type-ahead characters,
+            -- but only if stdin is available.
+            flushed <- io (IO.try (GHC.ConsoleHandler.flushConsole stdin))
+            case flushed of 
+            Left err | isDoesNotExistError err -> return ()
+                     | otherwise -> io (ioError err)
+            Right () -> return ()
+#endif
            -- enter the interactive loop
            interactiveLoop is_tty show_prompt
        Just expr -> do
@@ -274,15 +302,18 @@ runGHCi paths maybe_expr = do
   io $ do when (verbosity dflags > 0) $ putStrLn "Leaving GHCi."
 
 
-interactiveLoop is_tty show_prompt = do
+interactiveLoop is_tty show_prompt =
   -- Ignore ^C exceptions caught here
   ghciHandleDyn (\e -> case e of 
-                       Interrupted -> ghciUnblock (
+                       Interrupted -> do
 #if defined(mingw32_HOST_OS)
-                                               io (putStrLn "") >> 
+                               io (putStrLn "")
 #endif
-                                               interactiveLoop is_tty show_prompt)
-                       _other      -> return ()) $ do
+                               interactiveLoop is_tty show_prompt
+                       _other      -> return ()) $ 
+
+  ghciUnblock $ do -- unblock necessary if we recursed from the 
+                  -- exception handler above.
 
   -- read commands from stdin
 #ifdef USE_READLINE
@@ -365,10 +396,12 @@ readlineLoop = do
    session <- getSession
    (mod,imports) <- io (GHC.getContext session)
    io yield
+   saveSession -- for use by completion
    l <- io (readline (mkPrompt mod imports)
                `finally` setNonBlockingFD 0)
                -- readline sometimes puts stdin into blocking mode,
                -- so we need to put it back for the IO library
+   splatSavedSession
    case l of
        Nothing -> return ()
        Just l  ->
@@ -382,6 +415,11 @@ readlineLoop = do
 
 runCommand :: String -> GHCi Bool
 runCommand c = ghciHandle handler (doCommand c)
+  where 
+    doCommand (':' : command) = specialCommand command
+    doCommand stmt
+       = do timeIt (do nms <- runStmt stmt; finishEvalExpr nms)
+            return False
 
 -- This version is for the GHC command-line option -e.  The only difference
 -- from runCommand is that it catches the ExitException exception and
@@ -392,6 +430,14 @@ runCommandEval c = ghciHandle handleEval (doCommand c)
     handleEval e                    = do showException e
                                         io (exitWith (ExitFailure 1))
 
+    doCommand (':' : command) = specialCommand command
+    doCommand stmt
+       = do nms <- runStmt stmt
+           case nms of 
+               Nothing -> io (exitWith (ExitFailure 1))
+                 -- failure to run the command causes exit(1) for ghc -e.
+               _       -> finishEvalExpr nms
+
 -- This is the exception handler for exceptions generated by the
 -- user's code; it normally just prints out the exception.  The
 -- handler must be recursive, in case showing the exception causes
@@ -418,29 +464,26 @@ showException (DynException dyn) =
 showException other_exception
   = io (putStrLn ("*** Exception: " ++ show other_exception))
 
-doCommand (':' : command) = specialCommand command
-doCommand stmt
-   = do timeIt (do nms <- runStmt stmt; finishEvalExpr nms)
-        return False
-
-runStmt :: String -> GHCi [Name]
+runStmt :: String -> GHCi (Maybe [Name])
 runStmt stmt
- | null (filter (not.isSpace) stmt) = return []
+ | null (filter (not.isSpace) stmt) = return (Just [])
  | otherwise
  = do st <- getGHCiState
       session <- getSession
       result <- io $ withProgName (progname st) $ withArgs (args st) $
                     GHC.runStmt session stmt
       case result of
-       GHC.RunFailed      -> return []
+       GHC.RunFailed      -> return Nothing
        GHC.RunException e -> throw e  -- this is caught by runCommand(Eval)
-       GHC.RunOk names    -> return names
+       GHC.RunOk names    -> return (Just names)
 
 -- possibly print the type and revert CAFs after evaluating an expression
-finishEvalExpr names
+finishEvalExpr mb_names
  = do b <- isOptionSet ShowType
       session <- getSession
-      when b (mapM_ (showTypeOfName session) names)
+      case mb_names of
+       Nothing    -> return ()      
+       Just names -> when b (mapM_ (showTypeOfName session) names)
 
       flushInterpBuffers
       io installSignalHandlers
@@ -465,15 +508,21 @@ specialCommand :: String -> GHCi Bool
 specialCommand ('!':str) = shellEscape (dropWhile isSpace str)
 specialCommand str = do
   let (cmd,rest) = break isSpace str
-  cmds <- io (readIORef commands)
-  case [ (s,f) | (s,f) <- cmds, prefixMatch cmd s ] of
-     []      -> io (hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n" 
+  maybe_cmd <- io (lookupCommand cmd)
+  case maybe_cmd of
+    Nothing -> io (hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n" 
                                    ++ shortHelpText) >> return False)
-     [(_,f)] -> f (dropWhile isSpace rest)
-     cs      -> io (hPutStrLn stdout ("prefix " ++ cmd ++ 
-                                     " matches multiple commands (" ++ 
-                                      foldr1 (\a b -> a ++ ',':b) (map fst cs)
-                                        ++ ")") >> return False)
+    Just (_,f,_,_) -> f (dropWhile isSpace rest)
+
+lookupCommand :: String -> IO (Maybe Command)
+lookupCommand str = do
+  cmds <- readIORef commands
+  -- look for exact match first, then the first prefix match
+  case [ c | c <- cmds, str == cmdName c ] of
+     c:_ -> return (Just c)
+     [] -> case [ c | c@(s,_,_,_) <- cmds, prefixMatch str s ] of
+               [] -> return Nothing
+               c:_ -> return (Just c)
 
 -----------------------------------------------------------------------------
 -- To flush buffers for the *interpreted* computation we need
@@ -558,6 +607,12 @@ pprInfo exts (thing, fixity, insts)
 -----------------------------------------------------------------------------
 -- Commands
 
+runMain :: String -> GHCi ()
+runMain args = do
+  let ss = concat $ intersperse "," (map (\ s -> ('"':s)++"\"") (toArgs args))
+  runCommand $ '[': ss ++ "] `System.Environment.withArgs` main"
+  return ()
+
 addModule :: [FilePath] -> GHCi ()
 addModule files = do
   io (revertCAFs)                      -- always revert CAFs on load/add.
@@ -576,7 +631,7 @@ changeDirectory dir = do
        io $ putStr "Warning: changing directory causes all loaded modules to be unloaded,\nbecause the search path has changed.\n"
   io (GHC.setTargets session [])
   io (GHC.load session LoadAllTargets)
-  setContextAfterLoad []
+  setContextAfterLoad session []
   io (GHC.workingDirectoryChanged session)
   dir <- expandPath dir
   io (setCurrentDirectory dir)
@@ -588,7 +643,7 @@ defineMacro s = do
   if (null macro_name) 
        then throwDyn (CmdLineError "invalid macro name") 
        else do
-  if (macro_name `elem` map fst cmds) 
+  if (macro_name `elem` map cmdName cmds)
        then throwDyn (CmdLineError 
                ("command '" ++ macro_name ++ "' is already defined"))
        else do
@@ -603,7 +658,7 @@ defineMacro s = do
   case maybe_hv of
      Nothing -> return ()
      Just hv -> io (writeIORef commands --
-                   ((macro_name, keepGoing (runMacro hv)) : cmds))
+                   (cmds ++ [(macro_name, keepGoing (runMacro hv), False, completeNone)]))
 
 runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi ()
 runMacro fun s = do
@@ -613,15 +668,15 @@ runMacro fun s = do
 undefineMacro :: String -> GHCi ()
 undefineMacro macro_name = do
   cmds <- io (readIORef commands)
-  if (macro_name `elem` map fst builtin_commands) 
+  if (macro_name `elem` map cmdName builtin_commands) 
        then throwDyn (CmdLineError
                ("command '" ++ macro_name ++ "' cannot be undefined"))
        else do
-  if (macro_name `notElem` map fst cmds) 
+  if (macro_name `notElem` map cmdName cmds) 
        then throwDyn (CmdLineError 
                ("command '" ++ macro_name ++ "' not defined"))
        else do
-  io (writeIORef commands (filter ((/= macro_name) . fst) cmds))
+  io (writeIORef commands (filter ((/= macro_name) . cmdName) cmds))
 
 
 loadModule :: [(FilePath, Maybe Phase)] -> GHCi SuccessFlag
@@ -656,9 +711,9 @@ loadModule' files = do
 
 checkModule :: String -> GHCi ()
 checkModule m = do
-  let modl = mkModule m
+  let modl = GHC.mkModule m
   session <- getSession
-  result <- io (GHC.checkModule session modl printErrorsAndWarnings)
+  result <- io (GHC.checkModule session modl)
   case result of
     Nothing -> io $ putStrLn "Nothing"
     Just r  -> io $ putStrLn (showSDoc (
@@ -681,25 +736,45 @@ reloadModule "" = do
 reloadModule m = do
   io (revertCAFs)              -- always revert CAFs on reload.
   session <- getSession
-  ok <- io (GHC.load session (LoadUpTo (mkModule m)))
+  ok <- io (GHC.load session (LoadUpTo (GHC.mkModule m)))
   afterLoad ok session
 
 afterLoad ok session = do
   io (revertCAFs)  -- always revert CAFs on load.
   graph <- io (GHC.getModuleGraph session)
-  let mods = map GHC.ms_mod graph
-  mods' <- filterM (io . GHC.isLoaded session) mods
-  setContextAfterLoad mods'
-  modulesLoadedMsg ok mods'
+  graph' <- filterM (io . GHC.isLoaded session . GHC.ms_mod) graph
+  setContextAfterLoad session graph'
+  modulesLoadedMsg ok (map GHC.ms_mod graph')
 
-setContextAfterLoad [] = do
-  session <- getSession
+setContextAfterLoad session [] = do
   io (GHC.setContext session [] [prelude_mod])
-setContextAfterLoad (m:_) = do
-  session <- getSession
-  b <- io (GHC.moduleIsInterpreted session m)
-  if b then io (GHC.setContext session [m] []) 
-       else io (GHC.setContext session []  [m])
+setContextAfterLoad session ms = do
+  -- load a target if one is available, otherwise load the topmost module.
+  targets <- io (GHC.getTargets session)
+  case [ m | Just m <- map (findTarget ms) targets ] of
+       []    -> 
+         let graph' = flattenSCCs (GHC.topSortModuleGraph True ms Nothing) in
+         load_this (last graph')         
+       (m:_) -> 
+         load_this m
+ where
+   findTarget ms t
+    = case filter (`matches` t) ms of
+       []    -> Nothing
+       (m:_) -> Just m
+
+   summary `matches` Target (TargetModule m) _
+       = GHC.ms_mod summary == m
+   summary `matches` Target (TargetFile f _) _ 
+       | Just f' <- GHC.ml_hs_file (GHC.ms_location summary)   = f == f'
+   summary `matches` target
+       = False
+
+   load_this summary | m <- GHC.ms_mod summary = do
+       b <- io (GHC.moduleIsInterpreted session m)
+       if b then io (GHC.setContext session [m] []) 
+                    else io (GHC.setContext session []  [prelude_mod,m])
+
 
 modulesLoadedMsg :: SuccessFlag -> [Module] -> GHCi ()
 modulesLoadedMsg ok mods = do
@@ -744,10 +819,13 @@ shellEscape str = io (system str >> return False)
 -----------------------------------------------------------------------------
 -- create tags file for currently loaded modules.
 
-createTagsFileCmd :: String -> GHCi ()
-createTagsFileCmd "-c" = ghciCreateTagsFile CTags "tags"
-createTagsFileCmd "-e" = ghciCreateTagsFile ETags "TAGS"
-createTagsFileCmd _  = throwDyn (CmdLineError "syntax:  :tags -c|-e")
+createETagsFileCmd, createCTagsFileCmd :: String -> GHCi ()
+
+createCTagsFileCmd ""   = ghciCreateTagsFile CTags "tags"
+createCTagsFileCmd file = ghciCreateTagsFile CTags file
+
+createETagsFileCmd ""    = ghciCreateTagsFile ETags "TAGS"
+createETagsFileCmd file  = ghciCreateTagsFile ETags file
 
 data TagsKind = ETags | CTags
 
@@ -772,7 +850,7 @@ createTagsFile session tagskind tagFile = do
         is_interpreted <- GHC.moduleIsInterpreted session m
         -- should we just skip these?
         when (not is_interpreted) $
-          throwDyn (CmdLineError ("module '" ++ moduleUserString m ++ "' is not interpreted"))
+          throwDyn (CmdLineError ("module '" ++ moduleString m ++ "' is not interpreted"))
 
         mbModInfo <- GHC.getModuleInfo session m
         let unqual 
@@ -862,7 +940,7 @@ browseCmd m =
 browseModule m exports_only = do
   s <- getSession
 
-  let modl = mkModule m
+  let modl = GHC.mkModule m
   is_interpreted <- io (GHC.moduleIsInterpreted s modl)
   when (not is_interpreted && not exports_only) $
        throwDyn (CmdLineError ("module '" ++ m ++ "' is not interpreted"))
@@ -921,13 +999,13 @@ separate :: Session -> [String] -> [Module] -> [Module]
   -> GHCi ([Module],[Module])
 separate session []           as bs = return (as,bs)
 separate session (('*':m):ms) as bs = do
-   let modl = mkModule m
+   let modl = GHC.mkModule m
    b <- io (GHC.moduleIsInterpreted session modl)
    if b then separate session ms (modl:as) bs
        else throwDyn (CmdLineError ("module '" ++ m ++ "' is not interpreted"))
-separate session (m:ms)       as bs = separate session ms as (mkModule m:bs)
+separate session (m:ms)       as bs = separate session ms as (GHC.mkModule m:bs)
 
-prelude_mod = mkModule "Prelude"
+prelude_mod = GHC.mkModule "Prelude"
 
 
 addToContext mods = do
@@ -1105,6 +1183,112 @@ cleanType ty = do
        then return ty
        else return $! GHC.dropForAlls ty
 
+-- -----------------------------------------------------------------------------
+-- Completion
+
+#ifdef USE_READLINE
+completeWord :: String -> Int -> Int -> IO (Maybe (String, [String]))
+completeWord w start end = do
+  line <- Readline.getLineBuffer
+  case w of 
+     ':':_ | all isSpace (take (start-1) line) -> wrapCompleter completeCmd w
+     _other
+       | Just c <- is_cmd line -> do
+          maybe_cmd <- lookupCommand c
+           let (n,w') = selectWord (words' 0 line)
+          case maybe_cmd of
+            Nothing -> return Nothing
+            Just (_,_,False,complete) -> wrapCompleter complete w
+            Just (_,_,True,complete) -> let complete' w = do rets <- complete w
+                                                              return (map (drop n) rets)
+                                         in wrapCompleter complete' w'
+       | otherwise     -> do
+               --printf "complete %s, start = %d, end = %d\n" w start end
+               wrapCompleter completeIdentifier w
+    where words' _ [] = []
+          words' n str = let (w,r) = break isSpace str
+                             (s,r') = span isSpace r
+                         in (n,w):words' (n+length w+length s) r'
+          -- In a Haskell expression we want to parse 'a-b' as three words
+          -- where a compiler flag (ie. -fno-monomorphism-restriction) should
+          -- only be a single word.
+          selectWord [] = (0,w)
+          selectWord ((offset,x):xs)
+              | offset+length x >= start = (start-offset,take (end-offset) x)
+              | otherwise = selectWord xs
+
+is_cmd line 
+ | ((':':w) : _) <- words (dropWhile isSpace line) = Just w
+ | otherwise = Nothing
+
+completeNone w = return []
+
+completeCmd w = do
+  cmds <- readIORef commands
+  return (filter (w `isPrefixOf`) (map (':':) (map cmdName cmds)))
+
+completeMacro w = do
+  cmds <- readIORef commands
+  let cmds' = [ cmd | cmd <- map cmdName cmds, cmd `elem` map cmdName builtin_commands ]
+  return (filter (w `isPrefixOf`) cmds')
+
+completeIdentifier w = do
+  s <- restoreSession
+  rdrs <- GHC.getRdrNamesInScope s
+  return (filter (w `isPrefixOf`) (map (showSDoc.ppr) rdrs))
+
+completeModule w = do
+  s <- restoreSession
+  dflags <- GHC.getSessionDynFlags s
+  let pkg_mods = allExposedModules dflags
+  return (filter (w `isPrefixOf`) (map (showSDoc.ppr) pkg_mods))
+
+completeHomeModule w = do
+  s <- restoreSession
+  g <- GHC.getModuleGraph s
+  let home_mods = map GHC.ms_mod g
+  return (filter (w `isPrefixOf`) (map (showSDoc.ppr) home_mods))
+
+completeSetOptions w = do
+  return (filter (w `isPrefixOf`) options)
+    where options = "args":"prog":allFlags
+
+completeFilename = Readline.filenameCompletionFunction
+
+completeHomeModuleOrFile = unionComplete completeHomeModule completeFilename
+
+unionComplete :: (String -> IO [String]) -> (String -> IO [String]) -> String -> IO [String]
+unionComplete f1 f2 w = do
+  s1 <- f1 w
+  s2 <- f2 w
+  return (s1 ++ s2)
+
+wrapCompleter :: (String -> IO [String]) -> String -> IO (Maybe (String,[String]))
+wrapCompleter fun w =  do
+  strs <- fun w
+  case strs of
+    []  -> return Nothing
+    [x] -> return (Just (x,[]))
+    xs  -> case getCommonPrefix xs of
+               ""   -> return (Just ("",xs))
+               pref -> return (Just (pref,xs))
+
+getCommonPrefix :: [String] -> String
+getCommonPrefix [] = ""
+getCommonPrefix (s:ss) = foldl common s ss
+  where common s "" = s
+       common "" s = ""
+       common (c:cs) (d:ds)
+          | c == d = c : common cs ds
+          | otherwise = ""
+
+allExposedModules :: DynFlags -> [Module]
+allExposedModules dflags 
+ = map GHC.mkModule (concat (map exposedModules (filter exposed (eltsUFM pkg_db))))
+ where
+  pkg_db = pkgIdMap (pkgState dflags)
+#endif
+
 -----------------------------------------------------------------------------
 -- GHCi monad
 
@@ -1141,6 +1325,12 @@ setGHCiState s = GHCi $ \r -> writeIORef r s
 -- for convenience...
 getSession = getGHCiState >>= return . session
 
+GLOBAL_VAR(saved_sess, no_saved_sess, Session)
+no_saved_sess = error "no saved_ses"
+saveSession = getSession >>= io . writeIORef saved_sess
+splatSavedSession = io (writeIORef saved_sess no_saved_sess)
+restoreSession = readIORef saved_sess
+
 getDynFlags = do
   s <- getSession
   io (GHC.getSessionDynFlags s)