summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2016-09-09 17:42:42 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2016-09-12 16:20:35 +0100
commit03541cbae50f0d1cdf99120ab88698f29a278159 (patch)
tree0cc7f0a0e7175505168afa3342a137fe11b9d78f /testsuite/tests/typecheck/should_compile
parent454033b54e2f7eef2354cc9d7ae7e7cba4dff09a (diff)
downloadhaskell-03541cbae50f0d1cdf99120ab88698f29a278159.tar.gz
Be less picky about reporing inaccessible code
Triggered by the discussion on Trac #12466, this patch makes GHC less aggressive about reporting an error when there are insoluble Givens. Being so agressive was making some libraries fail to compile, and is arguably wrong in at least some cases. See the discussion on the ticket. Several test now pass when they failed before; see the files-modified list for this patch.
Diffstat (limited to 'testsuite/tests/typecheck/should_compile')
-rw-r--r--testsuite/tests/typecheck/should_compile/T12466.hs9
-rw-r--r--testsuite/tests/typecheck/should_compile/T12466a.hs26
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
3 files changed, 37 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T12466.hs b/testsuite/tests/typecheck/should_compile/T12466.hs
new file mode 100644
index 0000000000..7940d99a59
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T12466.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+module T12466 where
+
+class Foo a where
+ foo :: (a ~ Int => Int) -> a -> a
+ foo _ a2 = a2
+
+instance Foo Char
diff --git a/testsuite/tests/typecheck/should_compile/T12466a.hs b/testsuite/tests/typecheck/should_compile/T12466a.hs
new file mode 100644
index 0000000000..d0749e6b0a
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T12466a.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+module T12466a where
+
+import GHC.TypeLits (Nat)
+import Unsafe.Coerce (unsafeCoerce)
+
+data Dict a where
+ Dict :: a => Dict a
+
+newtype a :- b = Sub (a => Dict b)
+
+axiom :: forall a b. Dict (a ~ b)
+axiom = unsafeCoerce (Dict :: Dict (a ~ a))
+
+type Divides n m = n ~ Gcd n m
+type family Gcd :: Nat -> Nat -> Nat where
+
+dividesGcd :: forall a b c. (Divides a b, Divides a c) :- Divides a (Gcd b c)
+dividesGcd = Sub axiom
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index b9f452d15c..40d986a617 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -539,3 +539,5 @@ test('T12381', normal, compile, [''])
test('T12082', normal, compile, [''])
test('T10635', normal, compile, [''])
test('T12170b', normal, compile, [''])
+test('T12466', normal, compile, [''])
+test('T12466a', normal, compile, [''])