
Matthew Pickering pushed to branch wip/gdc-files at Glasgow Haskell Compiler / GHC Commits: 39d7bac3 by Matthew Pickering at 2025-08-13T14:18:05+01:00 Rename interpreterBackend to bytecodeBackend - - - - - 5fb137ef by Matthew Pickering at 2025-08-14T14:53:22+01:00 WIP - - - - - 10 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backend.hs - compiler/GHC/Driver/Backend/Internal.hs - compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/phases.rst - docs/users_guide/separate_compilation.rst - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -30,7 +30,7 @@ module GHC ( -- * Flags and settings DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt, - ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend, + ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, noBackend, GhcMode(..), GhcLink(..), parseDynamicFlags, parseTargetFiles, getSessionDynFlags, ===================================== compiler/GHC/Driver/Backend.hs ===================================== @@ -47,7 +47,7 @@ module GHC.Driver.Backend , llvmBackend , jsBackend , viaCBackend - , interpreterBackend + , bytecodeBackend , noBackend , allBackends @@ -252,7 +252,7 @@ instance Show Backend where show = backendDescription -ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend +ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, jsBackend, noBackend :: Backend -- | The native code generator. @@ -310,7 +310,7 @@ viaCBackend = Named ViaC -- (foreign primops). -- -- See "GHC.StgToByteCode" -interpreterBackend = Named Interpreter +bytecodeBackend = Named Bytecode -- | A dummy back end that generates no code. -- @@ -419,7 +419,7 @@ backendDescription (Named NCG) = "native code generator" backendDescription (Named LLVM) = "LLVM" backendDescription (Named ViaC) = "compiling via C" backendDescription (Named JavaScript) = "compiling to JavaScript" -backendDescription (Named Interpreter) = "byte-code interpreter" +backendDescription (Named Bytecode) = "byte-code interpreter" backendDescription (Named NoBackend) = "no code generated" -- | This flag tells the compiler driver whether the back @@ -431,7 +431,7 @@ backendWritesFiles (Named NCG) = True backendWritesFiles (Named LLVM) = True backendWritesFiles (Named ViaC) = True backendWritesFiles (Named JavaScript) = True -backendWritesFiles (Named Interpreter) = False +backendWritesFiles (Named Bytecode) = False backendWritesFiles (Named NoBackend) = False -- | When the back end does write files, this value tells @@ -442,7 +442,7 @@ backendPipelineOutput (Named NCG) = Persistent backendPipelineOutput (Named LLVM) = Persistent backendPipelineOutput (Named ViaC) = Persistent backendPipelineOutput (Named JavaScript) = Persistent -backendPipelineOutput (Named Interpreter) = NoOutputFile +backendPipelineOutput (Named Bytecode) = NoOutputFile backendPipelineOutput (Named NoBackend) = NoOutputFile -- | This flag tells the driver whether the back end can @@ -453,7 +453,7 @@ backendCanReuseLoadedCode (Named NCG) = False backendCanReuseLoadedCode (Named LLVM) = False backendCanReuseLoadedCode (Named ViaC) = False backendCanReuseLoadedCode (Named JavaScript) = False -backendCanReuseLoadedCode (Named Interpreter) = True +backendCanReuseLoadedCode (Named Bytecode) = True backendCanReuseLoadedCode (Named NoBackend) = False -- | It is is true of every back end except @-fno-code@ @@ -478,7 +478,7 @@ backendGeneratesCode (Named NCG) = True backendGeneratesCode (Named LLVM) = True backendGeneratesCode (Named ViaC) = True backendGeneratesCode (Named JavaScript) = True -backendGeneratesCode (Named Interpreter) = True +backendGeneratesCode (Named Bytecode) = True backendGeneratesCode (Named NoBackend) = False backendGeneratesCodeForHsBoot :: Backend -> Bool @@ -486,7 +486,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True backendGeneratesCodeForHsBoot (Named LLVM) = True backendGeneratesCodeForHsBoot (Named ViaC) = True backendGeneratesCodeForHsBoot (Named JavaScript) = True -backendGeneratesCodeForHsBoot (Named Interpreter) = False +backendGeneratesCodeForHsBoot (Named Bytecode) = False backendGeneratesCodeForHsBoot (Named NoBackend) = False -- | When set, this flag turns on interface writing for @@ -498,7 +498,7 @@ backendSupportsInterfaceWriting (Named NCG) = True backendSupportsInterfaceWriting (Named LLVM) = True backendSupportsInterfaceWriting (Named ViaC) = True backendSupportsInterfaceWriting (Named JavaScript) = True -backendSupportsInterfaceWriting (Named Interpreter) = True +backendSupportsInterfaceWriting (Named Bytecode) = True backendSupportsInterfaceWriting (Named NoBackend) = False -- | When preparing code for this back end, the type @@ -510,7 +510,7 @@ backendRespectsSpecialise (Named NCG) = True backendRespectsSpecialise (Named LLVM) = True backendRespectsSpecialise (Named ViaC) = True backendRespectsSpecialise (Named JavaScript) = True -backendRespectsSpecialise (Named Interpreter) = False +backendRespectsSpecialise (Named Bytecode) = False backendRespectsSpecialise (Named NoBackend) = False -- | This back end wants the `mi_top_env` field of a @@ -522,7 +522,7 @@ backendWantsGlobalBindings (Named LLVM) = False backendWantsGlobalBindings (Named ViaC) = False backendWantsGlobalBindings (Named JavaScript) = False backendWantsGlobalBindings (Named NoBackend) = False -backendWantsGlobalBindings (Named Interpreter) = True +backendWantsGlobalBindings (Named Bytecode) = True -- | The back end targets a technology that implements -- `switch` natively. (For example, LLVM or C.) Therefore @@ -534,7 +534,7 @@ backendHasNativeSwitch (Named NCG) = False backendHasNativeSwitch (Named LLVM) = True backendHasNativeSwitch (Named ViaC) = True backendHasNativeSwitch (Named JavaScript) = True -backendHasNativeSwitch (Named Interpreter) = False +backendHasNativeSwitch (Named Bytecode) = False backendHasNativeSwitch (Named NoBackend) = False -- | As noted in the documentation for @@ -548,7 +548,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives backendPrimitiveImplementation (Named JavaScript) = JSPrimitives backendPrimitiveImplementation (Named ViaC) = GenericPrimitives -backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives +backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives -- | When this value is `IsValid`, the back end is @@ -560,7 +560,7 @@ backendSimdValidity (Named NCG) = IsValid backendSimdValidity (Named LLVM) = IsValid backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] -backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] +backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] -- | This flag says whether the back end supports large @@ -571,7 +571,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True backendSupportsEmbeddedBlobs (Named LLVM) = False backendSupportsEmbeddedBlobs (Named ViaC) = False backendSupportsEmbeddedBlobs (Named JavaScript) = False -backendSupportsEmbeddedBlobs (Named Interpreter) = False +backendSupportsEmbeddedBlobs (Named Bytecode) = False backendSupportsEmbeddedBlobs (Named NoBackend) = False -- | This flag tells the compiler driver that the back end @@ -586,7 +586,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True backendNeedsPlatformNcgSupport (Named LLVM) = False backendNeedsPlatformNcgSupport (Named ViaC) = False backendNeedsPlatformNcgSupport (Named JavaScript) = False -backendNeedsPlatformNcgSupport (Named Interpreter) = False +backendNeedsPlatformNcgSupport (Named Bytecode) = False backendNeedsPlatformNcgSupport (Named NoBackend) = False -- | This flag is set if the back end can generate code @@ -598,7 +598,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True backendSupportsUnsplitProcPoints (Named LLVM) = False backendSupportsUnsplitProcPoints (Named ViaC) = False backendSupportsUnsplitProcPoints (Named JavaScript) = False -backendSupportsUnsplitProcPoints (Named Interpreter) = False +backendSupportsUnsplitProcPoints (Named Bytecode) = False backendSupportsUnsplitProcPoints (Named NoBackend) = False -- | This flag guides the driver in resolving issues about @@ -616,7 +616,7 @@ backendSwappableWithViaC (Named NCG) = True backendSwappableWithViaC (Named LLVM) = True backendSwappableWithViaC (Named ViaC) = False backendSwappableWithViaC (Named JavaScript) = False -backendSwappableWithViaC (Named Interpreter) = False +backendSwappableWithViaC (Named Bytecode) = False backendSwappableWithViaC (Named NoBackend) = False -- | This flag is true if the back end works *only* with @@ -626,7 +626,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False backendUnregisterisedAbiOnly (Named LLVM) = False backendUnregisterisedAbiOnly (Named ViaC) = True backendUnregisterisedAbiOnly (Named JavaScript) = False -backendUnregisterisedAbiOnly (Named Interpreter) = False +backendUnregisterisedAbiOnly (Named Bytecode) = False backendUnregisterisedAbiOnly (Named NoBackend) = False -- | This flag is set if the back end generates C code in @@ -637,7 +637,7 @@ backendGeneratesHc (Named NCG) = False backendGeneratesHc (Named LLVM) = False backendGeneratesHc (Named ViaC) = True backendGeneratesHc (Named JavaScript) = False -backendGeneratesHc (Named Interpreter) = False +backendGeneratesHc (Named Bytecode) = False backendGeneratesHc (Named NoBackend) = False -- | This flag says whether SPT (static pointer table) @@ -649,7 +649,7 @@ backendSptIsDynamic (Named NCG) = False backendSptIsDynamic (Named LLVM) = False backendSptIsDynamic (Named ViaC) = False backendSptIsDynamic (Named JavaScript) = False -backendSptIsDynamic (Named Interpreter) = True +backendSptIsDynamic (Named Bytecode) = True backendSptIsDynamic (Named NoBackend) = False -- | If this flag is unset, then the driver ignores the flag @-fbreak-points@, @@ -660,7 +660,7 @@ backendSupportsBreakpoints = \case Named LLVM -> False Named ViaC -> False Named JavaScript -> False - Named Interpreter -> True + Named Bytecode -> True Named NoBackend -> False -- | If this flag is set, then the driver forces the @@ -671,7 +671,7 @@ backendForcesOptimization0 (Named NCG) = False backendForcesOptimization0 (Named LLVM) = False backendForcesOptimization0 (Named ViaC) = False backendForcesOptimization0 (Named JavaScript) = False -backendForcesOptimization0 (Named Interpreter) = True +backendForcesOptimization0 (Named Bytecode) = True backendForcesOptimization0 (Named NoBackend) = False -- | I don't understand exactly how this works. But if @@ -683,7 +683,7 @@ backendNeedsFullWays (Named NCG) = False backendNeedsFullWays (Named LLVM) = False backendNeedsFullWays (Named ViaC) = False backendNeedsFullWays (Named JavaScript) = False -backendNeedsFullWays (Named Interpreter) = True +backendNeedsFullWays (Named Bytecode) = True backendNeedsFullWays (Named NoBackend) = False -- | This flag is also special for the interpreter: if a @@ -695,7 +695,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing backendSpecialModuleSource (Named LLVM) = const Nothing backendSpecialModuleSource (Named ViaC) = const Nothing backendSpecialModuleSource (Named JavaScript) = const Nothing -backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing +backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing backendSpecialModuleSource (Named NoBackend) = const (Just "nothing") -- | This flag says whether the back end supports Haskell @@ -707,7 +707,7 @@ backendSupportsHpc (Named NCG) = True backendSupportsHpc (Named LLVM) = True backendSupportsHpc (Named ViaC) = True backendSupportsHpc (Named JavaScript) = False -backendSupportsHpc (Named Interpreter) = False +backendSupportsHpc (Named Bytecode) = False backendSupportsHpc (Named NoBackend) = True -- | This flag says whether the back end supports foreign @@ -718,7 +718,7 @@ backendSupportsCImport (Named NCG) = True backendSupportsCImport (Named LLVM) = True backendSupportsCImport (Named ViaC) = True backendSupportsCImport (Named JavaScript) = True -backendSupportsCImport (Named Interpreter) = True +backendSupportsCImport (Named Bytecode) = True backendSupportsCImport (Named NoBackend) = True -- | This flag says whether the back end supports foreign @@ -728,7 +728,7 @@ backendSupportsCExport (Named NCG) = True backendSupportsCExport (Named LLVM) = True backendSupportsCExport (Named ViaC) = True backendSupportsCExport (Named JavaScript) = True -backendSupportsCExport (Named Interpreter) = False +backendSupportsCExport (Named Bytecode) = False backendSupportsCExport (Named NoBackend) = True -- | When using this back end, it may be necessary or @@ -749,7 +749,7 @@ backendCDefs (Named NCG) = NoCDefs backendCDefs (Named LLVM) = LlvmCDefs backendCDefs (Named ViaC) = NoCDefs backendCDefs (Named JavaScript) = NoCDefs -backendCDefs (Named Interpreter) = NoCDefs +backendCDefs (Named Bytecode) = NoCDefs backendCDefs (Named NoBackend) = NoCDefs -- | This (defunctionalized) function generates code and @@ -768,7 +768,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput backendCodeOutput (Named LLVM) = LlvmCodeOutput backendCodeOutput (Named ViaC) = ViaCCodeOutput backendCodeOutput (Named JavaScript) = JSCodeOutput -backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend" +backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: interpreterBackend" backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend" backendUseJSLinker :: Backend -> Bool @@ -776,7 +776,7 @@ backendUseJSLinker (Named NCG) = False backendUseJSLinker (Named LLVM) = False backendUseJSLinker (Named ViaC) = False backendUseJSLinker (Named JavaScript) = True -backendUseJSLinker (Named Interpreter) = False +backendUseJSLinker (Named Bytecode) = False backendUseJSLinker (Named NoBackend) = False -- | This (defunctionalized) function tells the compiler @@ -795,7 +795,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline -backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline +backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline -- | Somewhere in the compiler driver, when compiling @@ -809,7 +809,7 @@ backendNormalSuccessorPhase (Named NCG) = As False backendNormalSuccessorPhase (Named LLVM) = LlvmOpt backendNormalSuccessorPhase (Named ViaC) = HCc backendNormalSuccessorPhase (Named JavaScript) = StopLn -backendNormalSuccessorPhase (Named Interpreter) = StopLn +backendNormalSuccessorPhase (Named Bytecode) = StopLn backendNormalSuccessorPhase (Named NoBackend) = StopLn -- | Name of the back end, if any. Used to migrate legacy @@ -820,7 +820,7 @@ backendName (Named NCG) = NCG backendName (Named LLVM) = LLVM backendName (Named ViaC) = ViaC backendName (Named JavaScript) = JavaScript -backendName (Named Interpreter) = Interpreter +backendName (Named Bytecode) = Bytecode backendName (Named NoBackend) = NoBackend @@ -833,7 +833,7 @@ allBackends = [ ncgBackend , llvmBackend , viaCBackend , jsBackend - , interpreterBackend + , bytecodeBackend , noBackend ] ===================================== compiler/GHC/Driver/Backend/Internal.hs ===================================== @@ -28,6 +28,6 @@ data BackendName | LLVM -- ^ Names the LLVM backend. | ViaC -- ^ Names the Via-C backend. | JavaScript -- ^ Names the JS backend. - | Interpreter -- ^ Names the ByteCode interpreter. + | Bytecode -- ^ Names the ByteCode interpreter. | NoBackend -- ^ Names the `-fno-code` backend. deriving (Eq, Show) ===================================== compiler/GHC/Driver/Downsweep.hs ===================================== @@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags)) <*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags)) let new_dflags = case enable_spec of - EnableByteCode -> dflags { backend = interpreterBackend } + EnableByteCode -> dflags { backend = bytecodeBackend } EnableObject -> dflags { backend = defaultBackendOf ms } EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms} let ms' = ms ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -105,7 +105,6 @@ module GHC.Driver.Main , showModuleIndex , hscAddSptEntries , writeInterfaceOnlyMode - , loadByteCode , genModDetails ) where @@ -869,25 +868,24 @@ hscRecompStatus return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do - -- Do need linkable - -- 1. Just check whether we have bytecode/object linkables and then - -- we will decide if we need them or not. - bc_linkable <- checkByteCode hsc_env checked_iface mod_details mod_summary (homeMod_bytecode old_linkable) + -- Check the status of all the linkable types we might need. + -- 1. The in-memory linkable we had at hand. + bc_in_memory_linkable <- checkByteCodeInMemory hsc_env mod_summary (homeMod_bytecode old_linkable) + -- 2. The bytecode object file + bc_obj_linkable <- checkByteCodeFromObject hsc_env mod_summary + -- 3. Bytecode from an interface whole core bindings. + bc_core_linkable <- checkByteCodeFromCoreBindings hsc_env checked_iface mod_details mod_summary + -- 4. The object file. obj_linkable <- liftIO $ checkObjects lcl_dflags (homeMod_object old_linkable) mod_summary - trace_if (hsc_logger hsc_env) (vcat [text "BCO linkable", nest 2 (ppr bc_linkable), text "Object Linkable", ppr obj_linkable]) + trace_if (hsc_logger hsc_env) + (vcat [text "BCO linkable", nest 2 (ppr bc_in_memory_linkable) + , text "BCO obj linkable", ppr bc_obj_linkable + , text "BCO core linkable", ppr bc_core_linkable + , text "Object Linkable", ppr obj_linkable]) - let just_bc = justBytecode <$> bc_linkable - just_o = justObjects <$> obj_linkable - _maybe_both_os = case (bc_linkable, obj_linkable) of - (UpToDateItem bc, UpToDateItem o) -> UpToDateItem (bytecodeAndObjects bc o) - -- If missing object code, just say we need to recompile because of object code. - (_, OutOfDateItem reason _) -> OutOfDateItem reason Nothing - -- If just missing byte code, just use the object code - -- so you should use -fprefer-byte-code with -fwrite-if-simplified-core or you'll - -- end up using bytecode on recompilation - (_, UpToDateItem {} ) -> just_o + let just_o = justObjects <$> obj_linkable - definitely_both_os = case (bc_linkable, obj_linkable) of + definitely_both_os = case (definitely_bc, obj_linkable) of (UpToDateItem bc, UpToDateItem o) -> UpToDateItem (bytecodeAndObjects bc o) -- If missing object code, just say we need to recompile because of object code. (_, OutOfDateItem reason _) -> OutOfDateItem reason Nothing @@ -896,17 +894,21 @@ hscRecompStatus -- end up using bytecode on recompilation (OutOfDateItem reason _, _ ) -> OutOfDateItem reason Nothing + -- When -fwrite-byte-code, we definitely need to have up-to-date bytecode. + definitely_bc = bc_obj_linkable `prefer` bc_in_memory_linkable + + -- If not -fwrite-byte-code, then we could use core bindings or object code if that's available. + maybe_bc = ((bc_obj_linkable `choose` bc_core_linkable) `prefer` bc_in_memory_linkable) + `choose` obj_linkable + -- pprTraceM "recomp" (ppr just_bc <+> ppr just_o) -- 2. Decide which of the products we will need let recomp_linkable_result = case () of _ | backendCanReuseLoadedCode (backend lcl_dflags) -> - case bc_linkable of - -- If bytecode is available for Interactive then don't load object code - UpToDateItem _ -> just_bc - _ -> case obj_linkable of - -- If o is availabe, then just use that - UpToDateItem _ -> just_o - _ -> outOfDateItemBecause MissingBytecode Nothing + if gopt Opt_WriteByteCode lcl_dflags + -- If the byte-code artifact needs to be produced, then we certainly need bytecode. + then justBytecode <$> definitely_bc + else justBytecode <$> maybe_bc -- Need object files for making object files | backendWritesFiles (backend lcl_dflags) -> if gopt Opt_ByteCodeAndObjectCode lcl_dflags @@ -924,6 +926,20 @@ hscRecompStatus msg $ NeedsRecompile reason return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface +-- | Prefer requires both arguments to be up-to-date. +-- but prefers to use the second argument. +prefer :: MaybeValidated Linkable -> MaybeValidated Linkable -> MaybeValidated Linkable +prefer (UpToDateItem _) (UpToDateItem l2) = UpToDateItem l2 +prefer r1 _ = r1 + +-- | Disjunction, choose either argument, but prefer the first one. +-- Report the failure of the first argument. +choose :: MaybeValidated Linkable -> MaybeValidated Linkable -> MaybeValidated Linkable +choose (UpToDateItem l1) _ = UpToDateItem l1 +choose _ (UpToDateItem l2) = UpToDateItem l2 +choose l1 _ = l1 + + -- | Check that the .o files produced by compilation are already up-to-date -- or not. checkObjects :: DynFlags -> Maybe Linkable -> ModSummary -> IO (MaybeValidated Linkable) @@ -959,34 +975,24 @@ checkObjects dflags mb_old_linkable summary = do -- | Check to see if we can reuse the old linkable, by this point we will -- have just checked that the old interface matches up with the source hash, so -- no need to check that again here -checkByteCode :: HscEnv -> ModIface -> ModDetails -> ModSummary -> Maybe Linkable -> IO (MaybeValidated Linkable) -checkByteCode hsc_env iface mod_details mod_sum mb_old_linkable = +checkByteCodeInMemory :: HscEnv -> ModSummary -> Maybe Linkable -> IO (MaybeValidated Linkable) +checkByteCodeInMemory hsc_env mod_sum mb_old_linkable = case mb_old_linkable of Just old_linkable | not (linkableIsNativeCodeOnly old_linkable) + -- If `-fwrite-byte-code` is enabled, then check that the .gbc file is + -- up-to-date with the linkable we have in our hand. + -- If ms_bytecode_date is Nothing, then the .gbc file does not exist yet. + -- Otherwise, check that the date matches the linkable date exactly. + , if gopt Opt_WriteByteCode (hsc_dflags hsc_env) + then maybe False (linkableTime old_linkable ==) (ms_bytecode_date mod_sum) + else True -> return $ (UpToDateItem old_linkable) - _ -> do - load_result <- loadByteCodeFromCoreBindings hsc_env iface mod_details mod_sum - case load_result of - Just linkable -> return $ UpToDateItem linkable - Nothing -> loadByteCode hsc_env iface mod_details mod_sum - --- | First attempt to use the bytecode object linkable if it exists. --- If that doesn't exist, then try to load bytecode from whole core bindings. -loadByteCode :: HscEnv -> ModIface -> ModDetails -> ModSummary -> IO (MaybeValidated Linkable) -loadByteCode hsc_env iface mod_details mod_sum = do - obj_result <- loadByteCodeFromObject hsc_env mod_sum - case obj_result of - Just linkable -> return $ UpToDateItem linkable - Nothing -> do - core_result <- loadByteCodeFromCoreBindings hsc_env iface mod_details mod_sum - case core_result of - Just linkable -> return $ UpToDateItem linkable - Nothing -> return $ outOfDateItemBecause MissingBytecode Nothing + _ -> return $ outOfDateItemBecause MissingBytecode Nothing -- | Load bytecode from a ".gbc" object file if it exists and is up-to-date -loadByteCodeFromObject :: HscEnv -> ModSummary -> IO (Maybe Linkable) -loadByteCodeFromObject hsc_env mod_sum = do +checkByteCodeFromObject :: HscEnv -> ModSummary -> IO (MaybeValidated Linkable) +checkByteCodeFromObject hsc_env mod_sum = do let obj_fn = ml_bytecode_file (ms_location mod_sum) obj_date = ms_bytecode_date mod_sum @@ -994,14 +1000,18 @@ loadByteCodeFromObject hsc_env mod_sum = do case (,) <$> obj_date <*> if_date of Just (obj_date, if_date) | obj_date >= if_date -> do - bco <- readBinByteCode hsc_env obj_fn - Just <$> loadByteCodeObjectLinkable hsc_env obj_date (ms_location mod_sum) bco - _ -> return Nothing + -- Don't force this if we reuse the linkable already loaded into memory, but we have to check + -- that the one we have on disk would be suitable as well. + linkable <- unsafeInterleaveIO $ do + bco <- readBinByteCode hsc_env obj_fn + loadByteCodeObjectLinkable hsc_env obj_date (ms_location mod_sum) bco + return $ UpToDateItem linkable + _ -> return $ outOfDateItemBecause MissingBytecode Nothing -- | Attempt to load bytecode from whole core bindings in the interface if they exist. -- This is a legacy code-path, these days it should be preferred to use the bytecode object linkable. -loadByteCodeFromCoreBindings :: HscEnv -> ModIface -> ModDetails -> ModSummary -> IO (Maybe Linkable) -loadByteCodeFromCoreBindings hsc_env iface mod_details mod_sum = do +checkByteCodeFromCoreBindings :: HscEnv -> ModIface -> ModDetails -> ModSummary -> IO (MaybeValidated Linkable) +checkByteCodeFromCoreBindings hsc_env iface mod_details mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum @@ -1010,8 +1020,8 @@ loadByteCodeFromCoreBindings hsc_env iface mod_details mod_sum = do ~(bco, fos) <- unsafeInterleaveIO $ compileWholeCoreBindings hsc_env (md_types mod_details) fi let bco' = LazyBCOs bco fos - return (Just (Linkable if_date this_mod (NE.singleton bco'))) - _ -> return Nothing + return $ UpToDateItem (Linkable if_date this_mod (NE.singleton bco')) + _ -> return $ outOfDateItemBecause MissingBytecode Nothing -------------------------------------------------------------- -- Compilers @@ -2231,8 +2241,11 @@ generateAndWriteByteCode hsc_env cgguts mod_location = do generateAndWriteByteCodeLinkable :: HscEnv -> CgInteractiveGuts -> ModLocation -> IO Linkable generateAndWriteByteCodeLinkable hsc_env cgguts mod_location = do - bco_time <- getCurrentTime bco_object <- generateAndWriteByteCode hsc_env cgguts mod_location + -- Either, get the same time as the .gbc file if it exists, or just the current time. + -- It's important the time of the linkable matches the time of the .gbc file for recompilation + -- checking. + bco_time <- maybe getCurrentTime pure =<< modificationTimeIfExists (ml_bytecode_file mod_location) loadByteCodeObjectLinkable hsc_env bco_time mod_location bco_object -- | Write foreign sources and foreign stubs to temporary files and compile them. ===================================== compiler/GHC/Driver/Pipeline.hs ===================================== @@ -279,8 +279,8 @@ compileOne' mHscMessage -- was set), force it to generate byte-code. This is NOT transitive and -- only applies to direct targets. | loadAsByteCode - = ( interpreterBackend - , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp + = ( bytecodeBackend + , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp ) | otherwise ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1925,9 +1925,9 @@ dynamic_flags_deps = [ , make_ord_flag defFlag "fno-code" (NoArg ((upd $ \d -> d { ghcLink=NoLink }) >> setBackend noBackend)) , make_ord_flag defFlag "fbyte-code" - (noArgM $ \dflags -> do - setBackend interpreterBackend - pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode)) + (NoArg $ do + setBackend bytecodeBackend + upd $ \dflags -> flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode)) , make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do setBackend $ platformDefaultBackend (targetPlatform dflags) dflags' <- liftEwM getCmdLineState @@ -3185,10 +3185,8 @@ parseReexportedModule str -- If we're linking a binary, then only backends that produce object -- code are allowed (requests for other target types are ignored). setBackend :: Backend -> DynP () -setBackend l = upd $ \ dfs -> - if ghcLink dfs /= LinkBinary || backendWritesFiles l - then dfs{ backend = l } - else dfs +setBackend l = do + upd $ \ dfs -> dfs{ backend = l } -- Changes the target only if we're compiling object code. This is -- used by -fasm and -fllvm, which switch from one to the other, but @@ -3707,6 +3705,11 @@ makeDynFlagsConsistent dflags setGeneralFlag' Opt_ExternalInterpreter $ addWay' WayDyn dflags + | LinkBinary <- ghcLink dflags + , gopt Opt_ByteCode dflags + = loop (dflags { ghcLink = NoLink }) + "Byte-code linking does not currently support linking an executable, enabling -no-link" + | LinkInMemory <- ghcLink dflags , not (gopt Opt_ExternalInterpreter dflags) , targetWays_ dflags /= hostFullWays ===================================== docs/users_guide/phases.rst ===================================== @@ -860,6 +860,19 @@ Options affecting code generation then any modules which are required to be compiled for Template Haskell evaluation will generate byte-code rather than object code. +.. ghc-flag:: -fwrite-byte-code + :shortdesc: Write byte-code object files + :type: dynamic + :category: codegen + + Write byte-code files (``.gbc``) when byte-code is generated. + These files can be used to avoid recompiling modules when using the byte-code + interpreter. + + By default when using :ghc-flag:`-fbyte-code` no byte-code files are written. + This flag is implied by :ghc-flag:`-fbyte-code-and-object-code`. + + .. _options-linker: ===================================== docs/users_guide/separate_compilation.rst ===================================== @@ -423,6 +423,25 @@ Redirecting the compilation output(s) Finally, the option ``-hcsuf`` ⟨suffix⟩ will change the ``.hc`` file suffix for compiler-generated intermediate C files. +.. ghc-flag:: -gbcsuf ⟨suffix⟩ + :shortdesc: set the suffix to use for bytecode files + :type: dynamic + :category: + + The option ``-gbcsuf`` ⟨suffix⟩ will change the ``.gbc`` file + suffix for bytecode files to whatever you specify. This is useful + when you want to avoid conflicts between different bytecode versions + or when building with different flags. + +.. ghc-flag:: -gbcdir ⟨dir⟩ + :shortdesc: set the directory for bytecode files + :type: dynamic + :category: + + The option ``-gbcdir`` ⟨dir⟩ will change the directory where + bytecode files (``.gbc``) are placed. By default, bytecode files + are placed in the same directory as the source files. + .. _keeping-intermediates: Keeping Intermediate Files ===================================== ghc/Main.hs ===================================== @@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do let dflt_backend = backend dflags0 (mode, bcknd, link) = case postLoadMode of - DoInteractive -> (CompManager, interpreterBackend, LinkInMemory) - DoEval _ -> (CompManager, interpreterBackend, LinkInMemory) - DoRun -> (CompManager, interpreterBackend, LinkInMemory) + DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory) + DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory) + DoRun -> (CompManager, bytecodeBackend, LinkInMemory) DoMake -> (CompManager, dflt_backend, LinkBinary) DoBackpack -> (CompManager, dflt_backend, LinkBinary) DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b1c19d07909bc15f26aab079b2d1e6... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b1c19d07909bc15f26aab079b2d1e6... You're receiving this email because of your account on gitlab.haskell.org.