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

Commits:

2 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,
    
    10
    +    ghcWithInterpreter, isHostStage,
    
    11 11
     
    
    12 12
         -- ** Target platform things
    
    13 13
         anyTargetOs, anyTargetArch, anyHostOs,
    
    ... ... @@ -247,10 +247,12 @@ libsuf st way
    247 247
     -- Build libraries for this stage targetting this Target
    
    248 248
     -- For example, we want to build RTS with stage1 for the host target as we produce a host executable with stage1  (which cross-compiles to stage2)
    
    249 249
     targetStage :: Stage -> Action Target
    
    250
    -targetStage (Stage0 {}) = getHostTarget
    
    251
    -targetStage (Stage1 {}) = getHostTarget
    
    252
    -targetStage (Stage2 {}) = getTargetTarget
    
    253
    -targetStage (Stage3 {}) = getTargetTarget
    
    250
    +targetStage stage | isHostStage stage = getHostTarget
    
    251
    +targetStage _ = getTargetTarget
    
    252
    +
    
    253
    +isHostStage :: Stage -> Bool
    
    254
    +isHostStage stage | stage <= Stage1 = True
    
    255
    +isHostStage _ = False
    
    254 256
     
    
    255 257
     queryTarget :: Stage -> (Target -> a) -> (Expr c b a)
    
    256 258
     queryTarget s f = expr (f <$> targetStage s)
    
    ... ... @@ -264,4 +266,3 @@ crossStage st = do
    264 266
       st_target <- targetStage (succStage st)
    
    265 267
       st_host   <- targetStage st
    
    266 268
       return (targetPlatformTriple st_target /= targetPlatformTriple st_host)
    267
    -

  • hadrian/src/Rules/Libffi.hs
    ... ... @@ -129,54 +129,21 @@ fixLibffiMakefile top =
    129 129
     
    
    130 130
     -- TODO: check code duplication w.r.t. ConfCcArgs
    
    131 131
     configureEnvironment :: Stage -> Action [CmdOption]
    
    132
    -configureEnvironment stage@Stage1 = do
    
    133
    -    -- TODO: This case should not exist: Strip and Objdump should be staged!
    
    134
    -    context <- libffiContext stage
    
    135
    -    cFlags  <- interpretInContext context $ mconcat
    
    136
    -               [ cArgs
    
    137
    -               , getStagedCCFlags ]
    
    138
    -    ldFlags <- interpretInContext context ldArgs
    
    139
    -    winTarget <- isWinTarget (succStage stage)
    
    140
    -    sequence $ [ builderEnvironment "CC" $ Cc CompileC stage
    
    141
    -               , builderEnvironment "CXX" $ Cc CompileC stage
    
    142
    -               , builderEnvironment "AR" (Ar Unpack stage)
    
    143
    -               , builderEnvironment "NM" (Nm stage)
    
    144
    -               , builderEnvironment "RANLIB" (Ranlib stage)
    
    145
    -               -- , remBuilderEnvironment "OBJDUMP"
    
    146
    -               -- , remBuilderEnvironment "STRIP"
    
    147
    -               , return . AddEnv  "CFLAGS" $ unwords  cFlags ++ " -w"
    
    148
    -               , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w"
    
    149
    -               , return . AddEnv "OBJDUMP" $ "objdump"
    
    150
    -               , return . AddEnv "STRIP" $ "strip" ]
    
    151
    -               ++ (if winTarget then
    
    152
    -                    -- TODO: Use staged LD for winTarget. This is only a hack because the wrong staged LD was provided.
    
    153
    -                    [remBuilderEnvironment "LD"]
    
    154
    -                  else
    
    155
    -                    [ -- TODO: This should be the staged LD, but that points to gcc and not ld. With the current gcc as linker config, libffi doesn't build shared libs.
    
    156
    -                    remBuilderEnvironment "LD"
    
    157
    -                   ])
    
    158
    -
    
    159 132
     configureEnvironment stage = do
    
    160 133
         context <- libffiContext stage
    
    161
    -    cFlags  <- interpretInContext context $ mconcat
    
    162
    -               [ cArgs
    
    163
    -               , getStagedCCFlags ]
    
    164
    -    ldFlags <- interpretInContext context ldArgs
    
    165
    -    winTarget <- isWinTarget stage
    
    134
    +    cFlags  <- interpretInContext context getStagedCCFlags
    
    135
    +    isCross <- flag CrossCompiling
    
    166 136
         sequence $ [ builderEnvironment "CC" $ Cc CompileC stage
    
    167
    -               , builderEnvironment "CXX" $ Cc CompileC stage
    
    168
    -               , builderEnvironment "AR" (Ar Unpack stage)
    
    169
    -               , builderEnvironment "NM" (Nm stage)
    
    170
    -               , builderEnvironment "RANLIB" (Ranlib stage)
    
    171
    -               , return . AddEnv  "CFLAGS" $ unwords  cFlags ++ " -w"
    
    172
    -               , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ]
    
    173
    -               ++ (if winTarget then
    
    174
    -                    -- TODO: We should use the staged LD here. Unfortunately, that differs from what's expected via $LD.
    
    175
    -                    []
    
    176
    -                  else
    
    177
    -                    [ -- TODO: This should be the staged LD, but that points to GCC and not LD.
    
    178
    -                    -- builderEnvironment "LD" (Ld stage)
    
    179
    -                   ])
    
    137
    +             , builderEnvironment "CXX" $ Cc CompileC stage
    
    138
    +             , builderEnvironment "AR" $ Ar Unpack stage
    
    139
    +             , builderEnvironment "NM" $ Nm stage
    
    140
    +             , builderEnvironment "RANLIB" $ Ranlib stage
    
    141
    +             , return . AddEnv  "CFLAGS" $ unwords  cFlags ++ " -w"
    
    142
    +             , return . AddEnv "LDFLAGS" $ "-w" ] ++
    
    143
    +             -- When we're building a cross-compiler, we have to be careful
    
    144
    +             -- which environment variables are propagated for the non-target
    
    145
    +             -- stages.
    
    146
    +             (if isHostStage stage && isCross then [remBuilderEnvironment "LD"] else [])
    
    180 147
     
    
    181 148
     -- Need the libffi archive and `trackAllow` all files in the build directory.
    
    182 149
     -- See [Libffi indicating inputs].