[Git][ghc/ghc][wip/T24634-oneshot-bytecode] 4 commits: try without forced dynamic

Torsten Schmits (@torsten.schmits) gitlab at gitlab.haskell.org
Sat Aug 3 12:45:25 UTC 2024



Torsten Schmits pushed to branch wip/T24634-oneshot-bytecode at Glasgow Haskell Compiler / GHC


Commits:
3f0c6f66 by Torsten Schmits at 2024-08-03T14:38:55+02:00
try without forced dynamic

- - - - -
bd233ea2 by Cheng Shao at 2024-08-03T14:44:53+02:00
Link bytecode from interface-stored core bindings in oneshot mode

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

- - - - -
b83f17f5 by Torsten Schmits at 2024-08-03T14:44:53+02:00
add new EPS field to avoid having to create ModDetails badly

- - - - -
b0026fd3 by Torsten Schmits at 2024-08-03T14:44:53+02:00
avoid assertion warning in test

- - - - -


23 changed files:

- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Main.hs
- + compiler/GHC/Driver/Main.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/External.hs
- testsuite/tests/bytecode/T24634/Hello.hs
- testsuite/tests/bytecode/T24634/Makefile
- testsuite/tests/bytecode/T24634/T24634.stdout
- testsuite/tests/bytecode/T24634/all.T
- testsuite/tests/bytecode/T24634/hello.c → testsuite/tests/bytecode/T24634/hello_c.c
- testsuite/tests/bytecode/T24634/hello.h → testsuite/tests/bytecode/T24634/hello_c.h
- + testsuite/tests/bytecode/T25090/A.hs
- + testsuite/tests/bytecode/T25090/B.hs
- + testsuite/tests/bytecode/T25090/C.hs
- + testsuite/tests/bytecode/T25090/C.hs-boot
- + testsuite/tests/bytecode/T25090/D.hs
- + testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/T25090.stdout
- + testsuite/tests/bytecode/T25090/all.T


Changes:

=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -602,7 +602,7 @@ toIfaceTopBind b =
           in (top_bndr, rhs')
 
         -- The sharing behaviour is currently disabled due to #22807, and relies on
-        -- finished #220056 to be re-enabled.
+        -- finished #20056 to be re-enabled.
         disabledDueTo22807 = True
 
         already_has_unfolding b = not disabledDueTo22807
@@ -774,8 +774,8 @@ outside of the hs-boot loop.
 Note [Interface File with Core: Sharing RHSs]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
-IMPORTANT: This optimisation is currently disabled due to #22027, it can be
-           re-enabled once #220056 is implemented.
+IMPORTANT: This optimisation is currently disabled due to #22807, it can be
+           re-enabled once #22056 is implemented.
 
 In order to avoid duplicating definitions for bindings which already have unfoldings
 we do some minor headstands to avoid serialising the RHS of a definition if it has


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -50,6 +50,7 @@ module GHC.Driver.Main
     , HscBackendAction (..), HscRecompStatus (..)
     , initModDetails
     , initWholeCoreBindings
+    , initWholeCoreBindingsEps
     , hscMaybeWriteIface
     , hscCompileCmmFile
 
@@ -106,6 +107,7 @@ module GHC.Driver.Main
     , showModuleIndex
     , hscAddSptEntries
     , writeInterfaceOnlyMode
+    , loadByteCode
     ) where
 
 import GHC.Prelude
@@ -275,7 +277,8 @@ import GHC.SysTools (initSysTools)
 import GHC.SysTools.BaseDir (findTopDir)
 
 import Data.Data hiding (Fixity, TyCon)
-import Data.List        ( nub, isPrefixOf, partition )
+import Data.Foldable (fold)
+import Data.List ( nub, isPrefixOf, partition )
 import qualified Data.List.NonEmpty as NE
 import Control.Monad
 import Data.IORef
@@ -976,24 +979,34 @@ loadByteCode iface mod_sum = do
 -- Compilers
 --------------------------------------------------------------
 
