X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fghci%2FGhciMonad.hs;h=d38046340af4d6108e3b04353649fce5dbc9bf9d;hb=3ee0e7596f55ebbe5eb99e2ba49dc4e2d7414262;hp=d56a581d04f9e960c6d5ab2e7a65cc0d3ca77ab8;hpb=38e7ac3ffa32d75c1922e7247a910e06d9957116;p=ghc-hetmet.git diff --git a/compiler/ghci/GhciMonad.hs b/compiler/ghci/GhciMonad.hs index d56a581..d380463 100644 --- a/compiler/ghci/GhciMonad.hs +++ b/compiler/ghci/GhciMonad.hs @@ -11,8 +11,9 @@ module GhciMonad where #include "HsVersions.h" import qualified GHC -import Outputable -import Panic hiding (showException) +import Outputable hiding (printForUser) +import qualified Outputable +import Panic hiding (showException) import Util import DynFlags import HscTypes @@ -20,7 +21,6 @@ import SrcLoc import Module import Numeric -import Control.Concurrent import Control.Exception as Exception import Data.Array import Data.Char @@ -42,11 +42,12 @@ data GHCiState = GHCiState args :: [String], prompt :: String, editor :: String, + stop :: String, session :: GHC.Session, options :: [GHCiOption], prelude :: GHC.Module, - resume :: [(SrcSpan, ThreadId, GHC.ResumeHandle)], - breaks :: !ActiveBreakPoints, + 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 @@ -61,19 +62,6 @@ data GHCiOption | RevertCAFs -- revert CAFs after every evaluation deriving Eq -data ActiveBreakPoints - = ActiveBreakPoints - { breakCounter :: !Int - , breakLocations :: ![(Int, BreakLocation)] -- break location uniquely numbered - } - -instance Outputable ActiveBreakPoints where - ppr activeBrks = prettyLocations $ breakLocations activeBrks - -emptyActiveBreakPoints :: ActiveBreakPoints -emptyActiveBreakPoints - = ActiveBreakPoints { breakCounter = 0, breakLocations = [] } - data BreakLocation = BreakLocation { breakModule :: !GHC.Module @@ -89,43 +77,19 @@ prettyLocations locs = vcat $ map (\(i, loc) -> brackets (int i) <+> ppr loc) $ instance Outputable BreakLocation where ppr loc = (ppr $ breakModule loc) <+> ppr (breakLoc loc) -getActiveBreakPoints :: GHCi ActiveBreakPoints -getActiveBreakPoints = liftM breaks getGHCiState - --- don't reset the counter back to zero? -discardActiveBreakPoints :: GHCi () -discardActiveBreakPoints = do - st <- getGHCiState - let oldActiveBreaks = breaks st - newActiveBreaks = oldActiveBreaks { breakLocations = [] } - setGHCiState $ st { breaks = newActiveBreaks } - -deleteBreak :: Int -> GHCi () -deleteBreak identity = do - st <- getGHCiState - let oldActiveBreaks = breaks st - oldLocations = breakLocations oldActiveBreaks - newLocations = filter (\loc -> fst loc /= identity) oldLocations - newActiveBreaks = oldActiveBreaks { breakLocations = newLocations } - setGHCiState $ st { breaks = newActiveBreaks } - recordBreak :: BreakLocation -> GHCi (Bool{- was already present -}, Int) recordBreak brkLoc = do st <- getGHCiState let oldActiveBreaks = breaks st - let oldLocations = breakLocations oldActiveBreaks -- don't store the same break point twice - case [ nm | (nm, loc) <- oldLocations, loc == brkLoc ] of + case [ nm | (nm, loc) <- oldActiveBreaks, loc == brkLoc ] of (nm:_) -> return (True, nm) [] -> do - let oldCounter = breakCounter oldActiveBreaks + let oldCounter = break_ctr st newCounter = oldCounter + 1 - newActiveBreaks = - oldActiveBreaks - { breakCounter = newCounter - , breakLocations = (oldCounter, brkLoc) : oldLocations - } - setGHCiState $ st { breaks = newActiveBreaks } + setGHCiState $ st { break_ctr = newCounter, + breaks = (oldCounter, brkLoc) : oldActiveBreaks + } return (False, oldCounter) newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> IO a } @@ -179,29 +143,11 @@ unsetOption opt io :: IO a -> GHCi a io m = GHCi { unGHCi = \s -> m >>= return } -popResume :: GHCi (Maybe (SrcSpan, ThreadId, GHC.ResumeHandle)) -popResume = do - st <- getGHCiState - case (resume st) of - [] -> return Nothing - (x:xs) -> do setGHCiState $ st { resume = xs } ; return (Just x) - -pushResume :: SrcSpan -> ThreadId -> GHC.ResumeHandle -> GHCi () -pushResume span threadId resumeAction = do - st <- getGHCiState - let oldResume = resume st - setGHCiState $ st { resume = (span, threadId, resumeAction) : oldResume } - -discardResumeContext :: GHCi () -discardResumeContext = do - st <- getGHCiState - setGHCiState st { resume = [] } - -showForUser :: SDoc -> GHCi String -showForUser doc = do +printForUser :: SDoc -> GHCi () +printForUser doc = do session <- getSession unqual <- io (GHC.getPrintUnqual session) - return $! showSDocForUser unqual doc + io $ Outputable.printForUser stdout unqual doc -- -------------------------------------------------------------------------- -- timing & statistics