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

GHC ghc-devs at haskell.org
Wed Nov 6 05:33:42 UTC 2013


#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


More information about the ghc-tickets mailing list