[Git][ghc/ghc][master] Refine the GHCI macro into HAVE[_{INTERNAL, EXTERNAL}]_INTERPRETER
Marge Bot
gitlab at gitlab.haskell.org
Tue Jun 11 22:40:43 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
39f50bff by Alp Mestanogullari at 2019-06-11T22:40:37Z
Refine the GHCI macro into HAVE[_{INTERNAL, EXTERNAL}]_INTERPRETER
As discussed in #16331, the GHCI macro, defined through 'ghci' flags
in ghc.cabal.in, ghc-bin.cabal.in and ghci.cabal.in, is supposed to indicate
whether GHC is built with support for an internal interpreter, that runs in
the same process. It is however overloaded in a few places to mean
"there is an interpreter available", regardless of whether it's an internal
or external interpreter.
For the sake of clarity and with the hope of more easily being able to
build stage 1 GHCs with external interpreter support, this patch splits
the previous GHCI macro into 3 different ones:
- HAVE_INTERNAL_INTERPRETER: GHC is built with an internal interpreter
- HAVE_EXTERNAL_INTERPRETER: GHC is built with support for external interpreters
- HAVE_INTERPRETER: HAVE_INTERNAL_INTERPRETER || HAVE_EXTERNAL_INTERPRETER
- - - - -
17 changed files:
- compiler/ghc.cabal.in
- compiler/ghci/GHCi.hs
- compiler/main/DynFlags.hs
- compiler/main/DynamicLoading.hs
- compiler/rename/RnExpr.hs
- compiler/simplCore/SimplCore.hs
- compiler/typecheck/TcAnnotations.hs
- compiler/typecheck/TcPluginM.hs
- compiler/utils/Util.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Settings/Packages.hs
- libraries/ghci/GHCi/BreakArray.hs
- libraries/ghci/GHCi/InfoTable.hsc
- libraries/ghci/ghci.cabal.in
- testsuite/tests/codeGen/should_compile/jmp_tbl.hs
- utils/ghc-in-ghci/settings.ghci
Changes:
=====================================
compiler/ghc.cabal.in
=====================================
@@ -25,6 +25,11 @@ 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
@@ -90,9 +95,15 @@ Library
-Wnoncanonical-monoid-instances
if flag(ghci)
- CPP-Options: -DGHCI
+ 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
=====================================
compiler/ghci/GHCi.hs
=====================================
@@ -51,7 +51,7 @@ module GHCi
import GhcPrelude
import GHCi.Message
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
import GHCi.Run
#endif
import GHCi.RemoteTypes
@@ -157,7 +157,7 @@ Other Notes on Remote GHCi
* Note [Remote Template Haskell] in libraries/ghci/GHCi/TH.hs
-}
-#if !defined(GHCI)
+#if !defined(HAVE_INTERNAL_INTERPRETER)
needExtInt :: IO a
needExtInt = throwIO
(InstallationError "this operation requires -fexternal-interpreter")
@@ -175,7 +175,7 @@ iservCmd hsc_env at HscEnv{..} msg
uninterruptibleMask_ $ do -- Note [uninterruptibleMask_]
iservCall iserv msg
| otherwise = -- Just run it directly
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
run msg
#else
needExtInt
@@ -391,7 +391,7 @@ lookupSymbol hsc_env at HscEnv{..} str
writeIORef iservLookupSymbolCache $! addToUFM cache str p
return (Just p)
| otherwise =
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
fmap fromRemotePtr <$> run (LookupSymbol (unpackFS str))
#else
needExtInt
@@ -642,7 +642,7 @@ wormholeRef dflags _r
| gopt Opt_ExternalInterpreter dflags
= throwIO (InstallationError
"this operation requires -fno-external-interpreter")
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
| otherwise
= localRef _r
#else
=====================================
compiler/main/DynFlags.hs
=====================================
@@ -320,8 +320,8 @@ import qualified EnumSet
import GHC.Foreign (withCString, peekCString)
import qualified GHC.LanguageExtensions as LangExt
-#if defined(GHCI)
-import Foreign (Ptr) -- needed for 2nd stage
+#if defined(HAVE_INTERPRETER)
+import Foreign (Ptr)
#endif
-- Note [Updating flag description in the User's Guide]
@@ -4342,7 +4342,7 @@ supportedExtensions :: [String]
supportedExtensions = concatMap toFlagSpecNamePair xFlags
where
toFlagSpecNamePair flg
-#if !defined(GHCI)
+#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
=====================================
compiler/main/DynamicLoading.hs
=====================================
@@ -3,7 +3,7 @@
-- | Dynamically lookup up values from modules and loading them.
module DynamicLoading (
initializePlugins,
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
-- * Loading plugins
loadFrontendPlugin,
@@ -27,7 +27,7 @@ module DynamicLoading (
import GhcPrelude
import DynFlags
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
import Linker ( linkModule, getHValue )
import GHCi ( wormhole )
import SrcLoc ( noSrcSpan )
@@ -76,7 +76,7 @@ import Control.Monad ( unless )
-- actual compilation starts. Idempotent operation. Should be re-called if
-- pluginModNames or pluginModNameOpts changes.
initializePlugins :: HscEnv -> DynFlags -> IO DynFlags
-#if !defined(GHCI)
+#if !defined(HAVE_INTERPRETER)
initializePlugins _ df
= do let pluginMods = pluginModNames df
unless (null pluginMods) (pluginError pluginMods)
@@ -96,7 +96,7 @@ initializePlugins hsc_env df
#endif
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
loadPlugins :: HscEnv -> IO [LoadedPlugin]
loadPlugins hsc_env
=====================================
compiler/rename/RnExpr.hs
=====================================
@@ -208,7 +208,7 @@ rnExpr (NegApp _ e _)
------------------------------------------
-- Template Haskell extensions
--- Don't ifdef-GHCI them because we want to fail gracefully
+-- 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
=====================================
compiler/simplCore/SimplCore.hs
=====================================
@@ -462,7 +462,7 @@ doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat
doCorePass CoreDoNothing = return
doCorePass (CoreDoPasses passes) = runCorePasses passes
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
doCorePass (CoreDoPluginPass _ pass) = {-# SCC "Plugin" #-} pass
#else
doCorePass pass at CoreDoPluginPass {} = pprPanic "doCorePass" (ppr pass)
=====================================
compiler/typecheck/TcAnnotations.hs
=====================================
@@ -28,7 +28,7 @@ import Outputable
-- Some platforms don't support the external interpreter, and
-- compilation on those platforms shouldn't fail just due to
-- annotations
-#ifndef GHCI
+#if !defined(HAVE_INTERNAL_INTERPRETER)
tcAnnotations :: [LAnnDecl GhcRn] -> TcM [Annotation]
tcAnnotations anns = do
dflags <- getDynFlags
=====================================
compiler/typecheck/TcPluginM.hs
=====================================
@@ -3,7 +3,7 @@
-- access select functions of the 'TcM', principally those to do with
-- reading parts of the state.
module TcPluginM (
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
-- * Basic TcPluginM functionality
TcPluginM,
tcPluginIO,
@@ -52,7 +52,7 @@ module TcPluginM (
#endif
) where
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
import GhcPrelude
import qualified TcRnMonad as TcM
=====================================
compiler/utils/Util.hs
=====================================
@@ -188,7 +188,7 @@ the flags are off.
-}
ghciSupported :: Bool
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
ghciSupported = True
#else
ghciSupported = False
=====================================
ghc/Main.hs
=====================================
@@ -25,12 +25,12 @@ import HscMain ( newHscEnv )
import DriverPipeline ( oneShot, compileFile )
import DriverMkDepend ( doMkDependHS )
import DriverBkp ( doBackpack )
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
#endif
-- Frontend plugins
-#if defined(GHCI)
+#if defined(HAVE_INTERPRETER)
import DynamicLoading ( loadFrontendPlugin, initializePlugins )
import Plugins
#else
@@ -271,7 +271,7 @@ main' postLoadMode dflags0 args flagWarnings = do
ghciUI :: HscEnv -> DynFlags -> [(FilePath, Maybe Phase)] -> Maybe [String]
-> Ghc ()
-#if !defined(GHCI)
+#if !defined(HAVE_INTERNAL_INTERPRETER)
ghciUI _ _ _ _ =
throwGhcException (CmdLineError "not built for interactive use")
#else
@@ -521,7 +521,7 @@ isDoEvalMode :: Mode -> Bool
isDoEvalMode (Right (Right (DoEval _))) = True
isDoEvalMode _ = False
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
isInteractiveMode :: PostLoadMode -> Bool
isInteractiveMode DoInteractive = True
isInteractiveMode _ = False
@@ -752,7 +752,7 @@ showBanner :: PostLoadMode -> DynFlags -> IO ()
showBanner _postLoadMode dflags = do
let verb = verbosity dflags
-#if defined(GHCI)
+#if defined(HAVE_INTERNAL_INTERPRETER)
-- Show the GHCi banner
when (isInteractiveMode _postLoadMode && verb >= 1) $ putStrLn ghciWelcomeMsg
#endif
@@ -844,7 +844,7 @@ dumpPackagesSimple dflags = putMsg dflags (pprPackagesSimple dflags)
-- Frontend plugin support
doFrontend :: ModuleName -> [(String, Maybe Phase)] -> Ghc ()
-#if !defined(GHCI)
+#if !defined(HAVE_INTERPRETER)
doFrontend modname _ = pluginError [modname]
#else
doFrontend modname srcs = do
=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -24,6 +24,11 @@ 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
@@ -63,7 +68,7 @@ Executable ghc
haskeline == 0.7.*,
time >= 1.8 && < 1.10,
transformers == 0.5.*
- CPP-Options: -DGHCI
+ CPP-Options: -DHAVE_INTERNAL_INTERPRETER
GHC-Options: -fno-warn-name-shadowing
Other-Modules:
GHCi.Leak
@@ -92,6 +97,12 @@ 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
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -17,6 +17,8 @@ packageArgs = do
intLib <- getIntegerPackage
compilerPath <- expr $ buildPath (vanillaContext stage compiler)
gmpBuildPath <- expr gmpBuildPath
+ win <- expr windowsHost
+ cross <- expr (flag CrossCompiling)
let includeGmp = "-I" ++ gmpBuildPath -/- "include"
mconcat
@@ -70,6 +72,7 @@ packageArgs = do
, builder (Cabal Flags) ? mconcat
[ ghcWithNativeCodeGen ? arg "ncg"
, ghcWithInterpreter ? notStage0 ? arg "ghci"
+ , notStage0 ? (not win && not cross) ? arg "ext-interp"
, flag CrossCompiling ? arg "-terminfo"
, notStage0 ? intLib == integerGmp ?
arg "integer-gmp"
@@ -84,6 +87,7 @@ packageArgs = do
, builder (Cabal Flags) ? mconcat
[ ghcWithInterpreter ? notStage0 ? arg "ghci"
+ , notStage0 ? (not win && not cross) ? arg "ext-interp"
, flag CrossCompiling ? arg "-terminfo"
-- the 'threaded' flag is True by default, but
-- let's record explicitly that we link all ghc
@@ -117,6 +121,8 @@ packageArgs = do
-- behind the @-fghci@ flag.
, package ghci ? mconcat
[ notStage0 ? builder (Cabal Flags) ? arg "ghci"
+ , notStage0 ? builder (Cabal Flags) ? (not win && not cross)
+ ? arg "ext-interp"
, flag CrossCompiling ? stage0 ? builder (Cabal Flags) ? arg "ghci" ]
-------------------------------- haddock -------------------------------
=====================================
libraries/ghci/GHCi/BreakArray.hs
=====================================
@@ -19,7 +19,7 @@
module GHCi.BreakArray
(
BreakArray
-#ifdef GHCI
+#if defined(HAVE_INTERPRETER)
(BA) -- constructor is exported only for ByteCodeGen
, newBreakArray
, getBreak
@@ -29,7 +29,7 @@ module GHCi.BreakArray
#endif
) where
-#ifdef GHCI
+#if defined(HAVE_INTERPRETER)
import Prelude -- See note [Why do we import Prelude here?]
import Control.Monad
import Data.Word
=====================================
libraries/ghci/GHCi/InfoTable.hsc
=====================================
@@ -10,13 +10,13 @@
--
module GHCi.InfoTable
(
-#ifdef GHCI
+#if defined(HAVE_INTERPRETER)
mkConInfoTable
#endif
) where
import Prelude -- See note [Why do we import Prelude here?]
-#ifdef GHCI
+#if defined(HAVE_INTERPRETER)
import Foreign
import Foreign.C
import GHC.Ptr
@@ -27,13 +27,13 @@ import qualified Data.ByteString as BS
#endif
ghciTablesNextToCode :: Bool
-#ifdef TABLES_NEXT_TO_CODE
+#if defined(TABLES_NEXT_TO_CODE)
ghciTablesNextToCode = True
#else
ghciTablesNextToCode = False
#endif
-#ifdef GHCI /* To end */
+#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 +387,4 @@ wORD_SIZE = (#const SIZEOF_HSINT)
conInfoTableSizeB :: Int
conInfoTableSizeB = wORD_SIZE + itblSize
-#endif /* GHCI */
+#endif /* HAVE_INTERPRETER */
=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -22,6 +22,11 @@ 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
@@ -48,7 +53,7 @@ library
UnboxedTuples
if flag(ghci)
- CPP-Options: -DGHCI
+ CPP-Options: -DHAVE_INTERNAL_INTERPRETER
exposed-modules:
GHCi.Run
GHCi.CreateBCO
@@ -56,6 +61,12 @@ 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:
=====================================
testsuite/tests/codeGen/should_compile/jmp_tbl.hs
=====================================
@@ -4,7 +4,7 @@
This funny module was reduced from a failing build of stage2 using
the new code generator and the linear register allocator, with this bug:
-"inplace/bin/ghc-stage1" -fPIC -dynamic -H32m -O -Wall -H64m -O0 -package-name ghc-7.1.20110414 -hide-all-packages -i -icompiler/basicTypes -icompiler/cmm -icompiler/codeGen -icompiler/coreSyn -icompiler/deSugar -icompiler/ghci -icompiler/hsSyn -icompiler/iface -icompiler/llvmGen -icompiler/main -icompiler/nativeGen -icompiler/parser -icompiler/prelude -icompiler/profiling -icompiler/rename -icompiler/simplCore -icompiler/simplStg -icompiler/specialise -icompiler/stgSyn -icompiler/stranal -icompiler/typecheck -icompiler/types -icompiler/utils -icompiler/vectorise -icompiler/stage2/build -icompiler/stage2/build/autogen -Icompiler/stage2/build -Icompiler/stage2/build/autogen -Icompiler/../libffi/build/include -Icompiler/stage2 -Icompiler/../libraries/base/cbits -Icompiler/../libraries/base/include -Icompiler/. -Icompiler/parser -Icompiler/utils -optP-DGHCI -optP-include -optPcompiler/stage2/build/autogen/cabal_macros.h -package Cabal-1.11.0 -package array-0.3.0.2 -package base-4.3.1.0 -package ghc-boot-0.0.0.0 -package bytestring-0.9.1.10 -package containers-0.4.0.0 -package directory-1.1.0.0 -package filepath-1.2.0.0 -package hoopl-3.8.7.0 -package hpc-0.5.0.6 -package old-time-1.0.0.6 -package process-1.0.1.4 -package template-haskell-2.5.0.0 -package unix-2.4.1.0 -Wall -fno-warn-name-shadowing -fno-warn-orphans -XHaskell98 -XNondecreasingIndentation -XCPP -XMagicHash -XUnboxedTuples -XPatternGuards -XForeignFunctionInterface -XEmptyDataDecls -XTypeSynonymInstances -XMultiParamTypeClasses -XFlexibleInstances -XRank2Types -XScopedTypeVariables -XDeriveDataTypeable -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 -O2 -O -DGHC_DEFAULT_NEW_CODEGEN -no-user-package-db -rtsopts -odir compiler/stage2/build -hidir compiler/stage2/build -stubdir compiler/stage2/build -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -c compiler/main/DriverPipeline.hs -o compiler/stage2/build/DriverPipeline.dyn_o -fforce-recomp -dno-debug-output -fno-warn-unused-binds
+"inplace/bin/ghc-stage1" -fPIC -dynamic -H32m -O -Wall -H64m -O0 -package-name ghc-7.1.20110414 -hide-all-packages -i -icompiler/basicTypes -icompiler/cmm -icompiler/codeGen -icompiler/coreSyn -icompiler/deSugar -icompiler/ghci -icompiler/hsSyn -icompiler/iface -icompiler/llvmGen -icompiler/main -icompiler/nativeGen -icompiler/parser -icompiler/prelude -icompiler/profiling -icompiler/rename -icompiler/simplCore -icompiler/simplStg -icompiler/specialise -icompiler/stgSyn -icompiler/stranal -icompiler/typecheck -icompiler/types -icompiler/utils -icompiler/vectorise -icompiler/stage2/build -icompiler/stage2/build/autogen -Icompiler/stage2/build -Icompiler/stage2/build/autogen -Icompiler/../libffi/build/include -Icompiler/stage2 -Icompiler/../libraries/base/cbits -Icompiler/../libraries/base/include -Icompiler/. -Icompiler/parser -Icompiler/utils -optP-DHAVE_INTERNAL_INTERPRETER -optP-include -optPcompiler/stage2/build/autogen/cabal_macros.h -package Cabal-1.11.0 -package array-0.3.0.2 -package base-4.3.1.0 -package ghc-boot-0.0.0.0 -package bytestring-0.9.1.10 -package containers-0.4.0.0 -package directory-1.1.0.0 -package filepath-1.2.0.0 -package hoopl-3.8.7.0 -package hpc-0.5.0.6 -package old-time-1.0.0.6 -package process-1.0.1.4 -package template-haskell-2.5.0.0 -package unix-2.4.1.0 -Wall -fno-warn-name-shadowing -fno-warn-orphans -XHaskell98 -XNondecreasingIndentation -XCPP -XMagicHash -XUnboxedTuples -XPatternGuards -XForeignFunctionInterface -XEmptyDataDecls -XTypeSynonymInstances -XMultiParamTypeClasses -XFlexibleInstances -XRank2Types -XScopedTypeVariables -XDeriveDataTypeable -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 -O2 -O -DGHC_DEFAULT_NEW_CODEGEN -no-user-package-db -rtsopts -odir compiler/stage2/build -hidir compiler/stage2/build -stubdir compiler/stage2/build -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -c compiler/main/DriverPipeline.hs -o compiler/stage2/build/DriverPipeline.dyn_o -fforce-recomp -dno-debug-output -fno-warn-unused-binds
ghc-stage1: panic! (the 'impossible' happened)
(GHC version 7.1.20110414 for x86_64-unknown-linux):
=====================================
utils/ghc-in-ghci/settings.ghci
=====================================
@@ -30,7 +30,7 @@
:set -Iincludes/dist-derivedconstants/header
:set -package=ghc-boot-th
:set -DSTAGE=2
-:set -DGHCI
+:set -DHAVE_INTERNAL_INTERPRETER
:set -DGHC_LOADED_INTO_GHCI
:set -XNoImplicitPrelude
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/39f50bff3ea913a7f4b1d915660bcf77b9327e2e
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/39f50bff3ea913a7f4b1d915660bcf77b9327e2e
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190611/c3975ea8/attachment-0001.html>
More information about the ghc-commits
mailing list