[Git][ghc/ghc][wip/torsten.schmits/oneshot-bytecode-squashed] Oneshot bytecode linking

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



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


Commits:
79b0072b by Cheng Shao at 2024-07-18T14:30:21+02:00
Oneshot bytecode linking

- - - - -


12 changed files:

- compiler/GHC/Driver/Main.hs
- + compiler/GHC/Driver/Main.hs-boot
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Module/ModIface.hs
- testsuite/tests/bytecode/T24634/Makefile
- + testsuite/tests/bytecode/T24634/T24634.stdout
- testsuite/tests/bytecode/T24634/all.T


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -106,6 +106,7 @@ module GHC.Driver.Main
     , showModuleIndex
     , hscAddSptEntries
     , writeInterfaceOnlyMode
+    , loadByteCode
     ) where
 
 import GHC.Prelude
@@ -292,6 +293,8 @@ import GHC.Types.TypeEnv
 import System.IO
 import {-# SOURCE #-} GHC.Driver.Pipeline
 import Data.Time
+import Data.Traversable
+import qualified Data.ByteString as BS
 
 import System.IO.Unsafe ( unsafeInterleaveIO )
 import GHC.Iface.Env ( trace_if )
@@ -991,7 +994,18 @@ initModDetails 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) = LM utc_time this_mod <$> mapM go uls
+initWholeCoreBindings hsc_env mod_iface details (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
+  -- them to temporary objects and refer to them as unlinked items
+  -- directly.
+  stub_uls <- for (mi_stub_objs mod_iface) $ \stub_obj -> do
+    f <- newTempName (hsc_logger hsc_env) (hsc_tmpfs hsc_env) (tmpDir (hsc_dflags hsc_env)) TFL_GhcSession "dyn_o"
+    BS.writeFile f stub_obj
+    pure $ DotO f
+  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)
@@ -1005,9 +1019,6 @@ initWholeCoreBindings hsc_env mod_iface details (LM utc_time this_mod uls) = LM
         -- in the interface file.
         LoadedBCOs <$> (unsafeInterleaveIO $ do
                   core_binds <- initIfaceCheck (text "l") hsc_env' $ typecheckWholeCoreBindings types_var fi
-                  -- MP: The NoStubs here is only from (I think) the TH `qAddForeignFilePath` feature but it's a bit unclear what to do
-                  -- with these files, do we have to read and serialise the foreign file? I will leave it for now until someone
-                  -- reports a bug.
                   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))
@@ -2044,7 +2055,10 @@ generateByteCode hsc_env cgguts mod_location = do
   stub_o <- case hasStub of
             Nothing -> return []
             Just stub_c -> do
-                stub_o <- compileForeign hsc_env LangC stub_c
+                -- Always compile foreign stubs as shared objects so
+                -- they can be properly loaded later when the bytecode
+                -- is loaded.
+                stub_o <- compileForeign (hscUpdateFlags setDynamicNow hsc_env) LangC stub_c
                 return [DotO stub_o]
 
   let hs_unlinked = [BCOs comp_bc spt_entries]


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


=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -796,7 +796,7 @@ hscBackendPipeline pipe_env hsc_env mod_sum result =
       HscUpdate iface ->  return (iface, 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
=====================================
@@ -582,9 +582,23 @@ runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
              do
               output_fn <- phaseOutputFilenameNew next_phase pipe_env hsc_env (Just location)
               (outputFilename, mStub, foreign_files, stg_infos, cg_infos) <-
-
                 hscGenHardCode hsc_env cgguts mod_location output_fn
-              final_iface <- mkFullIface hsc_env partial_iface stg_infos cg_infos
+
+              -- 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
+              foreign_os <-
+                mapM (uncurry (compileForeign hsc_env_stub)) foreign_files
+              let fos = maybe [] return stub_o ++ foreign_os
+                  iface_fos
+                    | gopt Opt_WriteIfSimplifiedCore dflags = fos
+                    | otherwise = []
+
+              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
@@ -596,12 +610,6 @@ runHscBackendPhase pipe_env hsc_env mod_name src_flavour location result = do
 
                   else return emptyHomeModInfoLinkable
 
-
-              stub_o <- mapM (compileStub hsc_env) mStub
-              foreign_os <-
-                mapM (uncurry (compileForeign hsc_env)) foreign_files
-              let fos = (maybe [] return stub_o ++ foreign_os)
-
               -- This is awkward, no linkable is produced here because we still
               -- have some way to do before the object file is produced
               -- In future we can split up the driver logic more so that this function


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -516,11 +516,6 @@ loadInterface doc_str mod from
         ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface)
 
         ; let final_iface = iface
