[Git][ghc/ghc][master] Make isTauTy detect higher-rank contexts
Marge Bot
gitlab at gitlab.haskell.org
Wed May 6 08:42:08 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
edec6a6c by Ryan Scott at 2020-05-06T04:41:57-04:00
Make isTauTy detect higher-rank contexts
Previously, `isTauTy` would only detect higher-rank `forall`s, not
higher-rank contexts, which led to some minor bugs observed
in #18127. Easily fixed by adding a case for
`(FunTy InvisArg _ _)`.
Fixes #18127.
- - - - -
7 changed files:
- compiler/GHC/Core/Type.hs
- + testsuite/tests/deriving/should_fail/T18127b.hs
- + testsuite/tests/deriving/should_fail/T18127b.stderr
- testsuite/tests/deriving/should_fail/all.T
- + testsuite/tests/typecheck/should_fail/T18127a.hs
- + testsuite/tests/typecheck/should_fail/T18127a.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1857,17 +1857,19 @@ fun_kind_arg_flags = go emptyTCvSubst
-- something is ill-kinded. But this can happen
-- when printing errors. Assume everything is Required.
--- @isTauTy@ tests if a type has no foralls
+-- @isTauTy@ tests if a type has no foralls or (=>)
isTauTy :: Type -> Bool
isTauTy ty | Just ty' <- coreView ty = isTauTy ty'
-isTauTy (TyVarTy _) = True
-isTauTy (LitTy {}) = True
-isTauTy (TyConApp tc tys) = all isTauTy tys && isTauTyCon tc
-isTauTy (AppTy a b) = isTauTy a && isTauTy b
-isTauTy (FunTy _ a b) = isTauTy a && isTauTy b
-isTauTy (ForAllTy {}) = False
-isTauTy (CastTy ty _) = isTauTy ty
-isTauTy (CoercionTy _) = False -- Not sure about this
+isTauTy (TyVarTy _) = True
+isTauTy (LitTy {}) = True
+isTauTy (TyConApp tc tys) = all isTauTy tys && isTauTyCon tc
+isTauTy (AppTy a b) = isTauTy a && isTauTy b
+isTauTy (FunTy af a b) = case af of
+ InvisArg -> False -- e.g., Eq a => b
+ VisArg -> isTauTy a && isTauTy b -- e.g., a -> b
+isTauTy (ForAllTy {}) = False
+isTauTy (CastTy ty _) = isTauTy ty
+isTauTy (CoercionTy _) = False -- Not sure about this
{-
%************************************************************************
=====================================
testsuite/tests/deriving/should_fail/T18127b.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE RankNTypes #-}
+module T18127b where
+
+import GHC.Generics
+
+data T1 = MkT1 (forall a. a) deriving (Eq, Generic)
+data T2 a = MkT2 (Show a => a) deriving (Eq, Generic)
=====================================
testsuite/tests/deriving/should_fail/T18127b.stderr
=====================================
@@ -0,0 +1,22 @@
+
+T18127b.hs:7:40: error:
+ • Can't make a derived instance of ‘Eq T1’:
+ Constructor ‘MkT1’ has a higher-rank type
+ Possible fix: use a standalone deriving declaration instead
+ • In the data declaration for ‘T1’
+
+T18127b.hs:7:44: error:
+ • Can't make a derived instance of ‘Generic T1’:
+ MkT1 must not have exotic unlifted or polymorphic arguments
+ • In the data declaration for ‘T1’
+
+T18127b.hs:8:42: error:
+ • Can't make a derived instance of ‘Eq (T2 a)’:
+ Constructor ‘MkT2’ has a higher-rank type
+ Possible fix: use a standalone deriving declaration instead
+ • In the data declaration for ‘T2’
+
+T18127b.hs:8:46: error:
+ • Can't make a derived instance of ‘Generic (T2 a)’:
+ MkT2 must not have exotic unlifted or polymorphic arguments
+ • In the data declaration for ‘T2’
=====================================
testsuite/tests/deriving/should_fail/all.T
=====================================
@@ -76,6 +76,7 @@ test('T15073', [extra_files(['T15073a.hs'])], multimod_compile_fail,
['T15073', '-v0'])
test('T16181', normal, compile_fail, [''])
test('T16923', normal, compile_fail, [''])
+test('T18127b', normal, compile_fail, [''])
test('deriving-via-fail', normal, compile_fail, [''])
test('deriving-via-fail2', normal, compile_fail, [''])
test('deriving-via-fail3', normal, compile_fail, [''])
=====================================
testsuite/tests/typecheck/should_fail/T18127a.hs
=====================================
@@ -0,0 +1,16 @@
+{-# LANGUAGE RankNTypes #-}
+module T18127a where
+
+a :: (forall a. a) -> ()
+a = undefined
+
+b :: (Show a => a) -> ()
+b = undefined
+
+type C = forall a. a
+c :: C -> ()
+c = undefined
+
+type D a = Show a => a
+d :: D a -> ()
+d = undefined
=====================================
testsuite/tests/typecheck/should_fail/T18127a.stderr
=====================================
@@ -0,0 +1,32 @@
+
+T18127a.hs:5:5: error:
+ • Cannot instantiate unification variable ‘a1’
+ with a type involving polytypes: (forall a. a) -> ()
+ GHC doesn't yet support impredicative polymorphism
+ • In the expression: undefined
+ In an equation for ‘a’: a = undefined
+
+T18127a.hs:8:5: error:
+ • Cannot instantiate unification variable ‘a3’
+ with a type involving polytypes: (Show a => a) -> ()
+ GHC doesn't yet support impredicative polymorphism
+ • In the expression: undefined
+ In an equation for ‘b’: b = undefined
+ • Relevant bindings include
+ b :: (Show a => a) -> () (bound at T18127a.hs:8:1)
+
+T18127a.hs:12:5: error:
+ • Cannot instantiate unification variable ‘a0’
+ with a type involving polytypes: C -> ()
+ GHC doesn't yet support impredicative polymorphism
+ • In the expression: undefined
+ In an equation for ‘c’: c = undefined
+
+T18127a.hs:16:5: error:
+ • Cannot instantiate unification variable ‘a2’
+ with a type involving polytypes: D a -> ()
+ GHC doesn't yet support impredicative polymorphism
+ • In the expression: undefined
+ In an equation for ‘d’: d = undefined
+ • Relevant bindings include
+ d :: D a -> () (bound at T18127a.hs:16:1)
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -563,3 +563,4 @@ test('T17021', normal, compile_fail, [''])
test('T17021b', normal, compile_fail, [''])
test('T17955', normal, compile_fail, [''])
test('T17173', normal, compile_fail, [''])
+test('T18127a', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edec6a6c205378caf15d1d874d7e901ba76dd293
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edec6a6c205378caf15d1d874d7e901ba76dd293
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200506/4cff9a6e/attachment-0001.html>
More information about the ghc-commits
mailing list