[GHC] #12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the following program: {{{ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE FlexibleInstances #-} import Control.Monad.Reader newtype AppM a = AppM (ReaderT Int IO a) deriving (Functor, Applicative, Monad, MonadReader) }}} The `MonadReader` deriving declaration should be `MonadReader Int`. GHC produces the following error message: {{{ • Expecting one more argument to ‘MonadReader’ Expected kind ‘* -> Constraint’, but ‘MonadReader’ has kind ‘* -> (* -> *) -> Constraint’ • In the newtype declaration for ‘AppM’ }}} This error message is confusing to me. The kind of `MonadReader` is `* -> (* -> *) -> Constraint`, as the error message states, which makes sense. However, the error message states that it expects kind `* -> Constraint`, despite the fact that `MonadReader Int` is actually of kind `(* -> *) -> Constraint`. ,,(This description is adapted from [http://stackoverflow.com/q/39172590/465378 this Stack Overflow question].),, -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by lexi.lambda: @@ -3,1 +3,1 @@ - {{{ + {{{#!haskell New description: Given the following program: {{{#!haskell {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE FlexibleInstances #-} import Control.Monad.Reader newtype AppM a = AppM (ReaderT Int IO a) deriving (Functor, Applicative, Monad, MonadReader) }}} The `MonadReader` deriving declaration should be `MonadReader Int`. GHC produces the following error message: {{{ • Expecting one more argument to ‘MonadReader’ Expected kind ‘* -> Constraint’, but ‘MonadReader’ has kind ‘* -> (* -> *) -> Constraint’ • In the newtype declaration for ‘AppM’ }}} This error message is confusing to me. The kind of `MonadReader` is `* -> (* -> *) -> Constraint`, as the error message states, which makes sense. However, the error message states that it expects kind `* -> Constraint`, despite the fact that `MonadReader Int` is actually of kind `(* -> *) -> Constraint`. ,,(This description is adapted from [http://stackoverflow.com/q/39172590/465378 this Stack Overflow question].),, -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mniip): Looks like it tries to unify `k -> Constrant ~ * -> (* -> *) -> Constraint`. It zonks `k ~ *` and then fails with `(* -> *) -> Constraint ~ Constraint`, and the `k = *` leaks into the error message -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: mniip Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mniip): * owner: => mniip -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: mniip Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mniip): Apparently it is a historical convention that expected/actual error messages are zonked, so in a sense the error is not "incorrect". I believe I have an alternative solution for this though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: mniip Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2484 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: => Phab:D2484 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind
signatures
-------------------------------------+-------------------------------------
Reporter: lexi.lambda | Owner: mniip
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2484
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: mniip Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2484 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: mniip Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2484 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 52c743033ab0d969101ab4616bfce3ecf2e6e472. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12546#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC