[commit: ghc] master: Test Trac #12950 (c469db4)

git at git.haskell.org git at git.haskell.org
Wed Dec 21 14:06:24 UTC 2016


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

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

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

commit c469db4e5e8814e4a4f1ed7f648514bedb800c25
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Dec 21 12:26:12 2016 +0000

    Test Trac #12950


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

c469db4e5e8814e4a4f1ed7f648514bedb800c25
 testsuite/tests/deSugar/should_compile/T12950.hs | 17 +++++++++++++++++
 testsuite/tests/deSugar/should_compile/all.T     |  1 +
 2 files changed, 18 insertions(+)

diff --git a/testsuite/tests/deSugar/should_compile/T12950.hs b/testsuite/tests/deSugar/should_compile/T12950.hs
new file mode 100644
index 0000000..a7fd2e3
--- /dev/null
+++ b/testsuite/tests/deSugar/should_compile/T12950.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE TypeFamilies #-}
+
+{-# OPTIONS_GHC -O #-}
+
+module T12950 where
+
+class C a where
+  type TF a; m :: a -> TF a
+
+instance C Int where
+  type TF Int = String; m = show
+
+overloaded :: C a => a -> (a,TF a)
+{-# INLINABLE overloaded #-}
+overloaded a = (a,m a)
+
+{-# SPECIALIZE overloaded :: Int -> (Int,TF Int) #-}
diff --git a/testsuite/tests/deSugar/should_compile/all.T b/testsuite/tests/deSugar/should_compile/all.T
index a731602..6d026db 100644
--- a/testsuite/tests/deSugar/should_compile/all.T
+++ b/testsuite/tests/deSugar/should_compile/all.T
@@ -106,3 +106,4 @@ test('DsStrictWarn', normal, compile, [''])
 test('T10662', normal, compile, ['-Wall'])
 test('T11414', normal, compile, [''])
 test('T12944', normal, compile, [''])
+test('T12950', normal, compile, [''])



More information about the ghc-commits mailing list