Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
40 changes: 4 additions & 36 deletions compiler/GHC/Driver/Downsweep.hs
Original file line number Diff line number Diff line change
Expand Up @@ -940,12 +940,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
}
-- Recursive call to catch the other cases
enable_code_gen_ms ms'
| dynamic_too_enable enable_spec ms -> do
let ms' = ms
{ ms_hspp_opts = gopt_set (ms_hspp_opts ms) Opt_BuildDynamicToo
}
-- Recursive call to catch the other cases
enable_code_gen_ms ms'
-- Note: dynamic_too_enable case removed - -dynamic-too is deprecated
| ext_interp_enable ms -> do
let ms' = ms
{ ms_hspp_opts = gopt_set (ms_hspp_opts ms) Opt_ExternalInterpreter
Expand All @@ -968,14 +963,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
-- can't compile anything anyway! See #16219.
isHomeUnitDefinite (ue_unitHomeUnit (ms_unitid ms) unit_env)

-- bytecode_and_enable: prefer bytecode over needing dynamic objects
-- Note: dynamic_too_enable logic removed - -dynamic-too is deprecated
bytecode_and_enable enable_spec ms =
-- In the situation where we **would** need to enable dynamic-too
-- IF we had decided we needed objects
dynamic_too_enable EnableObject ms
-- but we prefer to use bytecode rather than objects
&& prefer_bytecode
-- and we haven't already turned it on
&& not generate_both
prefer_bytecode && not generate_both
where
lcl_dflags = ms_hspp_opts ms
prefer_bytecode = case enable_spec of
Expand All @@ -985,29 +976,6 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do

generate_both = gopt Opt_ByteCodeAndObjectCode lcl_dflags

-- #8180 - when using TemplateHaskell, switch on -dynamic-too so
-- the linker can correctly load the object files. This isn't necessary
-- when using -fexternal-interpreter.
-- FIXME: Duplicated from makeDynFlagsConsistent
dynamic_too_enable enable_spec ms
| sTargetRTSLinkerOnlySupportsSharedLibs $ settings lcl_dflags =
not isDynWay && not dyn_too_enabled
&& enable_object
| otherwise =
hostIsDynamic && not hostIsProfiled && internalInterpreter &&
not isDynWay && not isProfWay && not dyn_too_enabled
&& enable_object
where
lcl_dflags = ms_hspp_opts ms
internalInterpreter = not (gopt Opt_ExternalInterpreter lcl_dflags)
dyn_too_enabled = gopt Opt_BuildDynamicToo lcl_dflags
isDynWay = hasWay (ways lcl_dflags) WayDyn
isProfWay = hasWay (ways lcl_dflags) WayProf
enable_object = case enable_spec of
EnableByteCode -> False
EnableByteCodeAndObject -> True
EnableObject -> True

-- #16331 - when no "internal interpreter" is available but we
-- need to process some TemplateHaskell or QuasiQuotes, we automatically
-- turn on -fexternal-interpreter.
Expand Down
47 changes: 6 additions & 41 deletions compiler/GHC/Driver/DynFlags.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ module GHC.Driver.DynFlags (
xopt_DuplicateRecordFields,
xopt_FieldSelectors,
lang_set,
DynamicTooState(..), dynamicTooState, setDynamicNow,
-- Note: DynamicTooState, dynamicTooState, setDynamicNow removed
-- -dynamic-too is deprecated, only dynamic objects are produced
OnOff(..),
DynFlags(..),
ParMakeCount(..),
Expand Down Expand Up @@ -296,10 +297,7 @@ data DynFlags = DynFlags {
dynOutputHi :: Maybe String,
dynLibLoader :: DynLibLoader,

dynamicNow :: !Bool, -- ^ Indicate if we are now generating dynamic output
-- because of -dynamic-too. This predicate is
-- used to query the appropriate fields
-- (outputFile/dynOutputFile, ways, etc.)
-- Note: dynamicNow field removed - -dynamic-too is deprecated

-- | This defaults to 'non-module'. It can be set by
-- 'GHC.Driver.Pipeline.setDumpPrefix' or 'ghc.GHCi.UI.runStmt' based on
Expand Down Expand Up @@ -618,7 +616,6 @@ defaultDynFlags mySettings =

dynObjectSuf_ = "dyn_" ++ phaseInputExt StopLn,
dynHiSuf_ = "dyn_hi",
dynamicNow = False,

pluginModNames = [],
pluginModNameOpts = [],
Expand Down Expand Up @@ -930,27 +927,8 @@ positionIndependent dflags = gopt Opt_PIC dflags || gopt Opt_PIE dflags
-- need Template-Haskell and GHC is dynamically linked (cf
-- GHC.Driver.Pipeline.compileOne').
--
-- We used to try and fall back from a dynamic-too failure but this feature
-- didn't work as expected (#20446) so it was removed to simplify the
-- implementation and not obscure latent bugs.

data DynamicTooState
= DT_Dont -- ^ Don't try to build dynamic objects too
| DT_OK -- ^ Will still try to generate dynamic objects
| DT_Dyn -- ^ Currently generating dynamic objects (in the backend)
deriving (Eq,Show,Ord)

dynamicTooState :: DynFlags -> DynamicTooState
dynamicTooState dflags
| not (gopt Opt_BuildDynamicToo dflags) = DT_Dont
| dynamicNow dflags = DT_Dyn
| otherwise = DT_OK

setDynamicNow :: DynFlags -> DynFlags
setDynamicNow dflags0 =
dflags0
{ dynamicNow = True
}
-- Note: DynamicTooState type and dynamicTooState/setDynamicNow functions removed
-- -dynamic-too is deprecated - only dynamic objects are produced now

data PkgDbRef
= GlobalPkgDb
Expand Down Expand Up @@ -1011,18 +989,7 @@ dopt_unset :: DynFlags -> DumpFlag -> DynFlags
dopt_unset dfs f = dfs{ dumpFlags = EnumSet.delete f (dumpFlags dfs) }

-- | Test whether a 'GeneralFlag' is set
--
-- Note that `dynamicNow` (i.e., dynamic objects built with `-dynamic-too`)
-- always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables
-- Opt_SplitSections.
--
gopt :: GeneralFlag -> DynFlags -> Bool
gopt Opt_PIC dflags
| dynamicNow dflags = True
gopt Opt_ExternalDynamicRefs dflags
| dynamicNow dflags = True
gopt Opt_SplitSections dflags
| dynamicNow dflags = False
gopt f dflags = f `EnumSet.member` generalFlags dflags

-- | Set a 'GeneralFlag'
Expand Down Expand Up @@ -1435,9 +1402,7 @@ languageExtensions (Just GHC2024)
LangExt.RoleAnnotations]

ways :: DynFlags -> Ways
ways dflags
| dynamicNow dflags = addWay WayDyn (targetWays_ dflags)
| otherwise = targetWays_ dflags
ways dflags = targetWays_ dflags

-- | Get target profile
targetProfile :: DynFlags -> Profile
Expand Down
35 changes: 5 additions & 30 deletions compiler/GHC/Driver/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1377,8 +1377,10 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do
let force_write_interface = gopt Opt_WriteInterface dflags
write_interface = backendWritesFiles (backend dflags)

-- Note: dynamicNow and DynamicTooState removed - -dynamic-too is deprecated
-- We now only write a single .hi file
write_iface dflags' iface =
let !iface_name = if dynamicNow dflags' then ml_dyn_hi_file mod_location else ml_hi_file mod_location
let !iface_name = ml_hi_file mod_location
profile = targetProfile dflags'
in
{-# SCC "writeIface" #-}
Expand All @@ -1389,43 +1391,16 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do

if (write_interface || force_write_interface) then do

-- FIXME: with -dynamic-too, "change" is only meaningful for the
-- non-dynamic interface, not for the dynamic one. We should have another
-- flag for the dynamic interface. In the meantime:
--
-- * when we write a single full interface, we check if we are
-- currently writing the dynamic interface due to -dynamic-too, in
-- which case we ignore "change".
--
-- * when we write two simple interfaces at once because of
-- dynamic-too, we use "change" both for the non-dynamic and the
-- dynamic interfaces. Hopefully both the dynamic and the non-dynamic
-- interfaces stay in sync...
--
let change = old_iface /= Just (mi_iface_hash iface)

let dt = dynamicTooState dflags

when (logHasDumpFlag logger Opt_D_dump_if_trace) $ putMsg logger $
hang (text "Writing interface(s):") 2 $ vcat
[ text "Kind:" <+> if is_simple then text "simple" else text "full"
, text "Hash change:" <+> ppr change
, text "DynamicToo state:" <+> text (show dt)
]

if is_simple
then when change $ do -- FIXME: see 'change' comment above
write_iface dflags iface
case dt of
DT_Dont -> return ()
DT_Dyn -> panic "Unexpected DT_Dyn state when writing simple interface"
DT_OK -> write_iface (setDynamicNow dflags) iface
else case dt of
DT_Dont | change -> write_iface dflags iface
DT_OK | change -> write_iface dflags iface
-- FIXME: see change' comment above
DT_Dyn -> write_iface dflags iface
_ -> return ()
-- Simply write the interface if there was a change
when change $ write_iface dflags iface

when (gopt Opt_WriteHie dflags) $ do
-- This is slightly hacky. A hie file is considered to be up to date
Expand Down
16 changes: 3 additions & 13 deletions compiler/GHC/Driver/Pipeline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -781,19 +781,9 @@ hscBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction
hscBackendPipeline pipe_env hsc_env mod_sum result =
if backendGeneratesCode (backend (hsc_dflags hsc_env)) then
do
res <- hscGenBackendPipeline pipe_env hsc_env mod_sum result
-- Only run dynamic-too if the backend generates object files
-- See Note [Writing interface files]
-- If we are writing a simple interface (not . backendWritesFiles), then
-- hscMaybeWriteIface in the regular pipeline will write both the hi and
-- dyn_hi files. This way we can avoid running the pipeline twice and
-- generating a duplicate linkable.
-- We must not run the backend a second time with `dynamicNow` enable because
-- all the work has already been done in the first pipeline.
when (gopt Opt_BuildDynamicToo (hsc_dflags hsc_env) && backendWritesFiles (backend (hsc_dflags hsc_env)) ) $ do
let dflags' = setDynamicNow (hsc_dflags hsc_env) -- set "dynamicNow"
() <$ hscGenBackendPipeline pipe_env (hscSetFlags dflags' hsc_env) mod_sum result
return res
-- Note: -dynamic-too is deprecated and ignored
-- We no longer run the backend twice - only dynamic objects are produced
hscGenBackendPipeline pipe_env hsc_env mod_sum result
else
case result of
HscUpdate iface -> return (iface, emptyHomeModInfoLinkable)
Expand Down
26 changes: 9 additions & 17 deletions compiler/GHC/Driver/Pipeline/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -544,7 +544,8 @@ runHscBackendPhase :: PipeEnv
runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
let dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
o_file = if dynamicNow dflags then ml_dyn_obj_file location else ml_obj_file location -- The real object file
-- Note: dynamicNow removed - always use standard object file path
o_file = ml_obj_file location -- The real object file
next_phase = hscPostBackendPhase src_flavour (backend dflags)
case result of
HscUpdate iface ->
Expand Down Expand Up @@ -887,35 +888,26 @@ getOutputFilename
getOutputFilename logger tmpfs stop_phase output basename dflags next_phase maybe_location
-- 1. If we are generating object files for a .hs file, then return the odir as the ModLocation
-- will have been modified to point to the accurate locations
-- Note: dynamicNow removed - always use standard object file path
| StopLn <- next_phase, Just loc <- maybe_location =
return $ if dynamicNow dflags then ml_dyn_obj_file loc
else ml_obj_file loc
return $ ml_obj_file loc
-- 2. If output style is persistent then
| is_last_phase, Persistent <- output = persistent_fn
-- 3. Specific file is only set when outputFile is set by -o
-- If we are in dynamic mode but -dyno is not set then write to the same path as
-- -o with a .dyn_* extension. This case is not triggered for object files which
-- are always handled by the ModLocation.
-- Note: dynamicNow removed - always use standard output file
| is_last_phase, SpecificFile <- output =
return $
if dynamicNow dflags
then case dynOutputFile_ dflags of
Nothing -> let ofile = getOutputFile_ dflags
new_ext = case takeExtension ofile of
"" -> "dyn"
ext -> "dyn_" ++ tail ext
in replaceExtension ofile new_ext
Just fn -> fn
else getOutputFile_ dflags
return $ getOutputFile_ dflags
| keep_this_output = persistent_fn
| Temporary lifetime <- output = newTempName logger tmpfs (tmpDir dflags) lifetime suffix
| otherwise = newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule
suffix
where
getOutputFile_ dflags =
case outputFile_ dflags of
Nothing -> pprPanic "SpecificFile: No filename" (ppr (dynamicNow dflags) $$
text (fromMaybe "-" (dynOutputFile_ dflags)))
getOutputFile_ dflags' =
case outputFile_ dflags' of
Nothing -> pprPanic "SpecificFile: No filename" (text (fromMaybe "-" (dynOutputFile_ dflags')))
Just fn -> fn

hcsuf = hcSuf dflags
Expand Down
31 changes: 11 additions & 20 deletions compiler/GHC/Driver/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@ module GHC.Driver.Session (
xopt_DuplicateRecordFields,
xopt_FieldSelectors,
lang_set,
DynamicTooState(..), dynamicTooState, setDynamicNow,
-- Note: DynamicTooState, dynamicTooState, setDynamicNow removed
-- -dynamic-too is deprecated
sccProfilingEnabled,
needSourceNotes,
OnOff(..),
Expand Down Expand Up @@ -1275,8 +1276,10 @@ dynamic_flags_deps = [
, make_ord_flag defGhcFlag "ddump-file-prefix"
(hasArg (setDumpPrefixForce . Just . flip (++) "."))

, make_ord_flag defGhcFlag "dynamic-too"
(NoArg (setGeneralFlag Opt_BuildDynamicToo))
-- -dynamic-too is deprecated and ignored - GHC now only produces dynamic objects
, make_dep_flag defGhcFlag "dynamic-too"
(NoArg (return ()))
"-dynamic-too is deprecated and ignored. Use -dynamic instead."

------- Keeping temporary files -------------------------------------
-- These can be singular (think ghc -c) or plural (think ghc --make)
Expand Down Expand Up @@ -3605,17 +3608,7 @@ makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc])
-- ensure that a later change doesn't invalidate an earlier check.
-- Be careful not to introduce potential loops!
makeDynFlagsConsistent dflags
-- Disable -dynamic-too on Windows (#8228, #7134, #5987)
| os == OSMinGW32 && gopt Opt_BuildDynamicToo dflags
= let dflags' = gopt_unset dflags Opt_BuildDynamicToo
warn = "-dynamic-too is not supported on Windows"
in loop dflags' warn
-- Disable -dynamic-too if we are are compiling with -dynamic already, otherwise
-- you get two dynamic object files (.o and .dyn_o). (#20436)
| ways dflags `hasWay` WayDyn && gopt Opt_BuildDynamicToo dflags
= let dflags' = gopt_unset dflags Opt_BuildDynamicToo
warn = "-dynamic-too is ignored when using -dynamic"
in loop dflags' warn
-- Note: -dynamic-too validation removed - flag is now deprecated and ignored

| gopt Opt_SplitSections dflags
, platformHasSubsectionsViaSymbols (targetPlatform dflags)
Expand Down Expand Up @@ -3840,15 +3833,13 @@ decodeSize str
foreign import ccall unsafe "setHeapSize" setHeapSize :: Int -> IO ()
foreign import ccall unsafe "enableTimingStats" enableTimingStats :: IO ()

-- Note: dynamicNow removed - -dynamic-too is deprecated
-- Always use the non-dynamic output file paths
outputFile :: DynFlags -> Maybe String
outputFile dflags
| dynamicNow dflags = dynOutputFile_ dflags
| otherwise = outputFile_ dflags
outputFile dflags = outputFile_ dflags

objectSuf :: DynFlags -> String
objectSuf dflags
| dynamicNow dflags = dynObjectSuf_ dflags
| otherwise = objectSuf_ dflags
objectSuf dflags = objectSuf_ dflags

-- | Pretty-print the difference between 2 DynFlags.
--
Expand Down
Loading
Loading