[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Bump bytestring submodule to 0.12.0.2

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Oct 4 10:16:54 UTC 2023



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


Commits:
9c9ca67e by Andrew Lelechenko at 2023-10-04T05:42:28-04:00
Bump bytestring submodule to 0.12.0.2

- - - - -
4e46dc2b by Andrew Lelechenko at 2023-10-04T05:42:28-04:00
Inline bucket_match

- - - - -
f6b2751f by Ben Gamari at 2023-10-04T05:43:05-04:00
configure: Fix #21712 again

This is a bit of a shot in the dark to fix #24033, which appears to be
another instance of #21712. For some reason the ld-override logic
*still* appears to be active on Darwin targets (or at least one).
Consequently, on misconfigured systems we may choose a non-`ld64`
linker.

It's a bit unclear exactly what happened in #24033 but ultimately the
check added for #21712 was not quite right, checking for the
`ghc_host_os` (the value of which depends upon the bootstrap compiler)
instead of the target platform. Fix this.

Fixes #24033.

- - - - -
2f0a101d by Krzysztof Gogolewski at 2023-10-04T05:43:42-04:00
Add a regression test for #24029

- - - - -
8cee3fd7 by sheaf at 2023-10-04T05:44:22-04:00
Fix non-symbolic children lookup of fixity decl

The fix for #23664 did not correctly account for non-symbolic names
when looking up children of a given parent. This one-line fix changes
that.

Fixes #24037

- - - - -
a4785b33 by Cheng Shao at 2023-10-04T05:44:59-04:00
rts: fix incorrect ticket reference

- - - - -
e037f459 by Ben Gamari at 2023-10-04T05:45:35-04:00
users-guide: Fix discussion of -Wpartial-fields

 * fix a few typos
 * add a new example showing when the warning fires
 * clarify the existing example
 * point out -Wincomplete-record-selects

Fixes #24049.

- - - - -
39672070 by Matthew Pickering at 2023-10-04T06:16:34-04:00
Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)"

This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2.

`-optP` should pass options to the preprocessor, that might be a very
different program to the C compiler, so passing the options to the C
compiler is likely to result in `-optP` being useless.

Fixes #17185 and #21291

- - - - -
4c41ad4f by Ben Gamari at 2023-10-04T06:16:35-04:00
rts/nonmoving: Fix on LLP64 platforms

Previously `NONMOVING_SEGMENT_MASK` and friends were defined with the `UL`
size suffix. However, this is wrong on LLP64 platforms like Windows,
where `long` is 32-bits.

Fixes #23003.
Fixes #24042.

- - - - -


27 changed files:

- compiler/GHC/Data/FastString.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/ghc.cabal.in
- docs/users_guide/using-warnings.rst
- driver/ghci/ghci-wrapper.cabal.in
- ghc/ghc-bin.cabal.in
- hadrian/hadrian.cabal
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Settings/Packages.hs
- libraries/bytestring
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- m4/find_ld.m4
- rts/include/rts/ghc_ffi.h
- rts/sm/NonMoving.h
- − testsuite/tests/driver/T16737.hs
- − testsuite/tests/driver/T16737.stdout
- − testsuite/tests/driver/T16737include/T16737.h
- testsuite/tests/driver/all.T
- + testsuite/tests/rename/should_compile/T24037.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/simplCore/should_compile/T24029.hs
- testsuite/tests/simplCore/should_compile/all.T
- utils/iserv/iserv.cabal.in


Changes:

=====================================
compiler/GHC/Data/FastString.hs
=====================================
@@ -506,6 +506,10 @@ bucket_match fs sbs = go fs
         go (fs@(FastString {fs_sbs=fs_sbs}) : ls)
           | fs_sbs == sbs = Just fs
           | otherwise     = go ls
+-- bucket_match used to inline before changes to instance Eq ShortByteString
+-- in bytestring-0.12, which made it slighhtly larger than inlining threshold.
+-- Non-inlining causes a small, but measurable performance regression, so let's force it.
+{-# INLINE bucket_match #-}
 
 mkFastStringBytes :: Ptr Word8 -> Int -> FastString
 mkFastStringBytes !ptr !len =


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -411,19 +411,6 @@ runCcPhase cc_phase pipe_env hsc_env location input_fn = do
          includePathsQuoteImplicit cmdline_include_paths)
   let include_paths = include_paths_quote ++ include_paths_global
 
