[GHC] #14066: Skolem escape at the kind level

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- This program should be rejected {{{ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE KindSignatures #-} module Foo2 where import Data.Kind ( Type ) import Data.Type.Equality import Data.Proxy import GHC.Exts data SameKind :: k -> k -> Type f (x :: Proxy a) = let g :: forall k (b :: k). SameKind a b g = undefined in () }}} But * 8.0 rejects it, with an unhelpful message * 8.2 accepts it, and the result satisfies Core Lint * HEAD accepts it, and produces a Core Lint Error -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description:
This program should be rejected {{{ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE KindSignatures #-}
module Foo2 where
import Data.Kind ( Type )
import Data.Type.Equality
import Data.Proxy
import GHC.Exts
data SameKind :: k -> k -> Type
f (x :: Proxy a) = let g :: forall k (b :: k). SameKind a b
g = undefined
in
() }}} But
* 8.0 rejects it, with an unhelpful message
* 8.2 accepts it, and the result satisfies Core Lint
* HEAD accepts it, and produces a Core Lint Error
New description: This program should be rejected {{{ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE KindSignatures #-} module Foo2 where import Data.Kind ( Type ) import Data.Type.Equality import Data.Proxy import GHC.Exts data SameKind :: k -> k -> Type f (x :: Proxy a) = let g :: forall k (b :: k). SameKind a b g = undefined in () }}} But * 8.0 rejects it, with an unhelpful message * 8.2 accepts it, and the result satisfies Core Lint * HEAD accepts it, and produces a Core Lint Error -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Probable cause: need an implication constraint in `tcExplicitTkBndrs` and similarly `Implicit`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Fixing this will probably cure #14040. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): This is a dup of #13364. But this one has more commentary, so keeping this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Richard: I'm eager to fix this, because it'll help clean up the ghastly mess in `Note [Scope-check inferred kinds]`. Quit a few other tickets seems to be messing about in this space too. Any progress? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13364, #14040 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: => #13364, #14040 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13364, #14040 | Differential Rev(s): Wiki Page: | https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/KindInference| -------------------------------------+------------------------------------- Changes (by kcsongor): * wikipage: => https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/KindInference -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14066: Skolem escape at the kind level
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13364, #14040 | Differential Rev(s):
Wiki Page: |
https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/KindInference|
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#14066: Skolem escape at the kind level -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T14066a, | dependent/should_fail/T14066{,c,d,e,f,g,h} Blocked By: | Blocking: Related Tickets: #13364, #14040 | Differential Rev(s): Wiki Page: | https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/KindInference| -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => dependent/should_compile/T14066a, dependent/should_fail/T14066{,c,d,e,f,g,h} * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14066#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC