summaryrefslogtreecommitdiff
path: root/ghc/InteractiveUI.hs
diff options
context:
space:
mode:
authorRoman Shatsov <roshats@gmail.com>2015-12-07 11:24:36 +0100
committerBen Gamari <ben@smart-cactus.org>2015-12-07 12:15:03 +0100
commit2110037e270c5ea36de63e4d95a3175751338571 (patch)
tree3079e261df8c29491fdb6a7049d5a3d1d4316642 /ghc/InteractiveUI.hs
parent91e985cd99e9f628e7cd01fc5dd0e6f596337446 (diff)
downloadhaskell-2110037e270c5ea36de63e4d95a3175751338571.tar.gz
Add isImport, isDecl, and isStmt functions to GHC API
Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1518 GHC Trac Issues: #9015
Diffstat (limited to 'ghc/InteractiveUI.hs')
-rw-r--r--ghc/InteractiveUI.hs33
1 files changed, 11 insertions, 22 deletions
diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs
index 772b39b9bc..f7b3603b6a 100644
--- a/ghc/InteractiveUI.hs
+++ b/ghc/InteractiveUI.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE CPP, MagicHash, NondecreasingIndentation, TupleSections,
- RecordWildCards #-}
+ RecordWildCards, MultiWayIf #-}
{-# OPTIONS -fno-cse #-}
-- -fno-cse is needed for GLOBAL_VAR's to behave properly
@@ -900,23 +900,17 @@ enqueueCommands cmds = do
-- | Entry point to execute some haskell code from user.
-- The return value True indicates success, as in `runOneCommand`.
runStmt :: String -> SingleStep -> GHCi (Maybe GHC.ExecResult)
-runStmt stmt step
- -- empty; this should be impossible anyways since we filtered out
- -- whitespace-only input in runOneCommand's noSpace
- | null (filter (not.isSpace) stmt)
- = return Nothing
-
- -- import
- | stmt `looks_like` "import "
- = do addImportToContext stmt; return (Just (GHC.ExecComplete (Right []) 0))
-
- | otherwise
- = do
- parse_res <- GhciMonad.isStmt stmt
- if parse_res
- then run_stmt
- else run_decl
+runStmt stmt step = do
+ dflags <- GHC.getInteractiveDynFlags
+ if | GHC.isStmt dflags stmt -> run_stmt
+ | GHC.isImport dflags stmt -> run_imports
+ | otherwise -> run_decl
+
where
+ run_imports = do
+ addImportToContext stmt
+ return (Just (GHC.ExecComplete (Right []) 0))
+
run_decl =
do _ <- liftIO $ tryIO $ hFlushAll stdin
m_result <- GhciMonad.runDecls stmt
@@ -938,11 +932,6 @@ runStmt stmt step
Nothing -> return Nothing
Just result -> Just <$> afterRunStmt (const True) result
- s `looks_like` prefix = prefix `isPrefixOf` dropWhile isSpace s
- -- Ignore leading spaces (see Trac #9914), so that
- -- ghci> data T = T
- -- (note leading spaces) works properly
-
-- | Clean up the GHCi environment after a statement has run
afterRunStmt :: (SrcSpan -> Bool) -> GHC.ExecResult -> GHCi GHC.ExecResult
afterRunStmt step_here run_result = do