summaryrefslogtreecommitdiff
path: root/ghc/InteractiveUI.hs
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2011-02-27 17:20:12 +0000
committerIan Lynagh <igloo@earth.li>2011-02-27 17:20:12 +0000
commit3da491217855adfe4eeace6493c9a625e23965ea (patch)
treeee7acc2eed00db983fde6f98e93a7ab6ba3c2bb4 /ghc/InteractiveUI.hs
parenteccb2d89eb4b34f31e8ea337d5f8673605f71665 (diff)
downloadhaskell-3da491217855adfe4eeace6493c9a625e23965ea.tar.gz
Improve GHCi line numbers in errors
When running commands from the user (as opposed to from a file), reset the line number to 1 at the start of each command.
Diffstat (limited to 'ghc/InteractiveUI.hs')
-rw-r--r--ghc/InteractiveUI.hs15
1 files changed, 9 insertions, 6 deletions
diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs
index 534709fa59..306213302d 100644
--- a/ghc/InteractiveUI.hs
+++ b/ghc/InteractiveUI.hs
@@ -417,7 +417,7 @@ runGHCi paths maybe_exprs = do
-- This would be a good place for runFileInputT.
Right hdl ->
do runInputTWithPrefs defaultPrefs defaultSettings $
- runCommands $ fileLoop hdl
+ runCommands False $ fileLoop hdl
liftIO (hClose hdl `catchIO` \_ -> return ())
where
getDirectory f = case takeDirectory f of "" -> "."; d -> d
@@ -452,7 +452,7 @@ runGHCi paths maybe_exprs = do
Nothing ->
do
-- enter the interactive loop
- runGHCiInput $ runCommands $ nextInputLine show_prompt is_tty
+ runGHCiInput $ runCommands True $ nextInputLine show_prompt is_tty
Just exprs -> do
-- just evaluate the expression we were given
enqueueCommands exprs
@@ -466,7 +466,7 @@ runGHCi paths maybe_exprs = do
-- this used to be topHandlerFastExit, see #2228
$ topHandler e
runInputTWithPrefs defaultPrefs defaultSettings $ do
- runCommands' handle (return Nothing)
+ runCommands' handle True (return Nothing)
-- and finally, exit
liftIO $ when (verbosity dflags > 0) $ putStrLn "Leaving GHCi."
@@ -591,12 +591,15 @@ queryQueue = do
c:cs -> do setGHCiState st{ cmdqueue = cs }
return (Just c)
-runCommands :: InputT GHCi (Maybe String) -> InputT GHCi ()
+runCommands :: Bool -> InputT GHCi (Maybe String) -> InputT GHCi ()
runCommands = runCommands' handler
runCommands' :: (SomeException -> GHCi Bool) -- Exception handler
+ -> Bool
-> InputT GHCi (Maybe String) -> InputT GHCi ()
-runCommands' eh getCmd = do
+runCommands' eh resetLineTo1 getCmd = do
+ when resetLineTo1 $ lift $ do st <- getGHCiState
+ setGHCiState $ st { line_number = 0 }
b <- ghandle (\e -> case fromException e of
Just UserInterrupt -> return $ Just False
_ -> case fromException e of
@@ -608,7 +611,7 @@ runCommands' eh getCmd = do
(runOneCommand eh getCmd)
case b of
Nothing -> return ()
- Just _ -> runCommands' eh getCmd
+ Just _ -> runCommands' eh resetLineTo1 getCmd
runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String)
-> InputT GHCi (Maybe Bool)