[commit: ghc] master: Test Trac #15943 (1235ca9)

git at git.haskell.org git at git.haskell.org
Thu Nov 29 11:43:43 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1235ca956c80d7035e1a6c50501a97de66d32b92/ghc

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

commit 1235ca956c80d7035e1a6c50501a97de66d32b92
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Nov 29 11:42:58 2018 +0000

    Test Trac #15943
    
    This test seems to work in HEAD


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

1235ca956c80d7035e1a6c50501a97de66d32b92
 .../tests/indexed-types/should_compile/T15943.hs   | 33 ++++++++++++++++++++++
 testsuite/tests/indexed-types/should_compile/all.T |  1 +
 2 files changed, 34 insertions(+)

diff --git a/testsuite/tests/indexed-types/should_compile/T15943.hs b/testsuite/tests/indexed-types/should_compile/T15943.hs
new file mode 100644
index 0000000..36edbbc
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T15943.hs
@@ -0,0 +1,33 @@
+{-# Language RankNTypes             #-}
+{-# Language DataKinds              #-}
+{-# Language KindSignatures         #-}
+{-# Language PolyKinds              #-}
+{-# Language TypeFamilyDependencies #-}
+{-# Language GADTs                  #-}
+{-# Language TypeSynonymInstances   #-}
+{-# Language FlexibleInstances      #-}
+{-# Language QuantifiedConstraints  #-}
+
+module T15943 where
+
+import Data.Type.Equality
+import Data.Coerce
+import Data.Type.Coercion
+import Data.Kind
+
+newtype WrapFalse a b = WrapFalse (Hom False a b)
+newtype WrapTrue  a b = WrapTrue  (Hom True  a b)
+
+class
+  (forall (x :: ob) (y :: ob). Coercible (WrapFalse x y) (WrapTrue y x))
+  =>
+  Ríki ob where
+
+  type Hom (or::Bool) = (res :: ob -> ob -> Type) | res -> or
+
+instance Ríki Type where
+  type Hom False = (->)
+  type Hom True  = Op
+
+newtype Op :: Type -> Type -> Type where
+  Op :: (b -> a) -> Op a b
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 551d382..409e1ef 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -294,6 +294,7 @@ test('T15322a', normal, compile_fail, [''])
 test('T15142', normal, compile, [''])
 test('T15352', normal, compile, [''])
 test('T15664', normal, compile, [''])
+test('T15943', normal, compile, [''])
 test('T15704', normal, compile, [''])
 test('T15711', normal, compile, ['-ddump-types'])
 test('T15852', normal, compile, ['-ddump-types'])



More information about the ghc-commits mailing list