[Git][ghc/ghc][master] Only export defaults when NamedDefaults are enabled (#25206)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Aug 27 00:40:38 UTC 2024



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


Commits:
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -


5 changed files:

- compiler/GHC/Tc/Gen/Export.hs
- + testsuite/tests/default/T25206.hs
- + testsuite/tests/default/T25206.stderr
- + testsuite/tests/default/T25206_helper.hs
- testsuite/tests/default/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -237,7 +237,15 @@ rnExports explicit_mod exports
                                                 Nothing -> Nothing
                                                 Just _  -> map drop_defaults <$> rn_exports
                           , tcg_default_exports = case exports of
-                              Nothing -> filterDefaultEnv ((Just this_mod ==) . cd_module) defaults
+                              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
                               _ -> foldMap (foldMap sndOf3) rn_exports
                           , tcg_dus = tcg_dus tcg_env `plusDU`
                                       usesOnly final_ns


=====================================
testsuite/tests/default/T25206.hs
=====================================
@@ -0,0 +1,7 @@
+module T25206 where
+
+import T25206_helper ()
+
+mod1 x = pf
+ where
+  (_,pf) = properFraction x


=====================================
testsuite/tests/default/T25206.stderr
=====================================
@@ -0,0 +1,2 @@
+[1 of 2] Compiling T25206_helper    ( T25206_helper.hs, T25206_helper.o )
+[2 of 2] Compiling T25206           ( T25206.hs, T25206.o )


=====================================
testsuite/tests/default/T25206_helper.hs
=====================================
@@ -0,0 +1,3 @@
+module T25206_helper where
+
+default (Rational)


=====================================
testsuite/tests/default/all.T
=====================================
@@ -30,3 +30,4 @@ test('default-fail05', normal, compile_fail, [''])
 test('default-fail06', normal, compile_fail, [''])
 test('default-fail07', normal, compile_fail, [''])
 test('default-fail08', normal, compile_fail, [''])
+test('T25206', [extra_files(['T25206_helper.hs'])], multimod_compile, ['T25206', ''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaab3d10675eb0090ac60dc81e524231ff706019

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaab3d10675eb0090ac60dc81e524231ff706019
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/20240826/155a5232/attachment-0001.html>


More information about the ghc-commits mailing list