summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
authorBrandon Chinn <brandon@leapyear.io>2020-07-17 19:29:43 -0700
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-07-29 15:07:11 -0400
commitc59064b0c60d3d779f5fd067be4b6648d8de23cf (patch)
tree57a3a7e9bddd4ac62fb172216c6cd4a74b14f8d6 /testsuite
parentb9a880fce484d0a87bb794b9d2d8a73e54819011 (diff)
downloadhaskell-c59064b0c60d3d779f5fd067be4b6648d8de23cf.tar.gz
Add regression test for #16341
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/deriving/should_compile/T16341.hs31
-rw-r--r--testsuite/tests/deriving/should_compile/all.T1
2 files changed, 32 insertions, 0 deletions
diff --git a/testsuite/tests/deriving/should_compile/T16341.hs b/testsuite/tests/deriving/should_compile/T16341.hs
new file mode 100644
index 0000000000..cd9fce6d73
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T16341.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveFoldable #-}
+{-# LANGUAGE DeriveLift #-}
+{-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneDeriving #-}
+
+module T16341 where
+
+import Language.Haskell.TH.Syntax (Lift)
+
+data Foo a where
+ Foo1 :: Foo Int
+ Foo2 :: (Bool -> Bool) -> Foo Bool
+
+-- These instances should work whether or not `Foo2` is a constructor in
+-- `Foo`, because the `Foo Int` designation precludes `Foo2` from being
+-- a reachable constructor
+deriving instance Show (Foo Int)
+deriving instance Eq (Foo Int)
+deriving instance Ord (Foo Int)
+deriving instance Lift (Foo Int)
+
+data Bar a b where
+ Bar1 :: b -> Bar Int b
+ Bar2 :: (Bool -> Bool) -> b -> Bar Bool b
+
+deriving instance Functor (Bar Int)
+deriving instance Foldable (Bar Int)
+deriving instance Traversable (Bar Int)
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index f6e9d43b06..86a48ccf7b 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -118,6 +118,7 @@ test('T15398', normal, compile, [''])
test('T15637', normal, compile, [''])
test('T15831', normal, compile, [''])
test('T16179', normal, compile, [''])
+test('T16341', normal, compile, [''])
test('T16518', normal, compile, [''])
test('T17324', normal, compile, [''])
test('T17339', normal, compile,