Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • hadrian/src/Oracles/Flag.hs
    ... ... @@ -7,7 +7,6 @@ module Oracles.Flag (
    7 7
         targetRTSLinkerOnlySupportsSharedLibs,
    
    8 8
         targetSupportsThreadedRts,
    
    9 9
         targetSupportsSMP,
    
    10
    -    ghcWithInterpreter,
    
    11 10
         useLibffiForAdjustors,
    
    12 11
         arSupportsDashL,
    
    13 12
         arSupportsAtFile
    
    ... ... @@ -146,31 +145,5 @@ targetSupportsSMP = do
    146 145
          | goodArch             -> return True
    
    147 146
          | otherwise            -> return False
    
    148 147
     
    
    149
    -
    
    150
    --- | When cross compiling, enable for stage0 to get ghci
    
    151
    --- support. But when not cross compiling, disable for
    
    152
    --- stage0, otherwise we introduce extra dependencies
    
    153
    --- like haskeline etc, and mixing stageBoot/stage0 libs
    
    154
    --- can cause extra trouble (e.g. #25406)
    
    155
    ---
    
    156
    --- Also checks whether the target supports GHCi.
    
    157
    -ghcWithInterpreter :: Stage -> Action Bool
    
    158
    -ghcWithInterpreter stage = do
    
    159
    -    is_cross <- flag CrossCompiling
    
    160
    -    goodOs <- anyTargetOs [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?,
    
    161
    -                          , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD
    
    162
    -                          , OSDarwin, OSKFreeBSD
    
    163
    -                          , OSWasi ]
    
    164
    -    goodArch <- (||) <$>
    
    165
    -                anyTargetArch [ ArchX86, ArchX86_64, ArchPPC
    
    166
    -                              , ArchAArch64, ArchS390X
    
    167
    -                              , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2
    
    168
    -                              , ArchRISCV64, ArchLoongArch64
    
    169
    -                              , ArchWasm32 ]
    
    170
    -                              <*> isArmTarget
    
    171
    -    -- Maybe this should just be false for cross compilers. But for now
    
    172
    -    -- I've kept the old behaviour where it will say yes. (See #25939)
    
    173
    -    return $ goodOs && goodArch && (stage >= Stage1 || is_cross)
    
    174
    -
    
    175 148
     useLibffiForAdjustors :: Action Bool
    
    176 149
     useLibffiForAdjustors = queryTargetTarget tgtUseLibffiForAdjustors

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -26,6 +26,7 @@ import Utilities
    26 26
     import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp))
    
    27 27
     import GHC.Toolchain.Program
    
    28 28
     import GHC.Platform.ArchOS
    
    29
    +import Settings.Program (ghcWithInterpreter)
    
    29 30
     
    
    30 31
     -- | Track this file to rebuild generated files whenever it changes.
    
    31 32
     trackGenerateHs :: Expr ()
    

  • 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)
    
    16 16
     import GHC.Toolchain.Program (prgFlags)
    
    17 17
     
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -11,6 +11,7 @@ import Settings.Builders.Common (wayCcArgs)
    11 11
     import GHC.Toolchain.Target
    
    12 12
     import GHC.Platform.ArchOS
    
    13 13
     import Data.Version.Extra
    
    14
    +import Settings.Program (ghcWithInterpreter)
    
    14 15
     
    
    15 16
     -- | Package-specific command-line arguments.
    
    16 17
     packageArgs :: Args
    

  • hadrian/src/Settings/Program.hs
    1 1
     module Settings.Program
    
    2 2
       ( programContext
    
    3
    +  , ghcWithInterpreter
    
    3 4
       ) where
    
    4 5
     
    
    5 6
     import Base
    
    6 7
     import Context
    
    7 8
     import Oracles.Flavour
    
    9
    +import Oracles.Flag
    
    8 10
     import Packages
    
    9 11
     
    
    12
    +import GHC.Platform.ArchOS
    
    13
    +import Settings.Builders.Common (anyTargetOs, anyTargetArch, isArmTarget)
    
    14
    +
    
    10 15
     -- TODO: there is duplication and inconsistency between this and
    
    11 16
     -- Rules.Program.getProgramContexts. There should only be one way to
    
    12 17
     -- get a context/contexts for a given stage and package.
    
    ... ... @@ -24,3 +29,33 @@ programContext stage pkg = do
    24 29
     
    
    25 30
               notStage0 (Stage0 {}) = False
    
    26 31
               notStage0 _ = True
    
    32
    +
    
    33
    +-- | When cross compiling, enable for stage0 to get ghci
    
    34
    +-- support. But when not cross compiling, disable for
    
    35
    +-- stage0, otherwise we introduce extra dependencies
    
    36
    +-- like haskeline etc, and mixing stageBoot/stage0 libs
    
    37
    +-- can cause extra trouble (e.g. #25406)
    
    38
    +--
    
    39
    +-- Also checks whether the target supports GHCi.
    
    40
    +ghcWithInterpreter :: Stage -> Action Bool
    
    41
    +ghcWithInterpreter stage = do
    
    42
    +    is_cross <- flag CrossCompiling
    
    43
    +    goodOs <- anyTargetOs [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?,
    
    44
    +                          , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD
    
    45
    +                          , OSDarwin, OSKFreeBSD
    
    46
    +                          , OSWasi ]
    
    47
    +    goodArch <- (||) <$>
    
    48
    +                anyTargetArch [ ArchX86, ArchX86_64, ArchPPC
    
    49
    +                              , ArchAArch64, ArchS390X
    
    50
    +                              , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2
    
    51
    +                              , ArchRISCV64, ArchLoongArch64
    
    52
    +                              , ArchWasm32 ]
    
    53
    +                              <*> isArmTarget
    
    54
    +    -- The explicit support list is essentially a list of platforms for which
    
    55
    +    -- the RTS linker has support. If the RTS linker is not supported then we
    
    56
    +    -- fall back on dynamic linking:
    
    57
    +    dynamicGhcProgs <- askDynGhcPrograms
    
    58
    +
    
    59
    +    -- Maybe this should just be false for cross compilers. But for now
    
    60
    +    -- I've kept the old behaviour where it will say yes. (See #25939)
    
    61
    +    return $ ((goodOs && goodArch) || dynamicGhcProgs) && (stage >= Stage1 || is_cross)