eliminate a bit of duplication
[ghc-hetmet.git] / compiler / ghci / InteractiveUI.hs
index 2be47c3..d524ff1 100644 (file)
@@ -22,9 +22,13 @@ import GHC              ( Session, LoadHowMuch(..), Target(..),  TargetId(..),
                           BreakIndex, SrcSpan, Resume, SingleStep )
 import PprTyThing
 import DynFlags
+
+#ifdef USE_READLINE
 import Packages
 import PackageConfig
 import UniqFM
+#endif
+
 import HscTypes                ( implicitTyThings )
 import Outputable       hiding (printForUser)
 import Module           -- for ModuleEnv
@@ -83,7 +87,9 @@ import GHC.IOBase     ( IOErrorType(InvalidArgument) )
 
 import Data.IORef      ( IORef, readIORef, writeIORef )
 
+#ifdef USE_READLINE
 import System.Posix.Internals ( setNonBlockingFD )
+#endif
 
 -----------------------------------------------------------------------------
 
@@ -158,7 +164,7 @@ helpText =
  "\n" ++
  "   <statement>                 evaluate/run <statement>\n" ++
  "   :add <filename> ...         add module(s) to the current target set\n" ++
- "   :browse [*]<module>         display the names defined by <module>\n" ++
+ "   :browse [[*]<module>]       display the names defined by <module>\n" ++
  "   :cd <dir>                   change directory to <dir>\n" ++
  "   :cmd <expr>                 run the commands returned by <expr>::IO String\n" ++
  "   :ctags [<file>]             create tags file for Vi (default: \"tags\")\n" ++
@@ -419,10 +425,11 @@ interactiveLoop is_tty show_prompt =
 -- the same directory while a process is running.
 
 checkPerms :: String -> IO Bool
-checkPerms name =
 #ifdef mingw32_HOST_OS
+checkPerms _ =
   return True
 #else
+checkPerms name =
   Util.handle (\_ -> return False) $ do
      st <- getFileStatus name
      me <- getRealUserID
@@ -1018,16 +1025,27 @@ shellEscape str = io (system str >> return False)
 browseCmd :: String -> GHCi ()
 browseCmd m = 
   case words m of
-    ['*':m] | looksLikeModuleName m -> browseModule m False
-    [m]     | looksLikeModuleName m -> browseModule m True
+    ['*':s] | looksLikeModuleName s -> do 
+        m <-  wantInterpretedModule s
+        browseModule m False
+    [s] | looksLikeModuleName s -> do
+        m <- lookupModule s
+        browseModule m True
+    [] -> do
+        s <- getSession
+        (as,bs) <- io $ GHC.getContext s
+                -- Guess which module the user wants to browse.  Pick
+                -- modules that are interpreted first.  The most
+                -- recently-added module occurs last, it seems.
+        case (as,bs) of
+          (as@(_:_), _)   -> browseModule (last as) True
+          ([],  bs@(_:_)) -> browseModule (last bs) True
+          ([],  [])  -> throwDyn (CmdLineError ":browse: no current module")
     _ -> throwDyn (CmdLineError "syntax:  :browse <module>")
 
-browseModule :: String -> Bool -> GHCi ()
-browseModule m exports_only = do
+browseModule :: Module -> Bool -> GHCi ()
+browseModule modl exports_only = do
   s <- getSession
-  modl <- if exports_only then lookupModule m
-                          else wantInterpretedModule m
-
   -- Temporarily set the context to the module we're interested in,
   -- just so we can get an appropriate PrintUnqualified
   (as,bs) <- io (GHC.getContext s)
@@ -1039,7 +1057,8 @@ browseModule m exports_only = do
 
   mb_mod_info <- io $ GHC.getModuleInfo s modl
   case mb_mod_info of
-    Nothing -> throwDyn (CmdLineError ("unknown module: " ++ m))
+    Nothing -> throwDyn (CmdLineError ("unknown module: " ++
+                                GHC.moduleNameString (GHC.moduleName modl)))
     Just mod_info -> do
         let names
               | exports_only = GHC.modInfoExports mod_info
@@ -1347,6 +1366,11 @@ showContext = do
 completeNone :: String -> IO [String]
 completeNone _w = return []
 
+completeMacro, completeIdentifier, completeModule,
+    completeHomeModule, completeSetOptions, completeFilename,
+    completeHomeModuleOrFile 
+    :: String -> IO [String]
+
 #ifdef USE_READLINE
 completeWord :: String -> Int -> Int -> IO (Maybe (String, [String]))
 completeWord w start end = do
@@ -1381,12 +1405,7 @@ completeWord w start end = do
               | offset+length x >= start = (start-offset,take (end-offset) x)
               | otherwise = selectWord xs
 
-
-completeCmd, completeMacro, completeIdentifier, completeModule,
-    completeHomeModule, completeSetOptions, completeFilename,
-    completeHomeModuleOrFile 
-    :: String -> IO [String]
-
+completeCmd :: String -> IO [String]
 completeCmd w = do
   cmds <- readIORef commands
   return (filter (w `isPrefixOf`) (map (':':) (map cmdName cmds)))
@@ -1448,11 +1467,10 @@ getCommonPrefix (s:ss) = foldl common s ss
 
 allExposedModules :: DynFlags -> [ModuleName]
 allExposedModules dflags 
- = map GHC.mkModuleName (concat (map exposedModules (filter exposed (eltsUFM pkg_db))))
+ = concat (map exposedModules (filter exposed (eltsUFM pkg_db)))
  where
   pkg_db = pkgIdMap (pkgState dflags)
 #else
-completeCmd        = completeNone
 completeMacro      = completeNone
 completeIdentifier = completeNone
 completeModule     = completeNone
@@ -1460,7 +1478,6 @@ completeHomeModule = completeNone
 completeSetOptions = completeNone
 completeFilename   = completeNone
 completeHomeModuleOrFile=completeNone
-completeBkpt       = completeNone
 #endif
 
 -- ---------------------------------------------------------------------------