Standalone derived Typeable instance for promoted lists is not found
On GHC 7.10.2, if I try and compile the following short program:
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |