[commit: ghc] ghc-8.2: Test #13435 in typecheck/should_run/T13435 (d40d5e8)

git at git.haskell.org git at git.haskell.org
Tue Mar 21 14:52:25 UTC 2017


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

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/d40d5e8b40a1a795fef43f0abdf7aaf143fca911/ghc

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

commit d40d5e8b40a1a795fef43f0abdf7aaf143fca911
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date:   Fri Mar 17 11:22:19 2017 -0400

    Test #13435 in typecheck/should_run/T13435
    
    (cherry picked from commit 66d174a9650c3099e2e694f71b43c2dac89b21b1)


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

d40d5e8b40a1a795fef43f0abdf7aaf143fca911
 testsuite/tests/typecheck/should_run/T13435.hs     | 14 ++++++++++++++
 testsuite/tests/typecheck/should_run/T13435.stdout |  1 +
 testsuite/tests/typecheck/should_run/all.T         |  1 +
 3 files changed, 16 insertions(+)

diff --git a/testsuite/tests/typecheck/should_run/T13435.hs b/testsuite/tests/typecheck/should_run/T13435.hs
new file mode 100644
index 0000000..95ee946
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/T13435.hs
@@ -0,0 +1,14 @@
+{-# Language FlexibleInstances, TypeFamilies, TypeInType, MagicHash #-}
+
+module Main where
+
+import Data.Kind
+import GHC.Exts
+
+class Shw (a :: TYPE rep) where
+  shw :: a -> String
+
+instance Int# ~ a => Shw (a :: TYPE IntRep) where
+  shw a = "I#" ++ show (I# a)
+
+main = putStrLn (shw 3#)
diff --git a/testsuite/tests/typecheck/should_run/T13435.stdout b/testsuite/tests/typecheck/should_run/T13435.stdout
new file mode 100644
index 0000000..ae451c2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_run/T13435.stdout
@@ -0,0 +1 @@
+I#3
diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T
index 61db61e..60b5fae 100755
--- a/testsuite/tests/typecheck/should_run/all.T
+++ b/testsuite/tests/typecheck/should_run/all.T
@@ -120,3 +120,4 @@ test('EtaExpandLevPoly', normal, compile_and_run, [''])
 test('TestTypeableBinary', normal, compile_and_run, [''])
 test('Typeable1', normal, compile_fail, [''])
 test('TypeableEq', normal, compile_and_run, [''])
+test('T13435', normal, compile_and_run, [''])



More information about the ghc-commits mailing list