[GHC] #15474: Error message mentions Any

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm not sure if this is a bug. File: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} module T15474 where import Data.Kind (Type) data Proxy a type Forall = forall t. Proxy t f1 :: forall (t :: Type). Proxy t f1 = f1 f2 :: Forall f2 = f1 }}} gives an error message mentioning Any: {{{ • Couldn't match type ‘GHC.Types.Any’ with ‘*’ Expected type: Proxy t Actual type: Proxy t0 }}} The appearance of Any is suspicious - I thought it's an implementation detail? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by monoidal: Old description:
I'm not sure if this is a bug. File:
{{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} module T15474 where
import Data.Kind (Type)
data Proxy a
type Forall = forall t. Proxy t
f1 :: forall (t :: Type). Proxy t f1 = f1
f2 :: Forall f2 = f1 }}}
gives an error message mentioning Any:
{{{ • Couldn't match type ‘GHC.Types.Any’ with ‘*’ Expected type: Proxy t Actual type: Proxy t0 }}}
The appearance of Any is suspicious - I thought it's an implementation detail?
New description: I'm not sure if this is a bug. File: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} module T15474 where import Data.Kind (Type) data Proxy a type Forall = forall t. Proxy t f1 :: forall (t :: Type). Proxy t f1 = f1 f2 :: Forall f2 = f1 }}} gives an error message mentioning Any: {{{ • Couldn't match type ‘GHC.Types.Any’ with ‘*’ Expected type: Proxy t Actual type: Proxy t0 }}} The appearance of Any is suspicious to me - I thought it's an implementation detail? -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, this is awkward. What is happening is that we end up with this: {{{ type Forall = forall (t :: Any). Proxy @Any t }}} I think that perhaps in this case we should kind-generalise the RHS of `Forall` to get {{{ type Forall k = forall (t :: k) . Proxy @k t }}} I'm not sure why we don't do this. We certainly do some kind- generalisation; e.g. if you write {{{ type T x = x }}} we end up with {{{ type T k (x :: k) = x }}} So why doesn't something like that happen for `Forall`? Interesting. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
So why doesn't something like that happen for Forall?
Ah, I think it's because * The kind of `Forall`'s RHS is just `Type` * And we do kind-generalise that kind; it has no free kind variables, so no kind-generalisation actually happens. And in any case the decl {{{ type Forall k = forall (t :: k). Proxy @k t }}} gives `Forall` the ambiguous kind `Forall :: forall k. Type`, which will do no one any good. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #14198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #14198 Comment: Another option, discussed in #14198, is to reject the declaration of `Forall` entirely after kind-generalizing its RHS, side the kind variable `k` is free-floating. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #14198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, rejection is probably best for now -- we can always do something else later. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15474: Error message mentions Any -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #14198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => TypeInType * priority: low => normal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15474#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC