[GHC] #8196: Core Lint error in Specialise with PolyKinds and derived instance

#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

#8196: Core Lint error in Specialise with PolyKinds and derived instance -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | simonpj Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Incorrect warning at | Architecture: compile-time | Unknown/Multiple Test Case: | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * owner: => simonpj Comment: I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8196#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8196: Core Lint error in Specialise with PolyKinds and derived instance -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | simonpj Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Incorrect warning at | Architecture: compile-time | Unknown/Multiple Test Case: | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by adamgundry): I realised that this may be nothing to do with '''deriving''', as a hand- written instance causes the same problem: {{{ instance forall (a :: k -> *)(b :: k) . Show (a b) => Show (T a b) where show (MkT x) = show x }}} On the other hand, everything works if one removes the kind polymorphism: {{{ instance forall (a :: * -> *)(b :: *) . Show (a b) => Show (T a b) where show (MkT x) = show x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8196#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8196: Core Lint error in Specialise with PolyKinds and derived instance
-------------------------------------------------+-------------------------
Reporter: adamgundry | Owner:
Type: bug | simonpj
Priority: normal | Status: new
Component: Compiler | Milestone:
Resolution: | Version: 7.7
Operating System: Unknown/Multiple | Keywords:
Type of failure: Incorrect warning at | Architecture:
compile-time | Unknown/Multiple
Test Case: | Difficulty:
Blocking: | Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Simon Peyton Jones

#8196: Core Lint error in Specialise with PolyKinds and derived instance
-------------------------------------------------+-------------------------
Reporter: adamgundry | Owner:
Type: bug | simonpj
Priority: normal | Status: new
Component: Compiler | Milestone:
Resolution: | Version: 7.7
Operating System: Unknown/Multiple | Keywords:
Type of failure: Incorrect warning at | Architecture:
compile-time | Unknown/Multiple
Test Case: | Difficulty:
Blocking: | Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Simon Peyton Jones

#8196: Core Lint error in Specialise with PolyKinds and derived instance -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | simonpj Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Incorrect warning at | Architecture: compile-time | Unknown/Multiple Test Case: | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by monoidal): Should this ticket be closed as fixed? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8196#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8196: Core Lint error in Specialise with PolyKinds and derived instance -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | simonpj Priority: normal | Status: Component: Compiler | closed Resolution: fixed | Milestone: Operating System: Unknown/Multiple | Version: 7.7 Type of failure: Incorrect warning at | Keywords: compile-time | Architecture: Test Case: | Unknown/Multiple simplCore/should_compile/T8196 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => closed * testcase: => simplCore/should_compile/T8196 * resolution: => fixed Comment: Yes, it should. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8196#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC