summaryrefslogtreecommitdiff
path: root/ghc/Main.hs
diff options
context:
space:
mode:
authorJohn Ericson <John.Ericson@Obsidian.Systems>2019-07-11 18:42:35 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-10-04 21:45:49 -0400
commit0dded5ecd2f02e13292818ae3729d32832c014f3 (patch)
treead5d985078d94e8bdc4ad5d65be2d052e6dd42c2 /ghc/Main.hs
parenteb892b28b92351358dd7cb0ee6b0b1a1d7fcc98e (diff)
downloadhaskell-0dded5ecd2f02e13292818ae3729d32832c014f3.tar.gz
Always enable the external interpreter
You can always just not use or even build `iserv`. I don't think the maintenance cost of the CPP is worth...I can't even tell what the benefit is.
Diffstat (limited to 'ghc/Main.hs')
-rw-r--r--ghc/Main.hs41
1 files changed, 29 insertions, 12 deletions
diff --git a/ghc/Main.hs b/ghc/Main.hs
index d53c71a779..4cdf3ecb94 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE CPP, NondecreasingIndentation, TupleSections #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NondecreasingIndentation #-}
+{-# LANGUAGE TupleSections #-}
{-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
-----------------------------------------------------------------------------
@@ -30,12 +33,8 @@ import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
#endif
-- Frontend plugins
-#if defined(HAVE_INTERPRETER)
import DynamicLoading ( loadFrontendPlugin )
import Plugins
-#else
-import DynamicLoading ( pluginError )
-#endif
#if defined(HAVE_INTERNAL_INTERPRETER)
import DynamicLoading ( initializePlugins )
#endif
@@ -44,6 +43,8 @@ import Module ( ModuleName )
-- Various other random stuff that we need
import GHC.HandleEncoding
+import GHC.Platform
+import GHC.Platform.Host
import Config
import Constants
import HscTypes
@@ -54,6 +55,8 @@ import DynFlags hiding (WarnReason(..))
import ErrUtils
import FastString
import Outputable
+import SysTools.BaseDir
+import SysTools.Settings
import SrcLoc
import Util
import Panic
@@ -74,6 +77,8 @@ import System.Environment
import System.Exit
import System.FilePath
import Control.Monad
+import Control.Monad.Trans.Class
+import Control.Monad.Trans.Except (throwE, runExceptT)
import Data.Char
import Data.List
import Data.Maybe
@@ -122,7 +127,7 @@ main = do
case mode of
Left preStartupMode ->
do case preStartupMode of
- ShowSupportedExtensions -> showSupportedExtensions
+ ShowSupportedExtensions -> showSupportedExtensions mbMinusB
ShowVersion -> showVersion
ShowNumVersion -> putStrLn cProjectVersion
ShowOptions isInteractive -> showOptions isInteractive
@@ -776,8 +781,24 @@ showInfo dflags = do
let sq x = " [" ++ x ++ "\n ]"
putStrLn $ sq $ intercalate "\n ," $ map show $ compilerInfo dflags
-showSupportedExtensions :: IO ()
-showSupportedExtensions = mapM_ putStrLn supportedLanguagesAndExtensions
+-- TODO use ErrUtils once that is disentangled from all the other GhcMonad stuff?
+showSupportedExtensions :: Maybe String -> IO ()
+showSupportedExtensions m_top_dir = do
+ res <- runExceptT $ do
+ top_dir <- lift (tryFindTopDir m_top_dir) >>= \case
+ Nothing -> throwE $ SettingsError_MissingData "Could not find the top directory, missing -B flag"
+ Just dir -> pure dir
+ initSettings top_dir
+ targetPlatformMini <- case res of
+ Right s -> pure $ platformMini $ sTargetPlatform s
+ Left (SettingsError_MissingData msg) -> do
+ hPutStrLn stderr $ "WARNING: " ++ show msg
+ hPutStrLn stderr $ "cannot know target platform so guessing target == host (native compiler)."
+ pure cHostPlatformMini
+ Left (SettingsError_BadData msg) -> do
+ hPutStrLn stderr msg
+ exitWith $ ExitFailure 1
+ mapM_ putStrLn $ supportedLanguagesAndExtensions targetPlatformMini
showVersion :: IO ()
showVersion = putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
@@ -847,15 +868,11 @@ dumpPackagesSimple dflags = putMsg dflags (pprPackagesSimple dflags)
-- Frontend plugin support
doFrontend :: ModuleName -> [(String, Maybe Phase)] -> Ghc ()
-#if !defined(HAVE_INTERPRETER)
-doFrontend modname _ = pluginError [modname]
-#else
doFrontend modname srcs = do
hsc_env <- getSession
frontend_plugin <- liftIO $ loadFrontendPlugin hsc_env modname
frontend frontend_plugin
(reverse $ frontendPluginOpts (hsc_dflags hsc_env)) srcs
-#endif
-- -----------------------------------------------------------------------------
-- ABI hash support