Skip to content

Commit 733f9e1

Browse files
committed
Fix after merge of ghc-prim into ghc-internal
1 parent 2ee86bd commit 733f9e1

File tree

2 files changed

+16
-5
lines changed

2 files changed

+16
-5
lines changed

Build.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -167,6 +167,8 @@ buildGhcStage1 opts cabal ghc0 dst = do
167167
ExitSuccess -> pure ()
168168
ExitFailure n -> do
169169
putStrLn $ "cabal-install failed with error code: " ++ show n
170+
putStrLn cabal_stdout
171+
putStrLn cabal_stderr
170172
putStrLn $ "Logs can be found in \"" ++ dst ++ "/cabal.{stdout,stderr}\""
171173
exitFailure
172174

@@ -496,17 +498,17 @@ buildBootLibraries cabal ghc ghcpkg derive_constants genapply genprimop opts dst
496498
run_genapply [derived_constants, "-V32"] (src_rts </> "AutoApply_V32.cmm")
497499
run_genapply [derived_constants, "-V64"] (src_rts </> "AutoApply_V64.cmm")
498500

499-
-- Generate primop code for ghc-prim
501+
-- Generate primop code for ghc-internal
500502
--
501-
-- Note that this can't be done in a Setup.hs for ghc-prim because
503+
-- Note that this can't be done in a Setup.hs for ghc-internal because
502504
-- cabal-install can't build Setup.hs because it depends on base, Cabal, etc.
503505
-- libraries that aren't built yet.
504506
let primops_txt = src </> "libraries/ghc/GHC/Builtin/primops.txt"
505507
let primops_txt_pp = primops_txt <.> ".pp"
506508
primops <- readCreateProcess (shell $ "gcc -E -undef -traditional -P -x c " ++ primops_txt_pp) ""
507509
writeFile primops_txt primops
508-
writeFile (src </> "libraries/ghc-prim/GHC/Prim.hs") =<< readCreateProcess (runGenPrimop genprimop ["--make-haskell-source"]) primops
509-
writeFile (src </> "libraries/ghc-prim/GHC/PrimopWrappers.hs") =<< readCreateProcess (runGenPrimop genprimop ["--make-haskell-wrappers"]) primops
510+
writeFile (src </> "libraries/ghc-internal/src/GHC/Internal/Prim.hs") =<< readCreateProcess (runGenPrimop genprimop ["--make-haskell-source"]) primops
511+
writeFile (src </> "libraries/ghc-internal/src/GHC/Internal/PrimopWrappers.hs") =<< readCreateProcess (runGenPrimop genprimop ["--make-haskell-wrappers"]) primops
510512

511513
-- build libffi
512514
msg " - Building libffi..."

compiler/GHC/Driver/Pipeline.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,8 @@ import GHC.Platform
4949

5050
import GHC.Utils.Monad ( MonadIO(liftIO), mapMaybeM )
5151

52+
import GHC.Builtin.Names
53+
5254
import GHC.Driver.Main
5355
import GHC.Driver.Env hiding ( Hsc )
5456
import GHC.Driver.Errors
@@ -91,6 +93,7 @@ import GHC.Data.StringBuffer ( hPutStringBuffer )
9193
import GHC.Data.Maybe ( expectJust )
9294

9395
import GHC.Iface.Make ( mkFullIface )
96+
import GHC.Iface.Load ( getGhcPrimIface )
9497
import GHC.Runtime.Loader ( initializePlugins )
9598

9699

@@ -817,7 +820,13 @@ hscGenBackendPipeline pipe_env hsc_env mod_sum result = do
817820
let !linkable = Linkable part_time (ms_mod mod_sum) (NE.singleton (DotO final_object ModuleObject))
818821
-- Add the object linkable to the potential bytecode linkable which was generated in HscBackend.
819822
return (mlinkable { homeMod_object = Just linkable })
820-
return (miface, final_linkable)
823+
824+
-- when building ghc-internal with cabal-install, we still want the virtual
825+
-- interface for gHC_PRIM in the cache
826+
let miface_final
827+
| ms_mod mod_sum == gHC_PRIM = getGhcPrimIface hsc_env
828+
| otherwise = miface
829+
return (miface_final, final_linkable)
821830

822831
asPipeline :: P m => Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe ObjFile)
823832
asPipeline use_cpp pipe_env hsc_env location input_fn =

0 commit comments

Comments
 (0)