[commit: ghc] master: Test #9111. (f73d42f)

git at git.haskell.org git at git.haskell.org
Wed Jun 11 13:32:38 UTC 2014


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

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

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

commit f73d42f0c88153bcfec23d8f35d0721272539867
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Jun 11 08:34:58 2014 -0400

    Test #9111.


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

f73d42f0c88153bcfec23d8f35d0721272539867
 libraries/base/tests/T9111.hs | 10 ++++++++++
 libraries/base/tests/all.T    |  2 ++
 2 files changed, 12 insertions(+)

diff --git a/libraries/base/tests/T9111.hs b/libraries/base/tests/T9111.hs
new file mode 100644
index 0000000..b2d1716
--- /dev/null
+++ b/libraries/base/tests/T9111.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE DataKinds #-}
+
+module T9111 where
+
+import Data.Typeable
+
+a = typeRep (Proxy :: Proxy 'True)
+b = typeRep (Proxy :: Proxy Typeable)
+c = typeRep (Proxy :: Proxy (~))
+d = typeRep (Proxy :: Proxy 'Left)
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index 31c6344..12a2410 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -166,3 +166,5 @@ test('T8766',
         , only_ways(['normal'])],
       compile_and_run,
       ['-O'])
+
+test('T9111', normal, compile, [''])



More information about the ghc-commits mailing list