summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_fail/T15862.hs
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2019-06-14 11:07:46 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-06-15 23:35:03 -0400
commit25ee60cdae6ddedaf6b4677c6327c0f31c81073a (patch)
tree7cd719be751cda761613ac86ae8f11181e1b7a09 /testsuite/tests/typecheck/should_fail/T15862.hs
parent57b718481d5363ab33df4c7814f74897418f79d7 (diff)
downloadhaskell-25ee60cdae6ddedaf6b4677c6327c0f31c81073a.tar.gz
Synchronize ClsInst.doTyConApp with TcTypeable validity checks (#15862)
Issue #15862 demonstrated examples of type constructors on which `TcTypeable.tyConIsTypeable` would return `False`, but the `Typeable` constraint solver in `ClsInst` (in particular, `doTyConApp`) would try to generate `Typeable` evidence for anyway, resulting in disaster. This incongruity was caused by the fact that `doTyConApp` was using a weaker validity check than `tyConIsTypeable` to determine if a type constructor warrants `Typeable` evidence or not. The solution, perhaps unsurprisingly, is to use `tyConIsTypeable` in `doTyConApp` instead. To avoid import cycles between `ClsInst` and `TcTypeable`, I factored out `tyConIsTypeable` into its own module, `TcTypeableValidity`. Fixes #15862.
Diffstat (limited to 'testsuite/tests/typecheck/should_fail/T15862.hs')
-rw-r--r--testsuite/tests/typecheck/should_fail/T15862.hs36
1 files changed, 36 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_fail/T15862.hs b/testsuite/tests/typecheck/should_fail/T15862.hs
new file mode 100644
index 0000000000..c98b5939d1
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T15862.hs
@@ -0,0 +1,36 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE UnboxedSums #-}
+module Bug where
+
+import Data.Kind
+import Type.Reflection
+
+newtype Foo = MkFoo (forall a. a)
+
+foo :: TypeRep MkFoo
+foo = typeRep @MkFoo
+
+type family F a
+type instance F Int = Type
+
+data Bar = forall (a :: F Int). MkBar a
+
+bar :: TypeRep (MkBar True)
+bar = typeRep
+
+data Quux = MkQuux (# Bool | Int #)
+
+quux :: TypeRep MkQuux
+quux = typeRep
+
+data Quuz :: (Type ~ Type) => Type where
+ MkQuuz :: Quuz
+
+quuz :: TypeRep MkQuuz
+quuz = typeRep