X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fghci%2FGhciMonad.hs;h=2c5a0a53a44a38a1f17306ece17c2d7f0adb4a45;hp=eaea844991185f784356e6586e06f50671d4228f;hb=c148796dad1a36849a62ad8f3838b428e65c9310;hpb=075a7bad2ab4e8360badfa2d0ae25c4d8eaf61f6 diff --git a/compiler/ghci/GhciMonad.hs b/compiler/ghci/GhciMonad.hs index eaea844..2c5a0a5 100644 --- a/compiler/ghci/GhciMonad.hs +++ b/compiler/ghci/GhciMonad.hs @@ -11,22 +11,30 @@ module GhciMonad where #include "HsVersions.h" import qualified GHC -import {-#SOURCE#-} Debugger -import Breakpoints -import Outputable -import Panic hiding (showException) +import Outputable hiding (printForUser, printForUserPartWay) +import qualified Outputable +import Panic hiding (showException) import Util import DynFlags - +import HscTypes +import SrcLoc +import Module +import ObjLink +import Linker +import StaticFlags + +import Data.Maybe import Numeric import Control.Exception as Exception +import Data.Array import Data.Char -import Data.Dynamic import Data.Int ( Int64 ) import Data.IORef import Data.List import Data.Typeable import System.CPUTime +import System.Directory +import System.Environment import System.IO import Control.Monad as Monad import GHC.Exts @@ -34,25 +42,89 @@ import GHC.Exts ----------------------------------------------------------------------------- -- GHCi monad +type Command = (String, String -> GHCi Bool, Maybe String, String -> IO [String]) + data GHCiState = GHCiState { progname :: String, args :: [String], prompt :: String, editor :: String, + stop :: String, session :: GHC.Session, options :: [GHCiOption], prelude :: GHC.Module, - bkptTable :: IORef (BkptTable GHC.Module), - topLevel :: Bool + break_ctr :: !Int, + breaks :: ![(Int, BreakLocation)], + tickarrays :: ModuleEnv TickArray, + -- tickarrays caches the TickArray for loaded modules, + -- so that we don't rebuild it each time the user sets + -- a breakpoint. + -- ":" at the GHCi prompt repeats the last command, so we + -- remember is here: + last_command :: Maybe Command, + cmdqueue :: [String], + remembered_ctx :: [(CtxtCmd, [String], [String])], + -- we remember the :module commands between :loads, so that + -- on a :reload we can replay them. See bugs #2049, + -- #1873, #1360. Previously we tried to remember modules that + -- were supposed to be in the context but currently had errors, + -- but this was complicated. Just replaying the :module commands + -- seems to be the right thing. + virtual_path :: FilePath, + ghc_e :: Bool -- True if this is 'ghc -e' (or runghc) } +data CtxtCmd + = SetContext + | AddModules + | RemModules + +type TickArray = Array Int [(BreakIndex,SrcSpan)] + data GHCiOption = ShowTiming -- show time/allocs after evaluation | ShowType -- show the type of expressions | RevertCAFs -- revert CAFs after every evaluation deriving Eq +data BreakLocation + = BreakLocation + { breakModule :: !GHC.Module + , breakLoc :: !SrcSpan + , breakTick :: {-# UNPACK #-} !Int + , onBreakCmd :: String + } + +instance Eq BreakLocation where + loc1 == loc2 = breakModule loc1 == breakModule loc2 && + breakTick loc1 == breakTick loc2 + +prettyLocations :: [(Int, BreakLocation)] -> SDoc +prettyLocations [] = text "No active breakpoints." +prettyLocations locs = vcat $ map (\(i, loc) -> brackets (int i) <+> ppr loc) $ reverse $ locs + +instance Outputable BreakLocation where + ppr loc = (ppr $ breakModule loc) <+> ppr (breakLoc loc) <+> + if null (onBreakCmd loc) + then empty + else doubleQuotes (text (onBreakCmd loc)) + +recordBreak :: BreakLocation -> GHCi (Bool{- was already present -}, Int) +recordBreak brkLoc = do + st <- getGHCiState + let oldActiveBreaks = breaks st + -- don't store the same break point twice + case [ nm | (nm, loc) <- oldActiveBreaks, loc == brkLoc ] of + (nm:_) -> return (True, nm) + [] -> do + let oldCounter = break_ctr st + newCounter = oldCounter + 1 + setGHCiState $ st { break_ctr = newCounter, + breaks = (oldCounter, brkLoc) : oldActiveBreaks + } + return (False, oldCounter) + newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> IO a } startGHCi :: GHCi a -> GHCiState -> IO a @@ -60,28 +132,45 @@ startGHCi g state = do ref <- newIORef state; unGHCi g ref instance Monad GHCi where (GHCi m) >>= k = GHCi $ \s -> m s >>= \a -> unGHCi (k a) s - return a = GHCi $ \s -> return a + return a = GHCi $ \_ -> return a + +instance Functor GHCi where + fmap f m = m >>= return . f ghciHandleDyn :: Typeable t => (t -> GHCi a) -> GHCi a -> GHCi a ghciHandleDyn h (GHCi m) = GHCi $ \s -> Exception.catchDyn (m s) (\e -> unGHCi (h e) s) +getGHCiState :: GHCi GHCiState getGHCiState = GHCi $ \r -> readIORef r +setGHCiState :: GHCiState -> GHCi () setGHCiState s = GHCi $ \r -> writeIORef r s -- for convenience... +getSession :: GHCi Session getSession = getGHCiState >>= return . session +getPrelude :: GHCi Module getPrelude = getGHCiState >>= return . prelude GLOBAL_VAR(saved_sess, no_saved_sess, GHC.Session) + +no_saved_sess :: Session no_saved_sess = error "no saved_ses" + +saveSession :: GHCi () saveSession = getSession >>= io . writeIORef saved_sess + +splatSavedSession :: GHCi () splatSavedSession = io (writeIORef saved_sess no_saved_sess) + +restoreSession :: IO Session restoreSession = readIORef saved_sess +getDynFlags :: GHCi DynFlags getDynFlags = do s <- getSession io (GHC.getSessionDynFlags s) +setDynFlags :: DynFlags -> GHCi [PackageId] setDynFlags dflags = do s <- getSession io (GHC.setSessionDynFlags s dflags) @@ -102,41 +191,42 @@ unsetOption opt setGHCiState (st{ options = filter (/= opt) (options st) }) io :: IO a -> GHCi a -io m = GHCi { unGHCi = \s -> m >>= return } - -isTopLevel :: GHCi Bool -isTopLevel = getGHCiState >>= return . topLevel - -getBkptTable :: GHCi (BkptTable GHC.Module) -getBkptTable = do table_ref <- getGHCiState >>= return . bkptTable - io$ readIORef table_ref - -setBkptTable :: BkptTable GHC.Module -> GHCi () -setBkptTable new_table = do - table_ref <- getGHCiState >>= return . bkptTable - io$ writeIORef table_ref new_table - -modifyBkptTable :: (BkptTable GHC.Module -> BkptTable GHC.Module) -> GHCi () -modifyBkptTable f = do - bt <- getBkptTable - new_bt <- io . evaluate$ f bt - setBkptTable new_bt - -showForUser :: SDoc -> GHCi String -showForUser doc = do +io m = GHCi (\_ -> m) + +printForUser :: SDoc -> GHCi () +printForUser doc = do session <- getSession unqual <- io (GHC.getPrintUnqual session) - return $! showSDocForUser unqual doc + io $ Outputable.printForUser stdout unqual doc --- -------------------------------------------------------------------------- --- Inferior Sessions Exceptions (used by the debugger) +printForUserPartWay :: SDoc -> GHCi () +printForUserPartWay doc = do + session <- getSession + unqual <- io (GHC.getPrintUnqual session) + io $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc + +withVirtualPath :: GHCi a -> GHCi a +withVirtualPath m = do + ghci_wd <- io getCurrentDirectory -- Store the cwd of GHCi + st <- getGHCiState + io$ setCurrentDirectory (virtual_path st) + result <- m -- Evaluate in the virtual wd.. + vwd <- io getCurrentDirectory + setGHCiState (st{ virtual_path = vwd}) -- Update the virtual path + io$ setCurrentDirectory ghci_wd -- ..and restore GHCi wd + return result + +runStmt :: String -> GHC.SingleStep -> GHCi GHC.RunResult +runStmt expr step = withVirtualPath$ do + session <- getSession + st <- getGHCiState + io$ withProgName (progname st) $ withArgs (args st) $ + GHC.runStmt session expr step -data InfSessionException = - StopChildSession -- A child session requests to be stopped - | StopParentSession -- A child session requests to be stopped - -- AND that the parent session quits after that - | ChildSessionStopped String -- A child session has stopped - deriving Typeable +resume :: GHC.SingleStep -> GHCi GHC.RunResult +resume step = withVirtualPath$ do + session <- getSession + io$ GHC.resume session step -- -------------------------------------------------------------------------- @@ -170,10 +260,11 @@ printTimes allocs psecs ----------------------------------------------------------------------------- -- reverting CAFs -revertCAFs :: IO () +revertCAFs :: GHCi () revertCAFs = do - rts_revertCAFs - turnOffBuffering + io $ rts_revertCAFs + s <- getGHCiState + when (not (ghc_e s)) $ io turnOffBuffering -- Have to turn off buffering again, because we just -- reverted stdout, stderr & stdin to their defaults. @@ -184,56 +275,54 @@ foreign import ccall "revertCAFs" rts_revertCAFs :: IO () -- To flush buffers for the *interpreted* computation we need -- to refer to *its* stdout/stderr handles -GLOBAL_VAR(flush_interp, error "no flush_interp", IO ()) -GLOBAL_VAR(turn_off_buffering, error "no flush_stdout", IO ()) - -command_sequence :: [String] -> String -command_sequence = unwords . intersperse "Prelude.>>" - -no_buffer :: String -> String -no_buffer h = unwords ["System.IO.hSetBuffering", - "System.IO." ++ h, - "System.IO.NoBuffering"] +GLOBAL_VAR(stdin_ptr, error "no stdin_ptr", Ptr ()) +GLOBAL_VAR(stdout_ptr, error "no stdout_ptr", Ptr ()) +GLOBAL_VAR(stderr_ptr, error "no stderr_ptr", Ptr ()) -no_buf_cmd :: String -no_buf_cmd = command_sequence $ map no_buffer ["stdout", "stderr", "stdin"] - -flush_buffer :: String -> String -flush_buffer h = unwords ["System.IO.hFlush", "System.IO." ++ h] - -flush_cmd :: String -flush_cmd = command_sequence [flush_buffer "stdout", flush_buffer "stderr"] +-- After various attempts, I believe this is the least bad way to do +-- what we want. We know look up the address of the static stdin, +-- stdout, and stderr closures in the loaded base package, and each +-- time we need to refer to them we cast the pointer to a Handle. +-- This avoids any problems with the CAF having been reverted, because +-- we'll always get the current value. +-- +-- The previous attempt that didn't work was to compile an expression +-- like "hSetBuffering stdout NoBuffering" into an expression of type +-- IO () and run this expression each time we needed it, but the +-- problem is that evaluating the expression might cache the contents +-- of the Handle rather than referring to it from its static address +-- each time. There's no safe workaround for this. initInterpBuffering :: GHC.Session -> IO () initInterpBuffering session - = do -- we don't want to be fooled by any modules lying around in the current - -- directory when we compile these code fragments, so set the import - -- path to be empty while we compile them. + = do -- make sure these are linked dflags <- GHC.getSessionDynFlags session - GHC.setSessionDynFlags session dflags{importPaths=[]} - - maybe_hval <- GHC.compileExpr session no_buf_cmd - - case maybe_hval of - Just hval -> writeIORef turn_off_buffering (unsafeCoerce# hval :: IO ()) - other -> panic "interactiveUI:setBuffering" - - maybe_hval <- GHC.compileExpr session flush_cmd - case maybe_hval of - Just hval -> writeIORef flush_interp (unsafeCoerce# hval :: IO ()) - _ -> panic "interactiveUI:flush" - - GHC.setSessionDynFlags session dflags - GHC.workingDirectoryChanged session + initDynLinker dflags + + -- ToDo: we should really look up these names properly, but + -- it's a fiddle and not all the bits are exposed via the GHC + -- interface. + mb_stdin_ptr <- ObjLink.lookupSymbol "base_GHCziHandle_stdin_closure" + mb_stdout_ptr <- ObjLink.lookupSymbol "base_GHCziHandle_stdout_closure" + mb_stderr_ptr <- ObjLink.lookupSymbol "base_GHCziHandle_stderr_closure" + + let f ref (Just ptr) = writeIORef ref ptr + f _ Nothing = panic "interactiveUI:setBuffering2" + zipWithM f [stdin_ptr,stdout_ptr,stderr_ptr] + [mb_stdin_ptr,mb_stdout_ptr,mb_stderr_ptr] return () - flushInterpBuffers :: GHCi () flushInterpBuffers - = io $ do Monad.join (readIORef flush_interp) - return () + = io $ do getHandle stdout_ptr >>= hFlush + getHandle stderr_ptr >>= hFlush turnOffBuffering :: IO () turnOffBuffering - = do Monad.join (readIORef turn_off_buffering) - return () + = do hdls <- mapM getHandle [stdin_ptr,stdout_ptr,stderr_ptr] + mapM_ (\h -> hSetBuffering h NoBuffering) hdls + +getHandle :: IORef (Ptr ()) -> IO Handle +getHandle ref = do + (Ptr addr) <- readIORef ref + case addrToHValue# addr of (# hval #) -> return (unsafeCoerce# hval)