[GHC] #8506: misleading error message for duplicate type class instances

#8506: misleading error message for duplicate type class instances -------------------------------------------+------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- In the following code I accidentally declared a type class more than once, and the error message had absolutely nothing to do with that! {{{ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TemplateHaskell #-} module Numerical.Types.Nat(Nat(..),nat) where import Data.Typeable import Data.Data import Language.Haskell.TH hiding (reify) data Nat = S !Nat | Z deriving (Eq,Show,Read,Typeable,Data) nat :: Int -> TypeQ nat n | n >= 0 = localNat n | otherwise = error "nat: negative" where localNat 0 = conT 'Z localNat n = conT 'S `appT` localNat (n-1) ---------------------- ---------------------- {-# LANGUAGE PolyKinds #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-} module Numerical.Types.Shape where import Numerical.Types.Nat import Data.Data type N0 = Z type N1= S N0 type N2 = S N1 type N3 = S N2 type N4 = S N3 type N5 = S N4 type N6 = S N5 type N7 = S N6 type N8 = S N7 type N9 = S N8 type N10 = S N9 class Shapable (n :: Nat) where -- zero rank is boring but lets include it for completeness class Shapable Z where class Shapable One where {- I get the following error src/Numerical/Types/Shape.hs:97:17: Unexpected type `Z' where type variable expected In the declaration of `Shape Z' -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances --------------------------------------------+------------------------------ Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by carter): GHC should give an erro about multiple class instances, but I guess the renamer phase hits the constants in the instance heads before that multiple declaration conflict would happen. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances --------------------------------------------+------------------------------ Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): You are both right. (Poor error message, but it comes from the parser.) Is this better? {{{ T8506.hs:54:16: Unexpected type ‛Z’ In the class declaration for ‛Shapable’ A class declaration should have form class Shapable a b c where ... }}} Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances --------------------------------------------+------------------------------ Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by carter): that'd be better. It brings attention to the whole "you wrote a class dec rather than an instance like you meant to" Also, the paste above actually gives the following Error (assuming N1 is used rather than One ). Mixed up my examples when sharing {{{ src/Numerical/Types/Shape.hs:88:16: Unexpected type `Z' where type variable expected In the declaration of `Shapable Z' }}} which is a bit inscrutable because it doesn't mention "you're declaring a class" to clarify more, here's the snippet that triggered the original error (i gave a further reduced example above) {{{ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TemplateHaskell #-} module Numerical.Types.Nat(Nat(..),nat) where import Data.Typeable import Data.Data import Language.Haskell.TH hiding (reify) data Nat = S !Nat | Z deriving (Eq,Show,Read,Typeable,Data) nat :: Int -> TypeQ nat n | n >= 0 = localNat n | otherwise = error "nat: negative" where localNat 0 = conT 'Z localNat n = conT 'S `appT` localNat (n-1) ---------------------- ---------------------- {-# LANGUAGE PolyKinds #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-} module Numerical.Types.Shape where import Numerical.Types.Nat import Data.Data type N0 = Z type N1= S N0 type N2 = S N1 type N3 = S N2 type N4 = S N3 type N5 = S N4 type N6 = S N5 type N7 = S N6 type N8 = S N7 type N9 = S N8 type N10 = S N9 class Shapable (n :: Nat) where data (Shape n ):: * -- zero rank is boring but lets include it for completeness class Shapable Z where data Shape Z = Shape0 class Shapable (S Z) where data Shape (S Z) = Shape1 {-# UNPACK #-} !Int {- I get the following error src/Numerical/Types/Shape.hs:97:17: Unexpected type `Z' where type variable expected In the declaration of `Shape Z' -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances --------------------------------------------+------------------------------ Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Yes, you included the snippet when you opened the ticket. I'll commit the improved message later today. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances
--------------------------------------------+------------------------------
Reporter: carter | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8506: misleading error message for duplicate type class instances
--------------------------------------------+------------------------------
Reporter: carter | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8506: misleading error message for duplicate type class instances ---------------------------------------------+----------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: parser/should_fail/T8506 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------------+----------------------------- Changes (by simonpj): * status: new => closed * testcase: => parser/should_fail/T8506 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances ---------------------------------------------+----------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: parser/should_fail/T8506 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------------+----------------------------- Comment (by carter): awesome, thanks! I merely wanted to highlight the distinction of {{{ src/Numerical/Types/Shape.hs:97:17: Unexpected type `Z' where type variable expected In the declaration of `Shape Z' }}} when theres a data family in the class vs {{{ src/Numerical/Types/Shape.hs:88:16: Unexpected type `Z' where type variable expected In the declaration of `Shapable Z' }}} because it wasn't clear to me, and that was part of why the original original snippet was especially confusing. Namely that it seemed to be saying I couldn't instantiate a data family (in addition to the whole typeclass dec needs to have variables as parameters) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8506#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8506: misleading error message for duplicate type class instances
---------------------------------------------+-----------------------------
Reporter: carter | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.6.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: parser/should_fail/T8506 | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
---------------------------------------------+-----------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC