Matthew Pickering pushed to branch wip/bytecode-library at Glasgow Haskell Compiler / GHC
Commits:
-
99b973a9
by Matthew Pickering at 2025-08-28T17:23:50+01:00
17 changed files:
- compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/Driver/ByteCode.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Unit/Finder.hs
- libraries/ghci/GHCi/Message.hs
- testsuite/tests/cabal/Bytecode.hs
- testsuite/tests/cabal/Makefile
- testsuite/tests/cabal/all.T
- testsuite/tests/cabal/bytecode.pkg
- + testsuite/tests/cabal/bytecode.script
- testsuite/tests/cabal/pkg_bytecode.stderr
- testsuite/tests/cabal/pkg_bytecode.stdout
Changes:
... | ... | @@ -9,6 +9,7 @@ module GHC.ByteCode.Serialize |
9 | 9 | , writeBytecodeLib
|
10 | 10 | , readBytecodeLib
|
11 | 11 | , mkBytecodeLib
|
12 | + , decodeOnDiskByteCodeObject
|
|
12 | 13 | )
|
13 | 14 | where
|
14 | 15 |
... | ... | @@ -6,7 +6,8 @@ import GHC.Prelude |
6 | 6 | import GHC.Driver.Session
|
7 | 7 | import GHC.Driver.CodeOutput
|
8 | 8 | import GHC.Driver.Env
|
9 | -import GHC.Runtime.Interpreter
|
|
9 | +import GHC.Runtime.Interpreter.Types
|
|
10 | + ( interpreterDynamic, interpreterProfiled )
|
|
10 | 11 | import GHC.ByteCode.Types
|
11 | 12 | |
12 | 13 | import GHC.Linker.Types
|
... | ... | @@ -23,9 +24,11 @@ import Data.Time |
23 | 24 | import GHC.Platform.Ways
|
24 | 25 | |
25 | 26 | import GHC.ByteCode.Serialize
|
27 | +import System.OsPath
|
|
26 | 28 | |
27 | 29 | -- | Write foreign sources and foreign stubs to temporary files and compile them.
|
28 | -outputAndCompileForeign :: HscEnv -> Module -> ModLocation -> [(ForeignSrcLang, FilePath)] -> ForeignStubs -> IO [FilePath]
|
|
30 | +outputAndCompileForeign :: HscEnv -> Module -> Maybe OsPath -- ^ Source file location
|
|
31 | + -> [(ForeignSrcLang, FilePath)] -> ForeignStubs -> IO [FilePath]
|
|
29 | 32 | outputAndCompileForeign hsc_env mod_name location foreign_files foreign_stubs = do
|
30 | 33 | let dflags = hsc_dflags hsc_env
|
31 | 34 | logger = hsc_logger hsc_env
|
... | ... | @@ -58,13 +61,13 @@ compile_for_interpreter hsc_env use = |
58 | 61 | adapt_way want = if want (hscInterp hsc_env) then addWay else removeWay
|
59 | 62 | |
60 | 63 | -- | Write the foreign sources and foreign stubs of a bytecode object to temporary files and compile them.
|
61 | -loadByteCodeObject :: HscEnv -> ModLocation -> ByteCodeObject
|
|
64 | +loadByteCodeObject :: HscEnv -> Maybe OsPath -> ByteCodeObject
|
|
62 | 65 | -> IO (CompiledByteCode, [FilePath])
|
63 | 66 | loadByteCodeObject hsc_env location (ByteCodeObject mod cbc foreign_srcs foreign_stubs) = do
|
64 | 67 | fos <- outputAndCompileForeign hsc_env mod location foreign_srcs foreign_stubs
|
65 | 68 | return (cbc, fos)
|
66 | 69 | |
67 | -loadByteCodeObjectLinkable :: HscEnv -> UTCTime -> ModLocation -> ByteCodeObject -> IO Linkable
|
|
70 | +loadByteCodeObjectLinkable :: HscEnv -> UTCTime -> Maybe OsPath -> ByteCodeObject -> IO Linkable
|
|
68 | 71 | loadByteCodeObjectLinkable hsc_env linkable_time location bco = do
|
69 | 72 | ~(cbc, fos) <- loadByteCodeObject hsc_env location bco
|
70 | 73 | return $! Linkable linkable_time (bco_module bco) (BCOs cbc :| [DotO fo ForeignObject | fo <- fos]) |
\ No newline at end of file |
... | ... | @@ -133,7 +133,7 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g |
133 | 133 | ViaCCodeOutput -> outputC logger dflags filenm dus1 final_stream pkg_deps
|
134 | 134 | LlvmCodeOutput -> outputLlvm logger llvm_config dflags filenm dus1 final_stream
|
135 | 135 | JSCodeOutput -> outputJS logger llvm_config dflags filenm final_stream
|
136 | - ; stubs_exist <- outputForeignStubs logger tmpfs dflags unit_state this_mod location stubs
|
|
136 | + ; stubs_exist <- outputForeignStubs logger tmpfs dflags unit_state this_mod (ml_hs_file_ospath $ location) stubs
|
|
137 | 137 | ; return (filenm, stubs_exist, foreign_fps, a)
|
138 | 138 | }
|
139 | 139 | |
... | ... | @@ -269,7 +269,7 @@ outputForeignStubs |
269 | 269 | -> DynFlags
|
270 | 270 | -> UnitState
|
271 | 271 | -> Module
|
272 | - -> ModLocation
|
|
272 | + -> Maybe OsPath -- ^ Source file location
|
|
273 | 273 | -> ForeignStubs
|
274 | 274 | -> IO (Bool, -- Header file created
|
275 | 275 | Maybe FilePath) -- C file created
|
... | ... | @@ -1015,7 +1015,7 @@ checkByteCodeFromObject hsc_env mod_sum = do |
1015 | 1015 | -- that the one we have on disk would be suitable as well.
|
1016 | 1016 | linkable <- unsafeInterleaveIO $ do
|
1017 | 1017 | bco <- readBinByteCode hsc_env obj_fn
|
1018 | - loadByteCodeObjectLinkable hsc_env obj_date (ms_location mod_sum) bco
|
|
1018 | + loadByteCodeObjectLinkable hsc_env obj_date (ml_hs_file_ospath $ ms_location mod_sum) bco
|
|
1019 | 1019 | return $ UpToDateItem linkable
|
1020 | 1020 | _ -> return $ outOfDateItemBecause MissingBytecode Nothing
|
1021 | 1021 | |
... | ... | @@ -2163,7 +2163,7 @@ hscInteractive hsc_env cgguts location = do |
2163 | 2163 | let tmpfs = hsc_tmpfs hsc_env
|
2164 | 2164 | ------------------ Create f-x-dynamic C-side stuff -----
|
2165 | 2165 | (_istub_h_exists, istub_c_exists)
|
2166 | - <- outputForeignStubs logger tmpfs dflags (hsc_units hsc_env) (cgi_module cgguts) location (cgi_foreign cgguts)
|
|
2166 | + <- outputForeignStubs logger tmpfs dflags (hsc_units hsc_env) (cgi_module cgguts) (ml_hs_file_ospath $ location) (cgi_foreign cgguts)
|
|
2167 | 2167 | return (istub_c_exists, comp_bc)
|
2168 | 2168 | |
2169 | 2169 | |
... | ... | @@ -2214,7 +2214,7 @@ generateByteCode :: HscEnv |
2214 | 2214 | -> IO (CompiledByteCode, [FilePath])
|
2215 | 2215 | generateByteCode hsc_env cgguts mod_location = do
|
2216 | 2216 | comp_bc' <- hscGenerateByteCode hsc_env cgguts mod_location
|
2217 | - fos <- outputAndCompileForeign hsc_env (cgi_module cgguts) mod_location (cgi_foreign_files cgguts) (cgi_foreign cgguts)
|
|
2217 | + fos <- outputAndCompileForeign hsc_env (cgi_module cgguts) (ml_hs_file_ospath $ mod_location) (cgi_foreign_files cgguts) (cgi_foreign cgguts)
|
|
2218 | 2218 | pure (comp_bc', fos)
|
2219 | 2219 | |
2220 | 2220 | -- | Generate a byte code object linkable and write it to a file if `-fwrite-bytecode` is enabled.
|
... | ... | @@ -2234,7 +2234,7 @@ generateAndWriteByteCodeLinkable hsc_env cgguts mod_location = do |
2234 | 2234 | -- It's important the time of the linkable matches the time of the .gbc file for recompilation
|
2235 | 2235 | -- checking.
|
2236 | 2236 | bco_time <- maybe getCurrentTime pure =<< modificationTimeIfExists (ml_bytecode_file mod_location)
|
2237 | - loadByteCodeObjectLinkable hsc_env bco_time mod_location bco_object
|
|
2237 | + loadByteCodeObjectLinkable hsc_env bco_time (ml_hs_file_ospath $ mod_location) bco_object
|
|
2238 | 2238 | |
2239 | 2239 | mkByteCodeObject :: HscEnv -> Module -> ModLocation -> CgInteractiveGuts -> IO ByteCodeObject
|
2240 | 2240 | mkByteCodeObject hsc_env mod mod_location cgguts = do
|
... | ... | @@ -2249,7 +2249,7 @@ generateFreshByteCodeLinkable :: HscEnv |
2249 | 2249 | generateFreshByteCodeLinkable hsc_env mod_name cgguts mod_location = do
|
2250 | 2250 | bco_time <- getCurrentTime
|
2251 | 2251 | bco_object <- mkByteCodeObject hsc_env (mkHomeModule (hsc_home_unit hsc_env) mod_name) mod_location cgguts
|
2252 | - loadByteCodeObjectLinkable hsc_env bco_time mod_location bco_object
|
|
2252 | + loadByteCodeObjectLinkable hsc_env bco_time (ml_hs_file_ospath $ mod_location) bco_object
|
|
2253 | 2253 | ------------------------------
|
2254 | 2254 | |
2255 | 2255 | hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> FilePath -> IO (Maybe FilePath)
|
... | ... | @@ -423,6 +423,13 @@ link' hsc_env batch_attempt_linking mHscMessager hpt |
423 | 423 | return Succeeded
|
424 | 424 | else do
|
425 | 425 | |
426 | + -- TODO: This is very awkward.
|
|
427 | + |
|
428 | + -- 1. Ban using --make mode to create -bytecodelib, since then you would not need in-memory linkables
|
|
429 | + -- 2. Make Linkable and ByteCodeObject more similar, so that you can translate between them.
|
|
430 | + -- * Either store .o files in ByteCodeObject <-- MP thinks this way
|
|
431 | + -- * or Store ForeignStubs/ForeignSrcs in Linkable
|
|
432 | + -- 3. Store ByteCodeObject in Linkable directly
|
|
426 | 433 | let hackyMPtodo l = [ ByteCodeObject (linkableModule l) cbc [] NoStubs | cbc <- linkableBCOs l ]
|
427 | 434 | |
428 | 435 | let linkObjectLinkable action =
|
... | ... | @@ -132,6 +132,7 @@ import qualified Data.IntMap.Strict as IM |
132 | 132 | import qualified Data.Map.Strict as M
|
133 | 133 | import Foreign.Ptr (nullPtr)
|
134 | 134 | import GHC.ByteCode.Serialize
|
135 | +import GHC.Data.Maybe (expectJust)
|
|
135 | 136 | |
136 | 137 | -- Note [Linkers and loaders]
|
137 | 138 | -- ~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... | ... | @@ -659,7 +660,7 @@ findBytecodeLinkableMaybe hsc_env mod locn = do |
659 | 660 | loadInterface (text "get_reachable_nodes" <+> parens (ppr mod))
|
660 | 661 | mod ImportBySystem
|
661 | 662 | bco <- readBinByteCode hsc_env bytecode_fn
|
662 | - Just <$> loadByteCodeObjectLinkable hsc_env bytecode_time locn bco
|
|
663 | + Just <$> loadByteCodeObjectLinkable hsc_env bytecode_time (ml_hs_file_ospath $ locn) bco
|
|
663 | 664 | |
664 | 665 | get_reachable_nodes :: HscEnv -> [Module] -> IO ([Module], UniqDSet UnitId)
|
665 | 666 | get_reachable_nodes hsc_env mods
|
... | ... | @@ -1155,16 +1156,16 @@ loadPackages interp hsc_env new_pkgs = do |
1155 | 1156 | |
1156 | 1157 | loadPackages' :: Interp -> HscEnv -> [UnitId] -> LoaderState -> IO LoaderState
|
1157 | 1158 | loadPackages' interp hsc_env new_pks pls = do
|
1158 | - pkgs' <- link (pkgs_loaded pls) new_pks
|
|
1159 | - return $! pls { pkgs_loaded = pkgs'
|
|
1160 | - }
|
|
1159 | + pls' <- link pls new_pks
|
|
1160 | + return $! pls'
|
|
1161 | 1161 | where
|
1162 | - link :: PkgsLoaded -> [UnitId] -> IO PkgsLoaded
|
|
1162 | + link :: LoaderState -> [UnitId] -> IO LoaderState
|
|
1163 | 1163 | link pkgs new_pkgs =
|
1164 | 1164 | foldM link_one pkgs new_pkgs
|
1165 | 1165 | |
1166 | + link_one :: LoaderState -> UnitId -> IO LoaderState
|
|
1166 | 1167 | link_one pkgs new_pkg
|
1167 | - | new_pkg `elemUDFM` pkgs -- Already linked
|
|
1168 | + | new_pkg `elemUDFM` (pkgs_loaded pkgs) -- Already linked
|
|
1168 | 1169 | = return pkgs
|
1169 | 1170 | |
1170 | 1171 | | Just pkg_cfg <- lookupUnitId (hsc_units hsc_env) new_pkg
|
... | ... | @@ -1172,19 +1173,15 @@ loadPackages' interp hsc_env new_pks pls = do |
1172 | 1173 | -- Link dependents first
|
1173 | 1174 | ; pkgs' <- link pkgs deps
|
1174 | 1175 | -- Now link the package itself
|
1175 | - ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
|
|
1176 | - ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
|
|
1177 | - | dep_pkg <- deps
|
|
1178 | - , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
|
|
1179 | - ]
|
|
1180 | - ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
|
|
1176 | + ; loadPackage interp hsc_env pkg_cfg pkgs'
|
|
1177 | + }
|
|
1181 | 1178 | |
1182 | 1179 | | otherwise
|
1183 | 1180 | = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
|
1184 | 1181 | |
1185 | 1182 | |
1186 | -loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
|
|
1187 | -loadPackage interp hsc_env pkg
|
|
1183 | +loadPackage :: Interp -> HscEnv -> UnitInfo -> LoaderState -> IO LoaderState
|
|
1184 | +loadPackage interp hsc_env pkg pls
|
|
1188 | 1185 | = do
|
1189 | 1186 | let dflags = hsc_dflags hsc_env
|
1190 | 1187 | let logger = hsc_logger hsc_env
|
... | ... | @@ -1268,7 +1265,7 @@ loadPackage interp hsc_env pkg |
1268 | 1265 | -- step to resolve everything.
|
1269 | 1266 | mapM_ (loadObj interp) objs
|
1270 | 1267 | mapM_ (loadArchive interp) archs
|
1271 | - mapM_ (loadBytecodeLibrary interp) bytecodes
|
|
1268 | + pls' <- foldM (loadBytecodeLibrary hsc_env interp) pls bytecodes
|
|
1272 | 1269 | |
1273 | 1270 | maybePutStr logger "linking ... "
|
1274 | 1271 | ok <- resolveObjs interp
|
... | ... | @@ -1282,11 +1279,35 @@ loadPackage interp hsc_env pkg |
1282 | 1279 | if succeeded ok
|
1283 | 1280 | then do
|
1284 | 1281 | maybePutStrLn logger "done."
|
1285 | - return (hs_classifieds, extra_classifieds, loaded_dlls)
|
|
1282 | + let deps = unitDepends pkg
|
|
1283 | + let new_pkg = unitId pkg
|
|
1284 | + let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
|
|
1285 | + | dep_pkg <- deps
|
|
1286 | + , Just loaded_pkg_info <- pure (lookupUDFM (pkgs_loaded pls') dep_pkg)
|
|
1287 | + ]
|
|
1288 | + let new_pkg_info = LoadedPkgInfo new_pkg hs_classifieds extra_classifieds loaded_dlls trans_deps
|
|
1289 | + return pls' { pkgs_loaded = addToUDFM (pkgs_loaded pls') new_pkg new_pkg_info }
|
|
1290 | + --return (addToUDFM pkgs' new_pkg new_pkg_info)
|
|
1291 | + -- return (hs_classifieds, extra_classifieds, loaded_dlls)
|
|
1286 | 1292 | else let errmsg = text "unable to load unit `"
|
1287 | 1293 | <> pprUnitInfoForUser pkg <> text "'"
|
1288 | 1294 | in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
|
1289 | 1295 | |
1296 | + |
|
1297 | +loadBytecodeLibrary :: HscEnv -> Interp -> LoaderState -> FilePath -> IO LoaderState
|
|
1298 | +loadBytecodeLibrary hsc_env interp pls path = do
|
|
1299 | + path' <- canonicalizePath path -- Note [loadObj and relative paths]
|
|
1300 | + -- TODO: see loadModuleLinkables in GHC/Linker/Loader.hs
|
|
1301 | + -- 0. Get the modification time of the module
|
|
1302 | + mod_time <- expectJust <$> modificationTimeIfExists path'
|
|
1303 | + -- 1. Read the bytecode library
|
|
1304 | + (BytecodeLib bcos) <- readBytecodeLib hsc_env path'
|
|
1305 | + bcos' <- mapM (decodeOnDiskByteCodeObject hsc_env) bcos
|
|
1306 | + linkables <- mapM (loadByteCodeObjectLinkable hsc_env mod_time Nothing) bcos'
|
|
1307 | + (pls', _) <- loadModuleLinkables interp hsc_env pls linkables
|
|
1308 | + return pls'
|
|
1309 | + |
|
1310 | + |
|
1290 | 1311 | {-
|
1291 | 1312 | Note [Crash early load_dyn and locateLib]
|
1292 | 1313 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... | ... | @@ -155,7 +155,7 @@ data LoaderState = LoaderState |
155 | 155 | -- ^ And the currently-loaded compiled modules (home package)
|
156 | 156 | |
157 | 157 | , pkgs_loaded :: !PkgsLoaded
|
158 | - -- ^ The currently-loaded packages; always object code
|
|
158 | + -- ^ The currently-loaded packages;
|
|
159 | 159 | -- haskell libraries, system libraries, transitive dependencies
|
160 | 160 | |
161 | 161 | , temp_sos :: ![(FilePath, String)]
|
... | ... | @@ -41,7 +41,6 @@ module GHC.Runtime.Interpreter |
41 | 41 | , loadDLL
|
42 | 42 | , loadArchive
|
43 | 43 | , loadObj
|
44 | - , loadBytecodeLibrary
|
|
45 | 44 | , unloadObj
|
46 | 45 | , addLibrarySearchPath
|
47 | 46 | , removeLibrarySearchPath
|
... | ... | @@ -78,6 +77,9 @@ import GHCi.RemoteTypes |
78 | 77 | import GHCi.ResolvedBCO
|
79 | 78 | import GHCi.BreakArray (BreakArray)
|
80 | 79 | import GHC.ByteCode.Breakpoints
|
80 | +import GHC.ByteCode.Serialize
|
|
81 | +import GHC.Driver.Env
|
|
82 | +import GHC.Driver.ByteCode
|
|
81 | 83 | |
82 | 84 | import GHC.ByteCode.Types
|
83 | 85 | import GHC.Linker.Types
|
... | ... | @@ -117,6 +119,7 @@ import qualified GHC.InfoProv as InfoProv |
117 | 119 | import GHC.Builtin.Names
|
118 | 120 | import GHC.Types.Name
|
119 | 121 | import qualified GHC.Unit.Home.Graph as HUG
|
122 | +import GHC.Utils.Misc
|
|
120 | 123 | |
121 | 124 | -- Standard libraries
|
122 | 125 | import GHC.Exts
|
... | ... | @@ -573,10 +576,6 @@ loadArchive interp path = do |
573 | 576 | path' <- canonicalizePath path -- Note [loadObj and relative paths]
|
574 | 577 | interpCmd interp (LoadArchive path')
|
575 | 578 | |
576 | -loadBytecodeLibrary :: Interp -> String -> IO ()
|
|
577 | -loadBytecodeLibrary interp path = do
|
|
578 | - path' <- canonicalizePath path -- Note [loadObj and relative paths]
|
|
579 | - putStrLn $ "I would load bytecode library but I'm not implemented yet" ++ path'
|
|
580 | 579 | |
581 | 580 | loadObj :: Interp -> String -> IO ()
|
582 | 581 | loadObj interp path = do
|
... | ... | @@ -781,16 +781,16 @@ mkBytecodePath fopts basename mod_basename = bytecode_basename <.> bytecodesuf |
781 | 781 | mkStubPaths
|
782 | 782 | :: FinderOpts
|
783 | 783 | -> ModuleName
|
784 | - -> ModLocation
|
|
785 | 784 | -> Maybe OsPath
|
786 | -mkStubPaths fopts mod location = do
|
|
785 | + -> Maybe OsPath
|
|
786 | +mkStubPaths fopts mod hs_file_location = do
|
|
787 | 787 | stub_basename <- in_stub_dir <|> src_basename
|
788 | 788 | pure (stub_basename `mappend` os "_stub" <.> os "h")
|
789 | 789 | where
|
790 | 790 | in_stub_dir = (</> mod_basename) <$> (finder_stubDir fopts)
|
791 | 791 | |
792 | 792 | mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod
|
793 | - src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
|
|
793 | + src_basename = OsPath.dropExtension <$> hs_file_location
|
|
794 | 794 | |
795 | 795 | -- -----------------------------------------------------------------------------
|
796 | 796 | -- findLinkable isn't related to the other stuff in here,
|
... | ... | @@ -86,6 +86,7 @@ data Message a where |
86 | 86 | LookupClosure :: String -> Message (Maybe HValueRef)
|
87 | 87 | LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
|
88 | 88 | LoadArchive :: String -> Message () -- error?
|
89 | + LoadBytecode :: String -> Message ()
|
|
89 | 90 | LoadObj :: String -> Message () -- error?
|
90 | 91 | UnloadObj :: String -> Message () -- error?
|
91 | 92 | AddLibrarySearchPath :: String -> Message (RemotePtr ())
|
... | ... | @@ -593,6 +594,7 @@ getMessage = do |
593 | 594 | 38 -> Msg <$> (ResumeSeq <$> get)
|
594 | 595 | 39 -> Msg <$> (LookupSymbolInDLL <$> get <*> get)
|
595 | 596 | 40 -> Msg <$> (WhereFrom <$> get)
|
597 | + 41 -> Msg <$> (LoadBytecode <$> get)
|
|
596 | 598 | _ -> error $ "Unknown Message code " ++ (show b)
|
597 | 599 | |
598 | 600 | putMessage :: Message a -> Put
|
1 | 1 | module Bytecode where
|
2 | 2 | |
3 | -bytecode = "bytecode" |
|
3 | +bytecode = "bytecode from a package" |
... | ... | @@ -300,9 +300,8 @@ PKGCONF08=bytecode.package.conf |
300 | 300 | LOCAL_GHC_PKG08 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONF08)
|
301 | 301 | pkg_bytecode :
|
302 | 302 | $(LOCAL_GHC_PKG08) init $(PKGCONF08)
|
303 | - @echo "bytecode-library-dirs: \$${pkgroot}" >> bytecode.pkg
|
|
304 | - @echo "import-dirs: \$${pkgroot}" >> bytecode.pkg
|
|
305 | - @echo "library-dirs: \$${pkgroot}" >> bytecode.pkg
|
|
303 | + mkdir outdir
|
|
304 | + mv Bytecode.hs outdir/
|
|
305 | + cd outdir && $(TEST_HC) -bytecodelib -hisuf=dyn_hi -dynamic -o testpkg-1.2.3.4-XXX.bytecode Bytecode.hs -fbyte-code -fwrite-interface -fwrite-byte-code -this-unit-id=testpkg-1.2.3.4-XXX
|
|
306 | 306 | $(LOCAL_GHC_PKG08) register --force bytecode.pkg
|
307 | - $(TEST_HC) -bytecodelib -o testpkg-1.2.3.4-XXX.bytecode Bytecode.hs -fbyte-code -fwrite-interface -fwrite-byte-code
|
|
308 | - $(TEST_HC) --interactive -package testpkg -package-db $(PKGCONF08) |
|
307 | + cat bytecode.script | $(TEST_HC) --interactive -package testpkg -package-db $(PKGCONF08) |
... | ... | @@ -35,7 +35,7 @@ test('ghcpkg06', [extra_files(['test.pkg', 'testdup.pkg'])], makefile_test, []) |
35 | 35 | |
36 | 36 | test('ghcpkg07', [extra_files(['test.pkg', 'test7a.pkg', 'test7b.pkg'])], makefile_test, [])
|
37 | 37 | |
38 | -test('pkg_bytecode', [extra_files(['bytecode.pkg', 'Bytecode.hs']), copy_files], makefile_test, [])
|
|
38 | +test('pkg_bytecode', [extra_files(['bytecode.pkg', 'Bytecode.hs', "bytecode.script"]), copy_files], makefile_test, [])
|
|
39 | 39 | |
40 | 40 | # Test that we *can* compile a module that also belongs to a package
|
41 | 41 | # (this was disallowed in GHC 6.4 and earlier)
|
... | ... | @@ -13,7 +13,8 @@ category: none |
13 | 13 | author: simonmar@microsoft.com
|
14 | 14 | exposed: True
|
15 | 15 | exposed-modules: Bytecode
|
16 | -import-dirs:
|
|
17 | -library-dirs:
|
|
16 | +import-dirs: ${pkgroot}/outdir
|
|
17 | +library-dirs: ${pkgroot}/outdir
|
|
18 | 18 | include-dirs:
|
19 | +bytecode-library-dirs: ${pkgroot}/outdir
|
|
19 | 20 | hs-libraries: testpkg-1.2.3.4-XXX |
1 | +import Bytecode
|
|
2 | +bytecode |
1 | -testpkg-1.2.3.4: cannot find any of ["Bytecode.hi","Bytecode.p_hi","Bytecode.dyn_hi","Bytecode.p_dyn_hi"] (ignoring)
|
|
2 | 1 | testpkg-1.2.3.4: cannot find any of ["libtestpkg-1.2.3.4-XXX.a","libtestpkg-1.2.3.4-XXX_p.a","libtestpkg-1.2.3.4-XXX-ghc9.15.20250811.so","libtestpkg-1.2.3.4-XXX_p-ghc9.15.20250811.so","libtestpkg-1.2.3.4-XXX-ghc9.15.20250811.dylib","libtestpkg-1.2.3.4-XXX_p-ghc9.15.20250811.dylib","testpkg-1.2.3.4-XXX-ghc9.15.20250811.dll","testpkg-1.2.3.4-XXX_p-ghc9.15.20250811.dll"] on library path (ignoring)
|
3 | -hs_classifieds [BytecodeLibrary ./testpkg-1.2.3.4-XXX.bytecode]
|
|
2 | +hs_classifieds
|
|
3 | + [BytecodeLibrary ./outdir/testpkg-1.2.3.4-XXX.bytecode]
|
|
4 | 4 | hs_classifieds
|
5 | 5 | [DLLPath /home/matt/ghc-bytecode/_new/stage1/lib/../lib/x86_64-linux-ghc-9.15.20250811/libHSghc-internal-9.1500.0-inplace-ghc9.15.20250811.so]
|
6 | 6 | hs_classifieds
|
1 | -Reading package info from "bytecode.pkg" ... done.
|
|
2 | 1 | [1 of 2] Compiling Bytecode ( Bytecode.hs, interpreted )
|
3 | 2 | [2 of 2] Linking testpkg-1.2.3.4-XXX.bytecode
|
3 | +Reading package info from "bytecode.pkg" ... done.
|
|
4 | 4 | GHCi, version 9.15.20250811: https://www.haskell.org/ghc/ :? for help
|
5 | -I would load bytecode library but I'm not implemented yet/tmp/nix-shell-4063774-0/ghctest-8522p1jo/test spaces/testsuite/tests/cabal/pkg_bytecode.run/testpkg-1.2.3.4-XXX.bytecode
|
|
5 | +ghci> ghci> "bytecode from a package"
|
|
6 | 6 | ghci> Leaving GHCi. |