[commit: ghc] master: Test Trac #10134 (30b32f4)

git at git.haskell.org git at git.haskell.org
Mon Aug 3 12:41:03 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/30b32f4ca83147544c4dafeb96fed70b791e40cd/ghc

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

commit 30b32f4ca83147544c4dafeb96fed70b791e40cd
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Aug 3 13:39:56 2015 +0100

    Test Trac #10134


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

30b32f4ca83147544c4dafeb96fed70b791e40cd
 testsuite/tests/polykinds/T10134.hs                   | 19 +++++++++++++++++++
 .../{ghci/scripts/T10321.hs => polykinds/T10134a.hs}  | 11 ++++-------
 testsuite/tests/polykinds/all.T                       |  1 +
 3 files changed, 24 insertions(+), 7 deletions(-)

diff --git a/testsuite/tests/polykinds/T10134.hs b/testsuite/tests/polykinds/T10134.hs
new file mode 100644
index 0000000..0b64625
--- /dev/null
+++ b/testsuite/tests/polykinds/T10134.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE DataKinds, TypeOperators, ConstraintKinds, TypeFamilies, NoMonoLocalBinds, NoMonomorphismRestriction #-}
+{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
+
+module T10134 where
+
+import GHC.TypeLits
+import T10134a
+import Prelude
+
+type Positive n = ((n-1)+1)~n
+
+data Dummy n d = Dummy { vec :: Vec n (Vec d Bool) }
+
+nextDummy :: Positive (2*(n+d)) => Dummy n d -> Dummy n d
+nextDummy d = Dummy { vec = vec dFst }
+   where (dFst,dSnd) = nextDummy' d
+
+nextDummy' :: Positive (2*(n+d)) => Dummy n d -> ( Dummy n d, Bool )
+nextDummy' _ = undefined
diff --git a/testsuite/tests/ghci/scripts/T10321.hs b/testsuite/tests/polykinds/T10134a.hs
similarity index 52%
copy from testsuite/tests/ghci/scripts/T10321.hs
copy to testsuite/tests/polykinds/T10134a.hs
index 44d264a..0d84d56 100644
--- a/testsuite/tests/ghci/scripts/T10321.hs
+++ b/testsuite/tests/polykinds/T10134a.hs
@@ -1,14 +1,11 @@
-{-# LANGUAGE DataKinds      #-}
-{-# LANGUAGE GADTs          #-}
 {-# LANGUAGE KindSignatures #-}
-{-# LANGUAGE TypeOperators  #-}
-
-module T10321 where
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeOperators #-}
+module T10134a where
 
 import GHC.TypeLits
 
 data Vec :: Nat -> * -> * where
   Nil  :: Vec 0 a
   (:>) :: a -> Vec n a -> Vec (n + 1) a
-
-infixr 5 :>
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 3c8096c..55041dc 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -119,3 +119,4 @@ test('T10503', normal, compile_fail, [''])
 test('T10570', normal, compile_fail, [''])
 test('T10670', normal, compile, [''])
 test('T10670a', normal, compile, [''])
+test('T10134', normal, multimod_compile, ['T10134.hs','-v0'])



More information about the ghc-commits mailing list