summaryrefslogtreecommitdiff
path: root/testsuite/tests/deriving
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2022-01-24 18:35:27 -0500
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-01-25 17:28:06 -0500
commit9d478d516a76298051993a60c196a1f61320b439 (patch)
tree709f8f3c7022bad0a551e49dbe5e46a6790f338d /testsuite/tests/deriving
parent871ce2a300ed35639a39a86f4c85fbcb605c5d7d (diff)
downloadhaskell-9d478d516a76298051993a60c196a1f61320b439.tar.gz
DeriveGeneric: look up datacon fixities using getDataConFixityFun
Previously, `DeriveGeneric` would look up the fixity of a data constructor using `getFixityEnv`, but this is subtly incorrect for data constructors defined in external modules. This sort of situation can happen with `StandaloneDeriving`, as noticed in #20994. In fact, the same bug has occurred in the past in #9830, and while that bug was fixed for `deriving Read` and `deriving Show`, the fix was never extended to `DeriveGeneric` due to an oversight. This patch corrects that oversight. Fixes #20994.
Diffstat (limited to 'testsuite/tests/deriving')
-rw-r--r--testsuite/tests/deriving/should_compile/T20994.hs27
-rw-r--r--testsuite/tests/deriving/should_compile/all.T1
2 files changed, 28 insertions, 0 deletions
diff --git a/testsuite/tests/deriving/should_compile/T20994.hs b/testsuite/tests/deriving/should_compile/T20994.hs
new file mode 100644
index 0000000000..807f16a9b6
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T20994.hs
@@ -0,0 +1,27 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UndecidableInstances #-}
+module T20994 where
+
+import Data.Kind (Constraint, Type)
+import GHC.Generics
+
+type (++) :: [a] -> [a] -> [a]
+type family xs ++ ys where
+ '[] ++ ys = ys
+ (x:xs) ++ ys = x:(xs ++ ys)
+
+type GetConFixities :: (Type -> Type) -> [FixityI]
+type family GetConFixities rep where
+ GetConFixities (D1 (MetaData _ _ _ _) f) = GetConFixities f
+ GetConFixities (C1 (MetaCons _ fix _) _) = '[fix]
+ GetConFixities (f :+: g) = GetConFixities f ++ GetConFixities g
+ GetConFixities V1 = '[]
+
+type Dict :: Constraint -> Type
+data Dict c where
+ Dict :: c => Dict c
+
+-- Check that (:) is `infixr 5` according to its Rep instance.
+test :: Dict (GetConFixities (Rep [a]) ~ [PrefixI, InfixI RightAssociative 5])
+test = Dict
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index 4a80c84cc1..a33cb364c3 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -136,3 +136,4 @@ test('T20496', multiline_grep_errmsg(r"rnd\n( .*\n)*"), compile, ['-ddump-tc-tra
test('T20375', normal, compile, [''])
test('T20387', normal, compile, [''])
test('T20501', normal, compile, [''])
+test('T20994', normal, compile, [''])