+add_iface_to_hpt :: ModIface -> ModDetails -> HscEnv -> HscEnv
+add_iface_to_hpt iface details =
+  hscUpdateHPT $ \ hpt ->
+    addToHpt hpt (moduleName (mi_module iface))
+    (HomeModInfo iface details emptyHomeModInfoLinkable)
 
 -- Knot tying!  See Note [Knot-tying typecheckIface]
 -- See Note [ModDetails and --make mode]
 initModDetails :: HscEnv -> ModIface -> IO ModDetails
 initModDetails hsc_env iface =
   fixIO $ \details' -> do
-    let act hpt  = addToHpt hpt (moduleName $ mi_module iface)
-                                (HomeModInfo iface details' emptyHomeModInfoLinkable)
-    let !hsc_env' = hscUpdateHPT act hsc_env
+    let !hsc_env' = add_iface_to_hpt iface details' hsc_env
     -- NB: This result is actually not that useful
     -- in one-shot mode, since we're not going to do
     -- any further typechecking.  It's much more useful
     -- in make mode, since this HMI will go into the HPT.
     genModDetails hsc_env' iface
 
--- Hydrate any WholeCoreBindings linkables into BCOs
-initWholeCoreBindings :: HscEnv -> ModIface -> ModDetails -> Linkable -> IO Linkable
-initWholeCoreBindings hsc_env mod_iface details (LM utc_time this_mod uls) = do
+-- | Hydrate any WholeCoreBindings linkables into BCOs, using the supplied
+-- action to initialize the appropriate environment for type checking.
+initWcbWithTcEnv ::
+  HscEnv ->
+  HscEnv ->
+  ModIface ->
+  TypeEnv ->
+  Linkable ->
+  IO Linkable
+initWcbWithTcEnv tc_hsc_env hsc_env mod_iface type_env (LM utc_time this_mod uls) = do
   -- If a module is compiled with -fbyte-code-and-object-code and it
   -- makes use of foreign stubs, then the interface file will also
   -- contain serialized stub dynamic objects, and we can simply write
@@ -1006,23 +1019,40 @@ initWholeCoreBindings hsc_env mod_iface details (LM utc_time this_mod uls) = do
   bytecode_uls <- for uls go
   pure $ LM utc_time this_mod $ stub_uls ++ bytecode_uls
   where
-    go (CoreBindings fi) = do
-        let act hpt  = addToHpt hpt (moduleName $ mi_module mod_iface)
-                                (HomeModInfo mod_iface details emptyHomeModInfoLinkable)
-        types_var <- newIORef (md_types details)
-        let kv = knotVarsFromModuleEnv (mkModuleEnv [(this_mod, types_var)])
-        let hsc_env' = hscUpdateHPT act hsc_env { hsc_type_env_vars = kv }
-        -- The bytecode generation itself is lazy because otherwise even when doing
-        -- recompilation checking the bytecode will be generated (which slows things down a lot)
-        -- the laziness is OK because generateByteCode just depends on things already loaded
-        -- in the interface file.
-        LoadedBCOs <$> (unsafeInterleaveIO $ do
-                  core_binds <- initIfaceCheck (text "l") hsc_env' $ typecheckWholeCoreBindings types_var fi
-                  let cgi_guts = CgInteractiveGuts this_mod core_binds (typeEnvTyCons (md_types details)) NoStubs Nothing []
-                  trace_if (hsc_logger hsc_env) (text "Generating ByteCode for" <+> (ppr this_mod))
-                  generateByteCode hsc_env cgi_guts (wcb_mod_location fi))
+    go (CoreBindings fi) =
+      -- The bytecode generation itself is lazy because otherwise even when doing
+      -- recompilation checking the bytecode will be generated (which slows things down a lot)
+      -- the laziness is OK because generateByteCode just depends on things already loaded
+      -- in the interface file.
+      LoadedBCOs <$> (unsafeInterleaveIO $ do
+        kv <- newIORef type_env
+        let
+          tc_hsc_env_with_kv = tc_hsc_env {
+            hsc_type_env_vars =
+              knotVarsFromModuleEnv (mkModuleEnv [(this_mod, kv)])
+          }
+        core_binds <- initIfaceCheck (text "l") tc_hsc_env_with_kv $
+                      typecheckWholeCoreBindings kv fi
+        let cgi_guts = CgInteractiveGuts this_mod core_binds (typeEnvTyCons type_env) NoStubs Nothing []
+        trace_if (hsc_logger hsc_env) (text "Generating ByteCode for" <+> ppr this_mod)
+        generateByteCode hsc_env cgi_guts (wcb_mod_location fi))
     go ul = return ul
 
+-- | Hydrate core bindings for a module in the home package table, for which we
+-- can obtain a 'ModDetails'.
+initWholeCoreBindings :: HscEnv -> ModIface -> ModDetails -> Linkable -> IO Linkable
+initWholeCoreBindings hsc_env iface details =
+  initWcbWithTcEnv (add_iface_to_hpt iface details hsc_env) hsc_env iface (md_types details)
+
+-- | Hydrate core bindings for a module in the external package state.
+-- This is used for home modules as well when compiling in oneshot mode.
+initWholeCoreBindingsEps :: HscEnv -> ModIface -> Linkable -> IO Linkable
+initWholeCoreBindingsEps hsc_env iface lnk = do
+  eps <- hscEPS hsc_env
+  let type_env = fold (lookupModuleEnv (eps_PTT eps) (mi_module iface))
+  initWcbWithTcEnv hsc_env hsc_env iface type_env lnk
+
+
 {-
 Note [ModDetails and --make mode]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/Driver/Main.hs-boot
=====================================
@@ -0,0 +1,8 @@
+module GHC.Driver.Main where
+
+import GHC.Driver.Env
+import GHC.Linker.Types
+import GHC.Prelude
+import GHC.Unit.Module.ModIface
+
+initWholeCoreBindingsEps :: HscEnv -> ModIface -> Linkable -> IO Linkable


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -587,12 +587,9 @@ runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
               -- When compiling with -fprefer-byte-code, always
               -- compile foreign stubs as shared objects to ensure
               -- they can be properly loaded.
-              let hsc_env_stub
-                    | gopt Opt_WriteIfSimplifiedCore dflags = hscUpdateFlags setDynamicNow hsc_env
-                    | otherwise = hsc_env
-              stub_o <- mapM (compileStub hsc_env_stub) mStub
+              stub_o <- mapM (compileStub hsc_env) mStub
               foreign_os <-
-                mapM (uncurry (compileForeign hsc_env_stub)) foreign_files
+                mapM (uncurry (compileForeign hsc_env)) foreign_files
               let fos = maybe [] return stub_o ++ foreign_os
                   iface_fos
                     | gopt Opt_WriteIfSimplifiedCore dflags = fos


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -536,6 +536,8 @@ loadInterface doc_str mod from
                 eps {
                   eps_PIT          = extendModuleEnv (eps_PIT eps) mod final_iface,
                   eps_PTE          = addDeclsToPTE   (eps_PTE eps) new_eps_decls,
+                  eps_PTT =
+                    extendModuleEnv (eps_PTT eps) mod (mkNameEnv new_eps_decls),
                   eps_rule_base    = extendRuleBaseList (eps_rule_base eps)
                                                         new_eps_rules,
                   eps_complete_matches


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -893,11 +893,11 @@ tcTopIfaceBindings :: IORef TypeEnv -> [IfaceBindingX IfaceMaybeRhs IfaceTopBndr
           -> IfL [CoreBind]
 tcTopIfaceBindings ty_var ver_decls
    = do
-      int <- mapM tcTopBinders  ver_decls
+      int <- mapM tcTopBinders ver_decls
       let all_ids :: [Id] = concatMap toList int
       liftIO $ modifyIORef ty_var (flip extendTypeEnvList (map AnId all_ids))
 
-      extendIfaceIdEnv all_ids $ mapM (tc_iface_bindings) int
+      extendIfaceIdEnv all_ids $ mapM tc_iface_bindings int
 
 tcTopBinders :: IfaceBindingX a IfaceTopBndrInfo -> IfL (IfaceBindingX a Id)
 tcTopBinders = traverse mk_top_id


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -55,6 +55,11 @@ import qualified Data.Map as M
 
 import System.FilePath
 import System.Directory
+import GHC.Driver.Env
+import {-# SOURCE #-} GHC.Driver.Main
+import Data.Time.Clock
+import GHC.Driver.Flags
+import GHC.Driver.Session
 
 data LinkDepsOpts = LinkDepsOpts
   { ldObjSuffix   :: !String                        -- ^ Suffix of .o files
@@ -69,6 +74,7 @@ data LinkDepsOpts = LinkDepsOpts
   , ldWays        :: !Ways                          -- ^ Enabled ways
   , ldLoadIface   :: SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
                                                     -- ^ Interface loader function
+  , ldHscEnv      :: !HscEnv
   }
 
 data LinkDeps = LinkDeps
@@ -282,13 +288,27 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   Found loc mod -> found loc mod
                   _ -> no_obj (moduleName mod)
         where
-            found loc mod = do {
-                -- ...and then find the linkable for it
-               mb_lnk <- findObjectLinkableMaybe mod loc ;
-               case mb_lnk of {
-                  Nothing  -> no_obj mod ;
-                  Just lnk -> adjust_linkable lnk
-              }}
+            found loc mod
+              | prefer_bytecode = do
+                  Succeeded iface <- ldLoadIface opts (text "load core bindings") mod
+                  case mi_extra_decls iface of
+                    Just extra_decls -> do
+                      t <- getCurrentTime
+                      initWholeCoreBindingsEps hsc_env iface $ LM t mod [CoreBindings $ WholeCoreBindings extra_decls mod loc]
+                    _ -> fallback_no_bytecode loc mod
+              | otherwise = fallback_no_bytecode loc mod
+
+            fallback_no_bytecode loc mod = do
+              mb_lnk <- findObjectLinkableMaybe mod loc
+              case mb_lnk of
+                Nothing  -> no_obj mod
+                Just lnk -> adjust_linkable lnk
+
+            prefer_bytecode = gopt Opt_UseBytecodeRatherThanObjects dflags
+
+            dflags = hsc_dflags hsc_env
+
+            hsc_env = ldHscEnv opts
 
             adjust_linkable lnk
                 | Just new_osuf <- maybe_normal_osuf = do


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -648,6 +648,7 @@ initLinkDepsOpts hsc_env = opts
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
+            , ldHscEnv      = hsc_env
             }
     dflags = hsc_dflags hsc_env
     load_iface msg mod = initIfaceCheck (text "loader") hsc_env


=====================================
compiler/GHC/Unit/External.hs
=====================================
@@ -45,6 +45,8 @@ type PackageCompleteMatches  = CompleteMatches
 type PackageIfaceTable = ModuleEnv ModIface
         -- Domain = modules in the imported packages
 
+type PackageTypeTable = ModuleEnv TypeEnv
+
 -- | Constructs an empty PackageIfaceTable
 emptyPackageIfaceTable :: PackageIfaceTable
 emptyPackageIfaceTable = emptyModuleEnv
@@ -68,6 +70,7 @@ initExternalPackageState = EPS
   , eps_PIT              = emptyPackageIfaceTable
   , eps_free_holes       = emptyInstalledModuleEnv
   , eps_PTE              = emptyTypeEnv
+  , eps_PTT              = emptyModuleEnv
   , eps_inst_env         = emptyInstEnv
   , eps_fam_inst_env     = emptyFamInstEnv
   , eps_rule_base        = mkRuleBase builtinRules
@@ -139,6 +142,8 @@ data ExternalPackageState
                 -- interface files we have sucked in. The domain of
                 -- the mapping is external-package modules
 
+        eps_PTT :: !PackageTypeTable,
+
         eps_inst_env     :: !PackageInstEnv,   -- ^ The total 'InstEnv' accumulated
                                                -- from all the external-package modules
         eps_fam_inst_env :: !PackageFamInstEnv,-- ^ The total 'FamInstEnv' accumulated


=====================================
testsuite/tests/bytecode/T24634/Hello.hs
=====================================
@@ -7,7 +7,7 @@ module Hello where
 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax
 
-foreign import capi "hello.h say_hello" say_hello :: IO Int
+foreign import capi "hello_c.h say_hello" say_hello :: IO Int
 
 mkHello :: DecsQ
 mkHello = do


=====================================
testsuite/tests/bytecode/T24634/Makefile
=====================================
@@ -3,7 +3,7 @@ include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
 T24634:
-	$(TEST_HC) -c -dynamic hello.c -o hello.o
-	$(TEST_HC) -c -fbyte-code-and-object-code Hello.hs
-	$(TEST_HC) -fprefer-byte-code hello.o Main.hs
+	$(TEST_HC) -c -dynamic hello_c.c -o hello_c.o
+	$(TEST_HC) -c -dynamic -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
+	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -dynamic -fno-ignore-interface-pragmas hello_c.o Main.hs -o Main
 	./Main


=====================================
testsuite/tests/bytecode/T24634/T24634.stdout
=====================================
@@ -1,3 +1,3 @@
-[2 of 3] Compiling Main             ( Main.hs, Main.o )
+[2 of 3] Compiling Main             ( Main.hs, Main.o, interpreted )
 [3 of 3] Linking Main
 42


=====================================
testsuite/tests/bytecode/T24634/all.T
=====================================
@@ -1,8 +1,7 @@
 test('T24634',
-     [extra_files(['hello.h', 'hello.c', 'Hello.hs', 'Main.hs']),
+     [extra_files(['hello_c.h', 'hello_c.c', 'Hello.hs', 'Main.hs']),
       req_c,
       req_th,
-      ignore_stderr
       ],
      makefile_test,
      [])


=====================================
testsuite/tests/bytecode/T24634/hello.c → testsuite/tests/bytecode/T24634/hello_c.c
=====================================
@@ -1,4 +1,4 @@
-#include "hello.h"
+#include "hello_c.h"
 
 int say_hello() {
   return 42;


=====================================
testsuite/tests/bytecode/T24634/hello.h → testsuite/tests/bytecode/T24634/hello_c.h
=====================================


=====================================
testsuite/tests/bytecode/T25090/A.hs
=====================================
@@ -0,0 +1,7 @@
+{-# language TemplateHaskell #-}
+module Main where
+
+import D
+
+main :: IO ()
+main = putStrLn (show ($splc :: Int))


=====================================
testsuite/tests/bytecode/T25090/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import {-# source #-} C (C)
+
+data B = B C


=====================================
testsuite/tests/bytecode/T25090/C.hs
=====================================
@@ -0,0 +1,8 @@
+module C where
+
+import B
+
+data C = C Int
+
+b :: B
+b = B (C 2024)


=====================================
testsuite/tests/bytecode/T25090/C.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module C where
+
+data C


=====================================
testsuite/tests/bytecode/T25090/D.hs
=====================================
@@ -0,0 +1,12 @@
+module D where
+
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+import B
+import C
+
+splc :: ExpQ
+splc =
+  lift @_ @Int num
+  where
+    B (C num) = b


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -0,0 +1,16 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25090a:
+	$(TEST_HC) -c -fbyte-code-and-object-code C.hs-boot
+	$(TEST_HC) -c -fbyte-code-and-object-code B.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code C.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code D.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code -fprefer-byte-code A.hs
+	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code D.o C.o B.o A.o -o exe
+	./exe
+
+T25090b:
+	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
+	./exe


=====================================
testsuite/tests/bytecode/T25090/T25090.stdout
=====================================
@@ -0,0 +1 @@
+2024


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -0,0 +1,14 @@
+def test_T25090(name):
+    return test(name,
+     [extra_files(['A.hs', 'B.hs', 'C.hs-boot', 'C.hs', 'D.hs']),
+      req_th,
+      # TODO why does this not work?
+      js_skip,
+      use_specs({'stdout': 'T25090.stdout'}),
+      ],
+     makefile_test,
+     [])
+
+test_T25090('T25090a')
+
+test_T25090('T25090b')



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/babc710a6dc415f17d3dc49417875a62429b7723...b0026fd3686a842faaba516076bd514060a9f10c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/babc710a6dc415f17d3dc49417875a62429b7723...b0026fd3686a842faaba516076bd514060a9f10c
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/20240803/ba8c8fb1/attachment-0001.html>


More information about the ghc-commits mailing list