[Git][ghc/ghc][wip/torsten.schmits/T25211-foreign-objects-interpreter-way] Build foreign objects for TH with interpreter's way when loading from iface
Torsten Schmits (@torsten.schmits)
gitlab at gitlab.haskell.org
Tue Aug 27 18:29:06 UTC 2024
Torsten Schmits pushed to branch wip/torsten.schmits/T25211-foreign-objects-interpreter-way at Glasgow Haskell Compiler / GHC
Commits:
2534dfe5 by Torsten Schmits at 2024-08-27T20:28:58+02:00
Build foreign objects for TH with interpreter's way when loading from iface
Fixes #25211
When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.
The results are then loaded by the interpreter, whose way may differ
from the current build's target way.
This patch ensures that foreign objects are compiled with the
interpreter's way.
- - - - -
2 changed files:
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
Changes:
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -1,8 +1,8 @@
{-# LANGUAGE LambdaCase #-}
-
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fprof-auto-top #-}
@@ -301,6 +301,9 @@ import GHC.Types.Unique.FM
import GHC.Types.Unique.DFM
import GHC.Cmm.Config (CmmConfig)
+#if defined(HAVE_INTERNAL_INTERPRETER)
+import GHC.Platform.Ways
+#endif
{- **********************************************************************
%* *
@@ -990,6 +993,32 @@ initModDetails hsc_env iface =
-- in make mode, since this HMI will go into the HPT.
genModDetails hsc_env' iface
+-- | Modify flags such that objects are compiled for the interpreter's way.
+-- This is necessary when building foreign objects for Template Haskell, since
+-- those are object code built outside of the pipeline, which means they aren't
+-- subject to the mechanism in 'enableCodeGenWhen' that requests dynamic build
+-- outputs for dependencies when the interpreter used for TH is dynamic but the
+-- main outputs aren't.
+-- Furthermore, the HPT only stores one set of objects with different names for
+-- bytecode linking in 'HomeModLinkable', so the usual hack for switching
+-- between ways in 'get_link_deps' doesn't work.
+compile_for_interpreter :: HscEnv -> (HscEnv -> IO a) -> IO a
+compile_for_interpreter hsc_env use =
+ use (hscUpdateFlags set_ways hsc_env)
+ where
+ set_ways dflags
+ | ExternalInterp {} <- interpInstance (hscInterp hsc_env)
+ = dflags
+#if defined(HAVE_INTERNAL_INTERPRETER)
+ | otherwise
+ = dflags {
+ dynamicNow = hostIsDynamic,
+ targetWays_ = update_ways WayProf (targetWays_ dflags)
+ }
+
+ update_ways = if hostIsProfiled then addWay else removeWay
+#endif
+
-- | If the 'Linkable' contains Core bindings loaded from an interface, replace
-- them with a lazy IO thunk that compiles them to bytecode and foreign objects.
--
@@ -2063,9 +2092,10 @@ generateByteCode :: HscEnv
-> IO (CompiledByteCode, [FilePath])
generateByteCode hsc_env cgguts mod_location = do
(hasStub, comp_bc) <- hscInteractive hsc_env cgguts mod_location
- stub_o <- traverse (compileForeign hsc_env LangC) hasStub
- foreign_files_o <- traverse (uncurry (compileForeign hsc_env)) (cgi_foreign_files cgguts)
- pure (comp_bc, maybeToList stub_o ++ foreign_files_o)
+ compile_for_interpreter hsc_env $ \ i_env -> do
+ stub_o <- traverse (compileForeign i_env LangC) hasStub
+ foreign_files_o <- traverse (uncurry (compileForeign i_env)) (cgi_foreign_files cgguts)
+ pure (comp_bc, maybeToList stub_o ++ foreign_files_o)
generateFreshByteCode :: HscEnv
-> ModuleName
=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -190,13 +190,9 @@ Even if that wasn't an issue, they are compiled for the session's 'Way', not its
associated module's, so the dynamic variant wouldn't be available when building
only static outputs.
-For now, this doesn't have much of an impact, since we're only supporting
-foreign imports initially, which produce very simple objects that can easily be
-handled by the linker when 'GHC.Linker.Loader.dynLoadObjs' creates a shared
-library from all object file inputs.
-However, for more complex circumstances, we should compile foreign stubs
-specially for TH according to the interpreter 'Way', or request dynamic products
-for TH dependencies like it happens for the conventional case.
+To mitigate this, we instead build foreign objects specially for the
+interpreter, updating the build flags in 'compile_for_interpreter' to use the
+interpreter's way.
Problem 4:
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2534dfe579f33b7240337e8095a350c075a54b28
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2534dfe579f33b7240337e8095a350c075a54b28
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/20240827/26d132fc/attachment-0001.html>
More information about the ghc-commits
mailing list