[GHC] #9575: -XAutoDeriveTypeable fails to generate instances
GHC
ghc-devs at haskell.org
Thu Sep 11 12:43:18 UTC 2014
#9575: -XAutoDeriveTypeable fails to generate instances
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.8.4
Component: Compiler | Version: 7.8.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
The following doesn't compile with GHC 7.8.3, but works with GHC HEAD. I
couldn't find a matching ticket, so I don't know if this was fixed
knowingly or not...
{{{#!hs
{-# LANGUAGE AutoDeriveTypeable #-}
import Data.Typeable (Typeable)
data T1 = C1 Int
deriving (Eq,Ord)
tvoid :: Typeable a => a -> IO ()
tvoid _ = return ()
main :: IO ()
main = tvoid (C1 0)
}}}
...fails for GHC 7.8.3 with
{{{
No instance for (Typeable T1) arising from a use of ‘tvoid’
In the expression: tvoid (C1 0)
In an equation for ‘main’: main = tvoid (C1 0)
}}}
I'm marking this with high priority, as it makes `-XAutoDeriveTypeable`
unusable on GHC 7.8.3 as it stands.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9575>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list