[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: configure: Correctly report when subsections-via-symbols is disabled

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Sep 17 20:45:33 UTC 2024



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


Commits:
e436ce2d by Ben Gamari at 2024-09-17T16:44:52-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
8905a6c0 by Mario Blažević at 2024-09-17T16:44:57-04:00
Modified the default export implementation to match the amended spec

- - - - -
c6e6749b by Sylvain Henry at 2024-09-17T16:45:09-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -


9 changed files:

- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Var.hs
- m4/fptools_set_haskell_platform_vars.m4
- − testsuite/tests/default/DefaultImport04.stdout
- testsuite/tests/default/DefaultImport04.hs → testsuite/tests/default/DefaultImportFail07.hs
- + testsuite/tests/default/DefaultImportFail07.stderr
- testsuite/tests/default/all.T
- + testsuite/tests/ffi/should_compile/T25255.hs
- testsuite/tests/ffi/should_compile/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -42,7 +42,7 @@ import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Name
 import GHC.Types.Name.Env
 import GHC.Types.Name.Set
-import GHC.Types.DefaultEnv (ClassDefaults (cd_class, cd_module), DefaultEnv,
+import GHC.Types.DefaultEnv (ClassDefaults (cd_class), DefaultEnv,
                              emptyDefaultEnv, filterDefaultEnv, isEmptyDefaultEnv)
 import GHC.Types.Avail
 import GHC.Types.SourceFile
@@ -192,7 +192,6 @@ rnExports explicit_mod exports
         ; let dflags = hsc_dflags hsc_env
               TcGblEnv { tcg_mod     = this_mod
                        , tcg_rdr_env = rdr_env
-                       , tcg_default = defaults
                        , tcg_imports = imports
                        , tcg_warns   = warns
                        , tcg_src     = hsc_src } = tcg_env
@@ -237,15 +236,7 @@ rnExports explicit_mod exports
                                                 Nothing -> Nothing
                                                 Just _  -> map drop_defaults <$> rn_exports
                           , tcg_default_exports = case exports of
-                              Nothing ->
-                                if xopt LangExt.NamedDefaults dflags then
-                                  -- NamedDefaults on: implicitly export the defaults declared in this module.
-                                  -- Test case: default/DefaultImport04.hs
-                                  filterDefaultEnv ((Just this_mod ==) . cd_module) defaults
-                                else
-                                  -- NamedDefaults off: do not export any defaults (fixes #25206).
-                                  -- Test case: default/T25206.hs
-                                  emptyDefaultEnv
+                              Nothing -> emptyDefaultEnv
                               _ -> foldMap (foldMap sndOf3) rn_exports
                           , tcg_dus = tcg_dus tcg_env `plusDU`
                                       usesOnly final_ns
@@ -265,18 +256,17 @@ type DontWarnExportNames = NameEnv (NE.NonEmpty SrcSpan)
 ~~~~~~~~~~~~~~~~~~~~~~~~~
 Named default declarations (see Note [Named default declarations] in
 GHC.Tc.Gen.Default) can be exported. A named default declaration is
-exported when
-
-* there is no export list, and we export all locally-declared defaults
-
-* or it is specified in the export list, using the `default` keyword
-  and the class name.  For example:
+exported only when it's specified in the export list, using the `default`
+keyword and the class name.  For example:
 
     module TextWrap (Text, default IsString) where
       import Data.String (IsString)
       import Data.Text (Text)
       default IsString (Text, String)
 
+A module with no explicit export list does not export any default
+declarations, and neither does the re-export of a whole imported module.
+
 The export item `default IsString` is parsed into the `IE` item
 
     IEThingAbs ext (L loc (IEDefault ext "IsString")) doc


=====================================
compiler/GHC/Types/Var.hs
=====================================
@@ -343,9 +343,12 @@ arbitrary value which will (and must!) be ignored.
 -}
 
 instance Outputable Var where
-  ppr var = sdocOption sdocSuppressVarKinds $ \supp_var_kinds ->
+  ppr var = docWithStyle ppr_code ppr_normal
+    where
+      -- don't display debug info with Code style (#25255)
+      ppr_code = ppr (varName var)
+      ppr_normal sty = sdocOption sdocSuppressVarKinds $ \supp_var_kinds ->
             getPprDebug $ \debug ->
-            getPprStyle $ \sty ->
             let
               ppr_var = case var of
                   (TyVar {})


=====================================
m4/fptools_set_haskell_platform_vars.m4
=====================================
@@ -154,12 +154,14 @@ AC_DEFUN([GHC_SUBSECTIONS_VIA_SYMBOLS],
     dnl See Note [autoconf assembler checks and -flto]
     AC_LINK_IFELSE(
         [AC_LANG_PROGRAM([], [__asm__ (".subsections_via_symbols");])],
-        [AC_MSG_RESULT(yes)
+        [
          if test x"$TargetArch" = xaarch64; then
             dnl subsections via symbols is busted on arm64
             TargetHasSubsectionsViaSymbols=NO
+            AC_MSG_RESULT([no, subsections-via-symbols are broken on AArch64/Darwin (GHC 24962)])
          else
             TargetHasSubsectionsViaSymbols=YES
+            AC_MSG_RESULT(yes)
          fi
         ],
         [TargetHasSubsectionsViaSymbols=NO


=====================================
testsuite/tests/default/DefaultImport04.stdout deleted
=====================================
@@ -1 +0,0 @@
-Product {getProduct = 1}


=====================================
testsuite/tests/default/DefaultImport04.hs → testsuite/tests/default/DefaultImportFail07.hs
=====================================


=====================================
testsuite/tests/default/DefaultImportFail07.stderr
=====================================
@@ -0,0 +1,32 @@
+[1 of 5] Compiling ExportShowSum    ( ExportShowSum.hs, ExportShowSum.o )
+[2 of 5] Compiling ExportImplicitMonoidProduct ( ExportImplicitMonoidProduct.hs, ExportImplicitMonoidProduct.o )
+[3 of 5] Compiling ReExportShowSumModule ( ReExportShowSumModule.hs, ReExportShowSumModule.o )
+[4 of 5] Compiling Main             ( DefaultImportFail07.hs, DefaultImportFail07.o )
+DefaultImportFail07.hs:6:8: error: [GHC-39999]
+    • Ambiguous type variable ‘a0’ arising from a use of ‘print’
+      prevents the constraint ‘(Show a0)’ from being solved.
+      Probable fix: use a type annotation to specify what ‘a0’ should be.
+      Potentially matching instances:
+        instance Show Ordering -- Defined in ‘GHC.Internal.Show’
+        instance Show Integer -- Defined in ‘GHC.Internal.Show’
+        ...plus 25 others
+        ...plus 19 instances involving out-of-scope types
+        (use -fprint-potential-instances to see them all)
+    • In the expression: print mempty
+      In an equation for ‘main’: main = print mempty
+
+DefaultImportFail07.hs:6:14: error: [GHC-39999]
+    • Ambiguous type variable ‘a0’ arising from a use of ‘mempty’
+      prevents the constraint ‘(Monoid a0)’ from being solved.
+      Probable fix: use a type annotation to specify what ‘a0’ should be.
+      Potentially matching instances:
+        instance Monoid a => Monoid (IO a)
+          -- Defined in ‘GHC.Internal.Base’
+        instance Monoid Ordering -- Defined in ‘GHC.Internal.Base’
+        ...plus 9 others
+        ...plus 7 instances involving out-of-scope types
+        (use -fprint-potential-instances to see them all)
+    • In the first argument of ‘print’, namely ‘mempty’
+      In the expression: print mempty
+      In an equation for ‘main’: main = print mempty
+


=====================================
testsuite/tests/default/all.T
=====================================
@@ -11,8 +11,6 @@ test('default11', normal, compile_and_run, [''])
 test('DefaultImport01', [extra_files(['ExportMonoidSum.hs'])], multimod_compile_and_run, ['DefaultImport01', ''])
 test('DefaultImport02', [extra_files(['ExportMonoidProduct.hs', 'ExportMonoidSum.hs'])], multimod_compile_and_run, ['DefaultImport02', ''])
 test('DefaultImport03', [extra_files(['ExportMonoidSum.hs', 'ReExportMonoidSum.hs'])], multimod_compile_and_run, ['DefaultImport03', ''])
-test('DefaultImport04', [extra_files(['ExportImplicitMonoidProduct.hs', 'ExportShowSum.hs', 'ReExportShowSumModule.hs'])],
-                 multimod_compile_and_run, ['DefaultImport04', ''])
 test('DefaultImport05', [extra_files(['ExportBitsInt.hs'])], multimod_compile_and_run, ['DefaultImport05', ''])
 test('DefaultImport07', [extra_files(['ExportMonoidProduct.hs', 'ExportMonoidSum.hs'])], multimod_compile, ['DefaultImport07', '-Wtype-defaults'])
 test('DefaultImport08', [extra_files(['ExportMonoidProduct.hs'])], multimod_compile, ['DefaultImport08', '-Wtype-defaults'])
@@ -22,6 +20,8 @@ test('DefaultImportFail03', [extra_files(['ExportMonoidSum.hs', 'UnExportMonoidS
 test('DefaultImportFail04', [extra_files(['ExportShowSum.hs', 'ReExportShowSumModule.hs'])], multimod_compile_fail, ['DefaultImportFail04', ''])
 test('DefaultImportFail05', [extra_files(['ExportMonoidProduct.hs', 'ExportShowSum.hs'])], multimod_compile_fail, ['DefaultImportFail05', ''])
 test('DefaultImportFail06', [extra_files(['ExportBitsInt.hs'])], multimod_compile_fail, ['DefaultImportFail06', ''])
+test('DefaultImportFail07', [extra_files(['ExportImplicitMonoidProduct.hs', 'ExportShowSum.hs', 'ReExportShowSumModule.hs'])],
+                 multimod_compile_fail, ['DefaultImportFail07', ''])
 test('default-fail01', normal, compile_fail, [''])
 test('default-fail02', normal, compile_fail, [''])
 test('default-fail03', normal, compile_fail, [''])


=====================================
testsuite/tests/ffi/should_compile/T25255.hs
=====================================
@@ -0,0 +1,6 @@
+module T25255 where
+
+foreign export ccall foo :: Int -> Int
+
+foo :: Int -> Int
+foo x = x + 10


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -42,3 +42,4 @@ test('T22043', normal, compile, [''])
 test('T22774', unless(js_arch() or arch('wasm32'), expect_fail), compile, [''])
 
 test('T24034', normal, compile, [''])
+test('T25255', normal, compile, ['-dppr-debug'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e00c410f68105e7cb92457527e721118c4d3d49...c6e6749b2b6b984dba7a707f4a1c15970763fc9e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e00c410f68105e7cb92457527e721118c4d3d49...c6e6749b2b6b984dba7a707f4a1c15970763fc9e
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/20240917/433b32a5/attachment-0001.html>


More information about the ghc-commits mailing list