[commit: ghc] master: A second test for Trac #12055 (1dcb32d)

git at git.haskell.org git at git.haskell.org
Mon Jun 13 11:00:17 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1dcb32ddba605bced2e0e0ce3f52b58e8ff33f5b/ghc

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

commit 1dcb32ddba605bced2e0e0ce3f52b58e8ff33f5b
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Jun 13 12:02:54 2016 +0100

    A second test for Trac #12055
    
    This one omits the extension, thereby making GHC 8.0 produce
    "GHC internal error".


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

1dcb32ddba605bced2e0e0ce3f52b58e8ff33f5b
 testsuite/tests/polykinds/{T12055.hs => T12055a.hs} | 12 ++++++------
 testsuite/tests/polykinds/T12055a.stderr            |  7 +++++++
 testsuite/tests/polykinds/all.T                     |  1 +
 3 files changed, 14 insertions(+), 6 deletions(-)

diff --git a/testsuite/tests/polykinds/T12055.hs b/testsuite/tests/polykinds/T12055a.hs
similarity index 77%
copy from testsuite/tests/polykinds/T12055.hs
copy to testsuite/tests/polykinds/T12055a.hs
index 3ffc221..dab5238 100644
--- a/testsuite/tests/polykinds/T12055.hs
+++ b/testsuite/tests/polykinds/T12055a.hs
@@ -7,14 +7,14 @@
 {-# LANGUAGE TypeOperators #-}
 {-# LANGUAGE TypeInType #-}
 
--- The code from the ticket lacked these extensions,
--- but crashed the compiler with "GHC internal error"
--- It doesn't crash now; and in this test case I've added
--- the extensions, which makes it compile cleanly
-{-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances, FunctionalDependencies #-}
+{-# LANGUAGE FlexibleInstances, UndecidableInstances, FunctionalDependencies #-}
 
+-- The code from the ticket lacked necessary extension FlexibleContexts
+-- which crashed the compiler with "GHC internal error"
+-- This test case reproduces that scenario
+{- # LANGUAGE FlexibleContexts #-}
 
-module T12055 where
+module T12055a where
 
 import GHC.Base ( Constraint, Type )
 import GHC.Exts ( type (~~) )
diff --git a/testsuite/tests/polykinds/T12055a.stderr b/testsuite/tests/polykinds/T12055a.stderr
new file mode 100644
index 0000000..fb76dd4
--- /dev/null
+++ b/testsuite/tests/polykinds/T12055a.stderr
@@ -0,0 +1,7 @@
+
+T12055a.hs:27:1: error:
+    • Non type-variable argument in the constraint: Category (Dom f)
+      (Use FlexibleContexts to permit this)
+    • In the context: (Category (Dom f), Category (Cod f))
+      While checking the super-classes of class ‘Functor’
+      In the class declaration for ‘Functor’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index c731441..bcc8dc4 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -149,3 +149,4 @@ test('KindVType', normal, compile_fail, [''])
 test('T11821', normal, compile, [''])
 test('T11640', normal, compile, [''])
 test('T12055', normal, compile, [''])
+test('T12055a', normal, compile_fail, [''])



More information about the ghc-commits mailing list