[commit: ghc] ghc-8.6: Add an expect_broken test for #14185 (dafffdc)
git at git.haskell.org
git at git.haskell.org
Mon Jul 30 22:26:34 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.6
Link : http://ghc.haskell.org/trac/ghc/changeset/dafffdc0f6e7088276af5842300526dd8e1506b8/ghc
>---------------------------------------------------------------
commit dafffdc0f6e7088276af5842300526dd8e1506b8
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date: Thu Jul 26 17:20:29 2018 -0400
Add an expect_broken test for #14185
Test Plan: validate
Reviewers: goldfire, bgamari, alpmestan
Reviewed By: alpmestan
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #14185
Differential Revision: https://phabricator.haskell.org/D4981
(cherry picked from commit 3581212e3a5ba42114f47ed83a96322e0e8028ab)
>---------------------------------------------------------------
dafffdc0f6e7088276af5842300526dd8e1506b8
testsuite/tests/typecheck/should_compile/T14185.hs | 30 ++++++++++++++++++++++
testsuite/tests/typecheck/should_compile/all.T | 1 +
2 files changed, 31 insertions(+)
diff --git a/testsuite/tests/typecheck/should_compile/T14185.hs b/testsuite/tests/typecheck/should_compile/T14185.hs
new file mode 100644
index 0000000..41e47d2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T14185.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE MagicHash, UnboxedTuples, MultiParamTypeClasses, TypeFamilies,
+ FunctionalDependencies, KindSignatures, PolyKinds, DataKinds,
+ UndecidableInstances #-}
+module T14185 where
+
+import GHC.Types
+import GHC.Prim
+
+
+class Unbox (t :: *) (r :: TYPE k) | t -> r, r -> t where
+ unbox :: t -> r
+ box :: r -> t
+
+instance Unbox Int Int# where
+ unbox (I# i) = i
+ box i = I# i
+
+instance Unbox Char Char# where
+ unbox (C# c) = c
+ box c = C# c
+
+instance (Unbox a a', Unbox b b') => Unbox (a,b) (# a', b' #) where
+ unbox (a,b) = (# unbox a, unbox b #)
+ box (# a, b #) = (box a, box b)
+
+testInt :: Int
+testInt = box (unbox 1)
+
+testTup :: (Int, Char)
+testTup = box (unbox (1, 'a'))
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 10295f5..1cc8cd8 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -624,6 +624,7 @@ test('T14735', normal, compile, [''])
test('T15180', normal, compile, [''])
test('T15232', normal, compile, [''])
test('T13833', normal, compile, [''])
+test('T14185', expect_broken(14185), compile, [''])
def onlyHsParLocs(x):
"""
More information about the ghc-commits
mailing list