-  -- pass -D or -optP to preprocessor when compiling foreign C files
-  -- (#16737). Doing it in this way is simpler and also enable the C
-  -- compiler to perform preprocessing and parsing in a single pass,
-  -- but it may introduce inconsistency if a different pgm_P is specified.
-  let opts = getOpts dflags opt_P
-      aug_imports = augmentImports dflags opts
-
-      more_preprocessor_opts = concat
-        [ ["-Xpreprocessor", i]
-        | not hcc
-        , i <- aug_imports
-        ]
-
   let gcc_extra_viac_flags = extraGccViaCFlags dflags
   let pic_c_flags = picCCOpts dflags
 
@@ -512,7 +499,6 @@ runCcPhase cc_phase pipe_env hsc_env location input_fn = do
                  ++ [ "-include", ghcVersionH ]
                  ++ framework_paths
                  ++ include_paths
-                 ++ more_preprocessor_opts
                  ++ pkg_extra_cc_opts
                  ))
 


=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -1308,12 +1308,16 @@ childGREPriority (LookupChild { wantedParent = wanted_parent
         | isTermVarOrFieldNameSpace ns
         , isTermVarOrFieldNameSpace other_ns
         = Just 0
-        | ns == varName
+        | isValNameSpace varName
         , other_ns == tcName
-        -- When looking up children, we sometimes want to a symbolic variable
-        -- name to resolve to a type constructor, e.g. for an infix declaration
-        -- "infix +!" we want to take into account both class methods and associated
-        -- types. See test T10816.
+        -- When looking up children, we sometimes want a value name
+        -- to resolve to a type constructor.
+        -- For example, for an infix declaration "infixr 3 +!" or "infix 2 `Fun`"
+        -- inside a class declaration, we want to account for the possibility
+        -- that the identifier refers to an associated type (type constructor
+        -- NameSpace), when otherwise "+!" would be in the term-level variable
+        -- NameSpace, and "Fun" would be in the term-level data constructor
+        -- NameSpace.  See tests T10816, T23664, T24037.
         = Just 1
         | ns == tcName
         , other_ns == dataName


=====================================
compiler/ghc.cabal.in
=====================================
@@ -98,7 +98,7 @@ Library
                    deepseq    >= 1.4 && < 1.6,
                    directory  >= 1   && < 1.4,
                    process    >= 1   && < 1.7,
-                   bytestring >= 0.9 && < 0.12,
+                   bytestring >= 0.9 && < 0.13,
                    binary     == 0.8.*,
                    time       >= 1.4 && < 1.13,
                    containers >= 0.6.2.1 && < 0.7,


=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -2157,16 +2157,19 @@ of ``-W(no-)*``.
     :since: 8.4
 
     The option :ghc-flag:`-Wpartial-fields` warns about a record field
-    `f` that is defined in some, but not all, the contructors of a
-    data type, because `f`'s record selector function may fail.  For
-    exampe, the record selector function `f`, defined in the `Foo`
-    constructor record below, will fail when applied to ``Bar``, so
-    the compiler will emit a warning at its definition when
-    :ghc-flag:`-Wpartial-fields` is enabled.
+    ``f`` that is defined in some, but not all, of the constructors of a
+    data type, as such selector functions are partial. For example, when
+    :ghc-flag:`-Wpartial-fields` is enabled the compiler will emit a warning at
+    the definition of ``Foo`` below: ::
+
+        data Foo = Foo { f :: Int } | Bar
 
     The warning is suppressed if the field name begins with an underscore. ::
 
-        data Foo = Foo { f :: Int } | Bar
+        data Foo = Foo { _f :: Int } | Bar
+
+    Another related warning is :ghc-flag:`-Wincomplete-record-selectors`,
+    which warns at use sites rather than definition sites.
 
 .. ghc-flag:: -Wunused-packages
     :shortdesc: warn when package is requested on command line, but not needed.


=====================================
driver/ghci/ghci-wrapper.cabal.in
=====================================
@@ -29,4 +29,4 @@ Executable ghci
     -- We need to call the versioned ghc executable because the unversioned
     -- GHC executable is a wrapper that doesn't call FreeConsole and so
     -- breaks an interactive process like GHCi. See #21889, #14150 and #13411
-    CPP-Options: -DEXE_PATH="ghc- at ProjectVersion@"
+    cc-options: -DEXE_PATH="ghc- at ProjectVersion@"


=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -33,7 +33,7 @@ Executable ghc
     Main-Is: Main.hs
     Build-Depends: base       >= 4   && < 5,
                    array      >= 0.1 && < 0.6,
-                   bytestring >= 0.9 && < 0.12,
+                   bytestring >= 0.9 && < 0.13,
                    directory  >= 1   && < 1.4,
                    process    >= 1   && < 1.7,
                    filepath   >= 1   && < 1.5,


=====================================
hadrian/hadrian.cabal
=====================================
@@ -153,7 +153,7 @@ executable hadrian
                        , TypeFamilies
     build-depends:       Cabal                >= 3.10    && < 3.11
                        , base                 >= 4.11    && < 5
-                       , bytestring           >= 0.10    && < 0.12
+                       , bytestring           >= 0.10    && < 0.13
                        , containers           >= 0.5     && < 0.7
                        , directory            >= 1.3.1.0 && < 1.4
                        , extra                >= 1.4.7


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -515,8 +515,8 @@ createVersionWrapper pkg versioned_exe install_path = do
         | otherwise = 0
 
   cmd ghcPath (["-no-hs-main", "-o", install_path, "-I"++version_wrapper_dir
-              , "-DEXE_PATH=\"" ++ versioned_exe ++ "\""
-              , "-DINTERACTIVE_PROCESS=" ++ show interactive
+              , "-optc-DEXE_PATH=\"" ++ versioned_exe ++ "\""
+              , "-optc-DINTERACTIVE_PROCESS=" ++ show interactive
               ] ++ wrapper_files)
 
 {-


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -297,14 +297,11 @@ rtsPackageArgs = package rts ? do
     libzstdIncludeDir <- getSetting LibZstdIncludeDir
     libzstdLibraryDir <- getSetting LibZstdLibDir
 
+
     -- Arguments passed to GHC when compiling C and .cmm sources.
     let ghcArgs = mconcat
           [ arg "-Irts"
           , arg $ "-I" ++ path
-          , arg $ "-DRtsWay=\"rts_" ++ show way ++ "\""
-          -- Set the namespace for the rts fs functions
-          , arg $ "-DFS_NAMESPACE=rts"
-          , arg $ "-DCOMPILING_RTS"
           , notM targetSupportsSMP           ? arg "-DNOSMP"
           , way `elem` [debug, debugDynamic] ? pure [ "-DTICKY_TICKY"
                                                     , "-optc-DTICKY_TICKY"]
@@ -333,9 +330,16 @@ rtsPackageArgs = package rts ? do
                                                     , "-fno-omit-frame-pointer"
                                                     , "-g3"
                                                     , "-O0" ]
+          -- Set the namespace for the rts fs functions
+          , arg $ "-DFS_NAMESPACE=rts"
+
+          , arg $ "-DCOMPILING_RTS"
 
           , inputs ["**/RtsMessages.c", "**/Trace.c"] ?
-            arg ("-DProjectVersion=" ++ show projectVersion)
+            pure
+              ["-DProjectVersion=" ++ show projectVersion
+              , "-DRtsWay=\"rts_" ++ show way ++ "\""
+              ]
 
           , input "**/RtsUtils.c" ? pure
             [ "-DProjectVersion="            ++ show projectVersion
@@ -353,6 +357,7 @@ rtsPackageArgs = package rts ? do
             , "-DTargetVendor="              ++ show targetVendor
             , "-DGhcUnregisterised="         ++ show ghcUnreg
             , "-DTablesNextToCode="          ++ show ghcEnableTNC
+            , "-DRtsWay=\"rts_" ++ show way ++ "\""
             ]
 
           -- We're after pur performance here. So make sure fast math and


=====================================
libraries/bytestring
=====================================
@@ -1 +1 @@
-Subproject commit 2bdeb7b0e7dd100fce9e1f4d1ecf1cd6b5b9702c
+Subproject commit 39f40116a4adf8a3296067d64bd00e1a1e5e15bd


=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -75,7 +75,7 @@ Library
 
     build-depends: base       >= 4.7 && < 4.20,
                    binary     == 0.8.*,
-                   bytestring >= 0.10 && < 0.12,
+                   bytestring >= 0.10 && < 0.13,
                    containers >= 0.5 && < 0.7,
                    directory  >= 1.2 && < 1.4,
                    filepath   >= 1.3 && < 1.5,


=====================================
libraries/ghc-compact/ghc-compact.cabal
=====================================
@@ -41,7 +41,7 @@ library
 
   build-depends: ghc-prim   >= 0.5.3 && < 0.11,
                  base       >= 4.9.0 && < 4.20,
-                 bytestring >= 0.10.6.0 && <0.12
+                 bytestring >= 0.10.6.0 && <0.13
   ghc-options: -Wall
 
   exposed-modules: GHC.Compact


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -78,7 +78,7 @@ library
         base             >= 4.8 && < 4.20,
         ghc-prim         >= 0.5.0 && < 0.11,
         binary           == 0.8.*,
-        bytestring       >= 0.10 && < 0.12,
+        bytestring       >= 0.10 && < 0.13,
         containers       >= 0.5 && < 0.7,
         deepseq          >= 1.4 && < 1.6,
         filepath         == 1.4.*,


=====================================
libraries/haskeline
=====================================
@@ -1 +1 @@
-Subproject commit 0ea07e223685787893dccbcbb67f1720ef4cf80e
+Subproject commit 16ee820fc86f43045365f2c3536ad18147eb0b79


=====================================
m4/find_ld.m4
=====================================
@@ -70,19 +70,23 @@ AC_DEFUN([FIND_LD],[
         AC_CHECK_TARGET_TOOL([LD], [ld])
     }
 
-    if test "$ghc_host_os" = "darwin" ; then
+    case "$target" in
+    *-darwin)
         dnl N.B. Don't even try to find a more efficient linker on Darwin where
         dnl broken setups (e.g. unholy mixtures of Homebrew and the native
         dnl toolchain) are far too easy to come across.
         dnl
         dnl See #21712.
         AC_CHECK_TARGET_TOOL([LD], [ld])
-    elif test "x$enable_ld_override" = "xyes"; then
-        find_ld
-    else
-        AC_CHECK_TARGET_TOOL([LD], [ld])
-    fi
-
+        ;;
+    *)
+        if test "x$enable_ld_override" = "xyes"; then
+            find_ld
+        else
+            AC_CHECK_TARGET_TOOL([LD], [ld])
+        fi
+        ;;
+    esac
     CHECK_LD_COPY_BUG([$1])
 ])
 


