[commit: ghc] ghc-8.0: add regression test for #11145. (1d87402)

git at git.haskell.org git at git.haskell.org
Thu Mar 24 22:00:01 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/1d874025de87e9e987c84de4e6926bf199245545/ghc

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

commit 1d874025de87e9e987c84de4e6926bf199245545
Author: Dominik Bollmann <bollmann at seas.upenn.edu>
Date:   Fri Mar 11 10:38:28 2016 +0100

    add regression test for #11145.
    
    The original TH failure observed by the ticket, namely that Template
    Haskell quotes of data instance GADTs are broken, is not observable
    anymore in HEAD. I therefore just added the corresponding regression
    test.
    
    Test Plan: ./validate
    
    Reviewers: goldfire, austin, thomie, jstolarek, bgamari
    
    Reviewed By: bgamari
    
    Differential Revision: https://phabricator.haskell.org/D1978
    
    GHC Trac Issues: #11145
    
    (cherry picked from commit f3def7643d390db54d18b8c3d385c490fba58a41)


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

1d874025de87e9e987c84de4e6926bf199245545
 testsuite/tests/th/T11145.hs     | 9 +++++++++
 testsuite/tests/th/T11145.stderr | 8 ++++++++
 testsuite/tests/th/all.T         | 1 +
 3 files changed, 18 insertions(+)

diff --git a/testsuite/tests/th/T11145.hs b/testsuite/tests/th/T11145.hs
new file mode 100644
index 0000000..f3968e9
--- /dev/null
+++ b/testsuite/tests/th/T11145.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TemplateHaskell #-}
+module T11145 where
+
+data family Fuggle x y
+
+[d| data instance Fuggle Int (Maybe (a,b)) where
+      MkFuggle :: Fuggle Int (Maybe Bool) |]
diff --git a/testsuite/tests/th/T11145.stderr b/testsuite/tests/th/T11145.stderr
new file mode 100644
index 0000000..98e518c
--- /dev/null
+++ b/testsuite/tests/th/T11145.stderr
@@ -0,0 +1,8 @@
+
+T11145.hs:8:1: error:
+    • Data constructor ‘MkFuggle’ returns type ‘Fuggle
+                                                  Int (Maybe Bool)’
+        instead of an instance of its parent type ‘Fuggle
+                                                     Int (Maybe (a_a4MU, b_a4MV))’
+    • In the definition of data constructor ‘MkFuggle’
+      In the data instance declaration for ‘Fuggle’
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index db84c607..2116606 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -399,3 +399,4 @@ test('T11345', normal, compile_and_run, ['-v0 -dsuppress-uniques'])
 test('TH_finalizer', normal, compile, ['-v0'])
 test('T10603', normal, compile, ['-ddump-splices -dsuppress-uniques'])
 test('T11452', normal, compile_fail, ['-v0'])
+test('T11145', normal, compile_fail, ['-v0'])



More information about the ghc-commits mailing list