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

Commits:

3 changed files:

Changes:

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -606,8 +606,12 @@ generateVersionHs = do
    606 606
     generatePlatformHostHs :: Expr String
    
    607 607
     generatePlatformHostHs = do
    
    608 608
         trackGenerateHs
    
    609
    -    cHostPlatformArch <- queryHost (archOS_arch . tgtArchOs)
    
    610
    -    cHostPlatformOS   <- queryHost (archOS_OS . tgtArchOs)
    
    609
    +    stage <- getStage
    
    610
    +    let chooseHostQuery = case stage of
    
    611
    +            Stage0 {} -> queryHost
    
    612
    +            _         -> queryTarget
    
    613
    +    cHostPlatformArch <- chooseHostQuery (archOS_arch . tgtArchOs)
    
    614
    +    cHostPlatformOS   <- chooseHostQuery (archOS_OS . tgtArchOs)
    
    611 615
         return $ unlines
    
    612 616
             [ "module GHC.Platform.Host where"
    
    613 617
             , ""
    

  • testsuite/tests/cross/should_run/T26449.hs
    1
    +import Control.Monad
    
    2
    +import GHC.Platform.ArchOS
    
    3
    +import GHC.Platform.Host
    
    4
    +import System.Info
    
    5
    +
    
    6
    +main :: IO ()
    
    7
    +main =
    
    8
    +  when ((arch, os) /= (arch', os')) $
    
    9
    +    fail $
    
    10
    +      "System.Info says host platform is "
    
    11
    +        <> show (arch, os)
    
    12
    +        <> " but GHC.Platform.Host says "
    
    13
    +        <> show (arch', os')
    
    14
    +  where
    
    15
    +    (arch', os') =
    
    16
    +      (stringEncodeArch hostPlatformArch, stringEncodeOS hostPlatformOS)

  • testsuite/tests/cross/should_run/all.T
    1
    +test('T26449', [], compile_and_run, [''])