diff options
-rw-r--r-- | compiler/ghc.cabal.in | 11 | ||||
-rw-r--r-- | compiler/main/DynFlags.hs | 17 | ||||
-rw-r--r-- | compiler/main/DynamicLoading.hs | 38 | ||||
-rw-r--r-- | compiler/main/HeaderInfo.hs | 10 | ||||
-rw-r--r-- | compiler/rename/RnExpr.hs | 2 | ||||
-rw-r--r-- | compiler/simplCore/SimplCore.hs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcPluginM.hs | 7 | ||||
-rw-r--r-- | ghc/Main.hs | 41 | ||||
-rw-r--r-- | ghc/ghc-bin.cabal.in | 15 | ||||
-rw-r--r-- | hadrian/src/Settings/Packages.hs | 4 | ||||
-rw-r--r-- | libraries/ghci/GHCi/BreakArray.hs | 6 | ||||
-rw-r--r-- | libraries/ghci/GHCi/InfoTable.hsc | 6 | ||||
-rw-r--r-- | libraries/ghci/ghci.cabal.in | 11 |
13 files changed, 46 insertions, 126 deletions
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index f191370071..a612733de6 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -25,11 +25,6 @@ Flag ghci Default: False Manual: True -Flag ext-interp - Description: Support external interpreter - Default: True - Manual: True - Flag stage1 Description: Is this stage 1? Default: False @@ -98,12 +93,6 @@ Library CPP-Options: -DHAVE_INTERNAL_INTERPRETER Include-Dirs: ../rts/dist/build @FFIIncludeDir@ - if flag(ext-interp) - CPP-Options: -DHAVE_EXTERNAL_INTERPRETER - - if flag(ghci) || flag(ext-interp) - CPP-Options: -DHAVE_INTERPRETER - -- sanity-check to ensure not more than one integer flag is set if flag(integer-gmp) && flag(integer-simple) build-depends: invalid-cabal-flag-settings<0 diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 9e9e70ad28..465dd2737b 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -4360,26 +4360,25 @@ supportedLanguages = map (flagSpecName . snd) languageFlagsDeps supportedLanguageOverlays :: [String] supportedLanguageOverlays = map (flagSpecName . snd) safeHaskellFlagsDeps -supportedExtensions :: [String] -supportedExtensions = concatMap toFlagSpecNamePair xFlags +supportedExtensions :: PlatformMini -> [String] +supportedExtensions targetPlatformMini = concatMap toFlagSpecNamePair xFlags where toFlagSpecNamePair flg -#if !defined(HAVE_INTERPRETER) -- IMPORTANT! Make sure that `ghc --supported-extensions` omits -- "TemplateHaskell"/"QuasiQuotes" when it's known not to work out of the -- box. See also GHC #11102 and #16331 for more details about -- the rationale - | flagSpecFlag flg == LangExt.TemplateHaskell = [noName] - | flagSpecFlag flg == LangExt.QuasiQuotes = [noName] -#endif + | isAIX, flagSpecFlag flg == LangExt.TemplateHaskell = [noName] + | isAIX, flagSpecFlag flg == LangExt.QuasiQuotes = [noName] | otherwise = [name, noName] where + isAIX = platformMini_os targetPlatformMini == OSAIX noName = "No" ++ name name = flagSpecName flg -supportedLanguagesAndExtensions :: [String] -supportedLanguagesAndExtensions = - supportedLanguages ++ supportedLanguageOverlays ++ supportedExtensions +supportedLanguagesAndExtensions :: PlatformMini -> [String] +supportedLanguagesAndExtensions targetPlatformMini = + supportedLanguages ++ supportedLanguageOverlays ++ supportedExtensions targetPlatformMini -- | These -X<blah> flags cannot be reversed with -XNo<blah> languageFlagsDeps :: [(Deprecation, FlagSpec Language)] diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs index 64cc0a1216..ea09a8ceb5 100644 --- a/compiler/main/DynamicLoading.hs +++ b/compiler/main/DynamicLoading.hs @@ -3,7 +3,6 @@ -- | Dynamically lookup up values from modules and loading them. module DynamicLoading ( initializePlugins, -#if defined(HAVE_INTERPRETER) -- * Loading plugins loadFrontendPlugin, @@ -19,15 +18,11 @@ module DynamicLoading ( getValueSafely, getHValueSafely, lessUnsafeCoerce -#else - pluginError -#endif ) where import GhcPrelude import DynFlags -#if defined(HAVE_INTERPRETER) import Linker ( linkModule, getHValue ) import GHCi ( wormhole ) import SrcLoc ( noSrcSpan ) @@ -60,28 +55,11 @@ import Control.Monad ( when, unless ) import Data.Maybe ( mapMaybe ) import GHC.Exts ( unsafeCoerce# ) -#else - -import HscTypes ( HscEnv ) -import Module ( ModuleName, moduleNameString ) -import Panic - -import Data.List ( intercalate ) -import Control.Monad ( unless ) - -#endif - -- | Loads the plugins specified in the pluginModNames field of the dynamic -- flags. Should be called after command line arguments are parsed, but before -- actual compilation starts. Idempotent operation. Should be re-called if -- pluginModNames or pluginModNameOpts changes. initializePlugins :: HscEnv -> DynFlags -> IO DynFlags -#if !defined(HAVE_INTERPRETER) -initializePlugins _ df - = do let pluginMods = pluginModNames df - unless (null pluginMods) (pluginError pluginMods) - return df -#else initializePlugins hsc_env df | map lpModuleName (cachedPlugins df) == pluginModNames df -- plugins not changed @@ -93,10 +71,6 @@ initializePlugins hsc_env df = do loadedPlugins <- loadPlugins (hsc_env { hsc_dflags = df }) return $ df { cachedPlugins = loadedPlugins } where argumentsForPlugin p = map snd . filter ((== lpModuleName p) . fst) -#endif - - -#if defined(HAVE_INTERPRETER) loadPlugins :: HscEnv -> IO [LoadedPlugin] loadPlugins hsc_env @@ -302,15 +276,3 @@ 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/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs index d534fab1d5..bd984618a4 100644 --- a/compiler/main/HeaderInfo.hs +++ b/compiler/main/HeaderInfo.hs @@ -22,6 +22,7 @@ module HeaderInfo ( getImports import GhcPrelude +import GHC.Platform import HscTypes import Parser ( parseHeader ) import Lexer @@ -306,10 +307,12 @@ checkExtension :: DynFlags -> Located FastString -> Located String checkExtension dflags (dL->L l ext) -- Checks if a given extension is valid, and if so returns -- its corresponding flag. Otherwise it throws an exception. - = let ext' = unpackFS ext in - if ext' `elem` supportedLanguagesAndExtensions + = if ext' `elem` supported then cL l ("-X"++ext') else unsupportedExtnError dflags l ext' + where + ext' = unpackFS ext + supported = supportedLanguagesAndExtensions $ platformMini $ targetPlatform dflags languagePragParseError :: DynFlags -> SrcSpan -> a languagePragParseError dflags loc = @@ -325,7 +328,8 @@ unsupportedExtnError dflags loc unsup = text "Unsupported extension: " <> text unsup $$ if null suggestions then Outputable.empty else text "Perhaps you meant" <+> quotedListWithOr (map text suggestions) where - suggestions = fuzzyMatch unsup supportedLanguagesAndExtensions + supported = supportedLanguagesAndExtensions $ platformMini $ targetPlatform dflags + suggestions = fuzzyMatch unsup supported optionsErrorMsgs :: DynFlags -> [String] -> [Located String] -> FilePath -> Messages diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index f2f0685159..3ec24a7a6d 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -211,8 +211,6 @@ rnExpr (NegApp _ e _) ------------------------------------------ -- Template Haskell extensions --- Don't ifdef-HAVE_INTERPRETER them because we want to fail gracefully --- (not with an rnExpr crash) in a stage-1 compiler. rnExpr e@(HsBracket _ br_body) = rnBracket e br_body rnExpr (HsSpliceE _ splice) = rnSpliceExpr splice diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 572084c420..b3af87b2af 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -462,11 +462,7 @@ doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return doCorePass (CoreDoPasses passes) = runCorePasses passes -#if defined(HAVE_INTERPRETER) doCorePass (CoreDoPluginPass _ pass) = {-# SCC "Plugin" #-} pass -#else -doCorePass pass@CoreDoPluginPass {} = pprPanic "doCorePass" (ppr pass) -#endif doCorePass pass@CoreDesugar = pprPanic "doCorePass" (ppr pass) doCorePass pass@CoreDesugarOpt = pprPanic "doCorePass" (ppr pass) diff --git a/compiler/typecheck/TcPluginM.hs b/compiler/typecheck/TcPluginM.hs index 3785a4aac5..f4fe3013a3 100644 --- a/compiler/typecheck/TcPluginM.hs +++ b/compiler/typecheck/TcPluginM.hs @@ -3,7 +3,6 @@ -- access select functions of the 'TcM', principally those to do with -- reading parts of the state. module TcPluginM ( -#if defined(HAVE_INTERPRETER) -- * Basic TcPluginM functionality TcPluginM, tcPluginIO, @@ -49,10 +48,8 @@ module TcPluginM ( newEvVar, setEvBind, getEvBindsTcPluginM -#endif ) where -#if defined(HAVE_INTERPRETER) import GhcPrelude import qualified TcRnMonad as TcM @@ -190,7 +187,3 @@ setEvBind :: EvBind -> TcPluginM () setEvBind ev_bind = do tc_evbinds <- getEvBindsTcPluginM unsafeTcPluginTcM $ TcM.addTcEvBind tc_evbinds ev_bind -#else --- this dummy import is needed as a consequence of NoImplicitPrelude -import GhcPrelude () -#endif 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 diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index cf5fde03e3..721df4ea62 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -24,11 +24,6 @@ Flag ghci Default: False Manual: True -Flag ext-interp - Description: Build external interpreter support - Default: True - Manual: True - Flag threaded Description: Link the ghc executable against the threaded RTS Default: True @@ -44,6 +39,7 @@ Executable ghc directory >= 1 && < 1.4, process >= 1 && < 1.7, filepath >= 1 && < 1.5, + transformers == 0.5.*, ghc-boot == @ProjectVersionMunged@, ghc == @ProjectVersionMunged@ @@ -66,8 +62,7 @@ Executable ghc ghc-prim >= 0.5.0 && < 0.7, ghci == @ProjectVersionMunged@, haskeline == 0.7.*, - time >= 1.8 && < 1.10, - transformers == 0.5.* + time >= 1.8 && < 1.10 CPP-Options: -DHAVE_INTERNAL_INTERPRETER GHC-Options: -fno-warn-name-shadowing Other-Modules: @@ -97,12 +92,6 @@ Executable ghc if flag(threaded) ghc-options: -threaded - if flag(ext-interp) - cpp-options: -DHAVE_EXTERNAL_INTERPRETER - - if flag(ghci) || flag(ext-interp) - cpp-options: -DHAVE_INTERPRETER - Other-Extensions: CPP NondecreasingIndentation diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs index 98fe8a2e24..20bd114480 100644 --- a/hadrian/src/Settings/Packages.hs +++ b/hadrian/src/Settings/Packages.hs @@ -79,7 +79,6 @@ packageArgs = do , builder (Cabal Flags) ? mconcat [ ghcWithNativeCodeGen ? arg "ncg" , ghcWithInterpreter ? notStage0 ? arg "ghci" - , notStage0 ? not windowsHost ? notM cross ? arg "ext-interp" , cross ? arg "-terminfo" , notStage0 ? intLib == integerGmp ? arg "integer-gmp" @@ -94,7 +93,6 @@ packageArgs = do , builder (Cabal Flags) ? mconcat [ ghcWithInterpreter ? notStage0 ? arg "ghci" - , notStage0 ? not windowsHost ? notM cross ? arg "ext-interp" , cross ? arg "-terminfo" -- the 'threaded' flag is True by default, but -- let's record explicitly that we link all ghc @@ -128,8 +126,6 @@ packageArgs = do -- behind the @-fghci@ flag. , package ghci ? mconcat [ notStage0 ? builder (Cabal Flags) ? arg "ghci" - , notStage0 ? builder (Cabal Flags) ? not windowsHost ? notM cross - ? arg "ext-interp" , cross ? stage0 ? builder (Cabal Flags) ? arg "ghci" ] -------------------------------- haddock ------------------------------- diff --git a/libraries/ghci/GHCi/BreakArray.hs b/libraries/ghci/GHCi/BreakArray.hs index 41a2ab498f..8ab813a5a7 100644 --- a/libraries/ghci/GHCi/BreakArray.hs +++ b/libraries/ghci/GHCi/BreakArray.hs @@ -19,17 +19,14 @@ module GHCi.BreakArray ( BreakArray -#if defined(HAVE_INTERPRETER) (BA) -- constructor is exported only for ByteCodeGen , newBreakArray , getBreak , setBreakOn , setBreakOff , showBreakArray -#endif ) where -#if defined(HAVE_INTERPRETER) import Prelude -- See note [Why do we import Prelude here?] import Control.Monad import Data.Word @@ -116,6 +113,3 @@ readBA# array i = IO $ \s -> readBreakArray :: BreakArray -> Int -> IO Word8 readBreakArray (BA array) (I# i) = readBA# array i -#else -data BreakArray -#endif diff --git a/libraries/ghci/GHCi/InfoTable.hsc b/libraries/ghci/GHCi/InfoTable.hsc index 826e3bc2fd..ab13485e28 100644 --- a/libraries/ghci/GHCi/InfoTable.hsc +++ b/libraries/ghci/GHCi/InfoTable.hsc @@ -10,13 +10,10 @@ -- module GHCi.InfoTable ( -#if defined(HAVE_INTERPRETER) mkConInfoTable -#endif ) where import Prelude -- See note [Why do we import Prelude here?] -#if defined(HAVE_INTERPRETER) import Foreign import Foreign.C import GHC.Ptr @@ -24,7 +21,6 @@ import GHC.Exts import GHC.Exts.Heap import Data.ByteString (ByteString) import qualified Data.ByteString as BS -#endif ghciTablesNextToCode :: Bool #if defined(TABLES_NEXT_TO_CODE) @@ -33,7 +29,6 @@ ghciTablesNextToCode = True ghciTablesNextToCode = False #endif -#if defined(HAVE_INTERPRETER) /* To end */ -- NOTE: Must return a pointer acceptable for use in the header of a closure. -- If tables_next_to_code is enabled, then it must point the the 'code' field. -- Otherwise, it should point to the start of the StgInfoTable. @@ -387,4 +382,3 @@ wORD_SIZE = (#const SIZEOF_HSINT) conInfoTableSizeB :: Int conInfoTableSizeB = wORD_SIZE + itblSize -#endif /* HAVE_INTERPRETER */ diff --git a/libraries/ghci/ghci.cabal.in b/libraries/ghci/ghci.cabal.in index 4da94b3549..849e2a147a 100644 --- a/libraries/ghci/ghci.cabal.in +++ b/libraries/ghci/ghci.cabal.in @@ -22,11 +22,6 @@ Flag ghci Default: False Manual: True -Flag ext-interp - Description: Build external interpreter support - Default: True - Manual: True - source-repository head type: git location: https://gitlab.haskell.org/ghc/ghc.git @@ -61,12 +56,6 @@ library GHCi.Signals GHCi.TH - if flag(ext-interp) - CPP-Options: -DHAVE_EXTERNAL_INTERPRETER - - if flag(ghci) || flag(ext-interp) - CPP-Options: -DHAVE_INTERPRETER - include-dirs: @FFIIncludeDir@ exposed-modules: |