[GHC] #8196: Core Lint error in Specialise with PolyKinds and derived instance
GHC
ghc-devs at haskell.org
Thu Aug 29 15:39:05 UTC 2013
#8196: Core Lint error in Specialise with PolyKinds and derived instance
-------------------------+-------------------------------------------------
Reporter: | Owner:
adamgundry | Status: new
Type: bug | Milestone:
Priority: | Version: 7.7
normal | Operating System: Unknown/Multiple
Component: | Type of failure: Incorrect warning at
Compiler | compile-time
Keywords: | Test Case:
Architecture: | Blocking:
Unknown/Multiple |
Difficulty: |
Unknown |
Blocked By: |
Related Tickets: |
-------------------------+-------------------------------------------------
The following causes a lint error when compiled with `-O` (but not with
`-O0`):
{{{
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_GHC -dcore-lint -O #-}
data T a b = MkT (a b)
deriving Show
main = print (MkT (Just True))
}}}
For reference, the beginning of the (rather long) error message is:
{{{
*** Core Lint errors : in result of Specialise ***
<no location info>: Warning:
In the type ‛Main.T k_XlN Data.Maybe.Maybe GHC.Types.Bool’
Kind application error in
type ‛Main.T k_XlN Data.Maybe.Maybe GHC.Types.Bool’
Function kind = forall (k_alL :: BOX). (k_alL -> *) -> k_alL -> *
Arg kinds = [(k_XlN, BOX), (Data.Maybe.Maybe, * -> *),
(GHC.Types.Bool, *)]
}}}
It looks like something is wrong with the types of the derived `Show`
instance, when `PolyKinds` is enabled. A similar problem applies to `Eq`
(and perhaps other classes).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8196>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list