[Git][ghc/ghc][wip/hadrian-cross-stage2] 2 commits: Set cross-prefix appropiately

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Thu Sep 21 15:12:34 UTC 2023



Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC


Commits:
60a48d61 by Matthew Pickering at 2023-09-21T16:12:18+01:00
Set cross-prefix appropiately

- - - - -
20547b8d by Matthew Pickering at 2023-09-21T16:12:24+01:00
misleading comment

- - - - -


5 changed files:

- hadrian/src/Oracles/Setting.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/CabalReinstall.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs


Changes:

=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -255,7 +255,7 @@ targetStage :: Stage -> Action Target
 -- When we get there, we'll need to change the definition here.
 targetStage (Stage0 {}) = getHostTarget
 targetStage (Stage1 {}) = getHostTarget
-targetStage (Stage2 {}) = getTargetTarget -- the last two only make sense if the target can be executed locally
+targetStage (Stage2 {}) = getTargetTarget
 targetStage (Stage3 {}) = getTargetTarget
 
 queryTarget :: Stage -> (Target -> a) -> (Expr c b a)


=====================================
hadrian/src/Packages.hs
=====================================
@@ -27,6 +27,7 @@ import Base
 import Context
 import Oracles.Flag
 import Oracles.Setting
+import GHC.Toolchain.Target (targetPlatformTriple)
 
 -- | These are all GHC packages we know about. Build rules will be generated for
 -- all of them. However, not all of these packages will be built. For example,
@@ -164,11 +165,19 @@ linter name = program name ("linters" -/- name)
 setPath :: Package -> FilePath -> Package
 setPath pkg path = pkg { pkgPath = path }
 
+-- | Whether the StageN compiler is a cross-compiler or not.
+crossStage :: Stage -> Action Bool
+crossStage st = do
+  st_target <- targetStage st
+  st_host   <- targetStage (predStage st)
+  return (targetPlatformTriple st_target /= targetPlatformTriple st_host)
+
+
 -- | Target prefix to prepend to executable names.
-crossPrefix :: Action String
-crossPrefix = do
-    cross <- flag CrossCompiling
-    targetPlatform <- setting TargetPlatformFull
+crossPrefix :: Stage -> Action String
+crossPrefix st = do
+    cross <- crossStage st
+    targetPlatform <- targetPlatformTriple <$> targetStage st
     return $ if cross then targetPlatform ++ "-" else ""
 
 -- | Given a 'Context', compute the name of the program that is built in it
@@ -177,7 +186,7 @@ crossPrefix = do
 -- 'Library', the function simply returns its name.
 programName :: Context -> Action String
 programName Context {..} = do
-    prefix <- crossPrefix
+    prefix <- crossPrefix stage
     -- TODO: Can we extract this information from Cabal files?
     -- Alp: We could, but then the iserv package would have to
     --      use Cabal conditionals + a 'profiling' flag


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -274,7 +274,7 @@ bindistRules = do
 
         -- todo: do we need these wrappers on windows
         forM_ bin_targets $ \(pkg, _) -> do
-          needed_wrappers <- pkgToWrappers pkg
+          needed_wrappers <- pkgToWrappers Stage2 pkg
           forM_ needed_wrappers $ \wrapper_name -> do
             let suffix = if useGhcPrefix pkg
                            then "ghc-" ++ version
@@ -412,9 +412,9 @@ useGhcPrefix pkg
   | otherwise = True
 
 -- | Which wrappers point to a specific package
-pkgToWrappers :: Package -> Action [String]
-pkgToWrappers pkg = do
-    prefix <- crossPrefix
+pkgToWrappers :: Stage -> Package -> Action [String]
+pkgToWrappers stage pkg = do
+    prefix <- crossPrefix stage
     if  -- ghc also has the ghci script wrapper
         -- N.B. programName would add the crossPrefix therefore we must do the
         -- same here.
@@ -456,8 +456,8 @@ commonWrapper = pure $ "exec \"$executablename\" ${1+\"$@\"}\n"
 -- echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)"
 hsc2hsWrapper :: Action String
 hsc2hsWrapper = do
-  ccArgs <- map ("--cflag=" <>) . prgFlags . ccProgram . tgtCCompiler <$> targetStage Stage1
-  linkFlags <- map ("--lflag=" <>) . prgFlags . ccLinkProgram . tgtCCompilerLink <$> targetStage Stage1
+  ccArgs <- map ("--cflag=" <>) . prgFlags . ccProgram . tgtCCompiler <$> targetStage Stage2
+  linkFlags <- map ("--lflag=" <>) . prgFlags . ccLinkProgram . tgtCCompilerLink <$> targetStage Stage2
   wrapper <- drop 4 . lines <$> liftIO (readFile "utils/hsc2hs/hsc2hs.wrapper")
   return $ unlines
     ( "HSC2HS_EXTRA=\"" <> unwords (ccArgs ++ linkFlags) <> "\""


=====================================
hadrian/src/Rules/CabalReinstall.hs
=====================================
@@ -81,7 +81,7 @@ cabalBuildRules = do
                   | pkg == hpcBin = "hpc"
                   | otherwise     = pkgName pkg
             let cabal_bin_out = work_dir -/- "cabal-bin" -/- (pgmName bin_pkg)
-            needed_wrappers <- pkgToWrappers bin_pkg
+            needed_wrappers <- pkgToWrappers Stage2 bin_pkg
             forM_ needed_wrappers $ \wrapper_name -> do
               let wrapper_prefix = unlines
                     ["#!/usr/bin/env sh"


=====================================
hadrian/src/Settings/Builders/DeriveConstants.hs
=====================================
@@ -19,6 +19,8 @@ deriveConstantsBuilderArgs :: Args
 deriveConstantsBuilderArgs = builder DeriveConstants ? do
     cFlags <- includeCcArgs
     outs   <- getOutputs
+    stage <- getStage
+    let stage = Stage1
     let (outputFile, mode, tempDir) = case outs of
             [ofile, mode, tmpdir] -> (ofile,mode,tmpdir)
             [ofile, tmpdir]
@@ -31,12 +33,12 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do
         [ arg mode
         , arg "-o", arg outputFile
         , arg "--tmpdir", arg tempDir
-        , arg "--gcc-program", arg =<< getBuilderPath (Cc CompileC Stage1)
+        , arg "--gcc-program", arg =<< getBuilderPath (Cc CompileC stage)
         , pure $ concatMap (\a -> ["--gcc-flag", a]) cFlags
-        , arg "--nm-program", arg =<< getBuilderPath (Nm Stage1)
+        , arg "--nm-program", arg =<< getBuilderPath (Nm stage)
         , isSpecified Objdump ? mconcat [ arg "--objdump-program"
                                         , arg =<< getBuilderPath Objdump ]
-        , arg "--target-os", arg =<< queryTarget Stage1 queryOS ]
+        , arg "--target-os", arg =<< queryTarget stage queryOS ]
 
 includeCcArgs :: Args
 includeCcArgs = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7af07f2b86adc74da0eb14622be4d4ca71f0fec6...20547b8d8f6e5ae8323ebe9f82874dbef80276c2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7af07f2b86adc74da0eb14622be4d4ca71f0fec6...20547b8d8f6e5ae8323ebe9f82874dbef80276c2
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/20230921/394f360e/attachment-0001.html>


More information about the ghc-commits mailing list