
#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