-                               & set_mi_decls     (panic "No mi_decls in PIT")
-                               & set_mi_insts     (panic "No mi_insts in PIT")
-                               & set_mi_fam_insts (panic "No mi_fam_insts in PIT")
-                               & set_mi_rules     (panic "No mi_rules in PIT")
-                               & set_mi_anns      (panic "No mi_anns in PIT")
 
         ; let bad_boot = mi_boot iface == IsBoot
                           && isJust (lookupKnotVars (if_rec_types gbl_env) mod)


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -12,6 +12,7 @@
 module GHC.Iface.Make
    ( mkPartialIface
    , mkFullIface
+   , mkFullIfaceWithForeignStubs
    , mkIfaceTc
    , mkIfaceExports
    )
@@ -89,6 +90,8 @@ import GHC.Unit.Module.ModGuts
 import GHC.Unit.Module.ModSummary
 import GHC.Unit.Module.Deps
 
+import qualified Data.ByteString as BS
+import Data.Traversable
 import Data.Function
 import Data.List ( sortBy )
 import Data.Ord
@@ -127,23 +130,30 @@ 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 -> IO ModIface
-mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = 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
           | otherwise
           = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos
 
+    stub_objs <- for fos BS.readFile
+
     full_iface <-
       {-# SCC "addFingerprints" #-}
-      addFingerprints hsc_env (set_mi_decls decls partial_iface)
+      addFingerprints hsc_env $ set_mi_stub_objs stub_objs $ set_mi_decls decls partial_iface
 
     -- Debug printing
     let unit_state = hsc_units hsc_env


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -52,10 +52,14 @@ import Control.Applicative
 
 import qualified Data.Set as Set
 import qualified Data.Map as M
-import Data.List (isSuffixOf)
 
 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
@@ -71,6 +75,7 @@ data LinkDepsOpts = LinkDepsOpts
   , ldWays        :: !Ways                          -- ^ Enabled ways
   , ldLoadIface   :: SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)
                                                     -- ^ Interface loader function
+  , ldHscEnv      :: !HscEnv
   }
 
 data LinkDeps = LinkDeps
