[Git][ghc/ghc][wip/hadrian-cross-stage2] 2 commits: hadrian: Make text_simdutf flavour transformer configurable per-stage

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Fri Sep 27 12:36:24 UTC 2024



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


Commits:
cbb14af8 by Matthew Pickering at 2024-09-27T12:16:37+01:00
hadrian: Make text_simdutf flavour transformer configurable per-stage

Before it was globally enabled, which was probably not what you want as
you don't need text-simd for your boot compiler nor your boot compiler
if you're building a cross-compiler.

This brings it into line with the other modifiers.. such as ghcProfiled
etc

Fixes #25302

- - - - -
dc59add2 by Matthew Pickering at 2024-09-27T12:20:53+01:00
hadrian: Refactor system-cxx-std-lib rules0

I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules.

* For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`.
* The `system-cxx-std-lib` dependency is not read from cabal files.
* Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`.

Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`.

Fixes #25303

- - - - -


8 changed files:

- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs


Changes:

=====================================
hadrian/src/Flavour.hs
=====================================
@@ -300,7 +300,7 @@ useNativeBignum flavour =
 -- | Enable building the @text@ package with @simdutf@ support.
 enableTextWithSIMDUTF :: Flavour -> Flavour
 enableTextWithSIMDUTF flavour = flavour {
-  textWithSIMDUTF = True
+  textWithSIMDUTF = (>= Stage2)
 }
 
 -- | Build stage2 compiler with -fomit-interface-pragmas to reduce


=====================================
hadrian/src/Flavour/Type.hs
=====================================
@@ -25,7 +25,8 @@ data Flavour = Flavour {
     bignumCheck :: Bool,
     -- | Build the @text@ package with @simdutf@ support. Disabled by
     -- default due to packaging difficulties described in #20724.
-    textWithSIMDUTF :: Bool,
+    textWithSIMDUTF :: Stage -- ^ stage of the /built/ compiler
+                    -> Bool,
     -- | Build libraries these ways.
     libraryWays :: Ways,
     -- | Build RTS these ways.


=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -94,10 +94,11 @@ parsePackageData pkg = do
         sorted  = sort [ C.unPackageName p | C.Dependency p _ _ <- allDeps ]
         deps    = nubOrd sorted \\ [name]
         depPkgs = mapMaybe findPackageByName deps
+        cxxStdLib = elem "system-cxx-std-lib" deps
     return $ PackageData name version
                          (C.fromShortText (C.synopsis pd))
                          (C.fromShortText (C.description pd))
-                         depPkgs gpd
+                         depPkgs cxxStdLib gpd
   where
     -- Collect an overapproximation of dependencies by ignoring conditionals
     collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency]
@@ -151,7 +152,9 @@ configurePackage :: Context -> Action ()
 configurePackage context at Context {..} = do
     putProgressInfo $ "| Configure package " ++ quote (pkgName package)
     gpd     <- pkgGenericDescription package
-    depPkgs <- packageDependencies <$> readPackageData package
+    pd <- readPackageData package
+    let depPkgs = packageDependencies pd
+        needSystemCxxStdLib = dependsOnSystemCxxStdLib pd
 
     -- Stage packages are those we have in this stage.
     stagePkgs <- stagePackages stage
@@ -170,7 +173,12 @@ configurePackage context at Context {..} = do
     -- We'll need those packages in our package database.
     deps <- sequence [ pkgConfFile (context { package = pkg, iplace = forceBaseAfterGhcInternal pkg })
                      | pkg <- depPkgs, pkg `elem` stagePkgs ]
-    need $ extraPreConfigureDeps ++ deps
+    -- system-cxx-std-lib is magic.. it doesn't have a cabal file or source code, so we have
+    -- to treat it specially as `pkgConfFile` uses `readPackageData` to compute the version.
+    systemCxxStdLib <- sequence [ systemCxxStdLibConfPath (PackageDbLoc stage iplace) | needSystemCxxStdLib ]
+    need $ extraPreConfigureDeps
+            ++ deps
+            ++ systemCxxStdLib
 
     -- Figure out what hooks we need.
     let configureFile = replaceFileName (pkgCabalFile package) "configure"


=====================================
hadrian/src/Hadrian/Haskell/Cabal/Type.hs
=====================================
@@ -30,6 +30,7 @@ data PackageData = PackageData
     , synopsis                  :: String
     , description               :: String
     , packageDependencies       :: [Package]
+    , dependsOnSystemCxxStdLib  :: Bool
     , genericPackageDescription :: GenericPackageDescription
     } deriving (Eq, Generic, Show, Typeable)
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -221,9 +221,6 @@ copyRules = do
         prefix -/- "html/**"           <~ return "utils/haddock/haddock-api/resources"
         prefix -/- "latex/**"          <~ return "utils/haddock/haddock-api/resources"
 
-        forM_ [Inplace, Final] $ \iplace ->
-          root -/- relativePackageDbPath (PackageDbLoc stage iplace) -/- systemCxxStdLibConf %> \file -> do
-            copyFile ("mk" -/- "system-cxx-std-lib-1.0.conf") file
 
 generateRules :: Rules ()
 generateRules = do


=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -52,14 +52,6 @@ configurePackageRules = do
           isGmp <- (== "gmp") <$> interpretInContext ctx getBignumBackend
           when isGmp $
             need [buildP -/- "include/ghc-gmp.h"]
-        when (pkg == text) $ do
-          simdutf <- textWithSIMDUTF <$> flavour
-          when simdutf $ do
-            -- This is required, otherwise you get Error: hadrian:
-            -- Encountered missing or private dependencies:
-            -- system-cxx-std-lib ==1.0
-            cxxStdLib <- systemCxxStdLibConfPath $ PackageDbLoc stage Inplace
-            need [cxxStdLib]
         Cabal.configurePackage ctx
 
     root -/- "**/autogen/cabal_macros.h" %> \out -> do
@@ -114,6 +106,12 @@ registerPackageRules rs stage iplace = do
             target (Context stage compiler vanilla iplace) (GhcPkg Recache stage) [] []
         writeFileLines stamp []
 
+    -- Special rule for registering system-cxx-std-lib
+    root -/- relativePackageDbPath (PackageDbLoc stage iplace) -/- systemCxxStdLibConf %> \file -> do
+        copyFile ("mk" -/- "system-cxx-std-lib-1.0.conf") file
+        buildWithResources rs $
+            target (Context stage compiler vanilla iplace) (GhcPkg Recache stage) [] []
+
     -- Register a package.
     root -/- relativePackageDbPath (PackageDbLoc stage iplace) -/- "*.conf" %> \conf -> do
         historyDisable


=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -275,7 +275,7 @@ defaultFlavour = Flavour
     , packages           = defaultPackages
     , bignumBackend      = defaultBignumBackend
     , bignumCheck        = False
-    , textWithSIMDUTF    = False
+    , textWithSIMDUTF    = const False
     , libraryWays        = defaultLibraryWays
     , rtsWays            = defaultRtsWays
     , dynamicGhcPrograms = defaultDynamicGhcPrograms


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -192,7 +192,7 @@ packageArgs = do
 
         ---------------------------------- text --------------------------------
         , package text ?
-            ifM (textWithSIMDUTF <$> expr flavour)
+            ifM (compilerStageOption textWithSIMDUTF)
               (builder (Cabal Flags) ? arg "+simdutf")
               (builder (Cabal Flags) ? arg "-simdutf")
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2f63c368b6400753b80bef1da4a0e587757f2fe...dc59add291ee428398c323ce6a5a59078849b911

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2f63c368b6400753b80bef1da4a0e587757f2fe...dc59add291ee428398c323ce6a5a59078849b911
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/20240927/ed5541b5/attachment-0001.html>


More information about the ghc-commits mailing list