summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorÖmer Sinan Ağacan <omeragacan@gmail.com>2016-06-17 07:54:28 (GMT)
committerÖmer Sinan Ağacan <omeragacan@gmail.com>2016-06-17 08:31:52 (GMT)
commit930a525a5906fdd65ab0c3e804085d5875517a20 (patch)
tree32e8c25be234f9fd6c2668d94d9bd1a32670af84
parentc56f8bd0cfd44a4a6812b62fc5dca3190d3e749f (diff)
downloadghc-930a525a5906fdd65ab0c3e804085d5875517a20.zip
ghc-930a525a5906fdd65ab0c3e804085d5875517a20.tar.gz
ghc-930a525a5906fdd65ab0c3e804085d5875517a20.tar.bz2
Abort the build when a Core plugin pass is specified in stage1 compiler
This also makes the behavior the same with frontend plugin errors -- frontend was failing with an exception (`CmdLineError`) while the simplifier was just ignoring plugins. Now we abort with `CmdLineError` in both cases with a slightly improved error message. Test Plan: - add tests (will add tests once #12197 is implemented) - validate (done) Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2334 GHC Trac Issues: #11690
-rw-r--r--compiler/main/DynamicLoading.hs23
-rw-r--r--compiler/simplCore/SimplCore.hs8
-rw-r--r--ghc/Main.hs5
3 files changed, 33 insertions, 3 deletions
diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs
index e7a2b95..2b2365f 100644
--- a/compiler/main/DynamicLoading.hs
+++ b/compiler/main/DynamicLoading.hs
@@ -19,6 +19,8 @@ module DynamicLoading (
getValueSafely,
getHValueSafely,
lessUnsafeCoerce
+#else
+ pluginError,
#endif
) where
@@ -55,6 +57,16 @@ import Hooks
import Data.Maybe ( mapMaybe )
import GHC.Exts ( unsafeCoerce# )
+#else
+
+import Module ( ModuleName, moduleNameString )
+import Panic
+
+import Data.List ( intercalate )
+
+#endif
+
+#ifdef GHCI
loadPlugins :: HscEnv -> IO [(ModuleName, Plugin, [CommandLineOption])]
loadPlugins hsc_env
@@ -243,4 +255,15 @@ throwCmdLineErrorS dflags = throwCmdLineError . showSDoc dflags
throwCmdLineError :: String -> IO a
throwCmdLineError = throwGhcExceptionIO . CmdLineError
+
+#else
+
+pluginError :: [ModuleName] -> a
+pluginError modnames = throwGhcException (CmdLineError msg)
+ where
+ msg = "not built for interactive use - can't load plugins ("
+ -- module names are not z-encoded
+ ++ intercalate ", " (map moduleNameString modnames)
+ ++ ")"
+
#endif
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index 6884696..85ae8cd 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -59,6 +59,8 @@ import qualified GHC.LanguageExtensions as LangExt
#ifdef GHCI
import DynamicLoading ( loadPlugins )
import Plugins ( installCoreToDos )
+#else
+import DynamicLoading ( pluginError )
#endif
{-
@@ -350,7 +352,11 @@ getCoreToDo dflags
addPluginPasses :: [CoreToDo] -> CoreM [CoreToDo]
#ifndef GHCI
-addPluginPasses builtin_passes = return builtin_passes
+addPluginPasses builtin_passes
+ = do { dflags <- getDynFlags
+ ; let pluginMods = pluginModNames dflags
+ ; unless (null pluginMods) (pluginError pluginMods)
+ ; return builtin_passes }
#else
addPluginPasses builtin_passes
= do { hsc_env <- getHscEnv
diff --git a/ghc/Main.hs b/ghc/Main.hs
index 5605438..1a6cbeb 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -32,6 +32,8 @@ import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
#ifdef GHCI
import DynamicLoading
import Plugins
+#else
+import DynamicLoading ( pluginError )
#endif
import Module ( ModuleName )
@@ -841,8 +843,7 @@ dumpPackagesSimple dflags = putMsg dflags (pprPackagesSimple dflags)
doFrontend :: ModuleName -> [(String, Maybe Phase)] -> Ghc ()
#ifndef GHCI
-doFrontend _ _ =
- throwGhcException (CmdLineError "not built for interactive use")
+doFrontend modname _ = pluginError [modname]
#else
doFrontend modname srcs = do
hsc_env <- getSession