[project @ 2001-01-09 17:43:57 by rrt]
[ghc-hetmet.git] / ghc / compiler / ghci / InteractiveUI.hs
index 4160844..499998d 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: InteractiveUI.hs,v 1.13 2000/11/22 15:51:48 simonmar Exp $
+-- $Id: InteractiveUI.hs,v 1.24 2000/12/18 12:43:04 sewardj Exp $
 --
 -- GHC Interactive User Interface
 --
@@ -19,18 +19,25 @@ import DriverState
 import Linker
 import Module
 import Outputable
-import Panic
 import Util
+import PprType {- instance Outputable Type; do not delete -}
+import Panic   ( GhcException(..) )
 
 import Exception
+#ifndef NO_READLINE
 import Readline
+#endif
 import IOExts
 
+import Numeric
+import List
 import System
+import CPUTime
 import Directory
 import IO
 import Char
 
+
 -----------------------------------------------------------------------------
 
 ghciWelcomeMsg = "\ 
@@ -41,23 +48,29 @@ ghciWelcomeMsg = "\
 \||   || ||   || ||     (|     Bug reports to: glasgow-haskell-bugs@haskell.org \n\ 
 \(|___|| ||   || (|__|) \\\\______________________________________________________\n"
 
-commands :: [(String, String -> GHCi ())]
+commands :: [(String, String -> GHCi Bool)]
 commands = [
-  ("add",      addModule),
-  ("cd",       changeDirectory),
-  ("help",     help),
-  ("?",                help),
-  ("load",     loadModule),
-  ("module",   setContext),
-  ("reload",   reloadModule),
-  ("set",      setOptions),
-  ("type",     typeOfExpr),
+  ("add",      keepGoing addModule),
+  ("cd",       keepGoing changeDirectory),
+  ("help",     keepGoing help),
+  ("?",                keepGoing help),
+  ("load",     keepGoing loadModule),
+  ("module",   keepGoing setContext),
+  ("reload",   keepGoing reloadModule),
+  ("set",      keepGoing setOptions),
+  ("type",     keepGoing typeOfExpr),
+  ("unset",    keepGoing unsetOptions),
   ("quit",     quit)
   ]
 
+keepGoing :: (String -> GHCi ()) -> (String -> GHCi Bool)
+keepGoing a str = a str >> return False
+
 shortHelpText = "use :? for help.\n"
 
 helpText = "\ 
+\ Commands available from the prompt:\n\ 
+\\  
 \   <expr>             evaluate <expr>\n\ 
 \   :add <filename>     add a module to the current set\n\ 
 \   :cd <dir>          change directory to <dir>\n\ 
@@ -66,13 +79,21 @@ helpText = "\
 \   :module <mod>      set the context for expression evaluation to <mod>\n\ 
 \   :reload            reload the current module set\n\ 
 \   :set <option> ...  set options\n\ 
+\   :unset <option> ...        unset options\n\ 
 \   :type <expr>       show the type of <expr>\n\ 
 \   :quit              exit GHCi\n\ 
 \   :!<command>                run the shell command <command>\n\ 
+\\ 
+\ Options for `:set' and `:unset':\n\ 
+\\ 
+\    +s                 print timing/memory stats after each evaluation\n\ 
+\    +t                        print type after evaluation\n\ 
+\    -<flags>          most GHC command line flags can also be set here\n\ 
+\                         (eg. -v2, -fglasgow-exts, etc.)\n\ 
 \"
 
-interactiveUI :: CmState -> IO ()
-interactiveUI st = do
+interactiveUI :: CmState -> Maybe FilePath -> IO ()
+interactiveUI cmstate mod = do
    hPutStrLn stdout ghciWelcomeMsg
    hFlush stdout
    hSetBuffering stdout NoBuffering
@@ -81,13 +102,23 @@ interactiveUI st = do
    pkgs <- getPackageInfo
    linkPackages (reverse pkgs)
 
+   (cmstate', ok, mods) <-
+       case mod of
+            Nothing  -> return (cmstate, True, [])
+            Just m -> cmLoadModule cmstate m
+
 #ifndef NO_READLINE
    Readline.initialize
 #endif
-   _ <- (unGHCi uiLoop) GHCiState{ modules = [],
-                                  current_module = defaultCurrentModule,
-                                  target = Nothing,
-                                  cmstate = st }
+   let this_mod = case mods of 
+                       [] -> defaultCurrentModule
+                       m:ms -> m
+
+   (unGHCi uiLoop) GHCiState{ modules = mods,
+                             current_module = this_mod,
+                             target = mod,
+                             cmstate = cmstate',
+                             options = [ShowTiming]}
    return ()
 
 uiLoop :: GHCi ()
@@ -96,7 +127,8 @@ uiLoop = do
 #ifndef NO_READLINE
   l <- io (readline (moduleNameUserString (current_module st) ++ "> "))
 #else
-  l <- io (hGetLine stdin)
+  l_ok <- io (hGetLine stdin)
+  let l = Just l_ok
 #endif
   case l of
     Nothing -> exitGHCi
@@ -105,35 +137,47 @@ uiLoop = do
 #ifndef NO_READLINE
           io (addHistory l)
 #endif
-         runCommand l
-         uiLoop  
+         quit <- runCommand l
+          if quit then exitGHCi else uiLoop
 
-exitGHCi = io $ do putStrLn "Leaving GHCi."; exitWith ExitSuccess
+exitGHCi = io $ do putStrLn "Leaving GHCi." 
 
 -- Top level exception handler, just prints out the exception 
 -- and carries on.
+runCommand :: String -> GHCi Bool
 runCommand c = 
-  ghciHandle ( \other_exception ->io (putStrLn (show other_exception) )) $
+  ghciHandle ( 
+     \other_exception 
+        -> io (putStrLn (show other_exception)) >> return False
+  ) $
   ghciHandleDyn
     (\dyn -> case dyn of
                PhaseFailed phase code ->
                        io ( putStrLn ("Phase " ++ phase ++ " failed (code "
                                        ++ show code ++ ")"))
                Interrupted -> io (putStrLn "Interrupted.")
-               _ -> io (putStrLn (show (dyn :: BarfKind)))
+               _ -> io (putStrLn (show (dyn :: GhcException)))
+             >> return False
     ) $
    doCommand c
 
 doCommand (':' : command) = specialCommand command
-doCommand expr
+doCommand expr            = timeIt (evalExpr expr) >> return False
+
+evalExpr expr
  = do st <- getGHCiState
       dflags <- io (getDynFlags)
-      (new_cmstate, maybe_hvalue) <- 
+      (new_cmstate, maybe_stuff) <- 
         io (cmGetExpr (cmstate st) dflags (current_module st) expr)
       setGHCiState st{cmstate = new_cmstate}
-      case maybe_hvalue of
+      case maybe_stuff of
         Nothing -> return ()
-        Just hv -> io (cmRunExpr hv)
+        Just (hv, unqual, ty)
+          -> do io (cmRunExpr hv)
+                b <- isOptionSet ShowType
+                if b then io (printForUser stdout unqual (text "::" <+> ppr ty))
+                     else return ()
+       
 {-
   let (mod,'.':str) = break (=='.') expr
   case cmLookupSymbol (mkOrig varName (mkModuleName mod) (_PK_ str)) (cmstate st) of
@@ -142,17 +186,18 @@ doCommand expr
   return ()
 -}
 
-specialCommand ('!':str) = shellEscape (dropWhile isSpace str)
+specialCommand :: String -> GHCi Bool
+specialCommand ('!':str) = shellEscape (dropWhile isSpace str) 
 specialCommand str = do
   let (cmd,rest) = break isSpace str
   case [ (s,f) | (s,f) <- commands, prefixMatch cmd s ] of
-     []      -> io $ hPutStr stdout ("unknown command `:" ++ cmd ++ "'\n" 
-                                   ++ shortHelpText)
+     []      -> io (hPutStr stdout ("unknown command `:" ++ cmd ++ "'\n" 
+                                   ++ shortHelpText) >> return False)
      [(_,f)] -> f (dropWhile isSpace rest)
-     cs      -> io $ hPutStrLn stdout ("prefix " ++ cmd ++ 
-                                      " matches multiple commands (" ++ 
+     cs      -> io (hPutStrLn stdout ("prefix " ++ cmd ++ 
+                                     " matches multiple commands (" ++ 
                                       foldr1 (\a b -> a ++ ',':b) (map fst cs)
-                                        ++ ")")
+                                        ++ ")") >> return False)
 
 noArgs c = io (hPutStrLn stdout ("command `:" ++ c ++ "' takes no arguments"))
 
@@ -175,20 +220,22 @@ setContext m
        setGHCiState st{current_module = mkModuleName m}
 
 changeDirectory :: String -> GHCi ()
-changeDirectory = io . setCurrentDirectory
+changeDirectory d = io (setCurrentDirectory d)
 
 loadModule :: String -> GHCi ()
-loadModule path = do
+loadModule path = timeIt (loadModule' path)
+
+loadModule' path = do
   state <- getGHCiState
   cmstate1 <- io (cmUnload (cmstate state))
   (cmstate2, ok, mods) <- io (cmLoadModule cmstate1 path)
 
-  let new_state = GHCiState {
+  let new_state = state{
                        cmstate = cmstate2,
                        modules = mods,
                        current_module = case mods of 
                                           [] -> defaultCurrentModule
-                                          xs -> last xs,
+                                          xs -> head xs,
                        target = Just path
                   }
   setGHCiState new_state
@@ -209,45 +256,121 @@ reloadModule "" = do
   case target state of
    Nothing -> io (putStr "no current target\n")
    Just path
-      -> do (new_cmstate, ok, mod) <- io (cmLoadModule (cmstate state) path)
-            setGHCiState state{cmstate=new_cmstate}  
-reloadModule _ = noArgs ":reload"
+      -> do (new_cmstate, ok, mods) <- io (cmLoadModule (cmstate state) path)
+            setGHCiState 
+               state{cmstate=new_cmstate,
+                     modules = mods,
+                     current_module = case mods of 
+                                         [] -> defaultCurrentModule
+                                         xs -> head xs
+                    }
 
--- set options in the interpreter.  Syntax is exactly the same as the
--- ghc command line, except that certain options aren't available (-C,
--- -E etc.)
---
--- This is pretty fragile: most options won't work as expected.  ToDo:
--- figure out which ones & disallow them.
-setOptions :: String -> GHCi ()
-setOptions str =
-   io (do leftovers <- processArgs static_flags (words str) []
-         dyn_flags <- readIORef v_InitDynFlags
-         writeIORef v_DynFlags dyn_flags
-         leftovers <- processArgs dynamic_flags leftovers []
-         dyn_flags <- readIORef v_DynFlags
-         writeIORef v_InitDynFlags dyn_flags
-          if (not (null leftovers))
-               then throwDyn (OtherError ("unrecognised flags: " ++ 
-                                               unwords leftovers))
-               else return ()
-   )
+
+reloadModule _ = noArgs ":reload"
 
 typeOfExpr :: String -> GHCi ()
 typeOfExpr str 
   = do st <- getGHCiState
        dflags <- io (getDynFlags)
-       (st, maybe_ty) <- io (cmTypeExpr (cmstate st) dflags 
+       (st, maybe_ty) <- io (cmGetExpr (cmstate st) dflags 
                                (current_module st) str)
        case maybe_ty of
         Nothing -> return ()
-        Just (unqual, ty) -> io (printForUser stdout unqual (ppr ty))
+        Just (_, unqual, ty) -> io (printForUser stdout unqual (ppr ty)) 
 
-quit :: String -> GHCi ()
-quit _ = exitGHCi
+quit :: String -> GHCi Bool
+quit _ = return True
 
-shellEscape :: String -> GHCi ()
-shellEscape str = io (system str >> return ())
+shellEscape :: String -> GHCi Bool
+shellEscape str = io (system str >> return False)
+
+----------------------------------------------------------------------------
+-- Code for `:set'
+
+-- set options in the interpreter.  Syntax is exactly the same as the
+-- ghc command line, except that certain options aren't available (-C,
+-- -E etc.)
+--
+-- This is pretty fragile: most options won't work as expected.  ToDo:
+-- figure out which ones & disallow them.
+
+setOptions :: String -> GHCi ()
+setOptions ""
+  = do st <- getGHCiState
+       let opts = options st
+       io $ putStrLn (showSDoc (
+             text "options currently set: " <> 
+             if null opts
+                  then text "none."
+                  else hsep (map (\o -> char '+' <> text (optToStr o)) opts)
+          ))
+setOptions str
+  = do -- first, deal with the GHCi opts (+s, +t, etc.)
+       let opts = words str
+          (minus_opts, rest1) = partition isMinus opts
+          (plus_opts, rest2)  = partition isPlus rest1
+
+       if (not (null rest2)) 
+         then io (putStrLn ("unknown option: `" ++ head rest2 ++ "'"))
+         else do
+
+       mapM setOpt plus_opts
+
+       -- now, the GHC flags
+       io (do leftovers <- processArgs static_flags minus_opts []
+             dyn_flags <- readIORef v_InitDynFlags
+             writeIORef v_DynFlags dyn_flags
+             leftovers <- processArgs dynamic_flags leftovers []
+             dyn_flags <- readIORef v_DynFlags
+             writeIORef v_InitDynFlags dyn_flags
+              if (not (null leftovers))
+                then throwDyn (OtherError ("unrecognised flags: " ++ 
+                                               unwords leftovers))
+                else return ()
+         )
+
+unsetOptions :: String -> GHCi ()
+unsetOptions str
+  = do -- first, deal with the GHCi opts (+s, +t, etc.)
+       let opts = words str
+          (minus_opts, rest1) = partition isMinus opts
+          (plus_opts, rest2)  = partition isPlus rest1
+
+       if (not (null rest2)) 
+         then io (putStrLn ("unknown option: `" ++ head rest2 ++ "'"))
+         else do
+
+       mapM unsetOpt plus_opts
+       -- can't do GHC flags for now
+       if (not (null minus_opts))
+         then throwDyn (OtherError "can't unset GHC command-line flags")
+         else return ()
+
+isMinus ('-':s) = True
+isMinus _ = False
+
+isPlus ('+':s) = True
+isPlus _ = False
+
+setOpt ('+':str)
+  = case strToGHCiOpt str of
+       Nothing -> io (putStrLn ("unknown option: `" ++ str ++ "'"))
+       Just o  -> setOption o
+
+unsetOpt ('+':str)
+  = case strToGHCiOpt str of
+       Nothing -> io (putStrLn ("unknown option: `" ++ str ++ "'"))
+       Just o  -> unsetOption o
+
+strToGHCiOpt :: String -> (Maybe GHCiOption)
+strToGHCiOpt "s" = Just ShowTiming
+strToGHCiOpt "t" = Just ShowType
+strToGHCiOpt _   = Nothing
+
+optToStr :: GHCiOption -> String
+optToStr ShowTiming = "s"
+optToStr ShowType   = "t"
 
 -----------------------------------------------------------------------------
 -- GHCi monad
@@ -257,9 +380,12 @@ data GHCiState = GHCiState
        modules        :: [ModuleName],
        current_module :: ModuleName,
        target         :: Maybe FilePath,
-       cmstate        :: CmState
+       cmstate        :: CmState,
+       options        :: [GHCiOption]
      }
 
+data GHCiOption = ShowTiming | ShowType deriving Eq
+
 defaultCurrentModule = mkModuleName "Prelude"
 
 newtype GHCi a = GHCi { unGHCi :: GHCiState -> IO (GHCiState, a) }
@@ -271,6 +397,21 @@ instance Monad GHCi where
 getGHCiState   = GHCi $ \s -> return (s,s)
 setGHCiState s = GHCi $ \_ -> return (s,())
 
+isOptionSet :: GHCiOption -> GHCi Bool
+isOptionSet opt
+ = do st <- getGHCiState
+      return (opt `elem` options st)
+
+setOption :: GHCiOption -> GHCi ()
+setOption opt
+ = do st <- getGHCiState
+      setGHCiState (st{ options = opt : filter (/= opt) (options st) })
+
+unsetOption :: GHCiOption -> GHCi ()
+unsetOption opt
+ = do st <- getGHCiState
+      setGHCiState (st{ options = filter (/= opt) (options st) })
+
 io m = GHCi $ \s -> m >>= \a -> return (s,a)
 
 ghciHandle h (GHCi m) = GHCi $ \s -> 
@@ -305,3 +446,29 @@ findFile (d:ds) obj = do
   let path = d ++ '/':obj
   b <- doesFileExist path
   if b then return path else findFile ds obj
+
+-----------------------------------------------------------------------------
+-- timing & statistics
+
+timeIt :: GHCi a -> GHCi a
+timeIt action
+  = do b <- isOptionSet ShowTiming
+       if not b 
+         then action 
+         else do allocs1 <- io $ getAllocations
+                 time1   <- io $ getCPUTime
+                 a <- action
+                 allocs2 <- io $ getAllocations
+                 time2   <- io $ getCPUTime
+                 io $ printTimes (allocs2 - allocs1) (time2 - time1)
+                 return a
+
+foreign import "getAllocations" getAllocations :: IO Int
+
+printTimes :: Int -> Integer -> IO ()
+printTimes allocs psecs
+   = do let secs = (fromIntegral psecs / (10^12)) :: Float
+           secs_str = showFFloat (Just 2) secs
+       putStrLn (showSDoc (
+                parens (text (secs_str "") <+> text "secs" <> comma <+> 
+                        int allocs <+> text "bytes")))