[commit: ghc] ghc-8.0: More tests for Trac #12522 (801cbb4)
git at git.haskell.org
git at git.haskell.org
Mon Oct 10 15:00:30 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/801cbb42638714004587ba39d1d6b2bbc9ad3b9d/ghc
>---------------------------------------------------------------
commit 801cbb42638714004587ba39d1d6b2bbc9ad3b9d
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Mon Oct 10 13:57:01 2016 +0100
More tests for Trac #12522
These ones test the variations in coment:15 of the ticket
(cherry picked from commit a6111b8cc14a5dc019e2613f6f634dec4eb57a8a)
>---------------------------------------------------------------
801cbb42638714004587ba39d1d6b2bbc9ad3b9d
.../tests/indexed-types/should_compile/T12522b.hs | 20 ++++++++++++++++++++
testsuite/tests/indexed-types/should_compile/all.T | 1 +
.../tests/indexed-types/should_fail/T12522a.hs | 21 +++++++++++++++++++++
.../should_fail/T12522a.stderr} | 18 +++++++-----------
testsuite/tests/indexed-types/should_fail/all.T | 1 +
5 files changed, 50 insertions(+), 11 deletions(-)
diff --git a/testsuite/tests/indexed-types/should_compile/T12522b.hs b/testsuite/tests/indexed-types/should_compile/T12522b.hs
new file mode 100644
index 0000000..7501382
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T12522b.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeFamilyDependencies #-}
+{-# LANGUAGE TypeOperators #-}
+
+module T12522a where
+
+newtype I a = I a
+
+type family Curry (as :: [*]) b = f | f -> as b where
+ Curry '[] b = I b
+ Curry (a:as) b = a -> Curry as b
+
+data Uncurried (as :: [*]) b
+
+def :: Curry as b -> Uncurried as b
+def = undefined
+
+-- test2 :: Uncurried [Bool, Bool] Bool
+test2 = def $ \a b -> I $ a && b
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 9763d89..ab49be4 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -275,3 +275,4 @@ test('T11361', normal, compile, [''])
test('T11361a', normal, compile_fail, [''])
test('T12175', normal, compile, [''])
test('T12522', normal, compile, [''])
+test('T12522b', normal, compile, [''])
diff --git a/testsuite/tests/indexed-types/should_fail/T12522a.hs b/testsuite/tests/indexed-types/should_fail/T12522a.hs
new file mode 100644
index 0000000..eb855f4
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T12522a.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeFamilyDependencies #-}
+{-# LANGUAGE TypeOperators #-}
+
+module T12522a where
+
+newtype I a = I a
+
+type family Curry (as :: [*]) b = f | f -> as b where
+ Curry '[] b = I b
+ Curry (a:as) b = a -> Curry as b
+
+data Uncurried (as :: [*]) b
+
+def :: Curry as b -> Uncurried as b
+def = undefined
+
+-- test :: Uncurried [Int, String] String
+test = def $ \n s -> I $ show n ++ s
+
diff --git a/testsuite/tests/typecheck/should_compile/holes2.stderr b/testsuite/tests/indexed-types/should_fail/T12522a.stderr
similarity index 54%
copy from testsuite/tests/typecheck/should_compile/holes2.stderr
copy to testsuite/tests/indexed-types/should_fail/T12522a.stderr
index eb8d56f..7356791 100644
--- a/testsuite/tests/typecheck/should_compile/holes2.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T12522a.stderr
@@ -1,7 +1,10 @@
-holes2.hs:3:5: warning: [-Wdeferred-type-errors (in -Wdefault)]
+T12522a.hs:20:26: error:
• Ambiguous type variable ‘a0’ arising from a use of ‘show’
prevents the constraint ‘(Show a0)’ from being solved.
+ Relevant bindings include
+ n :: a0 (bound at T12522a.hs:20:15)
+ test :: Uncurried '[a0, [Char]] [Char] (bound at T12522a.hs:20:1)
Probable fix: use a type annotation to specify what ‘a0’ should be.
These potential instances exist:
instance Show Ordering -- Defined in ‘GHC.Show’
@@ -10,13 +13,6 @@ holes2.hs:3:5: warning: [-Wdeferred-type-errors (in -Wdefault)]
...plus 22 others
...plus five instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
- • In the expression: show _
- In an equation for ‘f’: f = show _
-
-holes2.hs:3:10: warning: [-Wtyped-holes (in -Wdefault)]
- • Found hole: _ :: a0
- Where: ‘a0’ is an ambiguous type variable
- • In the first argument of ‘show’, namely ‘_’
- In the expression: show _
- In an equation for ‘f’: f = show _
- • Relevant bindings include f :: String (bound at holes2.hs:3:1)
+ • In the first argument of ‘(++)’, namely ‘show n’
+ In the second argument of ‘($)’, namely ‘show n ++ s’
+ In the expression: I $ show n ++ s
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T
index 83dd708..7c55bde 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -140,3 +140,4 @@ test('T10899', normal, compile_fail, [''])
test('T11136', normal, compile_fail, [''])
test('T7788', normal, compile_fail, [''])
test('T12041', normal, compile_fail, [''])
+test('T12522a', normal, compile_fail, [''])
More information about the ghc-commits
mailing list