=====================================
rts/include/rts/ghc_ffi.h
=====================================
@@ -1,5 +1,5 @@
 /*
- * <ffi.h> wrapper working around #23586.
+ * <ffi.h> wrapper working around #23568.
  *
  * (c) The University of Glasgow 2023
  *


=====================================
rts/sm/NonMoving.h
=====================================
@@ -17,13 +17,13 @@
 #include "BeginPrivate.h"
 
 // Segments
-#define NONMOVING_SEGMENT_BITS 15UL   // 2^15 = 32kByte
+#define NONMOVING_SEGMENT_BITS 15ULL   // 2^15 = 32kByte
 // Mask to find base of segment
-#define NONMOVING_SEGMENT_MASK ((1UL << NONMOVING_SEGMENT_BITS) - 1)
+#define NONMOVING_SEGMENT_MASK (((uintptr_t)1 << NONMOVING_SEGMENT_BITS) - 1)
 // In bytes
-#define NONMOVING_SEGMENT_SIZE (1UL << NONMOVING_SEGMENT_BITS)
+#define NONMOVING_SEGMENT_SIZE ((uintptr_t)1 << NONMOVING_SEGMENT_BITS)
 // In words
-#define NONMOVING_SEGMENT_SIZE_W ((1UL << NONMOVING_SEGMENT_BITS) / SIZEOF_VOID_P)
+#define NONMOVING_SEGMENT_SIZE_W (((uintptr_t)1 << NONMOVING_SEGMENT_BITS) / SIZEOF_VOID_P)
 // In blocks
 #define NONMOVING_SEGMENT_BLOCKS (NONMOVING_SEGMENT_SIZE / BLOCK_SIZE)
 


=====================================
testsuite/tests/driver/T16737.hs deleted
=====================================
@@ -1,32 +0,0 @@
-{-# LANGUAGE TemplateHaskell #-}
-{-# OPTIONS_GHC -DFOO=2 -optP=-DBAR=3 -optc=-DBAZ=5 -optcxx=-DBAZ=7 #-}
-
-import Language.Haskell.TH.Syntax
-
-do
-  let code = unlines
-        [ "#if defined(__cplusplus)"
-        , "extern \"C\" {"
-        , "#endif"
-        , "#include <T16737.h>"
-        , "int FUN(void) {"
-        , "  return FOO * BAR * BAZ;"
-        , "}"
-        , "#if defined(__cplusplus)"
-        , "}"
-        , "#endif"
-        ]
-  addForeignSource LangC code
-  addForeignSource LangCxx code
-  pure []
-
-foreign import ccall unsafe "c_value"
-  c_value :: IO Int
-
-foreign import ccall unsafe "cxx_value"
-  cxx_value :: IO Int
-
-main :: IO ()
-main = do
-  print =<< c_value
-  print =<< cxx_value


=====================================
testsuite/tests/driver/T16737.stdout deleted
=====================================
@@ -1,2 +0,0 @@
-30
-42


=====================================
testsuite/tests/driver/T16737include/T16737.h deleted
=====================================
@@ -1,7 +0,0 @@
-#pragma once
-
-#if defined(__cplusplus)
-#define FUN cxx_value
-#else
-#define FUN c_value
-#endif


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -285,12 +285,6 @@ test('inline-check', [omit_ways(['hpc', 'profasm'])]
 test('T14452', js_broken(22261), makefile_test, [])
 test('T14923', normal, makefile_test, [])
 test('T15396', normal, compile_and_run, ['-package ghc'])
-test('T16737',
-     [extra_files(['T16737include/']),
-      req_th,
-      req_c,
-      expect_broken_for(16541, ghci_ways)],
-     compile_and_run, ['-optP=-isystem -optP=T16737include'])
 
 test('T17143', exit_code(1), run_command, ['{compiler} T17143.hs -S -fno-code'])
 test('T17786', unless(opsys('mingw32'), skip), makefile_test, [])


=====================================
testsuite/tests/rename/should_compile/T24037.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeFamilies, TypeOperators #-}
+
+module T24037 where
+
+class POrd a where
+  type Geq a b
+  infixr 6 `Geq`


=====================================
testsuite/tests/rename/should_compile/all.T
=====================================
@@ -215,6 +215,7 @@ test('T23434', normal, compile, [''])
 test('T23510b', normal, compile, [''])
 test('T23512b', normal, compile, [''])
 test('T23664', normal, compile, [''])
+test('T24037', normal, compile, [''])
 test('ExportWarnings1', extra_files(['ExportWarnings_base.hs', 'ExportWarnings_aux.hs']), multimod_compile, ['ExportWarnings1', '-v0 -Wno-duplicate-exports -Wx-custom'])
 test('ExportWarnings2', extra_files(['ExportWarnings_base.hs', 'ExportWarnings_aux.hs', 'ExportWarnings_aux2.hs']), multimod_compile, ['ExportWarnings2', '-v0 -Wno-duplicate-exports -Wx-custom'])
 test('ExportWarnings3', extra_files(['ExportWarnings_base.hs', 'ExportWarnings_aux.hs']), multimod_compile, ['ExportWarnings3', '-v0 -Wno-duplicate-exports -Wx-custom'])


=====================================
testsuite/tests/simplCore/should_compile/T24029.hs
=====================================
@@ -0,0 +1,21 @@
+{-# OPTIONS_GHC -O #-}
+module T24029 (surround) where
+
+data Buffer where
+  Buffer :: !Int -> Buffer
+
+newtype Builder = Builder (Buffer -> Buffer)
+
+c :: Builder -> Builder -> Builder
+c (Builder f) (Builder g) = Builder (\b -> f (g b))
+
+i :: Buffer -> Buffer
+i (Buffer x) = Buffer x
+
+surround :: Builder -> Builder
+surround f = f
+{-# NOINLINE [1] surround #-}
+
+{-# RULES
+"surround/surround" forall a. surround a = c (Builder (i . i)) a
+  #-}


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -502,3 +502,4 @@ test('T23938', [extra_files(['T23938A.hs'])], multimod_compile, ['T23938', '-O -
 test('T23922a', normal, compile, ['-O'])
 test('T23952', [extra_files(['T23952a.hs'])], multimod_compile, ['T23952', '-v0 -O'])
 test('T24014', normal, compile, ['-dcore-lint'])
+test('T24029', normal, compile, [''])


=====================================
utils/iserv/iserv.cabal.in
=====================================
@@ -33,7 +33,7 @@ Executable iserv
     Build-Depends: array      >= 0.5 && < 0.6,
                    base       >= 4   && < 5,
                    binary     >= 0.7 && < 0.11,
-                   bytestring >= 0.10 && < 0.12,
+                   bytestring >= 0.10 && < 0.13,
                    containers >= 0.5 && < 0.7,
                    deepseq    >= 1.4 && < 1.6,
                    ghci       == @ProjectVersionMunged@



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae6f38a340e5facc8f27921fb0a0ea2398827b69...4c41ad4f65ed12a1a1a519f2fc9a4d0c2e8400db

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae6f38a340e5facc8f27921fb0a0ea2398827b69...4c41ad4f65ed12a1a1a519f2fc9a4d0c2e8400db
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231004/448108e8/attachment-0001.html>


More information about the ghc-commits mailing list