[GHC] #11142: Type-level skolem capture leads to core lint error

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following ill-typed code is accepted. {{{ {-# LANGUAGE PolyKinds, RankNTypes #-} module Bug where data SameKind :: k -> k -> * foo :: forall b. (forall (a :: k). SameKind a b) -> () foo = undefined }}} Indeed, Core Lint catches this. But the type-checker should. The problem is that `SameKind` forces `a` and `b` to have the same kind. But they can't, because `a`'s kind is out of scope at `b`'s binding site. The program should be rejected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => bgamari * priority: normal => high * milestone: => 8.0.1 Comment: Works fine with `wip/spj-wildcard-refactor`. Ben please add this as a regression test. We get {{{ $ ghc-stage1 -c T11142.hs -dcore-lint -fforce-recomp -ddump-types TYPE SIGNATURES foo :: forall (k :: BOX) (b :: k). (forall (a :: k). SameKind a b) -> () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hmm. On your branch, how is it decided when to abstract over kind variables? Here are two functions with explicit kind variables written: {{{ ex1 :: (forall k (a :: k). Proxy a -> ()) -> () ex2 :: forall k. (forall (a :: k). Proxy a -> ()) -> () }}} These are different, and both are conceivably useful. How are they distinguished on your branch? In HEAD, there is a consistent rule: if a kind variable is first mentioned in a tyvarbinder, then the kind variable is brought into scope in the same list of tyvarbinders. Otherwise, it's at the top level. What's the new rule? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Always top level; c.f. #4426. Needs documentation I agree Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Also see this Note in `TcHsType`: {{{ Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. For example, consider T :: forall k. k -> * f :: (forall a. T a -> Int) -> Int When kind-checking f's type signature we generalise the kind at the outermost level, thus: f1 :: forall k. (forall (a:k). T k a -> Int) -> Int -- YES! and *not* at the inner forall: f2 :: (forall k. forall (a:k). T k a -> Int) -> Int -- NO! Reason: same as for HM inference on value level declarations, we want to infer the most general type. The f2 type signature would be *less applicable* than f1, because it requires a more polymorphic argument. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): That's true -- but we're not talking about kind generalization here, because the user is asking for it (albeit a bit indirectly). So: all kind variables that GHC invents are always quantified at the top level, but previously, users could specify kind variables to be quantified below top level. If that ability has been removed, this is a real loss of expressiveness that will bite. However, it's all easily recovered with the capabilities of my branch, where you can write kind quantification directly. So perhaps it all works out. But there's a bad migration story, because there will be no way to write higher-rank kind quantification that works in both GHC 7.10 and GHC 8.0. In any case, we need to clearly document the new behavior in the release notes. Is it worth trying to resurrect the old behavior on your branch, just to ease migration? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ekmett (added) Comment: I don't think I even knew that! The old behaviour is terribly inconsistent; type variables are quantified at top level, while kind variables are quantified locally. It is not at all easy to resurrect the old behaviour: the new data type for `HsType` simply can't express it, by design. All the implicit binders are in `HsImplicitBinders` which are at the top. This is only going to be notice by people who using higher-rank functions where the nested higher-rank type is itself kind-polymorphic. I don't think there are many such people. I'm strongly inclined not to worry. I'm copying Edward who is the person on the planet most likely to have explored this particular corner. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11142: Type-level skolem capture leads to core lint error
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: bgamari
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11142: Type-level skolem capture leads to core lint error -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T11142 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => polykinds/T11142 * status: new => closed * resolution: => fixed Comment: This mistake is now detected. See `Note [Scope-check inferred kinds]` in !TcHsType. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11142#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC