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

Commits:

3 changed files:

Changes:

  • hadrian/src/Base.hs
    ... ... @@ -149,14 +149,10 @@ ghcLibDeps stage iplace = do
    149 149
         ps <- mapM (\f -> stageLibPath stage <&> (-/- f))
    
    150 150
             [ "llvm-targets"
    
    151 151
             , "llvm-passes"
    
    152
    -        , "ghc-interp.js"
    
    153 152
             , "settings"
    
    154 153
             , "targets" -/- "default.target"
    
    155 154
             , "ghc-usage.txt"
    
    156 155
             , "ghci-usage.txt"
    
    157
    -        , "dyld.mjs"
    
    158
    -        , "post-link.mjs"
    
    159
    -        , "prelude.mjs"
    
    160 156
             ]
    
    161 157
         cxxStdLib <- systemCxxStdLibConfPath (PackageDbLoc stage iplace)
    
    162 158
         return (cxxStdLib : ps)
    

  • hadrian/src/Oracles/Setting.hs
    ... ... @@ -9,7 +9,7 @@ module Oracles.Setting (
    9 9
     
    
    10 10
         -- ** Target platform things
    
    11 11
         anyTargetOs, anyTargetArch, anyHostOs,
    
    12
    -    isElfTarget, isOsxTarget, isWinTarget, isJsTarget, isArmTarget,
    
    12
    +    isElfTarget, isOsxTarget, isWinTarget, isJsTarget, isWasmTarget, isArmTarget,
    
    13 13
         isWinHost,
    
    14 14
         targetArmVersion
    
    15 15
         ) where
    
    ... ... @@ -128,6 +128,9 @@ isWinTarget = anyTargetOs [OSMinGW32]
    128 128
     isJsTarget :: Action Bool
    
    129 129
     isJsTarget = anyTargetArch [ArchJavaScript]
    
    130 130
     
    
    131
    +isWasmTarget :: Action Bool
    
    132
    +isWasmTarget = anyTargetArch [ArchWasm32]
    
    133
    +
    
    131 134
     isOsxTarget :: Action Bool
    
    132 135
     isOsxTarget = anyTargetOs [OSDarwin]
    
    133 136
     
    

  • hadrian/src/Rules/Register.hs
    ... ... @@ -118,7 +118,18 @@ registerPackageRules rs stage iplace = do
    118 118
             pkgName <- getPackageNameFromConfFile conf
    
    119 119
             let pkg = unsafeFindPackageByName pkgName
    
    120 120
     
    
    121
    -        when (pkg == compiler) $ need =<< ghcLibDeps stage iplace
    
    121
    +        when (pkg == compiler) $ do
    
    122
    +            baseDeps <- ghcLibDeps stage iplace
    
    123
    +            jsTarget <- isJsTarget
    
    124
    +            wasmTarget <- isWasmTarget
    
    125
    +            libPath <- stageLibPath stage
    
    126
    +            let jsDeps
    
    127
    +                  | jsTarget  = ["ghc-interp.js"]
    
    128
    +                  | otherwise = []
    
    129
    +                wasmDeps
    
    130
    +                  | wasmTarget = ["dyld.mjs", "post-link.mjs", "prelude.mjs"]
    
    131
    +                  | otherwise  = []
    
    132
    +            need (baseDeps ++ map (libPath -/-) (jsDeps ++ wasmDeps))
    
    122 133
     
    
    123 134
             -- Only used in guard when Stage0 {} but can be GlobalLibs or InTreeLibs
    
    124 135
             isBoot <- (pkg `notElem`) <$> stagePackages stage