summaryrefslogtreecommitdiff
path: root/ghc/GHCi/UI
diff options
context:
space:
mode:
authorÖmer Sinan Ağacan <omeragacan@gmail.com>2019-01-09 18:44:48 +0300
committerÖmer Sinan Ağacan <omeragacan@gmail.com>2019-01-13 00:17:20 -0500
commita34ee61545930d569d0dbafb3a4a5db3a7a711e5 (patch)
tree940ad55163a9c12a97b15a529d7a2c57a8efef7a /ghc/GHCi/UI
parent448f0e7dd78a8d9404f1aa5e8522cc284360c06d (diff)
downloadhaskell-a34ee61545930d569d0dbafb3a4a5db3a7a711e5.tar.gz
Refactor GHCi UI to fix #11606, #12091, #15721, #16096
Instead of parsing and executing a statement or declaration directly we now parse them first and then execute in a separate step. This gives us the flexibility to inspect the parsed declaration before execution. Using this we now inspect parsed declarations, and if it's a single declaration of form `x = y` we execute it as `let x = y` instead, fixing a ton of problems caused by poor declaration support in GHCi. To avoid any users of the modules I left `execStmt` and `runDecls` unchanged and added `execStmt'` and `runDecls'` which work on parsed statements/declarations.
Diffstat (limited to 'ghc/GHCi/UI')
-rw-r--r--ghc/GHCi/UI/Monad.hs22
1 files changed, 17 insertions, 5 deletions
diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs
index 969111b214..cbf527e623 100644
--- a/ghc/GHCi/UI/Monad.hs
+++ b/ghc/GHCi/UI/Monad.hs
@@ -20,7 +20,7 @@ module GHCi.UI.Monad (
TickArray,
getDynFlags,
- runStmt, runDecls, resume, timeIt, recordBreak, revertCAFs,
+ runStmt, runDecls, runDecls', resume, timeIt, recordBreak, revertCAFs,
printForUserNeverQualify, printForUserModInfo,
printForUser, printForUserPartWay, prettyLocations,
@@ -46,7 +46,7 @@ import SrcLoc
import Module
import GHCi
import GHCi.RemoteTypes
-import HsSyn (ImportDecl, GhcPs)
+import HsSyn (ImportDecl, GhcPs, GhciLStmt, LHsDecl)
import Util
import Exception
@@ -338,8 +338,8 @@ printForUserPartWay doc = do
liftIO $ Outputable.printForUserPartWay dflags stdout (pprUserLength dflags) unqual doc
-- | Run a single Haskell expression
-runStmt :: String -> GHC.SingleStep -> GHCi (Maybe GHC.ExecResult)
-runStmt expr step = do
+runStmt :: GhciLStmt GhcPs -> String -> GHC.SingleStep -> GHCi (Maybe GHC.ExecResult)
+runStmt stmt stmt_text step = do
st <- getGHCiState
GHC.handleSourceError (\e -> do GHC.printException e; return Nothing) $ do
let opts = GHC.execOptions
@@ -348,7 +348,7 @@ runStmt expr step = do
, GHC.execSingleStep = step
, GHC.execWrap = \fhv -> EvalApp (EvalThis (evalWrapper st))
(EvalThis fhv) }
- Just <$> GHC.execStmt expr opts
+ Just <$> GHC.execStmt' stmt stmt_text opts
runDecls :: String -> GHCi (Maybe [GHC.Name])
runDecls decls = do
@@ -362,6 +362,18 @@ runDecls decls = do
r <- GHC.runDeclsWithLocation (progname st) (line_number st) decls
return (Just r)
+runDecls' :: [LHsDecl GhcPs] -> GHCi (Maybe [GHC.Name])
+runDecls' decls = do
+ st <- getGHCiState
+ reifyGHCi $ \x ->
+ withProgName (progname st) $
+ withArgs (args st) $
+ reflectGHCi x $
+ GHC.handleSourceError
+ (\e -> do GHC.printException e;
+ return Nothing)
+ (Just <$> GHC.runParsedDecls decls)
+
resume :: (SrcSpan -> Bool) -> GHC.SingleStep -> GHCi GHC.ExecResult
resume canLogSpan step = do
st <- getGHCiState