[commit: ghc] ghc-8.0: Add a testcase for #11362 (77de825)

git at git.haskell.org git at git.haskell.org
Thu Feb 18 12:24:09 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/77de825300a71be0769f23d70015716672e91ca4/ghc

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

commit 77de825300a71be0769f23d70015716672e91ca4
Author: Bartosz Nitka <niteria at gmail.com>
Date:   Mon Feb 15 09:16:43 2016 -0800

    Add a testcase for #11362
    
    This reproduces the issue that I encountered in #11362.
    
    Test Plan: this testcase
    
    Reviewers: simonpj, bgamari, austin
    
    Reviewed By: simonpj
    
    Subscribers: thomie, simonmar
    
    Differential Revision: https://phabricator.haskell.org/D1917
    
    GHC Trac Issues: #11362
    
    (cherry picked from commit 023742e444a415001d86d50a6ec331fe71d50426)


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

77de825300a71be0769f23d70015716672e91ca4
 testsuite/tests/polykinds/T11362.hs | 26 ++++++++++++++++++++++++++
 testsuite/tests/polykinds/all.T     |  2 ++
 2 files changed, 28 insertions(+)

diff --git a/testsuite/tests/polykinds/T11362.hs b/testsuite/tests/polykinds/T11362.hs
new file mode 100644
index 0000000..945d68f
--- /dev/null
+++ b/testsuite/tests/polykinds/T11362.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE GADTs #-}
+
+module T11362 where
+-- this file when compiled with -dunique-increment=-1 made GHC crash
+
+data Sum a b = L a | R b
+
+data Sum1 (a :: k1 -> *) (b :: k2 -> *) :: Sum k1 k2 -> * where
+  LL :: a i -> Sum1 a b (L i)
+  RR :: b i -> Sum1 a b (R i)
+
+data Code i o = F (Code (Sum i o) o)
+
+-- An interpretation for `Code` using a data family works:
+data family In (f :: Code i o) :: (i -> *) -> (o -> *)
+
+data instance In (F f) r o where
+  MkIn :: In f (Sum1 r (In (F f) r)) o -> In (F f) r o
+
+-- Requires polymorphic recursion
+data In' (f :: Code i o) :: (i -> *) -> o -> * where
+  MkIn' :: In' g (Sum1 r (In' (F g) r)) t -> In' (F g) r t
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index a5631a8..4500cfc 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -138,4 +138,6 @@ test('T11480a', normal, compile, [''])
 test('T11523', normal, compile, [''])
 test('T11520', normal, compile_fail, [''])
 test('T11516', normal, compile_fail, [''])
+test('T11362', normal, compile, ['-dunique-increment=-1'])
+  # -dunique-increment=-1 doesn't work inside the file
 test('T11399', normal, compile_fail, [''])



More information about the ghc-commits mailing list