[GHC] #10361: DeriveAnyClass does not fill in associated type defaults
GHC
ghc-devs at haskell.org
Tue Apr 28 11:28:57 UTC 2015
#10361: DeriveAnyClass does not fill in associated type defaults
-------------------------------------+-------------------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
I would expect `test1` and `test2` below to typecheck.
This is a reduced test case from trying to use `DeriveAnyClass` on the
`Generic` class of the `generics-sop` package, which unfortunately fails
due to this bug.
{{{
{-# LANGUAGE DeriveAnyClass, StandaloneDeriving, TypeFamilies #-}
module Test where
class C1 a where
type T1 a
type instance T1 a = Char
class C2 a where -- equivalent to C1
type T2 a
type instance T2 a = Char
class C3 a where -- equivalent to C1, C2
type T3 a
type instance T3 a = Char
data A = B
deriving C1
deriving instance C2 A
instance C3 A
-- fails
-- test1 :: T1 A
-- test1 = 'x'
-- fails
-- test2 :: T2 A
-- test2 = 'x'
-- succeeds
test3 :: T3 A
test3 = 'x'
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10361>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list