[Git][ghc/ghc][wip/hadrian-cross-stage2] 8 commits: hadrian: Refactor system-cxx-std-lib rules0

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



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


Commits:
e146b97f by Matthew Pickering at 2024-09-27T17:36:41+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

- - - - -
9908da66 by Matthew Pickering at 2024-09-27T17:36:41+01:00
fixes for simdutf8

- - - - -
f4ec9b83 by Matthew Pickering at 2024-09-27T17:36:41+01:00
use building for target in llvm flavour transformer

- - - - -
b4e3a77b by Matthew Pickering at 2024-09-27T17:36:41+01:00
bindist: Pass path to package database we want to recache

This fixes recaching on cross compilers

- - - - -
a4177c90 by Matthew Pickering at 2024-09-27T17:36:41+01:00
testsuite: T9930fail now passes on javascript

I didn't investigate why, but the comment says it should be fixed by
building a stage2 cross compiler (and it is).

- - - - -
73f911cf by Sven Tennie at 2024-09-27T17:36:41+01:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
af47a83a by Matthew Pickering at 2024-09-27T17:36:41+01:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
a22ee5c4 by Matthew Pickering at 2024-09-27T17:36:42+01:00
docker rev

- - - - -


15 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- configure.ac
- hadrian/src/BindistConfig.hs
- 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/BinaryDist.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- testsuite/tests/ghc-e/should_fail/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
   GIT_SSL_NO_VERIFY: "1"
 
   # Commit of ghc/ci-images repository from which to pull Docker images
-  DOCKER_REV: 486541129a8e7bf77c2cf7cd76ca998f690d5685
+  DOCKER_REV: 6efac743853f9c2172777e934d7aea44434415ec
 
   # Sequential version number of all cached things.
   # Bump to invalidate GitLab CI cache.


=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -106,6 +106,7 @@ data Opsys
 
 data LinuxDistro
   = Debian12
+  | Debian12Riscv
   | Debian11
   | Debian11Js
   | Debian10
@@ -305,6 +306,7 @@ distroName :: LinuxDistro -> String
 distroName Debian12   = "deb12"
 distroName Debian11   = "deb11"
 distroName Debian11Js = "deb11-emsdk-closure"
+distroName Debian12Riscv = "deb12-riscv"
 distroName Debian10   = "deb10"
 distroName Debian9    = "deb9"
 distroName Fedora33   = "fedora33"
@@ -627,6 +629,7 @@ data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
+          | RiscV        -- ^ Run this job when the "RISC-V" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
           | FreeBSDLabel -- ^ Run this job when the "FreeBSD" label is set.
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
@@ -674,6 +677,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
+validateRuleString RiscV        = labelString "RISC-V"
 validateRuleString WasmBackend  = labelString "wasm"
 validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
@@ -1123,6 +1127,9 @@ cross_jobs = [
   -- x86 -> aarch64
     validateBuilds Amd64 (Linux Debian11) (crossConfig "aarch64-linux-gnu" (Emulator "qemu-aarch64 -L /usr/aarch64-linux-gnu") Nothing)
 
+  -- x86_64 -> riscv
+  , addValidateRule RiscV (validateBuilds Amd64 (Linux Debian12Riscv) (crossConfig "riscv64-linux-gnu" (Emulator "qemu-riscv64 -L /usr/riscv64-linux-gnu") Nothing))
+
   -- Javascript
   , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11Js) javascriptConfig)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1855,6 +1855,71 @@
       "XZ_OPT": "-9"
     }
   },
+  "nightly-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "8 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "XZ_OPT": "-9"
+    }
+  },
   "nightly-x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -5222,6 +5287,70 @@
       "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
+  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+    }
+  },
   "x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",


=====================================
configure.ac
=====================================
@@ -561,7 +561,7 @@ AC_SUBST(InstallNameToolCmd)
 # versions of LLVM simultaneously, but that stopped working around
 # 3.5/3.6 release of LLVM.
 LlvmMinVersion=13  # inclusive
-LlvmMaxVersion=19 # not inclusive
+LlvmMaxVersion=20  # not inclusive
 AC_SUBST([LlvmMinVersion])
 AC_SUBST([LlvmMaxVersion])
 


