[commit: ghc] master: Test Trac #9750 (fe178b2)

git at git.haskell.org git at git.haskell.org
Tue Nov 4 10:39:22 UTC 2014


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

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

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

commit fe178b2729bb044b401b3fe670d12bcd3d14ad71
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Nov 4 10:37:38 2014 +0000

    Test Trac #9750


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

fe178b2729bb044b401b3fe670d12bcd3d14ad71
 testsuite/tests/polykinds/T9750.hs | 34 ++++++++++++++++++++++++++++++++++
 testsuite/tests/polykinds/all.T    |  1 +
 2 files changed, 35 insertions(+)

diff --git a/testsuite/tests/polykinds/T9750.hs b/testsuite/tests/polykinds/T9750.hs
new file mode 100644
index 0000000..9d865d0
--- /dev/null
+++ b/testsuite/tests/polykinds/T9750.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE FlexibleInstances      #-}
+{-# LANGUAGE TypeFamilies           #-}
+{-# LANGUAGE DataKinds              #-}
+{-# LANGUAGE ScopedTypeVariables    #-}
+
+module T9750 where
+
+import GHC.TypeLits ( Symbol, KnownSymbol )
+
+--------------------------------------------------------------------------------
+
+data Meta = MetaCons Symbol
+data M1 (c :: Meta) = M1
+
+class Generic a where
+  type Rep a :: *
+  from  :: a -> Rep a
+
+--------------------------------------------------------------------------------
+
+data A = A1
+
+instance Generic A where
+  type Rep A = M1 ('MetaCons "test")
+  from A1 = M1
+
+class GShow' f where
+  gshowsPrec' :: f -> ShowS
+
+instance (KnownSymbol c) => GShow' (M1 ('MetaCons c)) where
+  gshowsPrec' = error "urk"
+
+instance GShow' A where
+  gshowsPrec' = gshowsPrec' . from
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 5b02dda..48b0e61 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -108,3 +108,4 @@ test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263'])
 test('T9063', normal, compile, [''])
 test('T9200', normal, compile, [''])
 test('T9200b', normal, compile_fail, [''])
+test('T9750', normal, compile, [''])



More information about the ghc-commits mailing list