[Git][ghc/ghc][master] 2 commits: Add regression test for 17328
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Jun 13 13:46:50 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c90d96e4 by Victor Cacciari Miraldo at 2023-06-13T09:46:26-04:00
Add regression test for 17328
- - - - -
de58080c by Victor Cacciari Miraldo at 2023-06-13T09:46:26-04:00
Skip checking whether constructors are in scope when deriving
newtype instances.
Fixes #17328
- - - - -
4 changed files:
- compiler/GHC/Tc/Deriv.hs
- + testsuite/tests/deriving/should_compile/T17328.hs
- + testsuite/tests/deriving/should_compile/T17328a.hs
- testsuite/tests/deriving/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Deriv.hs
=====================================
@@ -1960,9 +1960,13 @@ doDerivInstErrorChecks1 mechanism =
case mechanism of
DerivSpecStock{dsm_stock_dit = dit}
-> data_cons_in_scope_check dit
- DerivSpecNewtype{dsm_newtype_dit = dit}
- -> do atf_coerce_based_error_checks
- data_cons_in_scope_check dit
+ -- No need to 'data_cons_in_scope_check' for newtype deriving.
+ -- Additionally, we also don't need to mark the constructos as
+ -- used because newtypes are handled separately elsewhere.
+ -- See Note [Tracking unused binding and imports] in GHC.Tc.Types
+ -- or #17328 for more.
+ DerivSpecNewtype{}
+ -> atf_coerce_based_error_checks
DerivSpecAnyClass{}
-> pure ()
DerivSpecVia{}
=====================================
testsuite/tests/deriving/should_compile/T17328.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE DerivingStrategies, StandaloneDeriving, GeneralizedNewtypeDeriving,
+ DerivingVia #-}
+
+module T17328 where
+
+import T17328a ( N1, N2(..) )
+
+import Data.Coerce
+
+deriving newtype instance Eq N1
+
=====================================
testsuite/tests/deriving/should_compile/T17328a.hs
=====================================
@@ -0,0 +1,8 @@
+module T17328a where
+
+newtype N1 = MkN1 N2
+
+newtype N2 = MkN2 N1
+
+instance Eq N2 where
+ (==) = const (const False)
=====================================
testsuite/tests/deriving/should_compile/all.T
=====================================
@@ -142,3 +142,4 @@ test('T22167', normal, compile, [''])
test('T22696a', normal, compile, [''])
test('T22696c', normal, compile, [''])
test('T23329', normal, multimod_compile, ['T23329', '-v0'])
+test('T17328', [extra_files(['T17328a.hs'])], multimod_compile, ['T17328', '-v0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed2dbdcab3272ac8d81075ef60920096d2481fb3...de58080c9d488c17519f64b633b171ec46ce65f0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed2dbdcab3272ac8d81075ef60920096d2481fb3...de58080c9d488c17519f64b633b171ec46ce65f0
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/20230613/71cfad8a/attachment-0001.html>
More information about the ghc-commits
mailing list