=====================================
hadrian/src/BindistConfig.hs
=====================================
@@ -33,3 +33,9 @@ implicitBindistConfig = do
   -- the target.
   cross <- flag CrossCompiling
   return $ if cross then crossBindist else normalBindist
+
+-- | Are we building things in this stage for the final target?
+buildingForTarget ::  Stage -> Action Bool
+buildingForTarget st = do
+  cfg <- implicitBindistConfig
+  return $ st >= (library_stage cfg)


=====================================
hadrian/src/Flavour.hs
=====================================
@@ -39,6 +39,7 @@ import Text.Parsec.Combinator as P
 import Text.Parsec.Char as P
 import Control.Monad.Except
 import UserSettings
+import BindistConfig
 
 
 flavourTransformers :: Map String (Flavour -> Flavour)
@@ -239,9 +240,9 @@ enableThreadSanitizer instrumentCmm = addArgs $ notStage0 ? mconcat
         ]
     ]
 
--- | Use the LLVM backend in stages 1 and later.
+-- | Use the LLVM backend in target stages
 viaLlvmBackend :: Flavour -> Flavour
-viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"
+viaLlvmBackend = addArgs $ staged buildingForTarget ? builder Ghc ? arg "-fllvm"
 
 -- | Build the GHC executable with profiling enabled in stages 2 and later. It
 -- is also recommended that you use this with @'dynamicGhcPrograms' = False@
@@ -301,7 +302,7 @@ useNativeBignum flavour =
 -- | Enable building the @text@ package with @simdutf@ support.
 enableTextWithSIMDUTF :: Flavour -> Flavour
 enableTextWithSIMDUTF flavour = flavour {
-  textWithSIMDUTF = (>= Stage2)
+  textWithSIMDUTF = buildingForTarget
 }
 
 -- | Build stage2 compiler with -fomit-interface-pragmas to reduce


=====================================
hadrian/src/Flavour/Type.hs
=====================================
@@ -26,7 +26,7 @@ data Flavour = Flavour {
     -- | Build the @text@ package with @simdutf@ support. Disabled by
     -- default due to packaging difficulties described in #20724.
     textWithSIMDUTF :: Stage -- ^ stage of the /built/ compiler
-                    -> Bool,
+                    -> Action 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/BinaryDist.hs
=====================================
@@ -227,8 +227,8 @@ buildBinDistDir root conf at BindistConfig{..} = do
     -- (c.f. #20267).
 
     -- Not going to work for cross
-    --ghcPkgName <- programName (vanillaContext Stage1 ghcPkg)
-    --cmd_ (bindistFilesDir -/- "bin" -/- ghcPkgName) ["recache"]
+    ghcPkgName <- programName (vanillaContext Stage1 ghcPkg)
+    cmd_ (bindistFilesDir -/- "bin" -/- ghcPkgName) ["recache", "--package-db", bindistFilesDir -/- "lib" -/- "package.conf.d" ]
 
 
     need ["docs"]


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -242,9 +242,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
=====================================
@@ -7,7 +7,6 @@ module Rules.Register (
 import Base
 import Context
 import Expression ( getContextData )
-import Flavour
 import Oracles.Setting
 import Hadrian.BuildPath
 import Hadrian.Expression
@@ -52,14 +51,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 +105,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    = const False
+    , textWithSIMDUTF    = const (return False)
     , libraryWays        = defaultLibraryWays
     , rtsWays            = defaultRtsWays
     , dynamicGhcPrograms = defaultDynamicGhcPrograms


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


=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -14,10 +14,8 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
 # and no failure is induced.
 test('T9930fail',
      [extra_files(['T9930']),
-      when(opsys('mingw32'), skip),
-      # broken for JS until cross-compilers become stage2 compilers (#19174)
-      # or until we bootstrap with a 9.10 compiler
-      js_broken(19174)],
+      when(opsys('mingw32'), skip)
+     ],
      makefile_test, ['T9930fail'])
 
 test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed47556df729efe9608853c99bcee7da72e8a557...a22ee5c462ca1e2c9d08404b4d62181eb60e6dac

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed47556df729efe9608853c99bcee7da72e8a557...a22ee5c462ca1e2c9d08404b4d62181eb60e6dac
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/bec0a8e6/attachment-0001.html>


More information about the ghc-commits mailing list