@@ -141,7 +146,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         -- 3.  For each dependent module, find its linkable
         --     This will either be in the HPT or (in the case of one-shot
         --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
+      lnks_needed <- mapM get_linkable mods_needed
 
       return $ LinkDeps
         { ldNeededLinkables = lnks_needed
@@ -267,7 +272,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
+    get_linkable mod      -- A home-package module
         | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
         = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
         | otherwise
@@ -284,13 +289,28 @@ 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 "makima") mod
+                  case mi_extra_decls iface of
+                    Just extra_decls -> do
+                      details <- initModDetails hsc_env iface
+                      t <- getCurrentTime
+                      initWholeCoreBindings hsc_env iface details $ LM t mod [CoreBindings $ WholeCoreBindings extra_decls mod undefined]
+                    _ -> 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
@@ -301,9 +321,13 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                         return lnk
 
             adjust_ul new_osuf (DotO file) = do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
+                -- file may already has new_osuf suffix. One example
+                -- is when we load bytecode from whole core bindings,
+                -- then the corresponding foreign stub objects are
+                -- compiled as shared objects and file may already has
+                -- .dyn_o suffix. And it's okay as long as the file to
+                -- load is already there.
+                let new_file = file -<.> new_osuf
                 ok <- doesFileExist new_file
                 if (not ok)
                    then dieWith opts span $
@@ -408,4 +432,3 @@ failNonStd opts srcspan = dieWith opts srcspan $
             Prof -> "with -prof"
             Dyn -> "with -dynamic"
 #endif
-


=====================================
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/Module/ModIface.hs
=====================================
@@ -22,6 +22,7 @@ module GHC.Unit.Module.ModIface
       , mi_anns
       , mi_decls
       , mi_extra_decls
+      , mi_stub_objs
       , mi_top_env
       , mi_insts
       , mi_fam_insts
@@ -56,6 +57,7 @@ module GHC.Unit.Module.ModIface
    , set_mi_rules
    , set_mi_decls
    , set_mi_extra_decls
+   , set_mi_stub_objs
    , set_mi_top_env
    , set_mi_hpc
    , set_mi_trust
@@ -119,6 +121,7 @@ import GHC.Utils.Binary
 import Control.DeepSeq
 import Control.Exception
 import qualified GHC.Data.Strict as Strict
+import Data.ByteString (ByteString)
 
 {- Note [Interface file stages]
    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -282,6 +285,13 @@ data ModIface_ (phase :: ModIfacePhase)
                 -- combined with mi_decls allows us to restart code generation.
                 -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs]
 
+        mi_stub_objs_ :: ![ByteString],
+                -- ^ Serialized foreign stub dynamic objects when
+                -- compiled with -fbyte-code-and-object-code, empty
+                -- and unused in other cases. This is required to make
+                -- whole core bindings properly work with foreign
+                -- stubs (see #24634).
+
         mi_top_env_  :: !(Maybe IfaceTopEnv),
                 -- ^ Just enough information to reconstruct the top level environment in
                 -- the /original source/ code for this module. which
@@ -453,6 +463,7 @@ instance Binary ModIface where
                  mi_anns_      = anns,
                  mi_decls_     = decls,
                  mi_extra_decls_ = extra_decls,
+                 mi_stub_objs_ = stub_objs,
                  mi_insts_     = insts,
                  mi_fam_insts_ = fam_insts,
                  mi_rules_     = rules,
@@ -497,6 +508,7 @@ instance Binary ModIface where
         lazyPut bh anns
         put_ bh decls
         put_ bh extra_decls
+        put_ bh stub_objs
         put_ bh insts
         put_ bh fam_insts
         lazyPut bh rules
@@ -529,6 +541,7 @@ instance Binary ModIface where
         anns        <- {-# SCC "bin_anns" #-} lazyGet bh
         decls       <- {-# SCC "bin_tycldecls" #-} get bh
         extra_decls <- get bh
+        stub_objs   <- get bh
         insts       <- {-# SCC "bin_insts" #-} get bh
         fam_insts   <- {-# SCC "bin_fam_insts" #-} get bh
         rules       <- {-# SCC "bin_rules" #-} lazyGet bh
@@ -558,6 +571,7 @@ instance Binary ModIface where
                  mi_warns_       = warns,
                  mi_decls_       = decls,
                  mi_extra_decls_ = extra_decls,
+                 mi_stub_objs_   = stub_objs,
                  mi_top_env_     = Nothing,
                  mi_insts_       = insts,
                  mi_fam_insts_   = fam_insts,
@@ -611,6 +625,7 @@ emptyPartialModIface mod
         mi_rules_       = [],
         mi_decls_       = [],
         mi_extra_decls_ = Nothing,
+        mi_stub_objs_   = [],
         mi_top_env_     = Nothing,
         mi_hpc_         = False,
         mi_trust_       = noIfaceTrustInfo,
@@ -664,7 +679,7 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase))
   rnf (PrivateModIface
                { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_
                , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_
-               , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_
+               , mi_decls_, mi_extra_decls_, mi_stub_objs_, mi_top_env_, mi_insts_
                , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_
                , mi_complete_matches_, mi_docs_, mi_final_exts_
                , mi_ext_fields_, mi_src_hash_ })
@@ -681,6 +696,7 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase))
     `seq` rnf mi_anns_
     `seq` rnf mi_decls_
     `seq` rnf mi_extra_decls_
+    `seq` rnf mi_stub_objs_
     `seq` rnf mi_top_env_
     `seq` rnf mi_insts_
     `seq` rnf mi_fam_insts_
@@ -844,6 +860,9 @@ set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val }
 set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase
 set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val }
 
+set_mi_stub_objs :: [ByteString] -> ModIface_ phase -> ModIface_ phase
+set_mi_stub_objs stub_objs iface = clear_mi_hi_bytes $ iface { mi_stub_objs_ = stub_objs }
+
 set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
 set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val }
 
@@ -940,6 +959,7 @@ However, with the pragma, the correct core is generated:
 {-# INLINE mi_anns #-}
 {-# INLINE mi_decls #-}
 {-# INLINE mi_extra_decls #-}
+{-# INLINE mi_stub_objs #-}
 {-# INLINE mi_top_env #-}
 {-# INLINE mi_insts #-}
 {-# INLINE mi_fam_insts #-}
@@ -957,7 +977,7 @@ However, with the pragma, the correct core is generated:
 pattern ModIface ::
   Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] ->
   [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings ->
-  [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] ->
+  [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> [ByteString] ->
   Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] ->
   AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs ->
   IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase ->
@@ -975,6 +995,7 @@ pattern ModIface
   , mi_anns
   , mi_decls
   , mi_extra_decls
+  , mi_stub_objs
   , mi_top_env
   , mi_insts
   , mi_fam_insts
@@ -1001,6 +1022,7 @@ pattern ModIface
     , mi_anns_ = mi_anns
     , mi_decls_ = mi_decls
     , mi_extra_decls_ = mi_extra_decls
+    , mi_stub_objs_ = mi_stub_objs
     , mi_top_env_ = mi_top_env
     , mi_insts_ = mi_insts
     , mi_fam_insts_ = mi_fam_insts


=====================================
testsuite/tests/bytecode/T24634/Makefile
=====================================
@@ -2,8 +2,8 @@ TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
-bytecode-capi:
-	$(TEST_HC) -c hello.c
+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
 	./Main


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


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



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/79b0072bd6f04e90132b6c2b6e2cf7f9481ec9ac

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/79b0072bd6f04e90132b6c2b6e2cf7f9481ec9ac
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/a3159389/attachment-0001.html>


More information about the ghc-commits mailing list