[GHC] #11635: Missleading error message when using polymorpic kinds

#11635: Missleading error message when using polymorpic kinds -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 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: -------------------------------------+------------------------------------- Example program: {{{ {-# LANGUAGE TypeInType, KindSignatures, ExplicitForAll #-} import Data.Kind data X (a :: forall k. k -> * ) = X }}} errors with {{{ polykind.hs:3:1: error: Expecting one more argument to ‘a’ Expected kind ‘k0’, but ‘a’ has kind ‘forall k. k -> *’ }}} Without `TypeInType`, the error is better, yet gives false hint: {{{ polykind.hs:3:23: error: Illegal kind: forall k. k -> * Did you mean to enable TypeInType? }}} --- For the record 7.10.3 doesn't recognise polymorphic kinds at all (same program, without `Data.Kind` import): {{{ polykind.hs:3:23: parse error on input ‘forall’ }}} Which makes me think that polymorphic kinds are somehow supported, but maybe not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Missleading error message when using polymorpic kinds -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType 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): * keywords: => TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Missleading error message when using polymorpic kinds -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType 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 phadej): And I found a workaround to make a code compile. It's not usable, but that's probably another issue: {{{ {-# LANGUAGE TypeInType, ImpredicativeTypes, KindSignatures, ExplicitForAll #-} import Data.Kind import Data.Proxy newtype X (a :: forall k. k -> * ) = X { x :: a Bool -> a (*) } -- X { x = \_ -> Proxy :: Proxy (*) } {- fails with: • Couldn't match kind ‘forall k1. k1 -> *’ with ‘forall k. k -> *’ When matching the kind of ‘Proxy’ • In the expression: Proxy :: Proxy * In the ‘x’ field of a record In the expression: X {x = \ _ -> Proxy :: Proxy *} -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Higher-rank kind in datatype definition rejected -------------------------------------+------------------------------------- Reporter: phadej | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType 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 goldfire): * owner: => goldfire Comment: I think the original program should be accepted. I see nothing wrong with it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Higher-rank kind in datatype definition rejected -------------------------------------+------------------------------------- Reporter: phadej | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType 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 ocharles): * cc: ocharles (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Higher-rank kind in datatype definition rejected
-------------------------------------+-------------------------------------
Reporter: phadej | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords: TypeInType
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

#11635: Higher-rank kind in datatype definition rejected -------------------------------------+------------------------------------- Reporter: phadej | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T11635 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge * testcase: => dependent/should_compile/T11635 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11635: Higher-rank kind in datatype definition rejected -------------------------------------+------------------------------------- Reporter: phadej | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | dependent/should_compile/T11635 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * failure: None/Unknown => GHC rejects valid program * resolution: => fixed * milestone: => 8.0.1 @@ -3,1 +3,1 @@ - {{{ + {{{#!hs New description: Example program: {{{#!hs {-# LANGUAGE TypeInType, KindSignatures, ExplicitForAll #-} import Data.Kind data X (a :: forall k. k -> * ) = X }}} errors with {{{ polykind.hs:3:1: error: Expecting one more argument to ‘a’ Expected kind ‘k0’, but ‘a’ has kind ‘forall k. k -> *’ }}} Without `TypeInType`, the error is better, yet gives false hint: {{{ polykind.hs:3:23: error: Illegal kind: forall k. k -> * Did you mean to enable TypeInType? }}} --- For the record 7.10.3 doesn't recognise polymorphic kinds at all (same program, without `Data.Kind` import): {{{ polykind.hs:3:23: parse error on input ‘forall’ }}} Which makes me think that polymorphic kinds are somehow supported, but maybe not. -- Comment: Merged as bae60f654ac5d99834818da9c50ad4bee54c334e. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC