
#11052: Standalone derived Typeable instance for promoted lists is not found -------------------------------------+------------------------------------- Reporter: liamoc | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On GHC 7.10.2, if I try and compile the following short program: {{{#!hs {-# LANGUAGE DataKinds, PolyKinds, DeriveDataTypeable, StandaloneDeriving #-} module Test where import Data.Typeable deriving instance Typeable '[] deriving instance Typeable '(:) nilTyCon = typeRepTyCon (typeRep (Proxy :: Proxy '[])) consTyCon = typeRepTyCon (typeRep (Proxy :: Proxy '(:) )) }}} Then GHC reports the following errors: {{{ Test.hs:9:27: No instance for (Typeable '[]) arising from a use of ‘typeRep’ In the first argument of ‘typeRepTyCon’, namely ‘(typeRep (Proxy :: Proxy '[]))’ In the expression: typeRepTyCon (typeRep (Proxy :: Proxy '[])) In an equation for ‘nilTyCon’: nilTyCon = typeRepTyCon (typeRep (Proxy :: Proxy '[])) Test.hs:10:27: No instance for (Typeable (':)) (maybe you haven't applied enough arguments to a function?) arising from a use of ‘typeRep’ In the first argument of ‘typeRepTyCon’, namely ‘(typeRep (Proxy :: Proxy (:)))’ In the expression: typeRepTyCon (typeRep (Proxy :: Proxy (:))) In an equation for ‘consTyCon’: consTyCon = typeRepTyCon (typeRep (Proxy :: Proxy (:))) }}} It seems a bug to me that the very instances I asked to be derived (and apparently were without complaint from GHC) are now not found by the typechecker in the very next line. I think that if the instance cannot be derived, GHC should say so, or if it can, then GHC should find it. I can't really see what's going on with the dump flags, because the typechecker fails before the desugarer runs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11052 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler