[commit: ghc] master: Add tests for #8128 and #8740 (90e99c4)

git at git.haskell.org git at git.haskell.org
Sun Jun 3 11:49:31 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/90e99c4cfd601601e56fc6041186ca3e070408d9/ghc

>---------------------------------------------------------------

commit 90e99c4cfd601601e56fc6041186ca3e070408d9
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Sun Jun 3 07:47:51 2018 -0400

    Add tests for #8128 and #8740
    
    Commit 08073e16cf672d8009309e4e55d4566af1ecaff4 (#11066) ended up
    fixing these, fortunately enough.


>---------------------------------------------------------------

90e99c4cfd601601e56fc6041186ca3e070408d9
 testsuite/tests/deriving/should_compile/T8128.hs     |  9 +++++++++
 testsuite/tests/deriving/should_compile/T8128.stderr | 14 ++++++++++++++
 testsuite/tests/deriving/should_compile/T8740.hs     | 17 +++++++++++++++++
 testsuite/tests/deriving/should_compile/T8740.stderr | 18 ++++++++++++++++++
 testsuite/tests/deriving/should_compile/all.T        |  2 ++
 5 files changed, 60 insertions(+)

diff --git a/testsuite/tests/deriving/should_compile/T8128.hs b/testsuite/tests/deriving/should_compile/T8128.hs
new file mode 100644
index 0000000..624702e
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8128.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE StandaloneDeriving, GADTs, FlexibleInstances #-}
+
+module T8128 where
+
+data T a where
+  MkT1 :: T Int
+  MkT2 :: Bool -> T Bool
+
+deriving instance Show (T Int)
diff --git a/testsuite/tests/deriving/should_compile/T8128.stderr b/testsuite/tests/deriving/should_compile/T8128.stderr
new file mode 100644
index 0000000..5f8b130
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8128.stderr
@@ -0,0 +1,14 @@
+
+T8128.hs:9:1: warning: [-Winaccessible-code (in -Wdefault)]
+    • Couldn't match type ‘Int’ with ‘Bool’
+      Inaccessible code in
+        a pattern with constructor: MkT2 :: Bool -> T Bool,
+        in an equation for ‘showsPrec’
+    • In the pattern: MkT2 b1
+      In an equation for ‘showsPrec’:
+          showsPrec a (MkT2 b1)
+            = showParen (a >= 11) ((.) (showString "MkT2 ") (showsPrec 11 b1))
+      When typechecking the code for ‘showsPrec’
+        in a derived instance for ‘Show (T Int)’:
+        To see the code I am typechecking, use -ddump-deriv
+      In the instance declaration for ‘Show (T Int)’
diff --git a/testsuite/tests/deriving/should_compile/T8740.hs b/testsuite/tests/deriving/should_compile/T8740.hs
new file mode 100644
index 0000000..95a114c
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8740.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneDeriving #-}
+module T8740 where
+
+data Abstract
+data Reified
+data Player
+
+data Elect p a where
+    ElectRefAsTypeOf :: Int -> Elect Abstract a -> Elect Abstract a
+    ElectHandle :: a -> Elect Reified a
+    Controller :: Elect Abstract Player
+    Owner :: Elect Abstract Player
+    You :: Elect Abstract Player
+
+deriving instance (Eq a) => Eq (Elect p a)
+deriving instance (Ord a) => Ord (Elect p a)
diff --git a/testsuite/tests/deriving/should_compile/T8740.stderr b/testsuite/tests/deriving/should_compile/T8740.stderr
new file mode 100644
index 0000000..9b60741
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8740.stderr
@@ -0,0 +1,18 @@
+
+T8740.hs:17:1: warning: [-Winaccessible-code (in -Wdefault)]
+    • Couldn't match type ‘Reified’ with ‘Abstract’
+      Inaccessible code in
+        a pattern with constructor:
+          ElectRefAsTypeOf :: forall a.
+                              Int -> Elect Abstract a -> Elect Abstract a,
+        in a case alternative
+    • In the pattern: ElectRefAsTypeOf {}
+      In a case alternative: ElectRefAsTypeOf {} -> GT
+      In the expression:
+        case b of
+          ElectRefAsTypeOf {} -> GT
+          ElectHandle b1 -> (a1 `compare` b1)
+          _ -> LT
+      When typechecking the code for ‘compare’
+        in a derived instance for ‘Ord (Elect p a)’:
+        To see the code I am typechecking, use -ddump-deriv
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index b2dd670..0e0494f 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -44,11 +44,13 @@ test('T7710', normal, compile, [''])
 
 test('AutoDeriveTypeable', normal, compile, [''])
 
+test('T8128', normal, compile, [''])
 test('T8138', reqlib('primitive'), compile, ['-O2'])
 test('T8165', normal, compile, [''])
 test('T8631', normal, compile, [''])
 test('T8758', [], multimod_compile, ['T8758a', '-v0'])
 test('T8678', normal, compile, [''])
+test('T8740', normal, compile, [''])
 test('T8865', normal, compile, [''])
 test('T8893', normal, compile, [''])
 test('T8950', normal, compile, [''])



More information about the ghc-commits mailing list