[GHC] #12546: GeneralizedNewtypeDeriving produces error messages with incorrect kind signatures
GHC
ghc-devs at haskell.org
Fri Aug 26 20:29:12 UTC 2016
#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
More information about the ghc-tickets
mailing list