Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • hadrian/src/Oracles/Setting.hs
    ... ... @@ -7,7 +7,7 @@ module Oracles.Setting (
    7 7
         -- * Helpers
    
    8 8
         ghcCanonVersion, cmdLineLengthLimit, targetSupportsRPaths, topDirectory,
    
    9 9
         libsuf, ghcVersionStage, bashPath, targetStage, crossStage, queryTarget, queryTargetTarget,
    
    10
    -    ghcWithInterpreter, isHostStage,
    
    10
    +    isHostStage,
    
    11 11
     
    
    12 12
         -- ** Target platform things
    
    13 13
         anyTargetOs, anyTargetArch, anyHostOs,
    
    ... ... @@ -181,22 +181,6 @@ targetSupportsRPaths stage = queryTargetTarget stage
    181 181
                                     (\t -> let os = archOS_OS (tgtArchOs t)
    
    182 182
                                            in osElfTarget os || osMachOTarget os)
    
    183 183
     
    
    184
    --- | Check whether the target supports GHCi.
    
    185
    -ghcWithInterpreter :: Stage -> Action Bool
    
    186
    -ghcWithInterpreter stage = do
    
    187
    -    goodOs <- anyTargetOs stage [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?,
    
    188
    -                          , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD
    
    189
    -                          , OSDarwin, OSKFreeBSD
    
    190
    -                          , OSWasi ]
    
    191
    -    goodArch <- (||) <$>
    
    192
    -                anyTargetArch stage [ ArchX86, ArchX86_64, ArchPPC
    
    193
    -                              , ArchAArch64, ArchS390X
    
    194
    -                              , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2
    
    195
    -                              , ArchRISCV64, ArchLoongArch64
    
    196
    -                              , ArchWasm32 ]
    
    197
    -                              <*> isArmTarget stage
    
    198
    -    return $ goodOs && goodArch && (stage >= Stage1)
    
    199
    -
    
    200 184
     -- | Which variant of the ARM architecture is the target (or 'Nothing' if not
    
    201 185
     -- ARM)?
    
    202 186
     targetArmVersion :: Stage -> Action (Maybe ArmISA)
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -12,6 +12,7 @@ import Hadrian.Oracles.TextFile (lookupStageBuildConfig)
    12 12
     import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL)
    
    13 13
     import Oracles.ModuleFiles
    
    14 14
     import Oracles.Setting
    
    15
    +import Settings.Program (ghcWithInterpreter)
    
    15 16
     import Hadrian.Haskell.Cabal.Type (PackageData(version))
    
    16 17
     import Hadrian.Haskell.Cabal
    
    17 18
     import Hadrian.Oracles.Cabal (readPackageData)
    
    ... ... @@ -489,7 +490,7 @@ generateSettings settingsFile = do
    489 490
         -- ROMES:TODO: WHERE HAS CROSS COMPILING GONE?
    
    490 491
         -- ("cross compiling", expr $ yesNo <$> crossStage (predStage stage))
    
    491 492
             [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit, Context.stage = predStage stage })))
    
    492
    -        , ("Use interpreter", expr $ yesNo <$> Oracles.Setting.ghcWithInterpreter stage)
    
    493
    +        , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
    
    493 494
             -- Hard-coded as Cabal queries these to determine way support and we
    
    494 495
             -- need to always advertise all ways when bootstrapping.
    
    495 496
             -- The settings file is generated at install time when installing a bindist.
    

  • hadrian/src/Settings/Builders/Cabal.hs
    ... ... @@ -11,7 +11,7 @@ import Settings.Builders.Common
    11 11
     import qualified Settings.Builders.Common as S
    
    12 12
     import Control.Exception (assert)
    
    13 13
     import qualified Data.Set as Set
    
    14
    -import Settings.Program (programContext)
    
    14
    +import Settings.Program (programContext, ghcWithInterpreter)
    
    15 15
     import GHC.Toolchain (ccLinkProgram, tgtCCompilerLink, targetPlatformTriple)
    
    16 16
     import GHC.Toolchain.Program (prgFlags)
    
    17 17
     
    
    ... ... @@ -139,7 +139,7 @@ libraryArgs = do
    139 139
         contextWay  <- getWay
    
    140 140
         package     <- getPackage
    
    141 141
         stage       <- getStage
    
    142
    -    withGhci    <- expr (ghcWithInterpreter stage)
    
    142
    +    withGhci    <- expr $ ghcWithInterpreter stage
    
    143 143
         dynPrograms <- expr (flavour >>= flip dynamicGhcPrograms stage)
    
    144 144
         ghciObjsSupported <- expr (targetSupportsGhciObjects stage)
    
    145 145
         let ways = Set.insert contextWay flavourWays
    

  • hadrian/src/Settings/Builders/RunTest.hs
    ... ... @@ -15,6 +15,7 @@ import CommandLine
    15 15
     import Oracles.TestSettings
    
    16 16
     import Packages
    
    17 17
     import Settings.Builders.Common
    
    18
    +import Settings.Program (ghcWithInterpreter)
    
    18 19
     import qualified Data.Set    as Set
    
    19 20
     import Flavour
    
    20 21
     import qualified Context.Type as C
    
    ... ... @@ -62,6 +63,7 @@ data TestCompilerArgs = TestCompilerArgs{
    62 63
      ,   leadingUnderscore :: Bool
    
    63 64
      ,   withNativeCodeGen :: Bool
    
    64 65
      ,   withInterpreter   :: Bool
    
    66
    + ,   cross             :: Bool
    
    65 67
      ,   interpForceDyn    :: Bool
    
    66 68
      ,   unregisterised    :: Bool
    
    67 69
      ,   tables_next_to_code :: Bool
    
    ... ... @@ -96,9 +98,9 @@ allowHaveLLVM = not . (`elem` ["wasm32", "javascript"])
    96 98
     --
    
    97 99
     inTreeCompilerArgs :: Stage -> Action TestCompilerArgs
    
    98 100
     inTreeCompilerArgs stg = do
    
    99
    -    isCrossStage <- crossStage stg
    
    101
    +    cross <- crossStage stg
    
    100 102
         let ghcStage = succStage stg
    
    101
    -        pkgCacheStage = if isCrossStage then ghcStage else stg
    
    103
    +        pkgCacheStage = if cross then ghcStage else stg
    
    102 104
         (hasDynamicRts, hasThreadedRts) <- do
    
    103 105
           ways <- interpretInContext (vanillaContext ghcStage rts) getRtsWays
    
    104 106
           return (dynamic `elem` ways, threaded `elem` ways)
    
    ... ... @@ -158,11 +160,11 @@ outOfTreeCompilerArgs = do
    158 160
         leadingUnderscore   <- getBooleanSetting TestLeadingUnderscore
    
    159 161
         withNativeCodeGen   <- getBooleanSetting TestGhcWithNativeCodeGen
    
    160 162
         withInterpreter     <- getBooleanSetting TestGhcWithInterpreter
    
    163
    +    cross               <- getBooleanSetting TestGhcCrossCompiling
    
    161 164
         interpForceDyn      <- getBooleanSetting TestRTSLinkerForceDyn
    
    162 165
         unregisterised      <- getBooleanSetting TestGhcUnregisterised
    
    163 166
         tables_next_to_code <- getBooleanSetting TestGhcTablesNextToCode
    
    164 167
         targetWithSMP       <- getBooleanSetting TestGhcWithSMP
    
    165
    -
    
    166 168
         debugAssertions     <- getBooleanSetting TestGhcDebugAssertions
    
    167 169
     
    
    168 170
         os          <- getTestSetting TestHostOS
    
    ... ... @@ -279,6 +281,7 @@ runTestBuilderArgs = builder Testsuite ? do
    279 281
     
    
    280 282
     
    
    281 283
                 , arg "-e", arg $ "config.have_interp=" ++ show withInterpreter
    
    284
    +            , arg "-e", arg $ "config.cross=" ++ show cross
    
    282 285
                 , arg "-e", arg $ "config.interp_force_dyn=" ++ show interpForceDyn
    
    283 286
                 , arg "-e", arg $ "config.unregisterised=" ++ show unregisterised
    
    284 287
                 , arg "-e", arg $ "config.tables_next_to_code=" ++ show tables_next_to_code
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -8,6 +8,7 @@ import Oracles.Flag
    8 8
     import Packages
    
    9 9
     import Settings
    
    10 10
     import Settings.Builders.Common (wayCcArgs)
    
    11
    +import Settings.Program (ghcWithInterpreter)
    
    11 12
     
    
    12 13
     import qualified GHC.Toolchain.Library as Lib
    
    13 14
     import GHC.Toolchain.Target
    
    ... ... @@ -82,16 +83,18 @@ packageArgs = do
    82 83
                 ]
    
    83 84
     
    
    84 85
               , builder (Cabal Flags) ? mconcat
    
    85
    -            -- For the ghc library, internal-interpreter only makes
    
    86
    -            -- sense when we're not cross compiling. For cross GHC,
    
    87
    -            -- external interpreter is used for loading target code
    
    88
    -            -- and internal interpreter is supposed to load native
    
    89
    -            -- code for plugins (!7377), however it's unfinished work
    
    90
    -            -- (#14335) and completely untested in CI for cross
    
    91
    -            -- backends at the moment, so we might as well disable it
    
    92
    -            -- for cross GHC.
    
    93
    -            -- TODO: MP
    
    94
    -            [ andM [ghcWithInterpreter stage, notM  isCrossStage] `cabalFlag` "internal-interpreter"
    
    86
    +            -- In order to enable internal-interpreter for the ghc
    
    87
    +            -- library:
    
    88
    +            --
    
    89
    +            -- 1. ghcWithInterpreter must be True ("Use interpreter" =
    
    90
    +            --    "YES")
    
    91
    +            -- 2. For non-cross case it can be enabled
    
    92
    +            -- 3. For cross case, disable for stage0 since that runs
    
    93
    +            --    on the host and must rely on external interpreter to
    
    94
    +            --    load target code, otherwise enable for stage1 since
    
    95
    +            --    that runs on the target and can use target's own
    
    96
    +            --    ghci object linker
    
    97
    +            [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage2]] `cabalFlag` "internal-interpreter"
    
    95 98
                 , orM [ notM cross, haveCurses ]  `cabalFlag` "terminfo"
    
    96 99
                 , arg "-build-tool-depends"
    
    97 100
                 , staged (buildFlag UseLibzstd) `cabalFlag` "with-libzstd"
    
    ... ... @@ -113,7 +116,7 @@ packageArgs = do
    113 116
                  , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ]
    
    114 117
     
    
    115 118
               , builder (Cabal Flags) ? mconcat
    
    116
    -            [ andM [ghcWithInterpreter stage, notM isCrossStage] `cabalFlag` "internal-interpreter"
    
    119
    +            [ (expr (ghcWithInterpreter stage)) `cabalFlag` "internal-interpreter"
    
    117 120
                 , ifM stage0
    
    118 121
                       -- We build a threaded stage 1 if the bootstrapping compiler
    
    119 122
                       -- supports it.