[Git][ghc/ghc][wip/torsten.schmits/oneshot-bytecode-pkgdeps] make mkFullIface backwards compatible

Torsten Schmits (@torsten.schmits) gitlab at gitlab.haskell.org
Thu Jul 18 12:29:36 UTC 2024



Torsten Schmits pushed to branch wip/torsten.schmits/oneshot-bytecode-pkgdeps at Glasgow Haskell Compiler / GHC


Commits:
08655002 by Torsten Schmits at 2024-07-18T14:29:29+02:00
make mkFullIface backwards compatible

- - - - -


3 changed files:

- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Make.hs


Changes:

=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -794,9 +794,9 @@ hscBackendPipeline pipe_env hsc_env mod_sum result =
   else
     case result of
       HscUpdate iface ->  return (iface, emptyHomeModInfoLinkable)
-      HscRecomp {} -> (,) <$> liftIO (mkFullIface hsc_env (hscs_partial_iface result) Nothing Nothing []) <*> pure emptyHomeModInfoLinkable
+      HscRecomp {} -> (,) <$> liftIO (mkFullIface hsc_env (hscs_partial_iface result) Nothing Nothing) <*> pure emptyHomeModInfoLinkable
     -- TODO: Why is there not a linkable?
-    -- Interpreter -> (,) <$> use (T_IO (mkFullIface hsc_env (hscs_partial_iface result) Nothing)) <*> pure Nothing
+    -- Interpreter -> (,) <$> use (T_IO (mkFullIfaceWithForeignStubs hsc_env (hscs_partial_iface result) Nothing)) <*> pure Nothing
 
 hscGenBackendPipeline :: P m
   => PipeEnv


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -598,7 +598,7 @@ runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
                     | gopt Opt_WriteIfSimplifiedCore dflags = fos
                     | otherwise = []
 
-              final_iface <- mkFullIface hsc_env partial_iface stg_infos cg_infos iface_fos
+              final_iface <- mkFullIfaceWithForeignStubs hsc_env partial_iface stg_infos cg_infos iface_fos
 
               -- See Note [Writing interface files]
               hscMaybeWriteIface logger dflags False final_iface mb_old_iface_hash mod_location
@@ -620,7 +620,7 @@ runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
               -- In interpreted mode the regular codeGen backend is not run so we
               -- generate a interface without codeGen info.
             do
-              final_iface <- mkFullIface hsc_env partial_iface Nothing Nothing []
+              final_iface <- mkFullIface hsc_env partial_iface Nothing Nothing
               hscMaybeWriteIface logger dflags True final_iface mb_old_iface_hash location
               bc <- generateFreshByteCode hsc_env mod_name (mkCgInteractiveGuts cgguts) mod_location
               return ([], final_iface, emptyHomeModInfoLinkable { homeMod_bytecode = Just bc } , panic "interpreter")


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -12,6 +12,7 @@
 module GHC.Iface.Make
    ( mkPartialIface
    , mkFullIface
+   , mkFullIfaceWithForeignStubs
    , mkIfaceTc
    , mkIfaceExports
    )
@@ -129,14 +130,19 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls
   = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust
              safe_mode usages docs mod_summary mod_details
 
+-- | Backwards compat interface for 'mkFullIfaceWithForeignStubs'.
+mkFullIface :: HscEnv -> PartialModIface -> Maybe StgCgInfos -> Maybe CmmCgInfos -> IO ModIface
+mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos =
+  mkFullIfaceWithForeignStubs hsc_env partial_iface mb_stg_infos mb_cmm_infos []
+
 -- | Fully instantiate an interface. Adds fingerprints and potentially code
 -- generator produced information.
 --
 -- CmmCgInfos is not available when not generating code (-fno-code), or when not
 -- generating interface pragmas (-fomit-interface-pragmas). See also
 -- Note [Conveying CAF-info and LFInfo between modules] in GHC.StgToCmm.Types.
-mkFullIface :: HscEnv -> PartialModIface -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [FilePath] -> IO ModIface
-mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos fos = do
+mkFullIfaceWithForeignStubs :: HscEnv -> PartialModIface -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [FilePath] -> IO ModIface
+mkFullIfaceWithForeignStubs hsc_env partial_iface mb_stg_infos mb_cmm_infos fos = do
     let decls
           | gopt Opt_OmitInterfacePragmas (hsc_dflags hsc_env)
           = mi_decls partial_iface
@@ -278,7 +284,7 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program
                    docs mod_summary
                    mod_details
 
-          mkFullIface hsc_env partial_iface Nothing Nothing []
+          mkFullIface hsc_env partial_iface Nothing Nothing
 
 mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource
          -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/08655002a3f2e6c89b87c3b3eb1c6888a3326c92

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/08655002a3f2e6c89b87c3b3eb1c6888a3326c92
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/20240718/7cf7b31c/attachment-0001.html>


More information about the ghc-commits mailing list