[commit: ghc] master: Test Trac #13244 (fed7136)
git at git.haskell.org
git at git.haskell.org
Wed Feb 22 11:20:17 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/fed7136c597868d1c13b96837a2b64137a9ee65c/ghc
>---------------------------------------------------------------
commit fed7136c597868d1c13b96837a2b64137a9ee65c
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Feb 22 11:19:49 2017 +0000
Test Trac #13244
>---------------------------------------------------------------
fed7136c597868d1c13b96837a2b64137a9ee65c
.../tests/indexed-types/should_compile/T13244.hs | 34 ++++++++++++++++++++++
testsuite/tests/indexed-types/should_compile/all.T | 1 +
2 files changed, 35 insertions(+)
diff --git a/testsuite/tests/indexed-types/should_compile/T13244.hs b/testsuite/tests/indexed-types/should_compile/T13244.hs
new file mode 100644
index 0000000..e1a65b9
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T13244.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE MagicHash, DataKinds, PolyKinds, TypeInType, TypeFamilies #-}
+
+module T13244 where
+
+import Data.Int
+import Data.Word
+import GHC.Prim
+import GHC.Types
+
+type family Rep x where
+ Rep Int = IntRep
+ Rep Int8 = IntRep
+ Rep Int16 = IntRep
+ Rep Int32 = IntRep
+ Rep Int64 = Int64Rep
+ Rep Bool = IntRep
+ Rep Char = IntRep
+ Rep Word = WordRep
+ Rep Word8 = WordRep
+ Rep Word16 = WordRep
+ Rep Word32 = WordRep
+ Rep Word64 = Word64Rep
+ Rep Float = FloatRep
+ Rep Double = DoubleRep
+
+class Unbox x where
+ type Unboxed x :: TYPE (Rep x)
+ unbox :: x -> Unboxed x
+ box :: Unboxed x -> x
+
+instance Unbox Int where
+ type Unboxed Int = Int#
+ unbox (I# i) = i
+ box = I#
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 26e24ad..cdce0f6 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -260,3 +260,4 @@ test('T12522b', normal, compile, [''])
test('T12676', normal, compile, [''])
test('T12526', normal, compile, [''])
test('T12538', normal, compile_fail, [''])
+test('T13244', normal, compile, [''])
More information about the ghc-commits
mailing list