[Git][ghc/ghc][wip/hadrian-cross-stage2] 2 commits: TEST_HAVE_INTREE

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Thu Oct 5 11:56:33 UTC 2023



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


Commits:
f662bd86 by GHC GitLab CI at 2023-10-05T11:55:56+00:00
TEST_HAVE_INTREE

- - - - -
3af1bd50 by GHC GitLab CI at 2023-10-05T11:56:18+00:00
askDynGhcPrograms, force cross

- - - - -


4 changed files:

- .gitlab/ci.sh
- hadrian/src/Oracles/Flavour.hs
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Settings/Program.hs


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -643,11 +643,18 @@ function test_hadrian() {
       rm proftest.hs
     fi
 
+    # The check-exact check-ppr programs etc can not be built when testing a cross compiler.
+    if [ -z "${CROSS_TARGET:-}" ]; then
+      TEST_HAVE_INTREE="--test-have-intree-files"
+    else
+      TEST_HAVE_INTREE=""
+    fi
+
     run_hadrian \
       test \
       --summary-junit=./junit.xml \
-      --test-have-intree-files \
       --test-compiler="${test_compiler}" \
+      $TEST_HAVE_INTREE \
       "runtest.opts+=${RUNTEST_ARGS:-}" \
       "runtest.opts+=--unexpected-output-dir=$TOP/unexpected-test-output" \
       || fail "hadrian main testsuite"


=====================================
hadrian/src/Oracles/Flavour.hs
=====================================
@@ -12,6 +12,7 @@ module Oracles.Flavour
 import Base
 import Flavour
 import Settings (flavour)
+import Oracles.Setting
 
 newtype DynGhcPrograms =
   DynGhcPrograms Stage deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
@@ -23,7 +24,10 @@ type instance RuleResult GhcProfiled = Bool
 
 oracles :: Rules ()
 oracles = do
-  void $ addOracle $ \(DynGhcPrograms stage) -> flip dynamicGhcPrograms stage =<< flavour
+  void $ addOracle $ \(DynGhcPrograms stage) -> do
+    cross <- crossStage stage
+    from_flavour <- flip dynamicGhcPrograms stage =<< flavour
+    return (from_flavour && not cross)
   void $ addOracle $ \(GhcProfiled stage) ->
     ghcProfiled <$> flavour <*> pure (succStage stage)
 


=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -26,6 +26,7 @@ import Utilities
 
 import qualified Data.Set    as Set
 import qualified Text.Parsec as Parsec
+import Oracles.Flavour
 
 docRoot :: FilePath
 docRoot = "doc"
@@ -268,7 +269,7 @@ buildPackageDocumentation = do
 
         -- Build Haddock documentation
         -- TODO: Pass the correct way from Rules via Context.
-        dynamicPrograms <- flip dynamicGhcPrograms (stage context)=<< flavour
+        dynamicPrograms <- askDynGhcPrograms (stage context)
         let haddockWay = if dynamicPrograms then dynamic else vanilla
 
         -- Build the dependencies of the package we are going to build documentation for


=====================================
hadrian/src/Settings/Program.hs
=====================================
@@ -14,16 +14,15 @@ import Packages
 programContext :: Stage -> Package -> Action Context
 programContext stage pkg = do
     profiled <- askGhcProfiled stage
-    dynGhcProgs <- askDynGhcPrograms stage --dynamicGhcPrograms =<< flavour
+    dynGhcProgs <- askDynGhcPrograms stage 
     -- Have to build static if it's a cross stage as we won't distribute the libraries built for the host.
-    cross <- crossStage stage
-    return $ Context stage pkg (wayFor profiled dynGhcProgs cross) Final
+    return $ Context stage pkg (wayFor profiled dynGhcProgs) Final
 
-    where wayFor prof dyn cross
+    where wayFor prof dyn 
             | prof && dyn                           =
                 error "programContext: profiling+dynamic not supported"
             | pkg == ghc && prof && notStage0 stage = profiling
-            | dyn && notStage0 stage && not cross   = dynamic
+            | dyn && notStage0 stage                = dynamic
             | otherwise                             = vanilla
 
           notStage0 (Stage0 {}) = False



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bb8990ea3c247bd407239d07cafc082f6ef1b66f...3af1bd50f8dcb93c995b595601c5e5736544028e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bb8990ea3c247bd407239d07cafc082f6ef1b66f...3af1bd50f8dcb93c995b595601c5e5736544028e
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/20231005/a4e8e1a4/attachment-0001.html>


More information about the ghc-commits mailing list