diff options
author | David Terei <davidterei@gmail.com> | 2012-01-25 18:17:16 -0800 |
---|---|---|
committer | David Terei <davidterei@gmail.com> | 2012-01-25 18:43:25 -0800 |
commit | a1edfab75b3f0aaa4cf730fae80415339427a2a0 (patch) | |
tree | d67ce4bf8f713748a6c0746672d7c0d9f586ea79 /ghc | |
parent | 0120d0d2ef80c7268deed747bb5888b3a2ef1b39 (diff) | |
download | haskell-a1edfab75b3f0aaa4cf730fae80415339427a2a0.tar.gz |
Improve source code documentation og GHCi main.
Diffstat (limited to 'ghc')
-rw-r--r-- | ghc/GhciMonad.hs | 16 | ||||
-rw-r--r-- | ghc/InteractiveUI.hs | 25 |
2 files changed, 37 insertions, 4 deletions
diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index be9a9f6b2f..263871b772 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -9,7 +9,20 @@ -- ----------------------------------------------------------------------------- -module GhciMonad where +module GhciMonad ( + GHCi(..), startGHCi, + GHCiState(..), setGHCiState, getGHCiState, modifyGHCiState, + GHCiOption(..), isOptionSet, setOption, unsetOption, + Command, + BreakLocation(..), + TickArray, + setDynFlags, + + runStmt, runDecls, resume, timeIt, recordBreak, revertCAFs, + + printForUser, printForUserPartWay, prettyLocations, + initInterpBuffering, turnOffBuffering, flushInterpBuffers + ) where #include "HsVersions.h" @@ -249,6 +262,7 @@ printForUserPartWay doc = do unqual <- GHC.getPrintUnqual liftIO $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc +-- | Run a single Haskell expression runStmt :: String -> GHC.SingleStep -> GHCi (Maybe GHC.RunResult) runStmt expr step = do st <- getGHCiState diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 1836087577..23eaa022ec 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -487,6 +487,7 @@ runGHCiInput f = do (setComplete ghciCompleteWord $ defaultSettings {historyFile = histFile}) f +-- | How to get the next input line from the user nextInputLine :: Bool -> Bool -> InputT GHCi (Maybe String) nextInputLine show_prompt is_tty | is_tty = do @@ -601,6 +602,7 @@ queryQueue = do c:cs -> do setGHCiState st{ cmdqueue = cs } return (Just c) +-- | The main read-eval-print loop runCommands :: InputT GHCi (Maybe String) -> InputT GHCi () runCommands = runCommands' handler @@ -620,9 +622,12 @@ runCommands' eh gCmd = do Nothing -> return () Just _ -> runCommands' eh gCmd +-- | Evaluate a single line of user input (either :<command> or Haskell code) runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String) -> InputT GHCi (Maybe Bool) runOneCommand eh gCmd = do + -- run a previously queued command if there is one, otherwise get new + -- input from user mb_cmd0 <- noSpace (lift queryQueue) mb_cmd1 <- maybe (noSpace gCmd) (return . Just) mb_cmd0 case mb_cmd1 of @@ -666,12 +671,19 @@ runOneCommand eh gCmd = do normSpace x = x -- SDM (2007-11-07): is userError the one to use here? collectError = userError "unterminated multiline command :{ .. :}" + + -- | Handle a line of input + doCommand :: String -> InputT GHCi (Maybe Bool) + + -- command doCommand (':' : cmd) = do result <- specialCommand cmd case result of True -> return Nothing _ -> return $ Just True - doCommand stmt = do + + -- haskell + doCommand stmt = do ml <- lift $ isOptionSet Multiline if ml then do @@ -736,16 +748,23 @@ declPrefixes :: [String] declPrefixes = ["class ","data ","newtype ","type ","instance ", "deriving ", "foreign "] +-- | Entry point to execute some haskell code from user runStmt :: String -> SingleStep -> GHCi Bool runStmt stmt step + -- empty | null (filter (not.isSpace) stmt) = return False + + -- import | "import " `isPrefixOf` stmt = do addImportToContext stmt; return False + + -- data, class, newtype... | any (flip isPrefixOf stmt) declPrefixes = do _ <- liftIO $ tryIO $ hFlushAll stdin result <- GhciMonad.runDecls stmt afterRunStmt (const True) (GHC.RunOk result) + | otherwise = do -- In the new IO library, read handles buffer data even if the Handle -- is set to NoBuffering. This causes problems for GHCi where there @@ -758,8 +777,7 @@ runStmt stmt step Nothing -> return False Just result -> afterRunStmt (const True) result ---afterRunStmt :: GHC.RunResult -> GHCi Bool - -- False <=> the statement failed to compile +-- | Clean up the GHCi environment after a statement has run afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool afterRunStmt _ (GHC.RunException e) = throw e afterRunStmt step_here run_result = do @@ -830,6 +848,7 @@ printTypeOfName n data MaybeCommand = GotCommand Command | BadCommand | NoLastCommand +-- | Entry point for execution a ':<command>' input from user specialCommand :: String -> InputT GHCi Bool specialCommand ('!':str) = lift $ shellEscape (dropWhile isSpace str) specialCommand str = do |