[commit: ghc] master: Test Trac #10634 (02a6b29)
git at git.haskell.org
git at git.haskell.org
Mon Jul 13 12:28:13 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/02a6b29cc85b2820016fb66ae426dee7ecd36895/ghc
>---------------------------------------------------------------
commit 02a6b29cc85b2820016fb66ae426dee7ecd36895
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Mon Jul 13 13:28:27 2015 +0100
Test Trac #10634
>---------------------------------------------------------------
02a6b29cc85b2820016fb66ae426dee7ecd36895
.../tests/indexed-types/should_compile/T10634.hs | 23 ++++++++++++++++++++++
testsuite/tests/indexed-types/should_compile/all.T | 2 +-
2 files changed, 24 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/indexed-types/should_compile/T10634.hs b/testsuite/tests/indexed-types/should_compile/T10634.hs
new file mode 100644
index 0000000..f02cf81
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T10634.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE TypeFamilies #-}
+module T10634 where
+
+import Data.Int (Int8, Int16, Int32)
+
+type family Up a
+type instance Up Int8 = Int16
+type instance Up Int16 = Int32
+
+class (Up (Down a) ~ a) => Convert a where
+ type Down a
+ down :: a -> Down a
+
+instance Convert Int16 where
+ type Down Int16 = Int8
+ down = fromIntegral
+
+instance Convert Int32 where
+ type Down Int32 = Int16
+ down = fromIntegral
+
+x :: Int8
+x = down 8
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 67be121..3bc73a3 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -260,4 +260,4 @@ test('T10139', normal, compile, [''])
test('T10340', normal, compile, [''])
test('T10226', normal, compile, [''])
test('T10507', normal, compile, [''])
-
+test('T10634', normal, compile, [''])
More information about the ghc-commits
mailing list