Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Utils/Outputable.hs
    ... ... @@ -39,7 +39,7 @@ module GHC.Utils.Outputable (
    39 39
             spaceIfSingleQuote,
    
    40 40
             isEmpty, nest,
    
    41 41
             ptext,
    
    42
    -        int, intWithCommas, integer, word64, word, float, double, rational, doublePrec,
    
    42
    +        int, intWithCommas, integer, natural, word64, word, float, double, rational, doublePrec,
    
    43 43
             parens, cparen, brackets, braces, quotes, quote, quoteIfPunsEnabled,
    
    44 44
             doubleQuotes, angleBrackets,
    
    45 45
             semi, comma, colon, dcolon, space, equals, dot, vbar,
    
    ... ... @@ -150,6 +150,7 @@ import System.IO ( Handle )
    150 150
     import System.FilePath
    
    151 151
     import Text.Printf
    
    152 152
     import Numeric (showFFloat)
    
    153
    +import Numeric.Natural (Natural)
    
    153 154
     import Data.Graph (SCC(..))
    
    154 155
     import Data.List (intersperse)
    
    155 156
     import Data.List.NonEmpty (NonEmpty (..))
    
    ... ... @@ -684,6 +685,7 @@ docToSDoc d = SDoc (\_ -> d)
    684 685
     
    
    685 686
     ptext    ::               PtrString  -> SDoc
    
    686 687
     int      :: IsLine doc => Int        -> doc
    
    688
    +natural  :: IsLine doc => Natural    -> doc
    
    687 689
     integer  :: IsLine doc => Integer    -> doc
    
    688 690
     word     ::               Integer    -> SDoc
    
    689 691
     word64   :: IsLine doc => Word64     -> doc
    
    ... ... @@ -695,6 +697,8 @@ rational :: Rational -> SDoc
    695 697
     ptext s     = docToSDoc $ Pretty.ptext s
    
    696 698
     {-# INLINE CONLIKE int #-}
    
    697 699
     int n       = text $ show n
    
    700
    +{-# INLINE CONLIKE natural #-}
    
    701
    +natural n   = text $ show n
    
    698 702
     {-# INLINE CONLIKE integer #-}
    
    699 703
     integer n   = text $ show n
    
    700 704
     {-# INLINE CONLIKE float #-}
    
    ... ... @@ -947,6 +951,9 @@ instance Outputable Int64 where
    947 951
     instance Outputable Int where
    
    948 952
         ppr n = int n
    
    949 953
     
    
    954
    +instance Outputable Natural where
    
    955
    +    ppr n = natural n
    
    956
    +
    
    950 957
     instance Outputable Integer where
    
    951 958
         ppr n = integer n
    
    952 959
     
    

  • hadrian/src/Rules/Gmp.hs
    ... ... @@ -12,7 +12,6 @@ import Utilities
    12 12
     import Hadrian.BuildPath
    
    13 13
     import Hadrian.Expression
    
    14 14
     import Settings.Builders.Common (cArgs, getStagedCCFlags)
    
    15
    -import GHC.Platform.ArchOS
    
    16 15
     
    
    17 16
     -- | Build in-tree GMP library objects (if GmpInTree flag is set) and return
    
    18 17
     -- their paths.
    
    ... ... @@ -128,7 +127,10 @@ gmpRules = do
    128 127
                     mconcat
    
    129 128
                         [ cArgs
    
    130 129
                         , getStagedCCFlags
    
    131
    -                    , anyTargetArch [ArchWasm32] ? arg "-fvisibility=default"
    
    130
    +                    -- gmp symbols are only used by bignum logic in
    
    131
    +                    -- ghc-internal and shouldn't be exported by the
    
    132
    +                    -- ghc-internal shared library.
    
    133
    +                    , arg "-fvisibility=hidden"
    
    132 134
                         ]
    
    133 135
                 env <- sequence
    
    134 136
                          [ builderEnvironment "CC" $ Cc CompileC (stage ctx)
    

  • m4/find_python.m4
    ... ... @@ -17,7 +17,7 @@ AC_DEFUN([FIND_PYTHON],[
    17 17
     
    
    18 18
         dnl If still not found, hard error: we require Python >= 3.7
    
    19 19
         AS_IF([test -z "$PYTHON"], [
    
    20
    -        AC_MSG_ERROR([Python 3.7 or later is required but no python interpreter was found. Please install Python >= 3.7 and re-run configure.])
    
    20
    +        AC_MSG_WARN([Python 3.7 or later is required but no python interpreter was found. This is needed by the testsuite driver.])
    
    21 21
         ])
    
    22 22
     
    
    23 23
         dnl Query the version string (X.Y.Z) of the selected interpreter
    
    ... ... @@ -31,10 +31,10 @@ AC_DEFUN([FIND_PYTHON],[
    31 31
     
    
    32 32
         dnl Enforce minimum version 3.7.0
    
    33 33
         AS_IF([test -z "$PythonVersion"], [
    
    34
    -        AC_MSG_ERROR([Failed to determine Python version for $PYTHON])
    
    34
    +        AC_MSG_WARN([Failed to determine Python version for $PYTHON])
    
    35 35
         ])
    
    36 36
         FP_COMPARE_VERSIONS([$PythonVersion], [-lt], [3.7.0], [
    
    37
    -        AC_MSG_ERROR([Python 3.7 or later is required, but $PYTHON reports $PythonVersion])
    
    37
    +        AC_MSG_WARN([Python 3.7 or later is required, but $PYTHON reports $PythonVersion])
    
    38 38
         ])
    
    39 39
     
    
    40 40
         dnl Canonicalise path for Windows
    

  • utils/jsffi/dyld.mjs
    ... ... @@ -291,7 +291,7 @@ const isNode = Boolean(globalThis?.process?.versions?.node);
    291 291
     // factor out browser-only/node-only logic into different modules. For
    
    292 292
     // now, just make these global let bindings optionally initialized if
    
    293 293
     // isNode and be careful to not use them in browser-only logic.
    
    294
    -let fs, http, path, require, stream, util, wasi, ws, zlib;
    
    294
    +let fs, http, path, require, stream, wasi, ws;
    
    295 295
     
    
    296 296
     if (isNode) {
    
    297 297
       require = (await import("node:module")).createRequire(import.meta.url);
    
    ... ... @@ -300,9 +300,7 @@ if (isNode) {
    300 300
       http = require("http");
    
    301 301
       path = require("path");
    
    302 302
       stream = require("stream");
    
    303
    -  util = require("util");
    
    304 303
       wasi = require("wasi");
    
    305
    -  zlib = require("zlib");
    
    306 304
     
    
    307 305
       // Optional npm dependencies loaded via NODE_PATH
    
    308 306
       try {
    
    ... ... @@ -561,30 +559,8 @@ args.rpc.opened.then(() => main(args));
    561 559
               }[path.extname(p)] || "application/octet-stream"
    
    562 560
             );
    
    563 561
     
    
    564
    -        const buf = Buffer.from(await fs.promises.readFile(p));
    
    565
    -        const etag = `sha512-${Buffer.from(
    
    566
    -          await crypto.subtle.digest("SHA-512", buf)
    
    567
    -        ).toString("base64")}`;
    
    568
    -
    
    569
    -        res.setHeader("ETag", etag);
    
    570
    -
    
    571
    -        if (req.headers["if-none-match"] === etag) {
    
    572
    -          res.writeHead(304);
    
    573
    -          res.end();
    
    574
    -          return;
    
    575
    -        }
    
    576
    -
    
    577
    -        res.setHeader("Content-Encoding", "br");
    
    578
    -
    
    579 562
             res.writeHead(200);
    
    580
    -        res.end(
    
    581
    -          await util.promisify(zlib.brotliCompress)(buf, {
    
    582
    -            params: {
    
    583
    -              [zlib.constants.BROTLI_PARAM_QUALITY]:
    
    584
    -                zlib.constants.BROTLI_MIN_QUALITY,
    
    585
    -            },
    
    586
    -          })
    
    587
    -        );
    
    563
    +        fs.createReadStream(p).pipe(res);
    
    588 564
             return;
    
    589 565
           }
    
    590 566